compiler: don't generate stubs for ambiguous direct interface methods
[official-gcc.git] / gcc / ada / exp_ch3.adb
blobd02a863045b666e45d10c0cc7cc1dae22bf6c92c
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-2022, 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 Contracts; use Contracts;
30 with Einfo; use Einfo;
31 with Einfo.Entities; use Einfo.Entities;
32 with Einfo.Utils; use Einfo.Utils;
33 with Errout; use Errout;
34 with Expander; use Expander;
35 with Exp_Aggr; use Exp_Aggr;
36 with Exp_Atag; use Exp_Atag;
37 with Exp_Ch4; use Exp_Ch4;
38 with Exp_Ch6; use Exp_Ch6;
39 with Exp_Ch7; use Exp_Ch7;
40 with Exp_Ch9; use Exp_Ch9;
41 with Exp_Dbug; use Exp_Dbug;
42 with Exp_Disp; use Exp_Disp;
43 with Exp_Dist; use Exp_Dist;
44 with Exp_Put_Image;
45 with Exp_Smem; use Exp_Smem;
46 with Exp_Strm; use Exp_Strm;
47 with Exp_Tss; use Exp_Tss;
48 with Exp_Util; use Exp_Util;
49 with Freeze; use Freeze;
50 with Ghost; use Ghost;
51 with Lib; use Lib;
52 with Namet; use Namet;
53 with Nlists; use Nlists;
54 with Nmake; use Nmake;
55 with Opt; use Opt;
56 with Restrict; use Restrict;
57 with Rident; use Rident;
58 with Rtsfind; use Rtsfind;
59 with Sem; use Sem;
60 with Sem_Aux; use Sem_Aux;
61 with Sem_Attr; use Sem_Attr;
62 with Sem_Cat; use Sem_Cat;
63 with Sem_Ch3; use Sem_Ch3;
64 with Sem_Ch6; use Sem_Ch6;
65 with Sem_Ch8; use Sem_Ch8;
66 with Sem_Disp; use Sem_Disp;
67 with Sem_Eval; use Sem_Eval;
68 with Sem_Mech; use Sem_Mech;
69 with Sem_Res; use Sem_Res;
70 with Sem_SCIL; use Sem_SCIL;
71 with Sem_Type; use Sem_Type;
72 with Sem_Util; use Sem_Util;
73 with Sinfo; use Sinfo;
74 with Sinfo.Nodes; use Sinfo.Nodes;
75 with Sinfo.Utils; use Sinfo.Utils;
76 with Stand; use Stand;
77 with Snames; use Snames;
78 with Tbuild; use Tbuild;
79 with Ttypes; use Ttypes;
80 with Validsw; use Validsw;
82 package body Exp_Ch3 is
84 -----------------------
85 -- Local Subprograms --
86 -----------------------
88 procedure Adjust_Discriminants (Rtype : Entity_Id);
89 -- This is used when freezing a record type. It attempts to construct
90 -- more restrictive subtypes for discriminants so that the max size of
91 -- the record can be calculated more accurately. See the body of this
92 -- procedure for details.
94 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id);
95 -- Build initialization procedure for given array type. Nod is a node
96 -- used for attachment of any actions required in its construction.
97 -- It also supplies the source location used for the procedure.
99 function Build_Discriminant_Formals
100 (Rec_Id : Entity_Id;
101 Use_Dl : Boolean) return List_Id;
102 -- This function uses the discriminants of a type to build a list of
103 -- formal parameters, used in Build_Init_Procedure among other places.
104 -- If the flag Use_Dl is set, the list is built using the already
105 -- defined discriminals of the type, as is the case for concurrent
106 -- types with discriminants. Otherwise new identifiers are created,
107 -- with the source names of the discriminants.
109 procedure Build_Discr_Checking_Funcs (N : Node_Id);
110 -- For each variant component, builds a function which checks whether
111 -- the component name is consistent with the current discriminants
112 -- and sets the component's Dcheck_Function attribute to refer to it.
113 -- N is the full type declaration node; the discriminant checking
114 -- functions are inserted after this node.
116 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id;
117 -- This function builds a static aggregate that can serve as the initial
118 -- value for an array type whose bounds are static, and whose component
119 -- type is a composite type that has a static equivalent aggregate.
120 -- The equivalent array aggregate is used both for object initialization
121 -- and for component initialization, when used in the following function.
123 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id;
124 -- This function builds a static aggregate that can serve as the initial
125 -- value for a record type whose components are scalar and initialized
126 -- with compile-time values, or arrays with similar initialization or
127 -- defaults. When possible, initialization of an object of the type can
128 -- be achieved by using a copy of the aggregate as an initial value, thus
129 -- removing the implicit call that would otherwise constitute elaboration
130 -- code.
132 procedure Build_Record_Init_Proc (N : Node_Id; Rec_Ent : Entity_Id);
133 -- Build record initialization procedure. N is the type declaration
134 -- node, and Rec_Ent is the corresponding entity for the record type.
136 procedure Build_Slice_Assignment (Typ : Entity_Id);
137 -- Build assignment procedure for one-dimensional arrays of controlled
138 -- types. Other array and slice assignments are expanded in-line, but
139 -- the code expansion for controlled components (when control actions
140 -- are active) can lead to very large blocks that GCC handles poorly.
142 procedure Build_Untagged_Equality (Typ : Entity_Id);
143 -- AI05-0123: Equality on untagged records composes. This procedure
144 -- builds the equality routine for an untagged record that has components
145 -- of a record type that has user-defined primitive equality operations.
146 -- The resulting operation is a TSS subprogram.
148 procedure Check_Stream_Attributes (Typ : Entity_Id);
149 -- Check that if a limited extension has a parent with user-defined stream
150 -- attributes, and does not itself have user-defined stream-attributes,
151 -- then any limited component of the extension also has the corresponding
152 -- user-defined stream attributes.
154 procedure Clean_Task_Names
155 (Typ : Entity_Id;
156 Proc_Id : Entity_Id);
157 -- If an initialization procedure includes calls to generate names
158 -- for task subcomponents, indicate that secondary stack cleanup is
159 -- needed after an initialization. Typ is the component type, and Proc_Id
160 -- the initialization procedure for the enclosing composite type.
162 procedure Copy_Discr_Checking_Funcs (N : Node_Id);
163 -- For a derived untagged type, copy the attributes that were set
164 -- for the components of the parent type onto the components of the
165 -- derived type. No new subprograms are constructed.
166 -- N is the full type declaration node, as for Build_Discr_Checking_Funcs.
168 procedure Expand_Freeze_Array_Type (N : Node_Id);
169 -- Freeze an array type. Deals with building the initialization procedure,
170 -- creating the packed array type for a packed array and also with the
171 -- creation of the controlling procedures for the controlled case. The
172 -- argument N is the N_Freeze_Entity node for the type.
174 procedure Expand_Freeze_Class_Wide_Type (N : Node_Id);
175 -- Freeze a class-wide type. Build routine Finalize_Address for the purpose
176 -- of finalizing controlled derivations from the class-wide's root type.
178 procedure Expand_Freeze_Enumeration_Type (N : Node_Id);
179 -- Freeze enumeration type with non-standard representation. Builds the
180 -- array and function needed to convert between enumeration pos and
181 -- enumeration representation values. N is the N_Freeze_Entity node
182 -- for the type.
184 procedure Expand_Freeze_Record_Type (N : Node_Id);
185 -- Freeze record type. Builds all necessary discriminant checking
186 -- and other ancillary functions, and builds dispatch tables where
187 -- needed. The argument N is the N_Freeze_Entity node. This processing
188 -- applies only to E_Record_Type entities, not to class wide types,
189 -- record subtypes, or private types.
191 procedure Expand_Tagged_Root (T : Entity_Id);
192 -- Add a field _Tag at the beginning of the record. This field carries
193 -- the value of the access to the Dispatch table. This procedure is only
194 -- called on root type, the _Tag field being inherited by the descendants.
196 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id);
197 -- Treat user-defined stream operations as renaming_as_body if the
198 -- subprogram they rename is not frozen when the type is frozen.
200 package Initialization_Control is
202 function Requires_Late_Init
203 (Decl : Node_Id; Rec_Type : Entity_Id) return Boolean;
204 -- Return True iff the given component declaration requires late
205 -- initialization, as defined by 3.3.1 (8.1/5).
207 function Has_Late_Init_Component
208 (Tagged_Rec_Type : Entity_Id) return Boolean;
209 -- Return True iff the given tagged record type has at least one
210 -- component that requires late initialization; this includes
211 -- components of ancestor types.
213 type Initialization_Mode is
214 (Full_Init, Full_Init_Except_Tag, Early_Init_Only, Late_Init_Only);
215 -- The initialization routine for a tagged type is passed in a
216 -- formal parameter of this type, indicating what initialization
217 -- is to be performed. This parameter defaults to Full_Init in all
218 -- cases except when the init proc of a type extension (let's call
219 -- that type T2) calls the init proc of its parent (let's call that
220 -- type T1). In that case, one of the other 3 values will
221 -- be passed in. In all three of those cases, the Tag component has
222 -- already been initialized before the call and is therefore not to be
223 -- modified. T2's init proc will either call T1's init proc
224 -- once (with Full_Init_Except_Tag as the parameter value) or twice
225 -- (first with Early_Init_Only, then later with Late_Init_Only),
226 -- depending on the result returned by Has_Late_Init_Component (T1).
227 -- In the latter case, the first call does not initialize any
228 -- components that require late initialization and the second call
229 -- then performs that deferred initialization.
230 -- Strictly speaking, the formal parameter subtype is actually Natural
231 -- but calls will only pass in values corresponding to literals
232 -- of this enumeration type.
234 function Make_Mode_Literal
235 (Loc : Source_Ptr; Mode : Initialization_Mode) return Node_Id
236 is (Make_Integer_Literal (Loc, Initialization_Mode'Pos (Mode)));
237 -- Generate an integer literal for a given mode value.
239 function Tag_Init_Condition
240 (Loc : Source_Ptr;
241 Init_Control_Formal : Entity_Id) return Node_Id;
242 function Early_Init_Condition
243 (Loc : Source_Ptr;
244 Init_Control_Formal : Entity_Id) return Node_Id;
245 function Late_Init_Condition
246 (Loc : Source_Ptr;
247 Init_Control_Formal : Entity_Id) return Node_Id;
248 -- These three functions each return a Boolean expression that
249 -- can be used to determine whether a given call to the initialization
250 -- expression for a tagged type should initialize (respectively)
251 -- the Tag component, the non-Tag components that do not require late
252 -- initialization, and the components that do require late
253 -- initialization.
255 end Initialization_Control;
257 procedure Initialization_Warning (E : Entity_Id);
258 -- If static elaboration of the package is requested, indicate
259 -- when a type does meet the conditions for static initialization. If
260 -- E is a type, it has components that have no static initialization.
261 -- if E is an entity, its initial expression is not compile-time known.
263 function Init_Formals (Typ : Entity_Id; Proc_Id : Entity_Id) return List_Id;
264 -- This function builds the list of formals for an initialization routine.
265 -- The first formal is always _Init with the given type. For task value
266 -- record types and types containing tasks, three additional formals are
267 -- added and Proc_Id is decorated with attribute Has_Master_Entity:
269 -- _Master : Master_Id
270 -- _Chain : in out Activation_Chain
271 -- _Task_Name : String
273 -- The caller must append additional entries for discriminants if required.
275 function Inline_Init_Proc (Typ : Entity_Id) return Boolean;
276 -- Returns true if the initialization procedure of Typ should be inlined
278 function In_Runtime (E : Entity_Id) return Boolean;
279 -- Check if E is defined in the RTL (in a child of Ada or System). Used
280 -- to avoid to bring in the overhead of _Input, _Output for tagged types.
282 function Is_Null_Statement_List (Stmts : List_Id) return Boolean;
283 -- Returns true if Stmts is made of null statements only, possibly wrapped
284 -- in a case statement, recursively. This latter pattern may occur for the
285 -- initialization procedure of an unchecked union.
287 function Make_Eq_Body
288 (Typ : Entity_Id;
289 Eq_Name : Name_Id) return Node_Id;
290 -- Build the body of a primitive equality operation for a tagged record
291 -- type, or in Ada 2012 for any record type that has components with a
292 -- user-defined equality. Factored out of Predefined_Primitive_Bodies.
294 function Make_Eq_Case
295 (E : Entity_Id;
296 CL : Node_Id;
297 Discrs : Elist_Id := New_Elmt_List) return List_Id;
298 -- Building block for variant record equality. Defined to share the code
299 -- between the tagged and untagged case. Given a Component_List node CL,
300 -- it generates an 'if' followed by a 'case' statement that compares all
301 -- components of local temporaries named X and Y (that are declared as
302 -- formals at some upper level). E provides the Sloc to be used for the
303 -- generated code.
305 -- IF E is an unchecked_union, Discrs is the list of formals created for
306 -- the inferred discriminants of one operand. These formals are used in
307 -- the generated case statements for each variant of the unchecked union.
309 function Make_Eq_If
310 (E : Entity_Id;
311 L : List_Id) return Node_Id;
312 -- Building block for variant record equality. Defined to share the code
313 -- between the tagged and untagged case. Given the list of components
314 -- (or discriminants) L, it generates a return statement that compares all
315 -- components of local temporaries named X and Y (that are declared as
316 -- formals at some upper level). E provides the Sloc to be used for the
317 -- generated code.
319 function Make_Neq_Body (Tag_Typ : Entity_Id) return Node_Id;
320 -- Search for a renaming of the inequality dispatching primitive of
321 -- this tagged type. If found then build and return the corresponding
322 -- rename-as-body inequality subprogram; otherwise return Empty.
324 procedure Make_Predefined_Primitive_Specs
325 (Tag_Typ : Entity_Id;
326 Predef_List : out List_Id;
327 Renamed_Eq : out Entity_Id);
328 -- Create a list with the specs of the predefined primitive operations.
329 -- For tagged types that are interfaces all these primitives are defined
330 -- abstract.
332 -- The following entries are present for all tagged types, and provide
333 -- the results of the corresponding attribute applied to the object.
334 -- Dispatching is required in general, since the result of the attribute
335 -- will vary with the actual object subtype.
337 -- _size provides result of 'Size attribute
338 -- typSR provides result of 'Read attribute
339 -- typSW provides result of 'Write attribute
340 -- typSI provides result of 'Input attribute
341 -- typSO provides result of 'Output attribute
342 -- typPI provides result of 'Put_Image attribute
344 -- The following entries are additionally present for non-limited tagged
345 -- types, and implement additional dispatching operations for predefined
346 -- operations:
348 -- _equality implements "=" operator
349 -- _assign implements assignment operation
350 -- typDF implements deep finalization
351 -- typDA implements deep adjust
353 -- The latter two are empty procedures unless the type contains some
354 -- controlled components that require finalization actions (the deep
355 -- in the name refers to the fact that the action applies to components).
357 -- The list of specs is returned in Predef_List
359 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean;
360 -- Returns True if there are representation clauses for type T that are not
361 -- inherited. If the result is false, the init_proc and the discriminant
362 -- checking functions of the parent can be reused by a derived type.
364 function Make_Null_Procedure_Specs (Tag_Typ : Entity_Id) return List_Id;
365 -- Ada 2005 (AI-251): Makes specs for null procedures associated with any
366 -- null procedures inherited from an interface type that have not been
367 -- overridden. Only one null procedure will be created for a given set of
368 -- inherited null procedures with homographic profiles.
370 function Predef_Spec_Or_Body
371 (Loc : Source_Ptr;
372 Tag_Typ : Entity_Id;
373 Name : Name_Id;
374 Profile : List_Id;
375 Ret_Type : Entity_Id := Empty;
376 For_Body : Boolean := False) return Node_Id;
377 -- This function generates the appropriate expansion for a predefined
378 -- primitive operation specified by its name, parameter profile and
379 -- return type (Empty means this is a procedure). If For_Body is false,
380 -- then the returned node is a subprogram declaration. If For_Body is
381 -- true, then the returned node is a empty subprogram body containing
382 -- no declarations and no statements.
384 function Predef_Stream_Attr_Spec
385 (Loc : Source_Ptr;
386 Tag_Typ : Entity_Id;
387 Name : TSS_Name_Type) return Node_Id;
388 -- Specialized version of Predef_Spec_Or_Body that apply to read, write,
389 -- input and output attribute whose specs are constructed in Exp_Strm.
391 function Predef_Deep_Spec
392 (Loc : Source_Ptr;
393 Tag_Typ : Entity_Id;
394 Name : TSS_Name_Type;
395 For_Body : Boolean := False) return Node_Id;
396 -- Specialized version of Predef_Spec_Or_Body that apply to _deep_adjust
397 -- and _deep_finalize
399 function Predefined_Primitive_Bodies
400 (Tag_Typ : Entity_Id;
401 Renamed_Eq : Entity_Id) return List_Id;
402 -- Create the bodies of the predefined primitives that are described in
403 -- Predefined_Primitive_Specs. When not empty, Renamed_Eq must denote
404 -- the defining unit name of the type's predefined equality as returned
405 -- by Make_Predefined_Primitive_Specs.
407 function Predefined_Primitive_Freeze (Tag_Typ : Entity_Id) return List_Id;
408 -- Freeze entities of all predefined primitive operations. This is needed
409 -- because the bodies of these operations do not normally do any freezing.
411 function Stream_Operation_OK
412 (Typ : Entity_Id;
413 Operation : TSS_Name_Type) return Boolean;
414 -- Check whether the named stream operation must be emitted for a given
415 -- type. The rules for inheritance of stream attributes by type extensions
416 -- are enforced by this function. Furthermore, various restrictions prevent
417 -- the generation of these operations, as a useful optimization or for
418 -- certification purposes and to save unnecessary generated code.
420 --------------------------
421 -- Adjust_Discriminants --
422 --------------------------
424 -- This procedure attempts to define subtypes for discriminants that are
425 -- more restrictive than those declared. Such a replacement is possible if
426 -- we can demonstrate that values outside the restricted range would cause
427 -- constraint errors in any case. The advantage of restricting the
428 -- discriminant types in this way is that the maximum size of the variant
429 -- record can be calculated more conservatively.
431 -- An example of a situation in which we can perform this type of
432 -- restriction is the following:
434 -- subtype B is range 1 .. 10;
435 -- type Q is array (B range <>) of Integer;
437 -- type V (N : Natural) is record
438 -- C : Q (1 .. N);
439 -- end record;
441 -- In this situation, we can restrict the upper bound of N to 10, since
442 -- any larger value would cause a constraint error in any case.
444 -- There are many situations in which such restriction is possible, but
445 -- for now, we just look for cases like the above, where the component
446 -- in question is a one dimensional array whose upper bound is one of
447 -- the record discriminants. Also the component must not be part of
448 -- any variant part, since then the component does not always exist.
450 procedure Adjust_Discriminants (Rtype : Entity_Id) is
451 Loc : constant Source_Ptr := Sloc (Rtype);
452 Comp : Entity_Id;
453 Ctyp : Entity_Id;
454 Ityp : Entity_Id;
455 Lo : Node_Id;
456 Hi : Node_Id;
457 P : Node_Id;
458 Loval : Uint;
459 Discr : Entity_Id;
460 Dtyp : Entity_Id;
461 Dhi : Node_Id;
462 Dhiv : Uint;
463 Ahi : Node_Id;
464 Ahiv : Uint;
465 Tnn : Entity_Id;
467 begin
468 Comp := First_Component (Rtype);
469 while Present (Comp) loop
471 -- If our parent is a variant, quit, we do not look at components
472 -- that are in variant parts, because they may not always exist.
474 P := Parent (Comp); -- component declaration
475 P := Parent (P); -- component list
477 exit when Nkind (Parent (P)) = N_Variant;
479 -- We are looking for a one dimensional array type
481 Ctyp := Etype (Comp);
483 if not Is_Array_Type (Ctyp) or else Number_Dimensions (Ctyp) > 1 then
484 goto Continue;
485 end if;
487 -- The lower bound must be constant, and the upper bound is a
488 -- discriminant (which is a discriminant of the current record).
490 Ityp := Etype (First_Index (Ctyp));
491 Lo := Type_Low_Bound (Ityp);
492 Hi := Type_High_Bound (Ityp);
494 if not Compile_Time_Known_Value (Lo)
495 or else Nkind (Hi) /= N_Identifier
496 or else No (Entity (Hi))
497 or else Ekind (Entity (Hi)) /= E_Discriminant
498 then
499 goto Continue;
500 end if;
502 -- We have an array with appropriate bounds
504 Loval := Expr_Value (Lo);
505 Discr := Entity (Hi);
506 Dtyp := Etype (Discr);
508 -- See if the discriminant has a known upper bound
510 Dhi := Type_High_Bound (Dtyp);
512 if not Compile_Time_Known_Value (Dhi) then
513 goto Continue;
514 end if;
516 Dhiv := Expr_Value (Dhi);
518 -- See if base type of component array has known upper bound
520 Ahi := Type_High_Bound (Etype (First_Index (Base_Type (Ctyp))));
522 if not Compile_Time_Known_Value (Ahi) then
523 goto Continue;
524 end if;
526 Ahiv := Expr_Value (Ahi);
528 -- The condition for doing the restriction is that the high bound
529 -- of the discriminant is greater than the low bound of the array,
530 -- and is also greater than the high bound of the base type index.
532 if Dhiv > Loval and then Dhiv > Ahiv then
534 -- We can reset the upper bound of the discriminant type to
535 -- whichever is larger, the low bound of the component, or
536 -- the high bound of the base type array index.
538 -- We build a subtype that is declared as
540 -- subtype Tnn is discr_type range discr_type'First .. max;
542 -- And insert this declaration into the tree. The type of the
543 -- discriminant is then reset to this more restricted subtype.
545 Tnn := Make_Temporary (Loc, 'T');
547 Insert_Action (Declaration_Node (Rtype),
548 Make_Subtype_Declaration (Loc,
549 Defining_Identifier => Tnn,
550 Subtype_Indication =>
551 Make_Subtype_Indication (Loc,
552 Subtype_Mark => New_Occurrence_Of (Dtyp, Loc),
553 Constraint =>
554 Make_Range_Constraint (Loc,
555 Range_Expression =>
556 Make_Range (Loc,
557 Low_Bound =>
558 Make_Attribute_Reference (Loc,
559 Attribute_Name => Name_First,
560 Prefix => New_Occurrence_Of (Dtyp, Loc)),
561 High_Bound =>
562 Make_Integer_Literal (Loc,
563 Intval => UI_Max (Loval, Ahiv)))))));
565 Set_Etype (Discr, Tnn);
566 end if;
568 <<Continue>>
569 Next_Component (Comp);
570 end loop;
571 end Adjust_Discriminants;
573 ------------------------------------------
574 -- Build_Access_Subprogram_Wrapper_Body --
575 ------------------------------------------
577 procedure Build_Access_Subprogram_Wrapper_Body
578 (Decl : Node_Id;
579 New_Decl : Node_Id)
581 Loc : constant Source_Ptr := Sloc (Decl);
582 Actuals : constant List_Id := New_List;
583 Type_Def : constant Node_Id := Type_Definition (Decl);
584 Type_Id : constant Entity_Id := Defining_Identifier (Decl);
585 Spec_Node : constant Node_Id :=
586 Copy_Subprogram_Spec (Specification (New_Decl));
587 -- This copy creates new identifiers for formals and subprogram.
589 Act : Node_Id;
590 Body_Node : Node_Id;
591 Call_Stmt : Node_Id;
592 Ptr : Entity_Id;
594 begin
595 if not Expander_Active then
596 return;
597 end if;
599 -- Create List of actuals for indirect call. The last parameter of the
600 -- subprogram declaration is the access value for the indirect call.
602 Act := First (Parameter_Specifications (Spec_Node));
604 while Present (Act) loop
605 exit when Act = Last (Parameter_Specifications (Spec_Node));
606 Append_To (Actuals,
607 Make_Identifier (Loc, Chars (Defining_Identifier (Act))));
608 Next (Act);
609 end loop;
611 Ptr :=
612 Defining_Identifier
613 (Last (Parameter_Specifications (Specification (New_Decl))));
615 if Nkind (Type_Def) = N_Access_Procedure_Definition then
616 Call_Stmt := Make_Procedure_Call_Statement (Loc,
617 Name =>
618 Make_Explicit_Dereference
619 (Loc, New_Occurrence_Of (Ptr, Loc)),
620 Parameter_Associations => Actuals);
621 else
622 Call_Stmt := Make_Simple_Return_Statement (Loc,
623 Expression =>
624 Make_Function_Call (Loc,
625 Name => Make_Explicit_Dereference
626 (Loc, New_Occurrence_Of (Ptr, Loc)),
627 Parameter_Associations => Actuals));
628 end if;
630 Body_Node := Make_Subprogram_Body (Loc,
631 Specification => Spec_Node,
632 Declarations => New_List,
633 Handled_Statement_Sequence =>
634 Make_Handled_Sequence_Of_Statements (Loc,
635 Statements => New_List (Call_Stmt)));
637 -- Place body in list of freeze actions for the type.
639 Append_Freeze_Action (Type_Id, Body_Node);
640 end Build_Access_Subprogram_Wrapper_Body;
642 ---------------------------
643 -- Build_Array_Init_Proc --
644 ---------------------------
646 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id) is
647 Comp_Type : constant Entity_Id := Component_Type (A_Type);
648 Comp_Simple_Init : constant Boolean :=
649 Needs_Simple_Initialization
650 (Typ => Comp_Type,
651 Consider_IS =>
652 not (Validity_Check_Copies and Is_Bit_Packed_Array (A_Type)));
653 -- True if the component needs simple initialization, based on its type,
654 -- plus the fact that we do not do simple initialization for components
655 -- of bit-packed arrays when validity checks are enabled, because the
656 -- initialization with deliberately out-of-range values would raise
657 -- Constraint_Error.
659 Body_Stmts : List_Id;
660 Has_Default_Init : Boolean;
661 Index_List : List_Id;
662 Loc : Source_Ptr;
663 Parameters : List_Id;
664 Proc_Id : Entity_Id;
666 function Init_Component return List_Id;
667 -- Create one statement to initialize one array component, designated
668 -- by a full set of indexes.
670 function Init_One_Dimension (N : Int) return List_Id;
671 -- Create loop to initialize one dimension of the array. The single
672 -- statement in the loop body initializes the inner dimensions if any,
673 -- or else the single component. Note that this procedure is called
674 -- recursively, with N being the dimension to be initialized. A call
675 -- with N greater than the number of dimensions simply generates the
676 -- component initialization, terminating the recursion.
678 --------------------
679 -- Init_Component --
680 --------------------
682 function Init_Component return List_Id is
683 Comp : Node_Id;
685 begin
686 Comp :=
687 Make_Indexed_Component (Loc,
688 Prefix => Make_Identifier (Loc, Name_uInit),
689 Expressions => Index_List);
691 if Has_Default_Aspect (A_Type) then
692 Set_Assignment_OK (Comp);
693 return New_List (
694 Make_Assignment_Statement (Loc,
695 Name => Comp,
696 Expression =>
697 Convert_To (Comp_Type,
698 Default_Aspect_Component_Value (First_Subtype (A_Type)))));
700 elsif Comp_Simple_Init then
701 Set_Assignment_OK (Comp);
702 return New_List (
703 Make_Assignment_Statement (Loc,
704 Name => Comp,
705 Expression =>
706 Get_Simple_Init_Val
707 (Typ => Comp_Type,
708 N => Nod,
709 Size => Component_Size (A_Type))));
711 else
712 Clean_Task_Names (Comp_Type, Proc_Id);
713 return
714 Build_Initialization_Call
715 (Loc => Loc,
716 Id_Ref => Comp,
717 Typ => Comp_Type,
718 In_Init_Proc => True,
719 Enclos_Type => A_Type);
720 end if;
721 end Init_Component;
723 ------------------------
724 -- Init_One_Dimension --
725 ------------------------
727 function Init_One_Dimension (N : Int) return List_Id is
728 Index : Entity_Id;
729 DIC_Call : Node_Id;
730 Result_List : List_Id;
732 function Possible_DIC_Call return Node_Id;
733 -- If the component type has Default_Initial_Conditions and a DIC
734 -- procedure that is not an empty body, then builds a call to the
735 -- DIC procedure and returns it.
737 -----------------------
738 -- Possible_DIC_Call --
739 -----------------------
741 function Possible_DIC_Call return Node_Id is
742 begin
743 -- When the component's type has a Default_Initial_Condition, then
744 -- create a call for the DIC check.
746 if Has_DIC (Comp_Type)
747 -- In GNATprove mode, the component DICs are checked by other
748 -- means. They should not be added to the record type DIC
749 -- procedure, so that the procedure can be used to check the
750 -- record type invariants or DICs if any.
752 and then not GNATprove_Mode
754 -- DIC checks for components of controlled types are done later
755 -- (see Exp_Ch7.Make_Deep_Array_Body).
757 and then not Is_Controlled (Comp_Type)
759 and then Present (DIC_Procedure (Comp_Type))
761 and then not Has_Null_Body (DIC_Procedure (Comp_Type))
762 then
763 return
764 Build_DIC_Call (Loc,
765 Make_Indexed_Component (Loc,
766 Prefix => Make_Identifier (Loc, Name_uInit),
767 Expressions => Index_List),
768 Comp_Type);
769 else
770 return Empty;
771 end if;
772 end Possible_DIC_Call;
774 -- Start of processing for Init_One_Dimension
776 begin
777 -- If the component does not need initializing, then there is nothing
778 -- to do here, so we return a null body. This occurs when generating
779 -- the dummy Init_Proc needed for Initialize_Scalars processing.
780 -- An exception is if component type has a Default_Initial_Condition,
781 -- in which case we generate a call to the type's DIC procedure.
783 if not Has_Non_Null_Base_Init_Proc (Comp_Type)
784 and then not Comp_Simple_Init
785 and then not Has_Task (Comp_Type)
786 and then not Has_Default_Aspect (A_Type)
787 and then (not Has_DIC (Comp_Type)
788 or else N > Number_Dimensions (A_Type))
789 then
790 DIC_Call := Possible_DIC_Call;
792 if Present (DIC_Call) then
793 return New_List (DIC_Call);
794 else
795 return New_List (Make_Null_Statement (Loc));
796 end if;
798 -- If all dimensions dealt with, we simply initialize the component
799 -- and append a call to component type's DIC procedure when needed.
801 elsif N > Number_Dimensions (A_Type) then
802 DIC_Call := Possible_DIC_Call;
804 if Present (DIC_Call) then
805 Result_List := Init_Component;
806 Append (DIC_Call, Result_List);
807 return Result_List;
809 else
810 return Init_Component;
811 end if;
813 -- Here we generate the required loop
815 else
816 Index :=
817 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
819 Append (New_Occurrence_Of (Index, Loc), Index_List);
821 return New_List (
822 Make_Implicit_Loop_Statement (Nod,
823 Identifier => Empty,
824 Iteration_Scheme =>
825 Make_Iteration_Scheme (Loc,
826 Loop_Parameter_Specification =>
827 Make_Loop_Parameter_Specification (Loc,
828 Defining_Identifier => Index,
829 Discrete_Subtype_Definition =>
830 Make_Attribute_Reference (Loc,
831 Prefix =>
832 Make_Identifier (Loc, Name_uInit),
833 Attribute_Name => Name_Range,
834 Expressions => New_List (
835 Make_Integer_Literal (Loc, N))))),
836 Statements => Init_One_Dimension (N + 1)));
837 end if;
838 end Init_One_Dimension;
840 -- Start of processing for Build_Array_Init_Proc
842 begin
843 -- The init proc is created when analyzing the freeze node for the type,
844 -- but it properly belongs with the array type declaration. However, if
845 -- the freeze node is for a subtype of a type declared in another unit
846 -- it seems preferable to use the freeze node as the source location of
847 -- the init proc. In any case this is preferable for gcov usage, and
848 -- the Sloc is not otherwise used by the compiler.
850 if In_Open_Scopes (Scope (A_Type)) then
851 Loc := Sloc (A_Type);
852 else
853 Loc := Sloc (Nod);
854 end if;
856 -- Nothing to generate in the following cases:
858 -- 1. Initialization is suppressed for the type
859 -- 2. An initialization already exists for the base type
861 if Initialization_Suppressed (A_Type)
862 or else Present (Base_Init_Proc (A_Type))
863 then
864 return;
865 end if;
867 Index_List := New_List;
869 -- We need an initialization procedure if any of the following is true:
871 -- 1. The component type has an initialization procedure
872 -- 2. The component type needs simple initialization
873 -- 3. Tasks are present
874 -- 4. The type is marked as a public entity
875 -- 5. The array type has a Default_Component_Value aspect
876 -- 6. The array component type has a Default_Initialization_Condition
878 -- The reason for the public entity test is to deal properly with the
879 -- Initialize_Scalars pragma. This pragma can be set in the client and
880 -- not in the declaring package, this means the client will make a call
881 -- to the initialization procedure (because one of conditions 1-3 must
882 -- apply in this case), and we must generate a procedure (even if it is
883 -- null) to satisfy the call in this case.
885 -- Exception: do not build an array init_proc for a type whose root
886 -- type is Standard.String or Standard.Wide_[Wide_]String, since there
887 -- is no place to put the code, and in any case we handle initialization
888 -- of such types (in the Initialize_Scalars case, that's the only time
889 -- the issue arises) in a special manner anyway which does not need an
890 -- init_proc.
892 Has_Default_Init := Has_Non_Null_Base_Init_Proc (Comp_Type)
893 or else Comp_Simple_Init
894 or else Has_Task (Comp_Type)
895 or else Has_Default_Aspect (A_Type)
896 or else Has_DIC (Comp_Type);
898 if Has_Default_Init
899 or else (not Restriction_Active (No_Initialize_Scalars)
900 and then Is_Public (A_Type)
901 and then not Is_Standard_String_Type (A_Type))
902 then
903 Proc_Id :=
904 Make_Defining_Identifier (Loc,
905 Chars => Make_Init_Proc_Name (A_Type));
907 -- If No_Default_Initialization restriction is active, then we don't
908 -- want to build an init_proc, but we need to mark that an init_proc
909 -- would be needed if this restriction was not active (so that we can
910 -- detect attempts to call it), so set a dummy init_proc in place.
911 -- This is only done though when actual default initialization is
912 -- needed (and not done when only Is_Public is True), since otherwise
913 -- objects such as arrays of scalars could be wrongly flagged as
914 -- violating the restriction.
916 if Restriction_Active (No_Default_Initialization) then
917 if Has_Default_Init then
918 Set_Init_Proc (A_Type, Proc_Id);
919 end if;
921 return;
922 end if;
924 Body_Stmts := Init_One_Dimension (1);
925 Parameters := Init_Formals (A_Type, Proc_Id);
927 Discard_Node (
928 Make_Subprogram_Body (Loc,
929 Specification =>
930 Make_Procedure_Specification (Loc,
931 Defining_Unit_Name => Proc_Id,
932 Parameter_Specifications => Parameters),
933 Declarations => New_List,
934 Handled_Statement_Sequence =>
935 Make_Handled_Sequence_Of_Statements (Loc,
936 Statements => Body_Stmts)));
938 Mutate_Ekind (Proc_Id, E_Procedure);
939 Set_Is_Public (Proc_Id, Is_Public (A_Type));
940 Set_Is_Internal (Proc_Id);
941 Set_Has_Completion (Proc_Id);
943 if not Debug_Generated_Code then
944 Set_Debug_Info_Off (Proc_Id);
945 end if;
947 -- Set Inlined on Init_Proc if it is set on the Init_Proc of the
948 -- component type itself (see also Build_Record_Init_Proc).
950 Set_Is_Inlined (Proc_Id, Inline_Init_Proc (Comp_Type));
952 -- Associate Init_Proc with type, and determine if the procedure
953 -- is null (happens because of the Initialize_Scalars pragma case,
954 -- where we have to generate a null procedure in case it is called
955 -- by a client with Initialize_Scalars set). Such procedures have
956 -- to be generated, but do not have to be called, so we mark them
957 -- as null to suppress the call. Kill also warnings for the _Init
958 -- out parameter, which is left entirely uninitialized.
960 Set_Init_Proc (A_Type, Proc_Id);
962 if Is_Null_Statement_List (Body_Stmts) then
963 Set_Is_Null_Init_Proc (Proc_Id);
964 Set_Warnings_Off (Defining_Identifier (First (Parameters)));
966 else
967 -- Try to build a static aggregate to statically initialize
968 -- objects of the type. This can only be done for constrained
969 -- one-dimensional arrays with static bounds.
971 Set_Static_Initialization
972 (Proc_Id,
973 Build_Equivalent_Array_Aggregate (First_Subtype (A_Type)));
974 end if;
975 end if;
976 end Build_Array_Init_Proc;
978 --------------------------------
979 -- Build_Discr_Checking_Funcs --
980 --------------------------------
982 procedure Build_Discr_Checking_Funcs (N : Node_Id) is
983 Rec_Id : Entity_Id;
984 Loc : Source_Ptr;
985 Enclosing_Func_Id : Entity_Id;
986 Sequence : Nat := 1;
987 Type_Def : Node_Id;
988 V : Node_Id;
990 function Build_Case_Statement
991 (Case_Id : Entity_Id;
992 Variant : Node_Id) return Node_Id;
993 -- Build a case statement containing only two alternatives. The first
994 -- alternative corresponds to the discrete choices given on the variant
995 -- that contains the components that we are generating the checks
996 -- for. If the discriminant is one of these return False. The second
997 -- alternative is an OTHERS choice that returns True indicating the
998 -- discriminant did not match.
1000 function Build_Dcheck_Function
1001 (Case_Id : Entity_Id;
1002 Variant : Node_Id) return Entity_Id;
1003 -- Build the discriminant checking function for a given variant
1005 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id);
1006 -- Builds the discriminant checking function for each variant of the
1007 -- given variant part of the record type.
1009 --------------------------
1010 -- Build_Case_Statement --
1011 --------------------------
1013 function Build_Case_Statement
1014 (Case_Id : Entity_Id;
1015 Variant : Node_Id) return Node_Id
1017 Alt_List : constant List_Id := New_List;
1018 Actuals_List : List_Id;
1019 Case_Node : Node_Id;
1020 Case_Alt_Node : Node_Id;
1021 Choice : Node_Id;
1022 Choice_List : List_Id;
1023 D : Entity_Id;
1024 Return_Node : Node_Id;
1026 begin
1027 Case_Node := New_Node (N_Case_Statement, Loc);
1028 Set_End_Span (Case_Node, Uint_0);
1030 -- Replace the discriminant which controls the variant with the name
1031 -- of the formal of the checking function.
1033 Set_Expression (Case_Node, Make_Identifier (Loc, Chars (Case_Id)));
1035 Choice := First (Discrete_Choices (Variant));
1037 if Nkind (Choice) = N_Others_Choice then
1038 Choice_List := New_Copy_List (Others_Discrete_Choices (Choice));
1039 else
1040 Choice_List := New_Copy_List (Discrete_Choices (Variant));
1041 end if;
1043 if not Is_Empty_List (Choice_List) then
1044 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
1045 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
1047 -- In case this is a nested variant, we need to return the result
1048 -- of the discriminant checking function for the immediately
1049 -- enclosing variant.
1051 if Present (Enclosing_Func_Id) then
1052 Actuals_List := New_List;
1054 D := First_Discriminant (Rec_Id);
1055 while Present (D) loop
1056 Append (Make_Identifier (Loc, Chars (D)), Actuals_List);
1057 Next_Discriminant (D);
1058 end loop;
1060 Return_Node :=
1061 Make_Simple_Return_Statement (Loc,
1062 Expression =>
1063 Make_Function_Call (Loc,
1064 Name =>
1065 New_Occurrence_Of (Enclosing_Func_Id, Loc),
1066 Parameter_Associations =>
1067 Actuals_List));
1069 else
1070 Return_Node :=
1071 Make_Simple_Return_Statement (Loc,
1072 Expression =>
1073 New_Occurrence_Of (Standard_False, Loc));
1074 end if;
1076 Set_Statements (Case_Alt_Node, New_List (Return_Node));
1077 Append (Case_Alt_Node, Alt_List);
1078 end if;
1080 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
1081 Choice_List := New_List (New_Node (N_Others_Choice, Loc));
1082 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
1084 Return_Node :=
1085 Make_Simple_Return_Statement (Loc,
1086 Expression =>
1087 New_Occurrence_Of (Standard_True, Loc));
1089 Set_Statements (Case_Alt_Node, New_List (Return_Node));
1090 Append (Case_Alt_Node, Alt_List);
1092 Set_Alternatives (Case_Node, Alt_List);
1093 return Case_Node;
1094 end Build_Case_Statement;
1096 ---------------------------
1097 -- Build_Dcheck_Function --
1098 ---------------------------
1100 function Build_Dcheck_Function
1101 (Case_Id : Entity_Id;
1102 Variant : Node_Id) return Entity_Id
1104 Body_Node : Node_Id;
1105 Func_Id : Entity_Id;
1106 Parameter_List : List_Id;
1107 Spec_Node : Node_Id;
1109 begin
1110 Body_Node := New_Node (N_Subprogram_Body, Loc);
1111 Sequence := Sequence + 1;
1113 Func_Id :=
1114 Make_Defining_Identifier (Loc,
1115 Chars => New_External_Name (Chars (Rec_Id), 'D', Sequence));
1116 Set_Is_Discriminant_Check_Function (Func_Id);
1118 Spec_Node := New_Node (N_Function_Specification, Loc);
1119 Set_Defining_Unit_Name (Spec_Node, Func_Id);
1121 Parameter_List := Build_Discriminant_Formals (Rec_Id, False);
1123 Set_Parameter_Specifications (Spec_Node, Parameter_List);
1124 Set_Result_Definition (Spec_Node,
1125 New_Occurrence_Of (Standard_Boolean, Loc));
1126 Set_Specification (Body_Node, Spec_Node);
1127 Set_Declarations (Body_Node, New_List);
1129 Set_Handled_Statement_Sequence (Body_Node,
1130 Make_Handled_Sequence_Of_Statements (Loc,
1131 Statements => New_List (
1132 Build_Case_Statement (Case_Id, Variant))));
1134 Mutate_Ekind (Func_Id, E_Function);
1135 Set_Mechanism (Func_Id, Default_Mechanism);
1136 Set_Is_Inlined (Func_Id, True);
1137 Set_Is_Pure (Func_Id, True);
1138 Set_Is_Public (Func_Id, Is_Public (Rec_Id));
1139 Set_Is_Internal (Func_Id, True);
1141 if not Debug_Generated_Code then
1142 Set_Debug_Info_Off (Func_Id);
1143 end if;
1145 Analyze (Body_Node);
1147 Append_Freeze_Action (Rec_Id, Body_Node);
1148 Set_Dcheck_Function (Variant, Func_Id);
1149 return Func_Id;
1150 end Build_Dcheck_Function;
1152 ----------------------------
1153 -- Build_Dcheck_Functions --
1154 ----------------------------
1156 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id) is
1157 Component_List_Node : Node_Id;
1158 Decl : Entity_Id;
1159 Discr_Name : Entity_Id;
1160 Func_Id : Entity_Id;
1161 Variant : Node_Id;
1162 Saved_Enclosing_Func_Id : Entity_Id;
1164 begin
1165 -- Build the discriminant-checking function for each variant, and
1166 -- label all components of that variant with the function's name.
1167 -- We only Generate a discriminant-checking function when the
1168 -- variant is not empty, to prevent the creation of dead code.
1170 Discr_Name := Entity (Name (Variant_Part_Node));
1171 Variant := First_Non_Pragma (Variants (Variant_Part_Node));
1173 while Present (Variant) loop
1174 Component_List_Node := Component_List (Variant);
1176 if not Null_Present (Component_List_Node) then
1177 Func_Id := Build_Dcheck_Function (Discr_Name, Variant);
1179 Decl :=
1180 First_Non_Pragma (Component_Items (Component_List_Node));
1181 while Present (Decl) loop
1182 Set_Discriminant_Checking_Func
1183 (Defining_Identifier (Decl), Func_Id);
1184 Next_Non_Pragma (Decl);
1185 end loop;
1187 if Present (Variant_Part (Component_List_Node)) then
1188 Saved_Enclosing_Func_Id := Enclosing_Func_Id;
1189 Enclosing_Func_Id := Func_Id;
1190 Build_Dcheck_Functions (Variant_Part (Component_List_Node));
1191 Enclosing_Func_Id := Saved_Enclosing_Func_Id;
1192 end if;
1193 end if;
1195 Next_Non_Pragma (Variant);
1196 end loop;
1197 end Build_Dcheck_Functions;
1199 -- Start of processing for Build_Discr_Checking_Funcs
1201 begin
1202 -- Only build if not done already
1204 if not Discr_Check_Funcs_Built (N) then
1205 Type_Def := Type_Definition (N);
1207 if Nkind (Type_Def) = N_Record_Definition then
1208 if No (Component_List (Type_Def)) then -- null record.
1209 return;
1210 else
1211 V := Variant_Part (Component_List (Type_Def));
1212 end if;
1214 else pragma Assert (Nkind (Type_Def) = N_Derived_Type_Definition);
1215 if No (Component_List (Record_Extension_Part (Type_Def))) then
1216 return;
1217 else
1218 V := Variant_Part
1219 (Component_List (Record_Extension_Part (Type_Def)));
1220 end if;
1221 end if;
1223 Rec_Id := Defining_Identifier (N);
1225 if Present (V) and then not Is_Unchecked_Union (Rec_Id) then
1226 Loc := Sloc (N);
1227 Enclosing_Func_Id := Empty;
1228 Build_Dcheck_Functions (V);
1229 end if;
1231 Set_Discr_Check_Funcs_Built (N);
1232 end if;
1233 end Build_Discr_Checking_Funcs;
1235 ----------------------------------------
1236 -- Build_Or_Copy_Discr_Checking_Funcs --
1237 ----------------------------------------
1239 procedure Build_Or_Copy_Discr_Checking_Funcs (N : Node_Id) is
1240 Typ : constant Entity_Id := Defining_Identifier (N);
1241 begin
1242 if Is_Unchecked_Union (Typ) or else not Has_Discriminants (Typ) then
1243 null;
1244 elsif not Is_Derived_Type (Typ)
1245 or else Has_New_Non_Standard_Rep (Typ)
1246 or else Is_Tagged_Type (Typ)
1247 then
1248 Build_Discr_Checking_Funcs (N);
1249 else
1250 Copy_Discr_Checking_Funcs (N);
1251 end if;
1252 end Build_Or_Copy_Discr_Checking_Funcs;
1254 --------------------------------
1255 -- Build_Discriminant_Formals --
1256 --------------------------------
1258 function Build_Discriminant_Formals
1259 (Rec_Id : Entity_Id;
1260 Use_Dl : Boolean) return List_Id
1262 Loc : Source_Ptr := Sloc (Rec_Id);
1263 Parameter_List : constant List_Id := New_List;
1264 D : Entity_Id;
1265 Formal : Entity_Id;
1266 Formal_Type : Entity_Id;
1267 Param_Spec_Node : Node_Id;
1269 begin
1270 if Has_Discriminants (Rec_Id) then
1271 D := First_Discriminant (Rec_Id);
1272 while Present (D) loop
1273 Loc := Sloc (D);
1275 if Use_Dl then
1276 Formal := Discriminal (D);
1277 Formal_Type := Etype (Formal);
1278 else
1279 Formal := Make_Defining_Identifier (Loc, Chars (D));
1280 Formal_Type := Etype (D);
1281 end if;
1283 Param_Spec_Node :=
1284 Make_Parameter_Specification (Loc,
1285 Defining_Identifier => Formal,
1286 Parameter_Type =>
1287 New_Occurrence_Of (Formal_Type, Loc));
1288 Append (Param_Spec_Node, Parameter_List);
1289 Next_Discriminant (D);
1290 end loop;
1291 end if;
1293 return Parameter_List;
1294 end Build_Discriminant_Formals;
1296 --------------------------------------
1297 -- Build_Equivalent_Array_Aggregate --
1298 --------------------------------------
1300 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id is
1301 Loc : constant Source_Ptr := Sloc (T);
1302 Comp_Type : constant Entity_Id := Component_Type (T);
1303 Index_Type : constant Entity_Id := Etype (First_Index (T));
1304 Proc : constant Entity_Id := Base_Init_Proc (T);
1305 Lo, Hi : Node_Id;
1306 Aggr : Node_Id;
1307 Expr : Node_Id;
1309 begin
1310 if not Is_Constrained (T)
1311 or else Number_Dimensions (T) > 1
1312 or else No (Proc)
1313 then
1314 Initialization_Warning (T);
1315 return Empty;
1316 end if;
1318 Lo := Type_Low_Bound (Index_Type);
1319 Hi := Type_High_Bound (Index_Type);
1321 if not Compile_Time_Known_Value (Lo)
1322 or else not Compile_Time_Known_Value (Hi)
1323 then
1324 Initialization_Warning (T);
1325 return Empty;
1326 end if;
1328 if Is_Record_Type (Comp_Type)
1329 and then Present (Base_Init_Proc (Comp_Type))
1330 then
1331 Expr := Static_Initialization (Base_Init_Proc (Comp_Type));
1333 if No (Expr) then
1334 Initialization_Warning (T);
1335 return Empty;
1336 end if;
1338 else
1339 Initialization_Warning (T);
1340 return Empty;
1341 end if;
1343 Aggr := Make_Aggregate (Loc, No_List, New_List);
1344 Set_Etype (Aggr, T);
1345 Set_Aggregate_Bounds (Aggr,
1346 Make_Range (Loc,
1347 Low_Bound => New_Copy (Lo),
1348 High_Bound => New_Copy (Hi)));
1349 Set_Parent (Aggr, Parent (Proc));
1351 Append_To (Component_Associations (Aggr),
1352 Make_Component_Association (Loc,
1353 Choices =>
1354 New_List (
1355 Make_Range (Loc,
1356 Low_Bound => New_Copy (Lo),
1357 High_Bound => New_Copy (Hi))),
1358 Expression => Expr));
1360 if Static_Array_Aggregate (Aggr) then
1361 return Aggr;
1362 else
1363 Initialization_Warning (T);
1364 return Empty;
1365 end if;
1366 end Build_Equivalent_Array_Aggregate;
1368 ---------------------------------------
1369 -- Build_Equivalent_Record_Aggregate --
1370 ---------------------------------------
1372 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id is
1373 Agg : Node_Id;
1374 Comp : Entity_Id;
1375 Comp_Type : Entity_Id;
1377 begin
1378 if not Is_Record_Type (T)
1379 or else Has_Discriminants (T)
1380 or else Is_Limited_Type (T)
1381 or else Has_Non_Standard_Rep (T)
1382 then
1383 Initialization_Warning (T);
1384 return Empty;
1385 end if;
1387 Comp := First_Component (T);
1389 -- A null record needs no warning
1391 if No (Comp) then
1392 return Empty;
1393 end if;
1395 while Present (Comp) loop
1397 -- Array components are acceptable if initialized by a positional
1398 -- aggregate with static components.
1400 if Is_Array_Type (Etype (Comp)) then
1401 Comp_Type := Component_Type (Etype (Comp));
1403 if Nkind (Parent (Comp)) /= N_Component_Declaration
1404 or else No (Expression (Parent (Comp)))
1405 or else Nkind (Expression (Parent (Comp))) /= N_Aggregate
1406 then
1407 Initialization_Warning (T);
1408 return Empty;
1410 elsif Is_Scalar_Type (Component_Type (Etype (Comp)))
1411 and then
1412 (not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1413 or else
1414 not Compile_Time_Known_Value (Type_High_Bound (Comp_Type)))
1415 then
1416 Initialization_Warning (T);
1417 return Empty;
1419 elsif
1420 not Static_Array_Aggregate (Expression (Parent (Comp)))
1421 then
1422 Initialization_Warning (T);
1423 return Empty;
1425 -- We need to return empty if the type has predicates because
1426 -- this would otherwise duplicate calls to the predicate
1427 -- function. If the type hasn't been frozen before being
1428 -- referenced in the current record, the extraneous call to
1429 -- the predicate function would be inserted somewhere before
1430 -- the predicate function is elaborated, which would result in
1431 -- an invalid tree.
1433 elsif Has_Predicates (Etype (Comp)) then
1434 return Empty;
1435 end if;
1437 elsif Is_Scalar_Type (Etype (Comp)) then
1438 Comp_Type := Etype (Comp);
1440 if Nkind (Parent (Comp)) /= N_Component_Declaration
1441 or else No (Expression (Parent (Comp)))
1442 or else not Compile_Time_Known_Value (Expression (Parent (Comp)))
1443 or else not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1444 or else not
1445 Compile_Time_Known_Value (Type_High_Bound (Comp_Type))
1446 then
1447 Initialization_Warning (T);
1448 return Empty;
1449 end if;
1451 -- For now, other types are excluded
1453 else
1454 Initialization_Warning (T);
1455 return Empty;
1456 end if;
1458 Next_Component (Comp);
1459 end loop;
1461 -- All components have static initialization. Build positional aggregate
1462 -- from the given expressions or defaults.
1464 Agg := Make_Aggregate (Sloc (T), New_List, New_List);
1465 Set_Parent (Agg, Parent (T));
1467 Comp := First_Component (T);
1468 while Present (Comp) loop
1469 Append
1470 (New_Copy_Tree (Expression (Parent (Comp))), Expressions (Agg));
1471 Next_Component (Comp);
1472 end loop;
1474 Analyze_And_Resolve (Agg, T);
1475 return Agg;
1476 end Build_Equivalent_Record_Aggregate;
1478 ----------------------------
1479 -- Init_Proc_Level_Formal --
1480 ----------------------------
1482 function Init_Proc_Level_Formal (Proc : Entity_Id) return Entity_Id is
1483 Form : Entity_Id;
1484 begin
1485 -- Move through the formals of the initialization procedure Proc to find
1486 -- the extra accessibility level parameter associated with the object
1487 -- being initialized.
1489 Form := First_Formal (Proc);
1490 while Present (Form) loop
1491 if Chars (Form) = Name_uInit_Level then
1492 return Form;
1493 end if;
1495 Next_Formal (Form);
1496 end loop;
1498 -- No formal was found, return Empty
1500 return Empty;
1501 end Init_Proc_Level_Formal;
1503 -------------------------------
1504 -- Build_Initialization_Call --
1505 -------------------------------
1507 -- References to a discriminant inside the record type declaration can
1508 -- appear either in the subtype_indication to constrain a record or an
1509 -- array, or as part of a larger expression given for the initial value
1510 -- of a component. In both of these cases N appears in the record
1511 -- initialization procedure and needs to be replaced by the formal
1512 -- parameter of the initialization procedure which corresponds to that
1513 -- discriminant.
1515 -- In the example below, references to discriminants D1 and D2 in proc_1
1516 -- are replaced by references to formals with the same name
1517 -- (discriminals)
1519 -- A similar replacement is done for calls to any record initialization
1520 -- procedure for any components that are themselves of a record type.
1522 -- type R (D1, D2 : Integer) is record
1523 -- X : Integer := F * D1;
1524 -- Y : Integer := F * D2;
1525 -- end record;
1527 -- procedure proc_1 (Out_2 : out R; D1 : Integer; D2 : Integer) is
1528 -- begin
1529 -- Out_2.D1 := D1;
1530 -- Out_2.D2 := D2;
1531 -- Out_2.X := F * D1;
1532 -- Out_2.Y := F * D2;
1533 -- end;
1535 function Build_Initialization_Call
1536 (Loc : Source_Ptr;
1537 Id_Ref : Node_Id;
1538 Typ : Entity_Id;
1539 In_Init_Proc : Boolean := False;
1540 Enclos_Type : Entity_Id := Empty;
1541 Discr_Map : Elist_Id := New_Elmt_List;
1542 With_Default_Init : Boolean := False;
1543 Constructor_Ref : Node_Id := Empty;
1544 Init_Control_Actual : Entity_Id := Empty) return List_Id
1546 Res : constant List_Id := New_List;
1548 Full_Type : Entity_Id;
1550 procedure Check_Predicated_Discriminant
1551 (Val : Node_Id;
1552 Discr : Entity_Id);
1553 -- Discriminants whose subtypes have predicates are checked in two
1554 -- cases:
1555 -- a) When an object is default-initialized and assertions are enabled
1556 -- we check that the value of the discriminant obeys the predicate.
1558 -- b) In all cases, if the discriminant controls a variant and the
1559 -- variant has no others_choice, Constraint_Error must be raised if
1560 -- the predicate is violated, because there is no variant covered
1561 -- by the illegal discriminant value.
1563 -----------------------------------
1564 -- Check_Predicated_Discriminant --
1565 -----------------------------------
1567 procedure Check_Predicated_Discriminant
1568 (Val : Node_Id;
1569 Discr : Entity_Id)
1571 Typ : constant Entity_Id := Etype (Discr);
1573 procedure Check_Missing_Others (V : Node_Id);
1574 -- Check that a given variant and its nested variants have an others
1575 -- choice, and generate a constraint error raise when it does not.
1577 --------------------------
1578 -- Check_Missing_Others --
1579 --------------------------
1581 procedure Check_Missing_Others (V : Node_Id) is
1582 Alt : Node_Id;
1583 Choice : Node_Id;
1584 Last_Var : Node_Id;
1586 begin
1587 Last_Var := Last_Non_Pragma (Variants (V));
1588 Choice := First (Discrete_Choices (Last_Var));
1590 -- An others_choice is added during expansion for gcc use, but
1591 -- does not cover the illegality.
1593 if Entity (Name (V)) = Discr then
1594 if Present (Choice)
1595 and then (Nkind (Choice) /= N_Others_Choice
1596 or else not Comes_From_Source (Choice))
1597 then
1598 Check_Expression_Against_Static_Predicate (Val, Typ);
1600 if not Is_Static_Expression (Val) then
1601 Prepend_To (Res,
1602 Make_Raise_Constraint_Error (Loc,
1603 Condition =>
1604 Make_Op_Not (Loc,
1605 Right_Opnd => Make_Predicate_Call (Typ, Val)),
1606 Reason => CE_Invalid_Data));
1607 end if;
1608 end if;
1609 end if;
1611 -- Check whether some nested variant is ruled by the predicated
1612 -- discriminant.
1614 Alt := First (Variants (V));
1615 while Present (Alt) loop
1616 if Nkind (Alt) = N_Variant
1617 and then Present (Variant_Part (Component_List (Alt)))
1618 then
1619 Check_Missing_Others
1620 (Variant_Part (Component_List (Alt)));
1621 end if;
1623 Next (Alt);
1624 end loop;
1625 end Check_Missing_Others;
1627 -- Local variables
1629 Def : Node_Id;
1631 -- Start of processing for Check_Predicated_Discriminant
1633 begin
1634 if Ekind (Base_Type (Full_Type)) = E_Record_Type then
1635 Def := Type_Definition (Parent (Base_Type (Full_Type)));
1636 else
1637 return;
1638 end if;
1640 if Policy_In_Effect (Name_Assert) = Name_Check
1641 and then not Predicates_Ignored (Etype (Discr))
1642 then
1643 Prepend_To (Res, Make_Predicate_Check (Typ, Val));
1644 end if;
1646 -- If discriminant controls a variant, verify that predicate is
1647 -- obeyed or else an Others_Choice is present.
1649 if Nkind (Def) = N_Record_Definition
1650 and then Present (Variant_Part (Component_List (Def)))
1651 and then Policy_In_Effect (Name_Assert) = Name_Ignore
1652 then
1653 Check_Missing_Others (Variant_Part (Component_List (Def)));
1654 end if;
1655 end Check_Predicated_Discriminant;
1657 -- Local variables
1659 Arg : Node_Id;
1660 Args : List_Id;
1661 Decls : List_Id;
1662 Decl : Node_Id;
1663 Discr : Entity_Id;
1664 First_Arg : Node_Id;
1665 Full_Init_Type : Entity_Id;
1666 Init_Call : Node_Id;
1667 Init_Type : Entity_Id;
1668 Proc : Entity_Id;
1670 -- Start of processing for Build_Initialization_Call
1672 begin
1673 pragma Assert (Constructor_Ref = Empty
1674 or else Is_CPP_Constructor_Call (Constructor_Ref));
1676 if No (Constructor_Ref) then
1677 Proc := Base_Init_Proc (Typ);
1678 else
1679 Proc := Base_Init_Proc (Typ, Entity (Name (Constructor_Ref)));
1680 end if;
1682 pragma Assert (Present (Proc));
1683 Init_Type := Etype (First_Formal (Proc));
1684 Full_Init_Type := Underlying_Type (Init_Type);
1686 -- Nothing to do if the Init_Proc is null, unless Initialize_Scalars
1687 -- is active (in which case we make the call anyway, since in the
1688 -- actual compiled client it may be non null).
1690 if Is_Null_Init_Proc (Proc) and then not Init_Or_Norm_Scalars then
1691 return Empty_List;
1693 -- Nothing to do for an array of controlled components that have only
1694 -- the inherited Initialize primitive. This is a useful optimization
1695 -- for CodePeer.
1697 elsif Is_Trivial_Subprogram (Proc)
1698 and then Is_Array_Type (Full_Init_Type)
1699 then
1700 return New_List (Make_Null_Statement (Loc));
1701 end if;
1703 -- Use the [underlying] full view when dealing with a private type. This
1704 -- may require several steps depending on derivations.
1706 Full_Type := Typ;
1707 loop
1708 if Is_Private_Type (Full_Type) then
1709 if Present (Full_View (Full_Type)) then
1710 Full_Type := Full_View (Full_Type);
1712 elsif Present (Underlying_Full_View (Full_Type)) then
1713 Full_Type := Underlying_Full_View (Full_Type);
1715 -- When a private type acts as a generic actual and lacks a full
1716 -- view, use the base type.
1718 elsif Is_Generic_Actual_Type (Full_Type) then
1719 Full_Type := Base_Type (Full_Type);
1721 elsif Ekind (Full_Type) = E_Private_Subtype
1722 and then (not Has_Discriminants (Full_Type)
1723 or else No (Discriminant_Constraint (Full_Type)))
1724 then
1725 Full_Type := Etype (Full_Type);
1727 -- The loop has recovered the [underlying] full view, stop the
1728 -- traversal.
1730 else
1731 exit;
1732 end if;
1734 -- The type is not private, nothing to do
1736 else
1737 exit;
1738 end if;
1739 end loop;
1741 -- If Typ is derived, the procedure is the initialization procedure for
1742 -- the root type. Wrap the argument in an conversion to make it type
1743 -- honest. Actually it isn't quite type honest, because there can be
1744 -- conflicts of views in the private type case. That is why we set
1745 -- Conversion_OK in the conversion node.
1747 if (Is_Record_Type (Typ)
1748 or else Is_Array_Type (Typ)
1749 or else Is_Private_Type (Typ))
1750 and then Init_Type /= Base_Type (Typ)
1751 then
1752 First_Arg := OK_Convert_To (Etype (Init_Type), Id_Ref);
1753 Set_Etype (First_Arg, Init_Type);
1755 else
1756 First_Arg := Id_Ref;
1757 end if;
1759 Args := New_List (Convert_Concurrent (First_Arg, Typ));
1761 -- In the tasks case, add _Master as the value of the _Master parameter
1762 -- and _Chain as the value of the _Chain parameter. At the outer level,
1763 -- these will be variables holding the corresponding values obtained
1764 -- from GNARL. At inner levels, they will be the parameters passed down
1765 -- through the outer routines.
1767 if Has_Task (Full_Type) then
1768 if Restriction_Active (No_Task_Hierarchy) then
1769 Append_To (Args, Make_Integer_Literal (Loc, Library_Task_Level));
1770 else
1771 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1772 end if;
1774 -- Add _Chain (not done for sequential elaboration policy, see
1775 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
1777 if Partition_Elaboration_Policy /= 'S' then
1778 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1779 end if;
1781 -- Ada 2005 (AI-287): In case of default initialized components
1782 -- with tasks, we generate a null string actual parameter.
1783 -- This is just a workaround that must be improved later???
1785 if With_Default_Init then
1786 Append_To (Args,
1787 Make_String_Literal (Loc,
1788 Strval => ""));
1790 else
1791 Decls :=
1792 Build_Task_Image_Decls (Loc, Id_Ref, Enclos_Type, In_Init_Proc);
1793 Decl := Last (Decls);
1795 Append_To (Args,
1796 New_Occurrence_Of (Defining_Identifier (Decl), Loc));
1797 Append_List (Decls, Res);
1798 end if;
1800 else
1801 Decls := No_List;
1802 Decl := Empty;
1803 end if;
1805 -- Handle the optionally generated formal *_skip_null_excluding_checks
1807 -- Look at the associated node for the object we are referencing and
1808 -- verify that we are expanding a call to an Init_Proc for an internally
1809 -- generated object declaration before passing True and skipping the
1810 -- relevant checks.
1812 if Needs_Conditional_Null_Excluding_Check (Full_Init_Type)
1813 and then Nkind (Id_Ref) in N_Has_Entity
1814 and then (Comes_From_Source (Id_Ref)
1815 or else (Present (Associated_Node (Id_Ref))
1816 and then Comes_From_Source
1817 (Associated_Node (Id_Ref))))
1818 then
1819 Append_To (Args, New_Occurrence_Of (Standard_True, Loc));
1820 end if;
1822 -- Add discriminant values if discriminants are present
1824 if Has_Discriminants (Full_Init_Type) then
1825 Discr := First_Discriminant (Full_Init_Type);
1826 while Present (Discr) loop
1828 -- If this is a discriminated concurrent type, the init_proc
1829 -- for the corresponding record is being called. Use that type
1830 -- directly to find the discriminant value, to handle properly
1831 -- intervening renamed discriminants.
1833 declare
1834 T : Entity_Id := Full_Type;
1836 begin
1837 if Is_Protected_Type (T) then
1838 T := Corresponding_Record_Type (T);
1839 end if;
1841 Arg :=
1842 Get_Discriminant_Value (
1843 Discr,
1845 Discriminant_Constraint (Full_Type));
1846 end;
1848 -- If the target has access discriminants, and is constrained by
1849 -- an access to the enclosing construct, i.e. a current instance,
1850 -- replace the reference to the type by a reference to the object.
1852 if Nkind (Arg) = N_Attribute_Reference
1853 and then Is_Access_Type (Etype (Arg))
1854 and then Is_Entity_Name (Prefix (Arg))
1855 and then Is_Type (Entity (Prefix (Arg)))
1856 then
1857 Arg :=
1858 Make_Attribute_Reference (Loc,
1859 Prefix => New_Copy (Prefix (Id_Ref)),
1860 Attribute_Name => Name_Unrestricted_Access);
1862 elsif In_Init_Proc then
1864 -- Replace any possible references to the discriminant in the
1865 -- call to the record initialization procedure with references
1866 -- to the appropriate formal parameter.
1868 if Nkind (Arg) = N_Identifier
1869 and then Ekind (Entity (Arg)) = E_Discriminant
1870 then
1871 Arg := New_Occurrence_Of (Discriminal (Entity (Arg)), Loc);
1873 -- Otherwise make a copy of the default expression. Note that
1874 -- we use the current Sloc for this, because we do not want the
1875 -- call to appear to be at the declaration point. Within the
1876 -- expression, replace discriminants with their discriminals.
1878 else
1879 Arg :=
1880 New_Copy_Tree (Arg, Map => Discr_Map, New_Sloc => Loc);
1881 end if;
1883 else
1884 if Is_Constrained (Full_Type) then
1885 Arg := Duplicate_Subexpr_No_Checks (Arg);
1886 else
1887 -- The constraints come from the discriminant default exps,
1888 -- they must be reevaluated, so we use New_Copy_Tree but we
1889 -- ensure the proper Sloc (for any embedded calls).
1890 -- In addition, if a predicate check is needed on the value
1891 -- of the discriminant, insert it ahead of the call.
1893 Arg := New_Copy_Tree (Arg, New_Sloc => Loc);
1894 end if;
1896 if Has_Predicates (Etype (Discr)) then
1897 Check_Predicated_Discriminant (Arg, Discr);
1898 end if;
1899 end if;
1901 -- Ada 2005 (AI-287): In case of default initialized components,
1902 -- if the component is constrained with a discriminant of the
1903 -- enclosing type, we need to generate the corresponding selected
1904 -- component node to access the discriminant value. In other cases
1905 -- this is not required, either because we are inside the init
1906 -- proc and we use the corresponding formal, or else because the
1907 -- component is constrained by an expression.
1909 if With_Default_Init
1910 and then Nkind (Id_Ref) = N_Selected_Component
1911 and then Nkind (Arg) = N_Identifier
1912 and then Ekind (Entity (Arg)) = E_Discriminant
1913 then
1914 Append_To (Args,
1915 Make_Selected_Component (Loc,
1916 Prefix => New_Copy_Tree (Prefix (Id_Ref)),
1917 Selector_Name => Arg));
1918 else
1919 Append_To (Args, Arg);
1920 end if;
1922 Next_Discriminant (Discr);
1923 end loop;
1924 end if;
1926 -- If this is a call to initialize the parent component of a derived
1927 -- tagged type, indicate that the tag should not be set in the parent.
1928 -- This is done via the actual parameter value for the Init_Control
1929 -- formal parameter, which is also used to deal with late initialization
1930 -- requirements.
1932 -- We pass in Full_Init_Except_Tag unless the caller tells us to do
1933 -- otherwise (by passing in a nonempty Init_Control_Actual parameter).
1935 if Is_Tagged_Type (Full_Init_Type)
1936 and then not Is_CPP_Class (Full_Init_Type)
1937 and then Nkind (Id_Ref) = N_Selected_Component
1938 and then Chars (Selector_Name (Id_Ref)) = Name_uParent
1939 then
1940 declare
1941 use Initialization_Control;
1942 begin
1943 Append_To (Args,
1944 (if Present (Init_Control_Actual)
1945 then Init_Control_Actual
1946 else Make_Mode_Literal (Loc, Full_Init_Except_Tag)));
1947 end;
1948 elsif Present (Constructor_Ref) then
1949 Append_List_To (Args,
1950 New_Copy_List (Parameter_Associations (Constructor_Ref)));
1951 end if;
1953 -- Pass the extra accessibility level parameter associated with the
1954 -- level of the object being initialized when required.
1956 if Is_Entity_Name (Id_Ref)
1957 and then Present (Init_Proc_Level_Formal (Proc))
1958 then
1959 Append_To (Args,
1960 Make_Parameter_Association (Loc,
1961 Selector_Name =>
1962 Make_Identifier (Loc, Name_uInit_Level),
1963 Explicit_Actual_Parameter =>
1964 Accessibility_Level (Id_Ref, Dynamic_Level)));
1965 end if;
1967 Append_To (Res,
1968 Make_Procedure_Call_Statement (Loc,
1969 Name => New_Occurrence_Of (Proc, Loc),
1970 Parameter_Associations => Args));
1972 if Needs_Finalization (Typ)
1973 and then Nkind (Id_Ref) = N_Selected_Component
1974 then
1975 if Chars (Selector_Name (Id_Ref)) /= Name_uParent then
1976 Init_Call :=
1977 Make_Init_Call
1978 (Obj_Ref => New_Copy_Tree (First_Arg),
1979 Typ => Typ);
1981 -- Guard against a missing [Deep_]Initialize when the type was not
1982 -- properly frozen.
1984 if Present (Init_Call) then
1985 Append_To (Res, Init_Call);
1986 end if;
1987 end if;
1988 end if;
1990 return Res;
1992 exception
1993 when RE_Not_Available =>
1994 return Empty_List;
1995 end Build_Initialization_Call;
1997 ----------------------------
1998 -- Build_Record_Init_Proc --
1999 ----------------------------
2001 procedure Build_Record_Init_Proc (N : Node_Id; Rec_Ent : Entity_Id) is
2002 Decls : constant List_Id := New_List;
2003 Discr_Map : constant Elist_Id := New_Elmt_List;
2004 Loc : constant Source_Ptr := Sloc (Rec_Ent);
2005 Counter : Nat := 0;
2006 Proc_Id : Entity_Id;
2007 Rec_Type : Entity_Id;
2009 Init_Control_Formal : Entity_Id := Empty; -- set in Build_Init_Statements
2010 Has_Late_Init_Comp : Boolean := False; -- set in Build_Init_Statements
2012 function Build_Assignment
2013 (Id : Entity_Id;
2014 Default : Node_Id) return List_Id;
2015 -- Build an assignment statement that assigns the default expression to
2016 -- its corresponding record component if defined. The left-hand side of
2017 -- the assignment is marked Assignment_OK so that initialization of
2018 -- limited private records works correctly. This routine may also build
2019 -- an adjustment call if the component is controlled.
2021 procedure Build_Discriminant_Assignments (Statement_List : List_Id);
2022 -- If the record has discriminants, add assignment statements to
2023 -- Statement_List to initialize the discriminant values from the
2024 -- arguments of the initialization procedure.
2026 function Build_Init_Statements (Comp_List : Node_Id) return List_Id;
2027 -- Build a list representing a sequence of statements which initialize
2028 -- components of the given component list. This may involve building
2029 -- case statements for the variant parts. Append any locally declared
2030 -- objects on list Decls.
2032 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id;
2033 -- Given an untagged type-derivation that declares discriminants, e.g.
2035 -- type R (R1, R2 : Integer) is record ... end record;
2036 -- type D (D1 : Integer) is new R (1, D1);
2038 -- we make the _init_proc of D be
2040 -- procedure _init_proc (X : D; D1 : Integer) is
2041 -- begin
2042 -- _init_proc (R (X), 1, D1);
2043 -- end _init_proc;
2045 -- This function builds the call statement in this _init_proc.
2047 procedure Build_CPP_Init_Procedure;
2048 -- Build the tree corresponding to the procedure specification and body
2049 -- of the IC procedure that initializes the C++ part of the dispatch
2050 -- table of an Ada tagged type that is a derivation of a CPP type.
2051 -- Install it as the CPP_Init TSS.
2053 procedure Build_Init_Procedure;
2054 -- Build the tree corresponding to the procedure specification and body
2055 -- of the initialization procedure and install it as the _init TSS.
2057 procedure Build_Offset_To_Top_Functions;
2058 -- Ada 2005 (AI-251): Build the tree corresponding to the procedure spec
2059 -- and body of Offset_To_Top, a function used in conjuction with types
2060 -- having secondary dispatch tables.
2062 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id);
2063 -- Add range checks to components of discriminated records. S is a
2064 -- subtype indication of a record component. Check_List is a list
2065 -- to which the check actions are appended.
2067 function Component_Needs_Simple_Initialization
2068 (T : Entity_Id) return Boolean;
2069 -- Determine if a component needs simple initialization, given its type
2070 -- T. This routine is the same as Needs_Simple_Initialization except for
2071 -- components of type Tag and Interface_Tag. These two access types do
2072 -- not require initialization since they are explicitly initialized by
2073 -- other means.
2075 function Parent_Subtype_Renaming_Discrims return Boolean;
2076 -- Returns True for base types N that rename discriminants, else False
2078 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean;
2079 -- Determine whether a record initialization procedure needs to be
2080 -- generated for the given record type.
2082 ----------------------
2083 -- Build_Assignment --
2084 ----------------------
2086 function Build_Assignment
2087 (Id : Entity_Id;
2088 Default : Node_Id) return List_Id
2090 Default_Loc : constant Source_Ptr := Sloc (Default);
2091 Typ : constant Entity_Id := Underlying_Type (Etype (Id));
2093 Adj_Call : Node_Id;
2094 Exp : Node_Id := Default;
2095 Kind : Node_Kind := Nkind (Default);
2096 Lhs : Node_Id;
2097 Res : List_Id;
2099 begin
2100 Lhs :=
2101 Make_Selected_Component (Default_Loc,
2102 Prefix => Make_Identifier (Loc, Name_uInit),
2103 Selector_Name => New_Occurrence_Of (Id, Default_Loc));
2104 Set_Assignment_OK (Lhs);
2106 -- Take a copy of Exp to ensure that later copies of this component
2107 -- declaration in derived types see the original tree, not a node
2108 -- rewritten during expansion of the init_proc. If the copy contains
2109 -- itypes, the scope of the new itypes is the init_proc being built.
2111 declare
2112 Map : Elist_Id := No_Elist;
2113 begin
2114 if Has_Late_Init_Comp then
2115 -- Map the type to the _Init parameter in order to
2116 -- handle "current instance" references.
2118 Map := New_Elmt_List
2119 (Elmt1 => Rec_Type,
2120 Elmt2 => Defining_Identifier (First
2121 (Parameter_Specifications
2122 (Parent (Proc_Id)))));
2124 -- If the type has an incomplete view, a current instance
2125 -- may have an incomplete type. In that case, it must also be
2126 -- replaced by the formal of the Init_Proc.
2128 if Nkind (Parent (Rec_Type)) = N_Full_Type_Declaration
2129 and then Present (Incomplete_View (Parent (Rec_Type)))
2130 then
2131 Append_Elmt (
2132 N => Incomplete_View (Parent (Rec_Type)),
2133 To => Map);
2134 Append_Elmt (
2135 N => Defining_Identifier
2136 (First
2137 (Parameter_Specifications
2138 (Parent (Proc_Id)))),
2139 To => Map);
2140 end if;
2141 end if;
2143 Exp := New_Copy_Tree (Exp, New_Scope => Proc_Id, Map => Map);
2144 end;
2146 Res := New_List (
2147 Make_Assignment_Statement (Loc,
2148 Name => Lhs,
2149 Expression => Exp));
2151 Set_No_Ctrl_Actions (First (Res));
2153 -- Adjust the tag if tagged (because of possible view conversions).
2154 -- Suppress the tag adjustment when not Tagged_Type_Expansion because
2155 -- tags are represented implicitly in objects, and when the record is
2156 -- initialized with a raise expression.
2158 if Is_Tagged_Type (Typ)
2159 and then Tagged_Type_Expansion
2160 and then Nkind (Exp) /= N_Raise_Expression
2161 and then (Nkind (Exp) /= N_Qualified_Expression
2162 or else Nkind (Expression (Exp)) /= N_Raise_Expression)
2163 then
2164 Append_To (Res,
2165 Make_Assignment_Statement (Default_Loc,
2166 Name =>
2167 Make_Selected_Component (Default_Loc,
2168 Prefix =>
2169 New_Copy_Tree (Lhs, New_Scope => Proc_Id),
2170 Selector_Name =>
2171 New_Occurrence_Of
2172 (First_Tag_Component (Typ), Default_Loc)),
2174 Expression =>
2175 Unchecked_Convert_To (RTE (RE_Tag),
2176 New_Occurrence_Of
2177 (Node (First_Elmt (Access_Disp_Table (Underlying_Type
2178 (Typ)))),
2179 Default_Loc))));
2180 end if;
2182 -- Adjust the component if controlled except if it is an aggregate
2183 -- that will be expanded inline.
2185 if Kind = N_Qualified_Expression then
2186 Kind := Nkind (Expression (Default));
2187 end if;
2189 if Needs_Finalization (Typ)
2190 and then Kind not in N_Aggregate | N_Extension_Aggregate
2191 and then not Is_Build_In_Place_Function_Call (Exp)
2192 then
2193 Adj_Call :=
2194 Make_Adjust_Call
2195 (Obj_Ref => New_Copy_Tree (Lhs),
2196 Typ => Etype (Id));
2198 -- Guard against a missing [Deep_]Adjust when the component type
2199 -- was not properly frozen.
2201 if Present (Adj_Call) then
2202 Append_To (Res, Adj_Call);
2203 end if;
2204 end if;
2206 -- If a component type has a predicate, add check to the component
2207 -- assignment. Discriminants are handled at the point of the call,
2208 -- which provides for a better error message.
2210 if Comes_From_Source (Exp)
2211 and then Predicate_Enabled (Typ)
2212 then
2213 Append (Make_Predicate_Check (Typ, Exp), Res);
2214 end if;
2216 return Res;
2218 exception
2219 when RE_Not_Available =>
2220 return Empty_List;
2221 end Build_Assignment;
2223 ------------------------------------
2224 -- Build_Discriminant_Assignments --
2225 ------------------------------------
2227 procedure Build_Discriminant_Assignments (Statement_List : List_Id) is
2228 Is_Tagged : constant Boolean := Is_Tagged_Type (Rec_Type);
2229 D : Entity_Id;
2230 D_Loc : Source_Ptr;
2232 begin
2233 if Has_Discriminants (Rec_Type)
2234 and then not Is_Unchecked_Union (Rec_Type)
2235 then
2236 D := First_Discriminant (Rec_Type);
2237 while Present (D) loop
2239 -- Don't generate the assignment for discriminants in derived
2240 -- tagged types if the discriminant is a renaming of some
2241 -- ancestor discriminant. This initialization will be done
2242 -- when initializing the _parent field of the derived record.
2244 if Is_Tagged
2245 and then Present (Corresponding_Discriminant (D))
2246 then
2247 null;
2249 else
2250 D_Loc := Sloc (D);
2251 Append_List_To (Statement_List,
2252 Build_Assignment (D,
2253 New_Occurrence_Of (Discriminal (D), D_Loc)));
2254 end if;
2256 Next_Discriminant (D);
2257 end loop;
2258 end if;
2259 end Build_Discriminant_Assignments;
2261 --------------------------
2262 -- Build_Init_Call_Thru --
2263 --------------------------
2265 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id is
2266 Parent_Proc : constant Entity_Id :=
2267 Base_Init_Proc (Etype (Rec_Type));
2269 Parent_Type : constant Entity_Id :=
2270 Etype (First_Formal (Parent_Proc));
2272 Uparent_Type : constant Entity_Id :=
2273 Underlying_Type (Parent_Type);
2275 First_Discr_Param : Node_Id;
2277 Arg : Node_Id;
2278 Args : List_Id;
2279 First_Arg : Node_Id;
2280 Parent_Discr : Entity_Id;
2281 Res : List_Id;
2283 begin
2284 -- First argument (_Init) is the object to be initialized.
2285 -- ??? not sure where to get a reasonable Loc for First_Arg
2287 First_Arg :=
2288 OK_Convert_To (Parent_Type,
2289 New_Occurrence_Of
2290 (Defining_Identifier (First (Parameters)), Loc));
2292 Set_Etype (First_Arg, Parent_Type);
2294 Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
2296 -- In the tasks case,
2297 -- add _Master as the value of the _Master parameter
2298 -- add _Chain as the value of the _Chain parameter.
2299 -- add _Task_Name as the value of the _Task_Name parameter.
2300 -- At the outer level, these will be variables holding the
2301 -- corresponding values obtained from GNARL or the expander.
2303 -- At inner levels, they will be the parameters passed down through
2304 -- the outer routines.
2306 First_Discr_Param := Next (First (Parameters));
2308 if Has_Task (Rec_Type) then
2309 if Restriction_Active (No_Task_Hierarchy) then
2310 Append_To
2311 (Args, Make_Integer_Literal (Loc, Library_Task_Level));
2312 else
2313 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
2314 end if;
2316 -- Add _Chain (not done for sequential elaboration policy, see
2317 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
2319 if Partition_Elaboration_Policy /= 'S' then
2320 Append_To (Args, Make_Identifier (Loc, Name_uChain));
2321 end if;
2323 Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
2324 First_Discr_Param := Next (Next (Next (First_Discr_Param)));
2325 end if;
2327 -- Append discriminant values
2329 if Has_Discriminants (Uparent_Type) then
2330 pragma Assert (not Is_Tagged_Type (Uparent_Type));
2332 Parent_Discr := First_Discriminant (Uparent_Type);
2333 while Present (Parent_Discr) loop
2335 -- Get the initial value for this discriminant
2336 -- ??? needs to be cleaned up to use parent_Discr_Constr
2337 -- directly.
2339 declare
2340 Discr : Entity_Id :=
2341 First_Stored_Discriminant (Uparent_Type);
2343 Discr_Value : Elmt_Id :=
2344 First_Elmt (Stored_Constraint (Rec_Type));
2346 begin
2347 while Original_Record_Component (Parent_Discr) /= Discr loop
2348 Next_Stored_Discriminant (Discr);
2349 Next_Elmt (Discr_Value);
2350 end loop;
2352 Arg := Node (Discr_Value);
2353 end;
2355 -- Append it to the list
2357 if Nkind (Arg) = N_Identifier
2358 and then Ekind (Entity (Arg)) = E_Discriminant
2359 then
2360 Append_To (Args,
2361 New_Occurrence_Of (Discriminal (Entity (Arg)), Loc));
2363 -- Case of access discriminants. We replace the reference
2364 -- to the type by a reference to the actual object.
2366 -- Is above comment right??? Use of New_Copy below seems mighty
2367 -- suspicious ???
2369 else
2370 Append_To (Args, New_Copy (Arg));
2371 end if;
2373 Next_Discriminant (Parent_Discr);
2374 end loop;
2375 end if;
2377 Res :=
2378 New_List (
2379 Make_Procedure_Call_Statement (Loc,
2380 Name =>
2381 New_Occurrence_Of (Parent_Proc, Loc),
2382 Parameter_Associations => Args));
2384 return Res;
2385 end Build_Init_Call_Thru;
2387 -----------------------------------
2388 -- Build_Offset_To_Top_Functions --
2389 -----------------------------------
2391 procedure Build_Offset_To_Top_Functions is
2393 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id);
2394 -- Generate:
2395 -- function Fxx (O : Address) return Storage_Offset is
2396 -- type Acc is access all <Typ>;
2397 -- begin
2398 -- return Acc!(O).Iface_Comp'Position;
2399 -- end Fxx;
2401 ----------------------------------
2402 -- Build_Offset_To_Top_Function --
2403 ----------------------------------
2405 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id) is
2406 Body_Node : Node_Id;
2407 Func_Id : Entity_Id;
2408 Spec_Node : Node_Id;
2409 Acc_Type : Entity_Id;
2411 begin
2412 Func_Id := Make_Temporary (Loc, 'F');
2413 Set_DT_Offset_To_Top_Func (Iface_Comp, Func_Id);
2415 -- Generate
2416 -- function Fxx (O : in Rec_Typ) return Storage_Offset;
2418 Spec_Node := New_Node (N_Function_Specification, Loc);
2419 Set_Defining_Unit_Name (Spec_Node, Func_Id);
2420 Set_Parameter_Specifications (Spec_Node, New_List (
2421 Make_Parameter_Specification (Loc,
2422 Defining_Identifier =>
2423 Make_Defining_Identifier (Loc, Name_uO),
2424 In_Present => True,
2425 Parameter_Type =>
2426 New_Occurrence_Of (RTE (RE_Address), Loc))));
2427 Set_Result_Definition (Spec_Node,
2428 New_Occurrence_Of (RTE (RE_Storage_Offset), Loc));
2430 -- Generate
2431 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2432 -- begin
2433 -- return -O.Iface_Comp'Position;
2434 -- end Fxx;
2436 Body_Node := New_Node (N_Subprogram_Body, Loc);
2437 Set_Specification (Body_Node, Spec_Node);
2439 Acc_Type := Make_Temporary (Loc, 'T');
2440 Set_Declarations (Body_Node, New_List (
2441 Make_Full_Type_Declaration (Loc,
2442 Defining_Identifier => Acc_Type,
2443 Type_Definition =>
2444 Make_Access_To_Object_Definition (Loc,
2445 All_Present => True,
2446 Null_Exclusion_Present => False,
2447 Constant_Present => False,
2448 Subtype_Indication =>
2449 New_Occurrence_Of (Rec_Type, Loc)))));
2451 Set_Handled_Statement_Sequence (Body_Node,
2452 Make_Handled_Sequence_Of_Statements (Loc,
2453 Statements => New_List (
2454 Make_Simple_Return_Statement (Loc,
2455 Expression =>
2456 Make_Op_Minus (Loc,
2457 Make_Attribute_Reference (Loc,
2458 Prefix =>
2459 Make_Selected_Component (Loc,
2460 Prefix =>
2461 Make_Explicit_Dereference (Loc,
2462 Unchecked_Convert_To (Acc_Type,
2463 Make_Identifier (Loc, Name_uO))),
2464 Selector_Name =>
2465 New_Occurrence_Of (Iface_Comp, Loc)),
2466 Attribute_Name => Name_Position))))));
2468 Mutate_Ekind (Func_Id, E_Function);
2469 Set_Mechanism (Func_Id, Default_Mechanism);
2470 Set_Is_Internal (Func_Id, True);
2472 if not Debug_Generated_Code then
2473 Set_Debug_Info_Off (Func_Id);
2474 end if;
2476 Analyze (Body_Node);
2478 Append_Freeze_Action (Rec_Type, Body_Node);
2479 end Build_Offset_To_Top_Function;
2481 -- Local variables
2483 Iface_Comp : Node_Id;
2484 Iface_Comp_Elmt : Elmt_Id;
2485 Ifaces_Comp_List : Elist_Id;
2487 -- Start of processing for Build_Offset_To_Top_Functions
2489 begin
2490 -- Offset_To_Top_Functions are built only for derivations of types
2491 -- with discriminants that cover interface types.
2492 -- Nothing is needed either in case of virtual targets, since
2493 -- interfaces are handled directly by the target.
2495 if not Is_Tagged_Type (Rec_Type)
2496 or else Etype (Rec_Type) = Rec_Type
2497 or else not Has_Discriminants (Etype (Rec_Type))
2498 or else not Tagged_Type_Expansion
2499 then
2500 return;
2501 end if;
2503 Collect_Interface_Components (Rec_Type, Ifaces_Comp_List);
2505 -- For each interface type with secondary dispatch table we generate
2506 -- the Offset_To_Top_Functions (required to displace the pointer in
2507 -- interface conversions)
2509 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
2510 while Present (Iface_Comp_Elmt) loop
2511 Iface_Comp := Node (Iface_Comp_Elmt);
2512 pragma Assert (Is_Interface (Related_Type (Iface_Comp)));
2514 -- If the interface is a parent of Rec_Type it shares the primary
2515 -- dispatch table and hence there is no need to build the function
2517 if not Is_Ancestor (Related_Type (Iface_Comp), Rec_Type,
2518 Use_Full_View => True)
2519 then
2520 Build_Offset_To_Top_Function (Iface_Comp);
2521 end if;
2523 Next_Elmt (Iface_Comp_Elmt);
2524 end loop;
2525 end Build_Offset_To_Top_Functions;
2527 ------------------------------
2528 -- Build_CPP_Init_Procedure --
2529 ------------------------------
2531 procedure Build_CPP_Init_Procedure is
2532 Body_Node : Node_Id;
2533 Body_Stmts : List_Id;
2534 Flag_Id : Entity_Id;
2535 Handled_Stmt_Node : Node_Id;
2536 Init_Tags_List : List_Id;
2537 Proc_Id : Entity_Id;
2538 Proc_Spec_Node : Node_Id;
2540 begin
2541 -- Check cases requiring no IC routine
2543 if not Is_CPP_Class (Root_Type (Rec_Type))
2544 or else Is_CPP_Class (Rec_Type)
2545 or else CPP_Num_Prims (Rec_Type) = 0
2546 or else not Tagged_Type_Expansion
2547 or else No_Run_Time_Mode
2548 then
2549 return;
2550 end if;
2552 -- Generate:
2554 -- Flag : Boolean := False;
2556 -- procedure Typ_IC is
2557 -- begin
2558 -- if not Flag then
2559 -- Copy C++ dispatch table slots from parent
2560 -- Update C++ slots of overridden primitives
2561 -- end if;
2562 -- end;
2564 Flag_Id := Make_Temporary (Loc, 'F');
2566 Append_Freeze_Action (Rec_Type,
2567 Make_Object_Declaration (Loc,
2568 Defining_Identifier => Flag_Id,
2569 Object_Definition =>
2570 New_Occurrence_Of (Standard_Boolean, Loc),
2571 Expression =>
2572 New_Occurrence_Of (Standard_True, Loc)));
2574 Body_Stmts := New_List;
2575 Body_Node := New_Node (N_Subprogram_Body, Loc);
2577 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2579 Proc_Id :=
2580 Make_Defining_Identifier (Loc,
2581 Chars => Make_TSS_Name (Rec_Type, TSS_CPP_Init_Proc));
2583 Mutate_Ekind (Proc_Id, E_Procedure);
2584 Set_Is_Internal (Proc_Id);
2586 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2588 Set_Parameter_Specifications (Proc_Spec_Node, New_List);
2589 Set_Specification (Body_Node, Proc_Spec_Node);
2590 Set_Declarations (Body_Node, New_List);
2592 Init_Tags_List := Build_Inherit_CPP_Prims (Rec_Type);
2594 Append_To (Init_Tags_List,
2595 Make_Assignment_Statement (Loc,
2596 Name =>
2597 New_Occurrence_Of (Flag_Id, Loc),
2598 Expression =>
2599 New_Occurrence_Of (Standard_False, Loc)));
2601 Append_To (Body_Stmts,
2602 Make_If_Statement (Loc,
2603 Condition => New_Occurrence_Of (Flag_Id, Loc),
2604 Then_Statements => Init_Tags_List));
2606 Handled_Stmt_Node :=
2607 New_Node (N_Handled_Sequence_Of_Statements, Loc);
2608 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2609 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2610 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2612 if not Debug_Generated_Code then
2613 Set_Debug_Info_Off (Proc_Id);
2614 end if;
2616 -- Associate CPP_Init_Proc with type
2618 Set_Init_Proc (Rec_Type, Proc_Id);
2619 end Build_CPP_Init_Procedure;
2621 --------------------------
2622 -- Build_Init_Procedure --
2623 --------------------------
2625 procedure Build_Init_Procedure is
2626 Body_Stmts : List_Id;
2627 Body_Node : Node_Id;
2628 Handled_Stmt_Node : Node_Id;
2629 Init_Tags_List : List_Id;
2630 Parameters : List_Id;
2631 Proc_Spec_Node : Node_Id;
2632 Record_Extension_Node : Node_Id;
2634 use Initialization_Control;
2635 begin
2636 Body_Stmts := New_List;
2637 Body_Node := New_Node (N_Subprogram_Body, Loc);
2638 Mutate_Ekind (Proc_Id, E_Procedure);
2640 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2641 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2643 Parameters := Init_Formals (Rec_Type, Proc_Id);
2644 Append_List_To (Parameters,
2645 Build_Discriminant_Formals (Rec_Type, True));
2647 -- For tagged types, we add a parameter to indicate what
2648 -- portion of the object's initialization is to be performed.
2649 -- This is used for two purposes:
2650 -- 1) When a type extension's initialization procedure calls
2651 -- the initialization procedure of the parent type, we do
2652 -- not want the parent to initialize the Tag component;
2653 -- it has been set already.
2654 -- 2) If an ancestor type has at least one component that requires
2655 -- late initialization, then we need to be able to initialize
2656 -- those components separately after initializing any other
2657 -- components.
2659 if Is_Tagged_Type (Rec_Type) then
2660 Init_Control_Formal := Make_Temporary (Loc, 'P');
2662 Append_To (Parameters,
2663 Make_Parameter_Specification (Loc,
2664 Defining_Identifier => Init_Control_Formal,
2665 Parameter_Type =>
2666 New_Occurrence_Of (Standard_Natural, Loc),
2667 Expression => Make_Mode_Literal (Loc, Full_Init)));
2668 end if;
2670 -- Create an extra accessibility parameter to capture the level of
2671 -- the object being initialized when its type is a limited record.
2673 if Is_Limited_Record (Rec_Type) then
2674 Append_To (Parameters,
2675 Make_Parameter_Specification (Loc,
2676 Defining_Identifier => Make_Defining_Identifier
2677 (Loc, Name_uInit_Level),
2678 Parameter_Type =>
2679 New_Occurrence_Of (Standard_Natural, Loc),
2680 Expression =>
2681 Make_Integer_Literal
2682 (Loc, Scope_Depth (Standard_Standard))));
2683 end if;
2685 Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
2686 Set_Specification (Body_Node, Proc_Spec_Node);
2687 Set_Declarations (Body_Node, Decls);
2689 -- N is a Derived_Type_Definition that renames the parameters of the
2690 -- ancestor type. We initialize it by expanding our discriminants and
2691 -- call the ancestor _init_proc with a type-converted object.
2693 if Parent_Subtype_Renaming_Discrims then
2694 Append_List_To (Body_Stmts, Build_Init_Call_Thru (Parameters));
2696 elsif Nkind (Type_Definition (N)) = N_Record_Definition then
2697 Build_Discriminant_Assignments (Body_Stmts);
2699 if not Null_Present (Type_Definition (N)) then
2700 Append_List_To (Body_Stmts,
2701 Build_Init_Statements (Component_List (Type_Definition (N))));
2702 end if;
2704 -- N is a Derived_Type_Definition with a possible non-empty
2705 -- extension. The initialization of a type extension consists in the
2706 -- initialization of the components in the extension.
2708 else
2709 Build_Discriminant_Assignments (Body_Stmts);
2711 Record_Extension_Node :=
2712 Record_Extension_Part (Type_Definition (N));
2714 if not Null_Present (Record_Extension_Node) then
2715 declare
2716 Stmts : constant List_Id :=
2717 Build_Init_Statements (
2718 Component_List (Record_Extension_Node));
2720 begin
2721 -- The parent field must be initialized first because the
2722 -- offset of the new discriminants may depend on it. This is
2723 -- not needed if the parent is an interface type because in
2724 -- such case the initialization of the _parent field was not
2725 -- generated.
2727 if not Is_Interface (Etype (Rec_Ent)) then
2728 declare
2729 Parent_IP : constant Name_Id :=
2730 Make_Init_Proc_Name (Etype (Rec_Ent));
2731 Stmt : Node_Id := First (Stmts);
2732 IP_Call : Node_Id := Empty;
2733 begin
2734 -- Look for a call to the parent IP associated with
2735 -- the record extension.
2736 -- The call will be inside not one but two
2737 -- if-statements (with the same condition). Testing
2738 -- the same Early_Init condition twice might seem
2739 -- redundant. However, as soon as we exit this loop,
2740 -- we are going to hoist the inner if-statement out
2741 -- of the outer one; the "redundant" test was built
2742 -- in anticipation of this hoisting.
2744 while Present (Stmt) loop
2745 if Nkind (Stmt) = N_If_Statement then
2746 declare
2747 Then_Stmt1 : Node_Id :=
2748 First (Then_Statements (Stmt));
2749 Then_Stmt2 : Node_Id;
2750 begin
2751 while Present (Then_Stmt1) loop
2752 if Nkind (Then_Stmt1) = N_If_Statement then
2753 Then_Stmt2 :=
2754 First (Then_Statements (Then_Stmt1));
2756 if Nkind (Then_Stmt2) =
2757 N_Procedure_Call_Statement
2758 and then Chars (Name (Then_Stmt2)) =
2759 Parent_IP
2760 then
2761 -- IP_Call is a call wrapped in an
2762 -- if statement.
2763 IP_Call := Then_Stmt1;
2764 exit;
2765 end if;
2766 end if;
2767 Next (Then_Stmt1);
2768 end loop;
2769 end;
2770 end if;
2772 Next (Stmt);
2773 end loop;
2775 -- If found then move it to the beginning of the
2776 -- statements of this IP routine
2778 if Present (IP_Call) then
2779 Remove (IP_Call);
2780 Prepend_List_To (Body_Stmts, New_List (IP_Call));
2781 end if;
2782 end;
2783 end if;
2785 Append_List_To (Body_Stmts, Stmts);
2786 end;
2787 end if;
2788 end if;
2790 -- Add here the assignment to instantiate the Tag
2792 -- The assignment corresponds to the code:
2794 -- _Init._Tag := Typ'Tag;
2796 -- Suppress the tag assignment when not Tagged_Type_Expansion because
2797 -- tags are represented implicitly in objects. It is also suppressed
2798 -- in case of CPP_Class types because in this case the tag is
2799 -- initialized in the C++ side.
2801 if Is_Tagged_Type (Rec_Type)
2802 and then Tagged_Type_Expansion
2803 and then not No_Run_Time_Mode
2804 then
2805 -- Case 1: Ada tagged types with no CPP ancestor. Set the tags of
2806 -- the actual object and invoke the IP of the parent (in this
2807 -- order). The tag must be initialized before the call to the IP
2808 -- of the parent and the assignments to other components because
2809 -- the initial value of the components may depend on the tag (eg.
2810 -- through a dispatching operation on an access to the current
2811 -- type). The tag assignment is not done when initializing the
2812 -- parent component of a type extension, because in that case the
2813 -- tag is set in the extension.
2815 if not Is_CPP_Class (Root_Type (Rec_Type)) then
2817 -- Initialize the primary tag component
2819 Init_Tags_List := New_List (
2820 Make_Assignment_Statement (Loc,
2821 Name =>
2822 Make_Selected_Component (Loc,
2823 Prefix => Make_Identifier (Loc, Name_uInit),
2824 Selector_Name =>
2825 New_Occurrence_Of
2826 (First_Tag_Component (Rec_Type), Loc)),
2827 Expression =>
2828 New_Occurrence_Of
2829 (Node
2830 (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2832 -- Ada 2005 (AI-251): Initialize the secondary tags components
2833 -- located at fixed positions (tags whose position depends on
2834 -- variable size components are initialized later ---see below)
2836 if Ada_Version >= Ada_2005
2837 and then not Is_Interface (Rec_Type)
2838 and then Has_Interfaces (Rec_Type)
2839 then
2840 declare
2841 Elab_Sec_DT_Stmts_List : constant List_Id := New_List;
2842 Elab_List : List_Id := New_List;
2844 begin
2845 Init_Secondary_Tags
2846 (Typ => Rec_Type,
2847 Target => Make_Identifier (Loc, Name_uInit),
2848 Init_Tags_List => Init_Tags_List,
2849 Stmts_List => Elab_Sec_DT_Stmts_List,
2850 Fixed_Comps => True,
2851 Variable_Comps => False);
2853 Elab_List := New_List (
2854 Make_If_Statement (Loc,
2855 Condition =>
2856 Tag_Init_Condition (Loc, Init_Control_Formal),
2857 Then_Statements => Init_Tags_List));
2859 if Elab_Flag_Needed (Rec_Type) then
2860 Append_To (Elab_Sec_DT_Stmts_List,
2861 Make_Assignment_Statement (Loc,
2862 Name =>
2863 New_Occurrence_Of
2864 (Access_Disp_Table_Elab_Flag (Rec_Type),
2865 Loc),
2866 Expression =>
2867 New_Occurrence_Of (Standard_False, Loc)));
2869 Append_To (Elab_List,
2870 Make_If_Statement (Loc,
2871 Condition =>
2872 New_Occurrence_Of
2873 (Access_Disp_Table_Elab_Flag (Rec_Type), Loc),
2874 Then_Statements => Elab_Sec_DT_Stmts_List));
2875 end if;
2877 Prepend_List_To (Body_Stmts, Elab_List);
2878 end;
2879 else
2880 Prepend_To (Body_Stmts,
2881 Make_If_Statement (Loc,
2882 Condition =>
2883 Tag_Init_Condition (Loc, Init_Control_Formal),
2884 Then_Statements => Init_Tags_List));
2885 end if;
2887 -- Case 2: CPP type. The imported C++ constructor takes care of
2888 -- tags initialization. No action needed here because the IP
2889 -- is built by Set_CPP_Constructors; in this case the IP is a
2890 -- wrapper that invokes the C++ constructor and copies the C++
2891 -- tags locally. Done to inherit the C++ slots in Ada derivations
2892 -- (see case 3).
2894 elsif Is_CPP_Class (Rec_Type) then
2895 pragma Assert (False);
2896 null;
2898 -- Case 3: Combined hierarchy containing C++ types and Ada tagged
2899 -- type derivations. Derivations of imported C++ classes add a
2900 -- complication, because we cannot inhibit tag setting in the
2901 -- constructor for the parent. Hence we initialize the tag after
2902 -- the call to the parent IP (that is, in reverse order compared
2903 -- with pure Ada hierarchies ---see comment on case 1).
2905 else
2906 -- Initialize the primary tag
2908 Init_Tags_List := New_List (
2909 Make_Assignment_Statement (Loc,
2910 Name =>
2911 Make_Selected_Component (Loc,
2912 Prefix => Make_Identifier (Loc, Name_uInit),
2913 Selector_Name =>
2914 New_Occurrence_Of
2915 (First_Tag_Component (Rec_Type), Loc)),
2916 Expression =>
2917 New_Occurrence_Of
2918 (Node
2919 (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2921 -- Ada 2005 (AI-251): Initialize the secondary tags components
2922 -- located at fixed positions (tags whose position depends on
2923 -- variable size components are initialized later ---see below)
2925 if Ada_Version >= Ada_2005
2926 and then not Is_Interface (Rec_Type)
2927 and then Has_Interfaces (Rec_Type)
2928 then
2929 Init_Secondary_Tags
2930 (Typ => Rec_Type,
2931 Target => Make_Identifier (Loc, Name_uInit),
2932 Init_Tags_List => Init_Tags_List,
2933 Stmts_List => Init_Tags_List,
2934 Fixed_Comps => True,
2935 Variable_Comps => False);
2936 end if;
2938 -- Initialize the tag component after invocation of parent IP.
2940 -- Generate:
2941 -- parent_IP(_init.parent); // Invokes the C++ constructor
2942 -- [ typIC; ] // Inherit C++ slots from parent
2943 -- init_tags
2945 declare
2946 Ins_Nod : Node_Id;
2948 begin
2949 -- Search for the call to the IP of the parent. We assume
2950 -- that the first init_proc call is for the parent.
2951 -- It is wrapped in an "if Early_Init_Condition"
2952 -- if-statement.
2954 Ins_Nod := First (Body_Stmts);
2955 while Present (Next (Ins_Nod))
2956 and then
2957 (Nkind (Ins_Nod) /= N_If_Statement
2958 or else (Nkind (First (Then_Statements (Ins_Nod)))
2959 /= N_Procedure_Call_Statement)
2960 or else not Is_Init_Proc
2961 (Name (First (Then_Statements
2962 (Ins_Nod)))))
2963 loop
2964 Next (Ins_Nod);
2965 end loop;
2967 -- The IC routine copies the inherited slots of the C+ part
2968 -- of the dispatch table from the parent and updates the
2969 -- overridden C++ slots.
2971 if CPP_Num_Prims (Rec_Type) > 0 then
2972 declare
2973 Init_DT : Entity_Id;
2974 New_Nod : Node_Id;
2976 begin
2977 Init_DT := CPP_Init_Proc (Rec_Type);
2978 pragma Assert (Present (Init_DT));
2980 New_Nod :=
2981 Make_Procedure_Call_Statement (Loc,
2982 New_Occurrence_Of (Init_DT, Loc));
2983 Insert_After (Ins_Nod, New_Nod);
2985 -- Update location of init tag statements
2987 Ins_Nod := New_Nod;
2988 end;
2989 end if;
2991 Insert_List_After (Ins_Nod, Init_Tags_List);
2992 end;
2993 end if;
2995 -- Ada 2005 (AI-251): Initialize the secondary tag components
2996 -- located at variable positions. We delay the generation of this
2997 -- code until here because the value of the attribute 'Position
2998 -- applied to variable size components of the parent type that
2999 -- depend on discriminants is only safely read at runtime after
3000 -- the parent components have been initialized.
3002 if Ada_Version >= Ada_2005
3003 and then not Is_Interface (Rec_Type)
3004 and then Has_Interfaces (Rec_Type)
3005 and then Has_Discriminants (Etype (Rec_Type))
3006 and then Is_Variable_Size_Record (Etype (Rec_Type))
3007 then
3008 Init_Tags_List := New_List;
3010 Init_Secondary_Tags
3011 (Typ => Rec_Type,
3012 Target => Make_Identifier (Loc, Name_uInit),
3013 Init_Tags_List => Init_Tags_List,
3014 Stmts_List => Init_Tags_List,
3015 Fixed_Comps => False,
3016 Variable_Comps => True);
3018 Append_List_To (Body_Stmts, Init_Tags_List);
3019 end if;
3020 end if;
3022 Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
3023 Set_Statements (Handled_Stmt_Node, Body_Stmts);
3025 -- Generate:
3026 -- Deep_Finalize (_init, C1, ..., CN);
3027 -- raise;
3029 if Counter > 0
3030 and then Needs_Finalization (Rec_Type)
3031 and then not Is_Abstract_Type (Rec_Type)
3032 and then not Restriction_Active (No_Exception_Propagation)
3033 then
3034 declare
3035 DF_Call : Node_Id;
3036 DF_Id : Entity_Id;
3038 begin
3039 -- Create a local version of Deep_Finalize which has indication
3040 -- of partial initialization state.
3042 DF_Id :=
3043 Make_Defining_Identifier (Loc,
3044 Chars => New_External_Name (Name_uFinalizer));
3046 Append_To (Decls, Make_Local_Deep_Finalize (Rec_Type, DF_Id));
3048 DF_Call :=
3049 Make_Procedure_Call_Statement (Loc,
3050 Name => New_Occurrence_Of (DF_Id, Loc),
3051 Parameter_Associations => New_List (
3052 Make_Identifier (Loc, Name_uInit),
3053 New_Occurrence_Of (Standard_False, Loc)));
3055 -- Do not emit warnings related to the elaboration order when a
3056 -- controlled object is declared before the body of Finalize is
3057 -- seen.
3059 if Legacy_Elaboration_Checks then
3060 Set_No_Elaboration_Check (DF_Call);
3061 end if;
3063 Set_Exception_Handlers (Handled_Stmt_Node, New_List (
3064 Make_Exception_Handler (Loc,
3065 Exception_Choices => New_List (
3066 Make_Others_Choice (Loc)),
3067 Statements => New_List (
3068 DF_Call,
3069 Make_Raise_Statement (Loc)))));
3070 end;
3071 else
3072 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
3073 end if;
3075 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
3077 if not Debug_Generated_Code then
3078 Set_Debug_Info_Off (Proc_Id);
3079 end if;
3081 -- Associate Init_Proc with type, and determine if the procedure
3082 -- is null (happens because of the Initialize_Scalars pragma case,
3083 -- where we have to generate a null procedure in case it is called
3084 -- by a client with Initialize_Scalars set). Such procedures have
3085 -- to be generated, but do not have to be called, so we mark them
3086 -- as null to suppress the call. Kill also warnings for the _Init
3087 -- out parameter, which is left entirely uninitialized.
3089 Set_Init_Proc (Rec_Type, Proc_Id);
3091 if Is_Null_Statement_List (Body_Stmts) then
3092 Set_Is_Null_Init_Proc (Proc_Id);
3093 Set_Warnings_Off (Defining_Identifier (First (Parameters)));
3094 end if;
3095 end Build_Init_Procedure;
3097 ---------------------------
3098 -- Build_Init_Statements --
3099 ---------------------------
3101 function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
3102 Checks : constant List_Id := New_List;
3103 Actions : List_Id := No_List;
3104 Counter_Id : Entity_Id := Empty;
3105 Comp_Loc : Source_Ptr;
3106 Decl : Node_Id;
3107 Id : Entity_Id;
3108 Parent_Stmts : List_Id;
3109 Parent_Id : Entity_Id := Empty;
3110 Stmts, Late_Stmts : List_Id := Empty_List;
3111 Typ : Entity_Id;
3113 procedure Increment_Counter
3114 (Loc : Source_Ptr; Late : Boolean := False);
3115 -- Generate an "increment by one" statement for the current counter
3116 -- and append it to the appropriate statement list.
3118 procedure Make_Counter (Loc : Source_Ptr);
3119 -- Create a new counter for the current component list. The routine
3120 -- creates a new defining Id, adds an object declaration and sets
3121 -- the Id generator for the next variant.
3123 -----------------------
3124 -- Increment_Counter --
3125 -----------------------
3127 procedure Increment_Counter
3128 (Loc : Source_Ptr; Late : Boolean := False) is
3129 begin
3130 -- Generate:
3131 -- Counter := Counter + 1;
3133 Append_To ((if Late then Late_Stmts else Stmts),
3134 Make_Assignment_Statement (Loc,
3135 Name => New_Occurrence_Of (Counter_Id, Loc),
3136 Expression =>
3137 Make_Op_Add (Loc,
3138 Left_Opnd => New_Occurrence_Of (Counter_Id, Loc),
3139 Right_Opnd => Make_Integer_Literal (Loc, 1))));
3140 end Increment_Counter;
3142 ------------------
3143 -- Make_Counter --
3144 ------------------
3146 procedure Make_Counter (Loc : Source_Ptr) is
3147 begin
3148 -- Increment the Id generator
3150 Counter := Counter + 1;
3152 -- Create the entity and declaration
3154 Counter_Id :=
3155 Make_Defining_Identifier (Loc,
3156 Chars => New_External_Name ('C', Counter));
3158 -- Generate:
3159 -- Cnn : Integer := 0;
3161 Append_To (Decls,
3162 Make_Object_Declaration (Loc,
3163 Defining_Identifier => Counter_Id,
3164 Object_Definition =>
3165 New_Occurrence_Of (Standard_Integer, Loc),
3166 Expression =>
3167 Make_Integer_Literal (Loc, 0)));
3168 end Make_Counter;
3170 -- Start of processing for Build_Init_Statements
3172 begin
3173 if Null_Present (Comp_List) then
3174 return New_List (Make_Null_Statement (Loc));
3175 end if;
3177 Parent_Stmts := New_List;
3178 Stmts := New_List;
3180 -- Loop through visible declarations of task types and protected
3181 -- types moving any expanded code from the spec to the body of the
3182 -- init procedure.
3184 if Is_Concurrent_Record_Type (Rec_Type) then
3185 declare
3186 Decl : constant Node_Id :=
3187 Parent (Corresponding_Concurrent_Type (Rec_Type));
3188 Def : Node_Id;
3189 N1 : Node_Id;
3190 N2 : Node_Id;
3192 begin
3193 if Is_Task_Record_Type (Rec_Type) then
3194 Def := Task_Definition (Decl);
3195 else
3196 Def := Protected_Definition (Decl);
3197 end if;
3199 if Present (Def) then
3200 N1 := First (Visible_Declarations (Def));
3201 while Present (N1) loop
3202 N2 := N1;
3203 N1 := Next (N1);
3205 if Nkind (N2) in N_Statement_Other_Than_Procedure_Call
3206 or else Nkind (N2) in N_Raise_xxx_Error
3207 or else Nkind (N2) = N_Procedure_Call_Statement
3208 then
3209 Append_To (Stmts,
3210 New_Copy_Tree (N2, New_Scope => Proc_Id));
3211 Rewrite (N2, Make_Null_Statement (Sloc (N2)));
3212 Analyze (N2);
3213 end if;
3214 end loop;
3215 end if;
3216 end;
3217 end if;
3219 -- Loop through components, skipping pragmas, in 2 steps. The first
3220 -- step deals with regular components. The second step deals with
3221 -- components that require late initialization.
3223 -- First pass : regular components
3225 Decl := First_Non_Pragma (Component_Items (Comp_List));
3226 while Present (Decl) loop
3227 Comp_Loc := Sloc (Decl);
3228 Build_Record_Checks
3229 (Subtype_Indication (Component_Definition (Decl)), Checks);
3231 Id := Defining_Identifier (Decl);
3232 Typ := Etype (Id);
3234 -- Leave any processing of component requiring late initialization
3235 -- for the second pass.
3237 if Initialization_Control.Requires_Late_Init (Decl, Rec_Type) then
3238 if not Has_Late_Init_Comp then
3239 Late_Stmts := New_List;
3240 end if;
3241 Has_Late_Init_Comp := True;
3243 -- Regular component cases
3245 else
3246 -- In the context of the init proc, references to discriminants
3247 -- resolve to denote the discriminals: this is where we can
3248 -- freeze discriminant dependent component subtypes.
3250 if not Is_Frozen (Typ) then
3251 Append_List_To (Stmts, Freeze_Entity (Typ, N));
3252 end if;
3254 -- Explicit initialization
3256 if Present (Expression (Decl)) then
3257 if Is_CPP_Constructor_Call (Expression (Decl)) then
3258 Actions :=
3259 Build_Initialization_Call
3260 (Comp_Loc,
3261 Id_Ref =>
3262 Make_Selected_Component (Comp_Loc,
3263 Prefix =>
3264 Make_Identifier (Comp_Loc, Name_uInit),
3265 Selector_Name =>
3266 New_Occurrence_Of (Id, Comp_Loc)),
3267 Typ => Typ,
3268 In_Init_Proc => True,
3269 Enclos_Type => Rec_Type,
3270 Discr_Map => Discr_Map,
3271 Constructor_Ref => Expression (Decl));
3272 else
3273 Actions := Build_Assignment (Id, Expression (Decl));
3274 end if;
3276 -- CPU, Dispatching_Domain, Priority, and Secondary_Stack_Size
3277 -- components are filled in with the corresponding rep-item
3278 -- expression of the concurrent type (if any).
3280 elsif Ekind (Scope (Id)) = E_Record_Type
3281 and then Present (Corresponding_Concurrent_Type (Scope (Id)))
3282 and then Chars (Id) in Name_uCPU
3283 | Name_uDispatching_Domain
3284 | Name_uPriority
3285 | Name_uSecondary_Stack_Size
3286 then
3287 declare
3288 Exp : Node_Id;
3289 Nam : Name_Id;
3290 pragma Warnings (Off, Nam);
3291 Ritem : Node_Id;
3293 begin
3294 if Chars (Id) = Name_uCPU then
3295 Nam := Name_CPU;
3297 elsif Chars (Id) = Name_uDispatching_Domain then
3298 Nam := Name_Dispatching_Domain;
3300 elsif Chars (Id) = Name_uPriority then
3301 Nam := Name_Priority;
3303 elsif Chars (Id) = Name_uSecondary_Stack_Size then
3304 Nam := Name_Secondary_Stack_Size;
3305 end if;
3307 -- Get the Rep Item (aspect specification, attribute
3308 -- definition clause or pragma) of the corresponding
3309 -- concurrent type.
3311 Ritem :=
3312 Get_Rep_Item
3313 (Corresponding_Concurrent_Type (Scope (Id)),
3314 Nam,
3315 Check_Parents => False);
3317 if Present (Ritem) then
3319 -- Pragma case
3321 if Nkind (Ritem) = N_Pragma then
3322 Exp := First (Pragma_Argument_Associations (Ritem));
3324 if Nkind (Exp) = N_Pragma_Argument_Association then
3325 Exp := Expression (Exp);
3326 end if;
3328 -- Conversion for Priority expression
3330 if Nam = Name_Priority then
3331 if Pragma_Name (Ritem) = Name_Priority
3332 and then not GNAT_Mode
3333 then
3334 Exp := Convert_To (RTE (RE_Priority), Exp);
3335 else
3336 Exp :=
3337 Convert_To (RTE (RE_Any_Priority), Exp);
3338 end if;
3339 end if;
3341 -- Aspect/Attribute definition clause case
3343 else
3344 Exp := Expression (Ritem);
3346 -- Conversion for Priority expression
3348 if Nam = Name_Priority then
3349 if Chars (Ritem) = Name_Priority
3350 and then not GNAT_Mode
3351 then
3352 Exp := Convert_To (RTE (RE_Priority), Exp);
3353 else
3354 Exp :=
3355 Convert_To (RTE (RE_Any_Priority), Exp);
3356 end if;
3357 end if;
3358 end if;
3360 -- Conversion for Dispatching_Domain value
3362 if Nam = Name_Dispatching_Domain then
3363 Exp :=
3364 Unchecked_Convert_To
3365 (RTE (RE_Dispatching_Domain_Access), Exp);
3367 -- Conversion for Secondary_Stack_Size value
3369 elsif Nam = Name_Secondary_Stack_Size then
3370 Exp := Convert_To (RTE (RE_Size_Type), Exp);
3371 end if;
3373 Actions := Build_Assignment (Id, Exp);
3375 -- Nothing needed if no Rep Item
3377 else
3378 Actions := No_List;
3379 end if;
3380 end;
3382 -- Composite component with its own Init_Proc
3384 elsif not Is_Interface (Typ)
3385 and then Has_Non_Null_Base_Init_Proc (Typ)
3386 then
3387 declare
3388 use Initialization_Control;
3389 Init_Control_Actual : Node_Id := Empty;
3390 Is_Parent : constant Boolean := Chars (Id) = Name_uParent;
3391 Init_Call_Stmts : List_Id;
3392 begin
3393 if Is_Parent and then Has_Late_Init_Component (Etype (Id))
3394 then
3395 Init_Control_Actual :=
3396 Make_Mode_Literal (Comp_Loc, Early_Init_Only);
3397 -- Parent_Id used later in second call to parent's
3398 -- init proc to initialize late-init components.
3399 Parent_Id := Id;
3400 end if;
3402 Init_Call_Stmts :=
3403 Build_Initialization_Call
3404 (Comp_Loc,
3405 Make_Selected_Component (Comp_Loc,
3406 Prefix =>
3407 Make_Identifier (Comp_Loc, Name_uInit),
3408 Selector_Name => New_Occurrence_Of (Id, Comp_Loc)),
3409 Typ,
3410 In_Init_Proc => True,
3411 Enclos_Type => Rec_Type,
3412 Discr_Map => Discr_Map,
3413 Init_Control_Actual => Init_Control_Actual);
3415 if Is_Parent then
3416 -- This is tricky. At first it looks like
3417 -- we are going to end up with nested
3418 -- if-statements with the same condition:
3419 -- if Early_Init_Condition then
3420 -- if Early_Init_Condition then
3421 -- Parent_TypeIP (...);
3422 -- end if;
3423 -- end if;
3424 -- But later we will hoist the inner if-statement
3425 -- out of the outer one; we do this because the
3426 -- init-proc call for the _Parent component of a type
3427 -- extension has to precede any other initialization.
3428 Actions :=
3429 New_List (Make_If_Statement (Loc,
3430 Condition =>
3431 Early_Init_Condition (Loc, Init_Control_Formal),
3432 Then_Statements => Init_Call_Stmts));
3433 else
3434 Actions := Init_Call_Stmts;
3435 end if;
3436 end;
3438 Clean_Task_Names (Typ, Proc_Id);
3440 -- Simple initialization. If the Esize is not yet set, we pass
3441 -- Uint_0 as expected by Get_Simple_Init_Val.
3443 elsif Component_Needs_Simple_Initialization (Typ) then
3444 Actions :=
3445 Build_Assignment
3446 (Id => Id,
3447 Default =>
3448 Get_Simple_Init_Val
3449 (Typ => Typ,
3450 N => N,
3451 Size =>
3452 (if Known_Esize (Id) then Esize (Id)
3453 else Uint_0)));
3455 -- Nothing needed for this case
3457 else
3458 Actions := No_List;
3459 end if;
3461 -- When the component's type has a Default_Initial_Condition,
3462 -- and the component is default initialized, then check the
3463 -- DIC here.
3465 if Has_DIC (Typ)
3466 and then No (Expression (Decl))
3467 and then Present (DIC_Procedure (Typ))
3468 and then not Has_Null_Body (DIC_Procedure (Typ))
3470 -- The DICs of ancestors are checked as part of the type's
3471 -- DIC procedure.
3473 and then Chars (Id) /= Name_uParent
3475 -- In GNATprove mode, the component DICs are checked by other
3476 -- means. They should not be added to the record type DIC
3477 -- procedure, so that the procedure can be used to check the
3478 -- record type invariants or DICs if any.
3480 and then not GNATprove_Mode
3481 then
3482 Append_New_To (Actions,
3483 Build_DIC_Call
3484 (Comp_Loc,
3485 Make_Selected_Component (Comp_Loc,
3486 Prefix =>
3487 Make_Identifier (Comp_Loc, Name_uInit),
3488 Selector_Name =>
3489 New_Occurrence_Of (Id, Comp_Loc)),
3490 Typ));
3491 end if;
3493 if Present (Checks) then
3494 if Chars (Id) = Name_uParent then
3495 Append_List_To (Parent_Stmts, Checks);
3496 else
3497 Append_List_To (Stmts, Checks);
3498 end if;
3499 end if;
3501 if Present (Actions) then
3502 if Chars (Id) = Name_uParent then
3503 Append_List_To (Parent_Stmts, Actions);
3504 else
3505 Append_List_To (Stmts, Actions);
3507 -- Preserve initialization state in the current counter
3509 if Needs_Finalization (Typ) then
3510 if No (Counter_Id) then
3511 Make_Counter (Comp_Loc);
3512 end if;
3514 Increment_Counter (Comp_Loc);
3515 end if;
3516 end if;
3517 end if;
3518 end if;
3520 Next_Non_Pragma (Decl);
3521 end loop;
3523 -- The parent field must be initialized first because variable
3524 -- size components of the parent affect the location of all the
3525 -- new components.
3527 Prepend_List_To (Stmts, Parent_Stmts);
3529 -- Set up tasks and protected object support. This needs to be done
3530 -- before any component with a per-object access discriminant
3531 -- constraint, or any variant part (which may contain such
3532 -- components) is initialized, because the initialization of these
3533 -- components may reference the enclosing concurrent object.
3535 -- For a task record type, add the task create call and calls to bind
3536 -- any interrupt (signal) entries.
3538 if Is_Task_Record_Type (Rec_Type) then
3540 -- In the case of the restricted run time the ATCB has already
3541 -- been preallocated.
3543 if Restricted_Profile then
3544 Append_To (Stmts,
3545 Make_Assignment_Statement (Loc,
3546 Name =>
3547 Make_Selected_Component (Loc,
3548 Prefix => Make_Identifier (Loc, Name_uInit),
3549 Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
3550 Expression =>
3551 Make_Attribute_Reference (Loc,
3552 Prefix =>
3553 Make_Selected_Component (Loc,
3554 Prefix => Make_Identifier (Loc, Name_uInit),
3555 Selector_Name => Make_Identifier (Loc, Name_uATCB)),
3556 Attribute_Name => Name_Unchecked_Access)));
3557 end if;
3559 Append_To (Stmts, Make_Task_Create_Call (Rec_Type));
3561 declare
3562 Task_Type : constant Entity_Id :=
3563 Corresponding_Concurrent_Type (Rec_Type);
3564 Task_Decl : constant Node_Id := Parent (Task_Type);
3565 Task_Def : constant Node_Id := Task_Definition (Task_Decl);
3566 Decl_Loc : Source_Ptr;
3567 Ent : Entity_Id;
3568 Vis_Decl : Node_Id;
3570 begin
3571 if Present (Task_Def) then
3572 Vis_Decl := First (Visible_Declarations (Task_Def));
3573 while Present (Vis_Decl) loop
3574 Decl_Loc := Sloc (Vis_Decl);
3576 if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
3577 if Get_Attribute_Id (Chars (Vis_Decl)) =
3578 Attribute_Address
3579 then
3580 Ent := Entity (Name (Vis_Decl));
3582 if Ekind (Ent) = E_Entry then
3583 Append_To (Stmts,
3584 Make_Procedure_Call_Statement (Decl_Loc,
3585 Name =>
3586 New_Occurrence_Of (RTE (
3587 RE_Bind_Interrupt_To_Entry), Decl_Loc),
3588 Parameter_Associations => New_List (
3589 Make_Selected_Component (Decl_Loc,
3590 Prefix =>
3591 Make_Identifier (Decl_Loc, Name_uInit),
3592 Selector_Name =>
3593 Make_Identifier
3594 (Decl_Loc, Name_uTask_Id)),
3595 Entry_Index_Expression
3596 (Decl_Loc, Ent, Empty, Task_Type),
3597 Expression (Vis_Decl))));
3598 end if;
3599 end if;
3600 end if;
3602 Next (Vis_Decl);
3603 end loop;
3604 end if;
3605 end;
3607 -- For a protected type, add statements generated by
3608 -- Make_Initialize_Protection.
3610 elsif Is_Protected_Record_Type (Rec_Type) then
3611 Append_List_To (Stmts,
3612 Make_Initialize_Protection (Rec_Type));
3613 end if;
3615 -- Second pass: components that require late initialization
3617 if Present (Parent_Id) then
3618 declare
3619 Parent_Loc : constant Source_Ptr := Sloc (Parent (Parent_Id));
3620 use Initialization_Control;
3621 begin
3622 -- We are building the init proc for a type extension.
3623 -- Call the parent type's init proc a second time, this
3624 -- time to initialize the parent's components that require
3625 -- late initialization.
3627 Append_List_To (Late_Stmts,
3628 Build_Initialization_Call
3629 (Loc => Parent_Loc,
3630 Id_Ref =>
3631 Make_Selected_Component (Parent_Loc,
3632 Prefix => Make_Identifier
3633 (Parent_Loc, Name_uInit),
3634 Selector_Name => New_Occurrence_Of (Parent_Id,
3635 Parent_Loc)),
3636 Typ => Etype (Parent_Id),
3637 In_Init_Proc => True,
3638 Enclos_Type => Rec_Type,
3639 Discr_Map => Discr_Map,
3640 Init_Control_Actual => Make_Mode_Literal
3641 (Parent_Loc, Late_Init_Only)));
3642 end;
3643 end if;
3645 if Has_Late_Init_Comp then
3646 Decl := First_Non_Pragma (Component_Items (Comp_List));
3647 while Present (Decl) loop
3648 Comp_Loc := Sloc (Decl);
3649 Id := Defining_Identifier (Decl);
3650 Typ := Etype (Id);
3652 if Initialization_Control.Requires_Late_Init (Decl, Rec_Type)
3653 then
3654 if Present (Expression (Decl)) then
3655 Append_List_To (Late_Stmts,
3656 Build_Assignment (Id, Expression (Decl)));
3658 elsif Has_Non_Null_Base_Init_Proc (Typ) then
3659 Append_List_To (Late_Stmts,
3660 Build_Initialization_Call (Comp_Loc,
3661 Make_Selected_Component (Comp_Loc,
3662 Prefix =>
3663 Make_Identifier (Comp_Loc, Name_uInit),
3664 Selector_Name => New_Occurrence_Of (Id, Comp_Loc)),
3665 Typ,
3666 In_Init_Proc => True,
3667 Enclos_Type => Rec_Type,
3668 Discr_Map => Discr_Map));
3670 Clean_Task_Names (Typ, Proc_Id);
3672 -- Preserve initialization state in the current counter
3674 if Needs_Finalization (Typ) then
3675 if No (Counter_Id) then
3676 Make_Counter (Comp_Loc);
3677 end if;
3679 Increment_Counter (Comp_Loc, Late => True);
3680 end if;
3681 elsif Component_Needs_Simple_Initialization (Typ) then
3682 Append_List_To (Late_Stmts,
3683 Build_Assignment
3684 (Id => Id,
3685 Default =>
3686 Get_Simple_Init_Val
3687 (Typ => Typ,
3688 N => N,
3689 Size => Esize (Id))));
3690 end if;
3691 end if;
3693 Next_Non_Pragma (Decl);
3694 end loop;
3695 end if;
3697 -- Process the variant part (incorrectly ignoring late
3698 -- initialization requirements for components therein).
3700 if Present (Variant_Part (Comp_List)) then
3701 declare
3702 Variant_Alts : constant List_Id := New_List;
3703 Var_Loc : Source_Ptr := No_Location;
3704 Variant : Node_Id;
3706 begin
3707 Variant :=
3708 First_Non_Pragma (Variants (Variant_Part (Comp_List)));
3709 while Present (Variant) loop
3710 Var_Loc := Sloc (Variant);
3711 Append_To (Variant_Alts,
3712 Make_Case_Statement_Alternative (Var_Loc,
3713 Discrete_Choices =>
3714 New_Copy_List (Discrete_Choices (Variant)),
3715 Statements =>
3716 Build_Init_Statements (Component_List (Variant))));
3717 Next_Non_Pragma (Variant);
3718 end loop;
3720 -- The expression of the case statement which is a reference
3721 -- to one of the discriminants is replaced by the appropriate
3722 -- formal parameter of the initialization procedure.
3724 Append_To (Stmts,
3725 Make_Case_Statement (Var_Loc,
3726 Expression =>
3727 New_Occurrence_Of (Discriminal (
3728 Entity (Name (Variant_Part (Comp_List)))), Var_Loc),
3729 Alternatives => Variant_Alts));
3730 end;
3731 end if;
3733 if No (Init_Control_Formal) then
3734 Append_List_To (Stmts, Late_Stmts);
3736 -- If no initializations were generated for component declarations
3737 -- and included in Stmts, then append a null statement to Stmts
3738 -- to make it a valid Ada tree.
3740 if Is_Empty_List (Stmts) then
3741 Append (Make_Null_Statement (Loc), Stmts);
3742 end if;
3744 return Stmts;
3745 else
3746 declare
3747 use Initialization_Control;
3749 If_Early : constant Node_Id :=
3750 (if Is_Empty_List (Stmts) then
3751 Make_Null_Statement (Loc)
3752 else
3753 Make_If_Statement (Loc,
3754 Condition =>
3755 Early_Init_Condition (Loc, Init_Control_Formal),
3756 Then_Statements => Stmts));
3757 If_Late : constant Node_Id :=
3758 (if Is_Empty_List (Late_Stmts) then
3759 Make_Null_Statement (Loc)
3760 else
3761 Make_If_Statement (Loc,
3762 Condition =>
3763 Late_Init_Condition (Loc, Init_Control_Formal),
3764 Then_Statements => Late_Stmts));
3765 begin
3766 return New_List (If_Early, If_Late);
3767 end;
3768 end if;
3769 exception
3770 when RE_Not_Available =>
3771 return Empty_List;
3772 end Build_Init_Statements;
3774 -------------------------
3775 -- Build_Record_Checks --
3776 -------------------------
3778 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
3779 Subtype_Mark_Id : Entity_Id;
3781 procedure Constrain_Array
3782 (SI : Node_Id;
3783 Check_List : List_Id);
3784 -- Apply a list of index constraints to an unconstrained array type.
3785 -- The first parameter is the entity for the resulting subtype.
3786 -- Check_List is a list to which the check actions are appended.
3788 ---------------------
3789 -- Constrain_Array --
3790 ---------------------
3792 procedure Constrain_Array
3793 (SI : Node_Id;
3794 Check_List : List_Id)
3796 C : constant Node_Id := Constraint (SI);
3797 Number_Of_Constraints : Nat := 0;
3798 Index : Node_Id;
3799 S, T : Entity_Id;
3801 procedure Constrain_Index
3802 (Index : Node_Id;
3803 S : Node_Id;
3804 Check_List : List_Id);
3805 -- Process an index constraint in a constrained array declaration.
3806 -- The constraint can be either a subtype name or a range with or
3807 -- without an explicit subtype mark. Index is the corresponding
3808 -- index of the unconstrained array. S is the range expression.
3809 -- Check_List is a list to which the check actions are appended.
3811 ---------------------
3812 -- Constrain_Index --
3813 ---------------------
3815 procedure Constrain_Index
3816 (Index : Node_Id;
3817 S : Node_Id;
3818 Check_List : List_Id)
3820 T : constant Entity_Id := Etype (Index);
3822 begin
3823 if Nkind (S) = N_Range then
3824 Process_Range_Expr_In_Decl (S, T, Check_List => Check_List);
3825 end if;
3826 end Constrain_Index;
3828 -- Start of processing for Constrain_Array
3830 begin
3831 T := Entity (Subtype_Mark (SI));
3833 if Is_Access_Type (T) then
3834 T := Designated_Type (T);
3835 end if;
3837 S := First (Constraints (C));
3838 while Present (S) loop
3839 Number_Of_Constraints := Number_Of_Constraints + 1;
3840 Next (S);
3841 end loop;
3843 -- In either case, the index constraint must provide a discrete
3844 -- range for each index of the array type and the type of each
3845 -- discrete range must be the same as that of the corresponding
3846 -- index. (RM 3.6.1)
3848 S := First (Constraints (C));
3849 Index := First_Index (T);
3850 Analyze (Index);
3852 -- Apply constraints to each index type
3854 for J in 1 .. Number_Of_Constraints loop
3855 Constrain_Index (Index, S, Check_List);
3856 Next (Index);
3857 Next (S);
3858 end loop;
3859 end Constrain_Array;
3861 -- Start of processing for Build_Record_Checks
3863 begin
3864 if Nkind (S) = N_Subtype_Indication then
3865 Find_Type (Subtype_Mark (S));
3866 Subtype_Mark_Id := Entity (Subtype_Mark (S));
3868 -- Remaining processing depends on type
3870 case Ekind (Subtype_Mark_Id) is
3871 when Array_Kind =>
3872 Constrain_Array (S, Check_List);
3874 when others =>
3875 null;
3876 end case;
3877 end if;
3878 end Build_Record_Checks;
3880 -------------------------------------------
3881 -- Component_Needs_Simple_Initialization --
3882 -------------------------------------------
3884 function Component_Needs_Simple_Initialization
3885 (T : Entity_Id) return Boolean
3887 begin
3888 return
3889 Needs_Simple_Initialization (T)
3890 and then not Is_RTE (T, RE_Tag)
3892 -- Ada 2005 (AI-251): Check also the tag of abstract interfaces
3894 and then not Is_RTE (T, RE_Interface_Tag);
3895 end Component_Needs_Simple_Initialization;
3897 --------------------------------------
3898 -- Parent_Subtype_Renaming_Discrims --
3899 --------------------------------------
3901 function Parent_Subtype_Renaming_Discrims return Boolean is
3902 De : Entity_Id;
3903 Dp : Entity_Id;
3905 begin
3906 if Base_Type (Rec_Ent) /= Rec_Ent then
3907 return False;
3908 end if;
3910 if Etype (Rec_Ent) = Rec_Ent
3911 or else not Has_Discriminants (Rec_Ent)
3912 or else Is_Constrained (Rec_Ent)
3913 or else Is_Tagged_Type (Rec_Ent)
3914 then
3915 return False;
3916 end if;
3918 -- If there are no explicit stored discriminants we have inherited
3919 -- the root type discriminants so far, so no renamings occurred.
3921 if First_Discriminant (Rec_Ent) =
3922 First_Stored_Discriminant (Rec_Ent)
3923 then
3924 return False;
3925 end if;
3927 -- Check if we have done some trivial renaming of the parent
3928 -- discriminants, i.e. something like
3930 -- type DT (X1, X2: int) is new PT (X1, X2);
3932 De := First_Discriminant (Rec_Ent);
3933 Dp := First_Discriminant (Etype (Rec_Ent));
3934 while Present (De) loop
3935 pragma Assert (Present (Dp));
3937 if Corresponding_Discriminant (De) /= Dp then
3938 return True;
3939 end if;
3941 Next_Discriminant (De);
3942 Next_Discriminant (Dp);
3943 end loop;
3945 return Present (Dp);
3946 end Parent_Subtype_Renaming_Discrims;
3948 ------------------------
3949 -- Requires_Init_Proc --
3950 ------------------------
3952 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
3953 Comp_Decl : Node_Id;
3954 Id : Entity_Id;
3955 Typ : Entity_Id;
3957 begin
3958 -- Definitely do not need one if specifically suppressed
3960 if Initialization_Suppressed (Rec_Id) then
3961 return False;
3962 end if;
3964 -- If it is a type derived from a type with unknown discriminants,
3965 -- we cannot build an initialization procedure for it.
3967 if Has_Unknown_Discriminants (Rec_Id)
3968 or else Has_Unknown_Discriminants (Etype (Rec_Id))
3969 then
3970 return False;
3971 end if;
3973 -- Otherwise we need to generate an initialization procedure if
3974 -- Is_CPP_Class is False and at least one of the following applies:
3976 -- 1. Discriminants are present, since they need to be initialized
3977 -- with the appropriate discriminant constraint expressions.
3978 -- However, the discriminant of an unchecked union does not
3979 -- count, since the discriminant is not present.
3981 -- 2. The type is a tagged type, since the implicit Tag component
3982 -- needs to be initialized with a pointer to the dispatch table.
3984 -- 3. The type contains tasks
3986 -- 4. One or more components has an initial value
3988 -- 5. One or more components is for a type which itself requires
3989 -- an initialization procedure.
3991 -- 6. One or more components is a type that requires simple
3992 -- initialization (see Needs_Simple_Initialization), except
3993 -- that types Tag and Interface_Tag are excluded, since fields
3994 -- of these types are initialized by other means.
3996 -- 7. The type is the record type built for a task type (since at
3997 -- the very least, Create_Task must be called)
3999 -- 8. The type is the record type built for a protected type (since
4000 -- at least Initialize_Protection must be called)
4002 -- 9. The type is marked as a public entity. The reason we add this
4003 -- case (even if none of the above apply) is to properly handle
4004 -- Initialize_Scalars. If a package is compiled without an IS
4005 -- pragma, and the client is compiled with an IS pragma, then
4006 -- the client will think an initialization procedure is present
4007 -- and call it, when in fact no such procedure is required, but
4008 -- since the call is generated, there had better be a routine
4009 -- at the other end of the call, even if it does nothing).
4011 -- Note: the reason we exclude the CPP_Class case is because in this
4012 -- case the initialization is performed by the C++ constructors, and
4013 -- the IP is built by Set_CPP_Constructors.
4015 if Is_CPP_Class (Rec_Id) then
4016 return False;
4018 elsif Is_Interface (Rec_Id) then
4019 return False;
4021 elsif (Has_Discriminants (Rec_Id)
4022 and then not Is_Unchecked_Union (Rec_Id))
4023 or else Is_Tagged_Type (Rec_Id)
4024 or else Is_Concurrent_Record_Type (Rec_Id)
4025 or else Has_Task (Rec_Id)
4026 then
4027 return True;
4028 end if;
4030 Id := First_Component (Rec_Id);
4031 while Present (Id) loop
4032 Comp_Decl := Parent (Id);
4033 Typ := Etype (Id);
4035 if Present (Expression (Comp_Decl))
4036 or else Has_Non_Null_Base_Init_Proc (Typ)
4037 or else Component_Needs_Simple_Initialization (Typ)
4038 then
4039 return True;
4040 end if;
4042 Next_Component (Id);
4043 end loop;
4045 -- As explained above, a record initialization procedure is needed
4046 -- for public types in case Initialize_Scalars applies to a client.
4047 -- However, such a procedure is not needed in the case where either
4048 -- of restrictions No_Initialize_Scalars or No_Default_Initialization
4049 -- applies. No_Initialize_Scalars excludes the possibility of using
4050 -- Initialize_Scalars in any partition, and No_Default_Initialization
4051 -- implies that no initialization should ever be done for objects of
4052 -- the type, so is incompatible with Initialize_Scalars.
4054 if not Restriction_Active (No_Initialize_Scalars)
4055 and then not Restriction_Active (No_Default_Initialization)
4056 and then Is_Public (Rec_Id)
4057 then
4058 return True;
4059 end if;
4061 return False;
4062 end Requires_Init_Proc;
4064 -- Start of processing for Build_Record_Init_Proc
4066 begin
4067 Rec_Type := Defining_Identifier (N);
4069 -- This may be full declaration of a private type, in which case
4070 -- the visible entity is a record, and the private entity has been
4071 -- exchanged with it in the private part of the current package.
4072 -- The initialization procedure is built for the record type, which
4073 -- is retrievable from the private entity.
4075 if Is_Incomplete_Or_Private_Type (Rec_Type) then
4076 Rec_Type := Underlying_Type (Rec_Type);
4077 end if;
4079 -- If we have a variant record with restriction No_Implicit_Conditionals
4080 -- in effect, then we skip building the procedure. This is safe because
4081 -- if we can see the restriction, so can any caller, calls to initialize
4082 -- such records are not allowed for variant records if this restriction
4083 -- is active.
4085 if Has_Variant_Part (Rec_Type)
4086 and then Restriction_Active (No_Implicit_Conditionals)
4087 then
4088 return;
4089 end if;
4091 -- If there are discriminants, build the discriminant map to replace
4092 -- discriminants by their discriminals in complex bound expressions.
4093 -- These only arise for the corresponding records of synchronized types.
4095 if Is_Concurrent_Record_Type (Rec_Type)
4096 and then Has_Discriminants (Rec_Type)
4097 then
4098 declare
4099 Disc : Entity_Id;
4100 begin
4101 Disc := First_Discriminant (Rec_Type);
4102 while Present (Disc) loop
4103 Append_Elmt (Disc, Discr_Map);
4104 Append_Elmt (Discriminal (Disc), Discr_Map);
4105 Next_Discriminant (Disc);
4106 end loop;
4107 end;
4108 end if;
4110 -- Derived types that have no type extension can use the initialization
4111 -- procedure of their parent and do not need a procedure of their own.
4112 -- This is only correct if there are no representation clauses for the
4113 -- type or its parent, and if the parent has in fact been frozen so
4114 -- that its initialization procedure exists.
4116 if Is_Derived_Type (Rec_Type)
4117 and then not Is_Tagged_Type (Rec_Type)
4118 and then not Is_Unchecked_Union (Rec_Type)
4119 and then not Has_New_Non_Standard_Rep (Rec_Type)
4120 and then not Parent_Subtype_Renaming_Discrims
4121 and then Present (Base_Init_Proc (Etype (Rec_Type)))
4122 then
4123 Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
4125 -- Otherwise if we need an initialization procedure, then build one,
4126 -- mark it as public and inlinable and as having a completion.
4128 elsif Requires_Init_Proc (Rec_Type)
4129 or else Is_Unchecked_Union (Rec_Type)
4130 then
4131 Proc_Id :=
4132 Make_Defining_Identifier (Loc,
4133 Chars => Make_Init_Proc_Name (Rec_Type));
4135 -- If No_Default_Initialization restriction is active, then we don't
4136 -- want to build an init_proc, but we need to mark that an init_proc
4137 -- would be needed if this restriction was not active (so that we can
4138 -- detect attempts to call it), so set a dummy init_proc in place.
4140 if Restriction_Active (No_Default_Initialization) then
4141 Set_Init_Proc (Rec_Type, Proc_Id);
4142 return;
4143 end if;
4145 Build_Offset_To_Top_Functions;
4146 Build_CPP_Init_Procedure;
4147 Build_Init_Procedure;
4149 Set_Is_Public (Proc_Id, Is_Public (Rec_Ent));
4150 Set_Is_Internal (Proc_Id);
4151 Set_Has_Completion (Proc_Id);
4153 if not Debug_Generated_Code then
4154 Set_Debug_Info_Off (Proc_Id);
4155 end if;
4157 Set_Is_Inlined (Proc_Id, Inline_Init_Proc (Rec_Type));
4159 -- Do not build an aggregate if Modify_Tree_For_C, this isn't
4160 -- needed and may generate early references to non frozen types
4161 -- since we expand aggregate much more systematically.
4163 if Modify_Tree_For_C then
4164 return;
4165 end if;
4167 declare
4168 Agg : constant Node_Id :=
4169 Build_Equivalent_Record_Aggregate (Rec_Type);
4171 procedure Collect_Itypes (Comp : Node_Id);
4172 -- Generate references to itypes in the aggregate, because
4173 -- the first use of the aggregate may be in a nested scope.
4175 --------------------
4176 -- Collect_Itypes --
4177 --------------------
4179 procedure Collect_Itypes (Comp : Node_Id) is
4180 Ref : Node_Id;
4181 Sub_Aggr : Node_Id;
4182 Typ : constant Entity_Id := Etype (Comp);
4184 begin
4185 if Is_Array_Type (Typ) and then Is_Itype (Typ) then
4186 Ref := Make_Itype_Reference (Loc);
4187 Set_Itype (Ref, Typ);
4188 Append_Freeze_Action (Rec_Type, Ref);
4190 Ref := Make_Itype_Reference (Loc);
4191 Set_Itype (Ref, Etype (First_Index (Typ)));
4192 Append_Freeze_Action (Rec_Type, Ref);
4194 -- Recurse on nested arrays
4196 Sub_Aggr := First (Expressions (Comp));
4197 while Present (Sub_Aggr) loop
4198 Collect_Itypes (Sub_Aggr);
4199 Next (Sub_Aggr);
4200 end loop;
4201 end if;
4202 end Collect_Itypes;
4204 begin
4205 -- If there is a static initialization aggregate for the type,
4206 -- generate itype references for the types of its (sub)components,
4207 -- to prevent out-of-scope errors in the resulting tree.
4208 -- The aggregate may have been rewritten as a Raise node, in which
4209 -- case there are no relevant itypes.
4211 if Present (Agg) and then Nkind (Agg) = N_Aggregate then
4212 Set_Static_Initialization (Proc_Id, Agg);
4214 declare
4215 Comp : Node_Id;
4216 begin
4217 Comp := First (Component_Associations (Agg));
4218 while Present (Comp) loop
4219 Collect_Itypes (Expression (Comp));
4220 Next (Comp);
4221 end loop;
4222 end;
4223 end if;
4224 end;
4225 end if;
4226 end Build_Record_Init_Proc;
4228 ----------------------------
4229 -- Build_Slice_Assignment --
4230 ----------------------------
4232 -- Generates the following subprogram:
4234 -- procedure array_typeSA
4235 -- (Source, Target : Array_Type,
4236 -- Left_Lo, Left_Hi : Index;
4237 -- Right_Lo, Right_Hi : Index;
4238 -- Rev : Boolean)
4239 -- is
4240 -- Li1 : Index;
4241 -- Ri1 : Index;
4243 -- begin
4244 -- if Left_Hi < Left_Lo then
4245 -- return;
4246 -- end if;
4248 -- if Rev then
4249 -- Li1 := Left_Hi;
4250 -- Ri1 := Right_Hi;
4251 -- else
4252 -- Li1 := Left_Lo;
4253 -- Ri1 := Right_Lo;
4254 -- end if;
4256 -- loop
4257 -- Target (Li1) := Source (Ri1);
4259 -- if Rev then
4260 -- exit when Li1 = Left_Lo;
4261 -- Li1 := Index'pred (Li1);
4262 -- Ri1 := Index'pred (Ri1);
4263 -- else
4264 -- exit when Li1 = Left_Hi;
4265 -- Li1 := Index'succ (Li1);
4266 -- Ri1 := Index'succ (Ri1);
4267 -- end if;
4268 -- end loop;
4269 -- end array_typeSA;
4271 procedure Build_Slice_Assignment (Typ : Entity_Id) is
4272 Loc : constant Source_Ptr := Sloc (Typ);
4273 Index : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
4275 Larray : constant Entity_Id := Make_Temporary (Loc, 'A');
4276 Rarray : constant Entity_Id := Make_Temporary (Loc, 'R');
4277 Left_Lo : constant Entity_Id := Make_Temporary (Loc, 'L');
4278 Left_Hi : constant Entity_Id := Make_Temporary (Loc, 'L');
4279 Right_Lo : constant Entity_Id := Make_Temporary (Loc, 'R');
4280 Right_Hi : constant Entity_Id := Make_Temporary (Loc, 'R');
4281 Rev : constant Entity_Id := Make_Temporary (Loc, 'D');
4282 -- Formal parameters of procedure
4284 Proc_Name : constant Entity_Id :=
4285 Make_Defining_Identifier (Loc,
4286 Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
4288 Lnn : constant Entity_Id := Make_Temporary (Loc, 'L');
4289 Rnn : constant Entity_Id := Make_Temporary (Loc, 'R');
4290 -- Subscripts for left and right sides
4292 Decls : List_Id;
4293 Loops : Node_Id;
4294 Stats : List_Id;
4296 begin
4297 -- Build declarations for indexes
4299 Decls := New_List;
4301 Append_To (Decls,
4302 Make_Object_Declaration (Loc,
4303 Defining_Identifier => Lnn,
4304 Object_Definition =>
4305 New_Occurrence_Of (Index, Loc)));
4307 Append_To (Decls,
4308 Make_Object_Declaration (Loc,
4309 Defining_Identifier => Rnn,
4310 Object_Definition =>
4311 New_Occurrence_Of (Index, Loc)));
4313 Stats := New_List;
4315 -- Build test for empty slice case
4317 Append_To (Stats,
4318 Make_If_Statement (Loc,
4319 Condition =>
4320 Make_Op_Lt (Loc,
4321 Left_Opnd => New_Occurrence_Of (Left_Hi, Loc),
4322 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc)),
4323 Then_Statements => New_List (Make_Simple_Return_Statement (Loc))));
4325 -- Build initializations for indexes
4327 declare
4328 F_Init : constant List_Id := New_List;
4329 B_Init : constant List_Id := New_List;
4331 begin
4332 Append_To (F_Init,
4333 Make_Assignment_Statement (Loc,
4334 Name => New_Occurrence_Of (Lnn, Loc),
4335 Expression => New_Occurrence_Of (Left_Lo, Loc)));
4337 Append_To (F_Init,
4338 Make_Assignment_Statement (Loc,
4339 Name => New_Occurrence_Of (Rnn, Loc),
4340 Expression => New_Occurrence_Of (Right_Lo, Loc)));
4342 Append_To (B_Init,
4343 Make_Assignment_Statement (Loc,
4344 Name => New_Occurrence_Of (Lnn, Loc),
4345 Expression => New_Occurrence_Of (Left_Hi, Loc)));
4347 Append_To (B_Init,
4348 Make_Assignment_Statement (Loc,
4349 Name => New_Occurrence_Of (Rnn, Loc),
4350 Expression => New_Occurrence_Of (Right_Hi, Loc)));
4352 Append_To (Stats,
4353 Make_If_Statement (Loc,
4354 Condition => New_Occurrence_Of (Rev, Loc),
4355 Then_Statements => B_Init,
4356 Else_Statements => F_Init));
4357 end;
4359 -- Now construct the assignment statement
4361 Loops :=
4362 Make_Loop_Statement (Loc,
4363 Statements => New_List (
4364 Make_Assignment_Statement (Loc,
4365 Name =>
4366 Make_Indexed_Component (Loc,
4367 Prefix => New_Occurrence_Of (Larray, Loc),
4368 Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
4369 Expression =>
4370 Make_Indexed_Component (Loc,
4371 Prefix => New_Occurrence_Of (Rarray, Loc),
4372 Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
4373 End_Label => Empty);
4375 -- Build the exit condition and increment/decrement statements
4377 declare
4378 F_Ass : constant List_Id := New_List;
4379 B_Ass : constant List_Id := New_List;
4381 begin
4382 Append_To (F_Ass,
4383 Make_Exit_Statement (Loc,
4384 Condition =>
4385 Make_Op_Eq (Loc,
4386 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
4387 Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
4389 Append_To (F_Ass,
4390 Make_Assignment_Statement (Loc,
4391 Name => New_Occurrence_Of (Lnn, Loc),
4392 Expression =>
4393 Make_Attribute_Reference (Loc,
4394 Prefix =>
4395 New_Occurrence_Of (Index, Loc),
4396 Attribute_Name => Name_Succ,
4397 Expressions => New_List (
4398 New_Occurrence_Of (Lnn, Loc)))));
4400 Append_To (F_Ass,
4401 Make_Assignment_Statement (Loc,
4402 Name => New_Occurrence_Of (Rnn, Loc),
4403 Expression =>
4404 Make_Attribute_Reference (Loc,
4405 Prefix =>
4406 New_Occurrence_Of (Index, Loc),
4407 Attribute_Name => Name_Succ,
4408 Expressions => New_List (
4409 New_Occurrence_Of (Rnn, Loc)))));
4411 Append_To (B_Ass,
4412 Make_Exit_Statement (Loc,
4413 Condition =>
4414 Make_Op_Eq (Loc,
4415 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
4416 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
4418 Append_To (B_Ass,
4419 Make_Assignment_Statement (Loc,
4420 Name => New_Occurrence_Of (Lnn, Loc),
4421 Expression =>
4422 Make_Attribute_Reference (Loc,
4423 Prefix =>
4424 New_Occurrence_Of (Index, Loc),
4425 Attribute_Name => Name_Pred,
4426 Expressions => New_List (
4427 New_Occurrence_Of (Lnn, Loc)))));
4429 Append_To (B_Ass,
4430 Make_Assignment_Statement (Loc,
4431 Name => New_Occurrence_Of (Rnn, Loc),
4432 Expression =>
4433 Make_Attribute_Reference (Loc,
4434 Prefix =>
4435 New_Occurrence_Of (Index, Loc),
4436 Attribute_Name => Name_Pred,
4437 Expressions => New_List (
4438 New_Occurrence_Of (Rnn, Loc)))));
4440 Append_To (Statements (Loops),
4441 Make_If_Statement (Loc,
4442 Condition => New_Occurrence_Of (Rev, Loc),
4443 Then_Statements => B_Ass,
4444 Else_Statements => F_Ass));
4445 end;
4447 Append_To (Stats, Loops);
4449 declare
4450 Spec : Node_Id;
4451 Formals : List_Id;
4453 begin
4454 Formals := New_List (
4455 Make_Parameter_Specification (Loc,
4456 Defining_Identifier => Larray,
4457 Out_Present => True,
4458 Parameter_Type =>
4459 New_Occurrence_Of (Base_Type (Typ), Loc)),
4461 Make_Parameter_Specification (Loc,
4462 Defining_Identifier => Rarray,
4463 Parameter_Type =>
4464 New_Occurrence_Of (Base_Type (Typ), Loc)),
4466 Make_Parameter_Specification (Loc,
4467 Defining_Identifier => Left_Lo,
4468 Parameter_Type =>
4469 New_Occurrence_Of (Index, Loc)),
4471 Make_Parameter_Specification (Loc,
4472 Defining_Identifier => Left_Hi,
4473 Parameter_Type =>
4474 New_Occurrence_Of (Index, Loc)),
4476 Make_Parameter_Specification (Loc,
4477 Defining_Identifier => Right_Lo,
4478 Parameter_Type =>
4479 New_Occurrence_Of (Index, Loc)),
4481 Make_Parameter_Specification (Loc,
4482 Defining_Identifier => Right_Hi,
4483 Parameter_Type =>
4484 New_Occurrence_Of (Index, Loc)));
4486 Append_To (Formals,
4487 Make_Parameter_Specification (Loc,
4488 Defining_Identifier => Rev,
4489 Parameter_Type =>
4490 New_Occurrence_Of (Standard_Boolean, Loc)));
4492 Spec :=
4493 Make_Procedure_Specification (Loc,
4494 Defining_Unit_Name => Proc_Name,
4495 Parameter_Specifications => Formals);
4497 Discard_Node (
4498 Make_Subprogram_Body (Loc,
4499 Specification => Spec,
4500 Declarations => Decls,
4501 Handled_Statement_Sequence =>
4502 Make_Handled_Sequence_Of_Statements (Loc,
4503 Statements => Stats)));
4504 end;
4506 Set_TSS (Typ, Proc_Name);
4507 Set_Is_Pure (Proc_Name);
4508 end Build_Slice_Assignment;
4510 -----------------------------
4511 -- Build_Untagged_Equality --
4512 -----------------------------
4514 procedure Build_Untagged_Equality (Typ : Entity_Id) is
4515 Build_Eq : Boolean;
4516 Comp : Entity_Id;
4517 Decl : Node_Id;
4518 Op : Entity_Id;
4519 Eq_Op : Entity_Id;
4521 function User_Defined_Eq (T : Entity_Id) return Entity_Id;
4522 -- Check whether the type T has a user-defined primitive equality. If so
4523 -- return it, else return Empty. If true for a component of Typ, we have
4524 -- to build the primitive equality for it.
4526 ---------------------
4527 -- User_Defined_Eq --
4528 ---------------------
4530 function User_Defined_Eq (T : Entity_Id) return Entity_Id is
4531 Op : constant Entity_Id := TSS (T, TSS_Composite_Equality);
4533 begin
4534 if Present (Op) then
4535 return Op;
4536 else
4537 return Get_User_Defined_Equality (T);
4538 end if;
4539 end User_Defined_Eq;
4541 -- Start of processing for Build_Untagged_Equality
4543 begin
4544 -- If a record component has a primitive equality operation, we must
4545 -- build the corresponding one for the current type.
4547 Build_Eq := False;
4548 Comp := First_Component (Typ);
4549 while Present (Comp) loop
4550 if Is_Record_Type (Etype (Comp))
4551 and then Present (User_Defined_Eq (Etype (Comp)))
4552 then
4553 Build_Eq := True;
4554 exit;
4555 end if;
4557 Next_Component (Comp);
4558 end loop;
4560 -- If there is a user-defined equality for the type, we do not create
4561 -- the implicit one.
4563 Eq_Op := Get_User_Defined_Equality (Typ);
4564 if Present (Eq_Op) then
4565 if Comes_From_Source (Eq_Op) then
4566 Build_Eq := False;
4567 else
4568 Eq_Op := Empty;
4569 end if;
4570 end if;
4572 -- If the type is derived, inherit the operation, if present, from the
4573 -- parent type. It may have been declared after the type derivation. If
4574 -- the parent type itself is derived, it may have inherited an operation
4575 -- that has itself been overridden, so update its alias and related
4576 -- flags. Ditto for inequality.
4578 if No (Eq_Op) and then Is_Derived_Type (Typ) then
4579 Eq_Op := Get_User_Defined_Equality (Etype (Typ));
4580 if Present (Eq_Op) then
4581 Copy_TSS (Eq_Op, Typ);
4582 Build_Eq := False;
4584 declare
4585 Op : constant Entity_Id := User_Defined_Eq (Typ);
4586 NE_Op : constant Entity_Id := Next_Entity (Eq_Op);
4588 begin
4589 if Present (Op) then
4590 Set_Alias (Op, Eq_Op);
4591 Set_Is_Abstract_Subprogram
4592 (Op, Is_Abstract_Subprogram (Eq_Op));
4594 if Chars (Next_Entity (Op)) = Name_Op_Ne then
4595 Set_Is_Abstract_Subprogram
4596 (Next_Entity (Op), Is_Abstract_Subprogram (NE_Op));
4597 end if;
4598 end if;
4599 end;
4600 end if;
4601 end if;
4603 -- If not inherited and not user-defined, build body as for a type with
4604 -- tagged components.
4606 if Build_Eq then
4607 Decl :=
4608 Make_Eq_Body (Typ, Make_TSS_Name (Typ, TSS_Composite_Equality));
4609 Op := Defining_Entity (Decl);
4610 Set_TSS (Typ, Op);
4611 Set_Is_Pure (Op);
4613 if Is_Library_Level_Entity (Typ) then
4614 Set_Is_Public (Op);
4615 end if;
4616 end if;
4617 end Build_Untagged_Equality;
4619 -----------------------------------
4620 -- Build_Variant_Record_Equality --
4621 -----------------------------------
4623 -- Generates:
4625 -- function <<Body_Id>> (Left, Right : T) return Boolean is
4626 -- [ X : T renames Left; ]
4627 -- [ Y : T renames Right; ]
4628 -- -- The above renamings are generated only if the parameters of
4629 -- -- this built function (which are passed by the caller) are not
4630 -- -- named 'X' and 'Y'; these names are required to reuse several
4631 -- -- expander routines when generating this body.
4633 -- begin
4634 -- -- Compare discriminants
4636 -- if X.D1 /= Y.D1 or else X.D2 /= Y.D2 or else ... then
4637 -- return False;
4638 -- end if;
4640 -- -- Compare components
4642 -- if X.C1 /= Y.C1 or else X.C2 /= Y.C2 or else ... then
4643 -- return False;
4644 -- end if;
4646 -- -- Compare variant part
4648 -- case X.D1 is
4649 -- when V1 =>
4650 -- if X.C2 /= Y.C2 or else X.C3 /= Y.C3 or else ... then
4651 -- return False;
4652 -- end if;
4653 -- ...
4654 -- when Vn =>
4655 -- if X.Cn /= Y.Cn or else ... then
4656 -- return False;
4657 -- end if;
4658 -- end case;
4660 -- return True;
4661 -- end _Equality;
4663 function Build_Variant_Record_Equality
4664 (Typ : Entity_Id;
4665 Body_Id : Entity_Id;
4666 Param_Specs : List_Id) return Node_Id
4668 Loc : constant Source_Ptr := Sloc (Typ);
4669 Def : constant Node_Id := Parent (Typ);
4670 Comps : constant Node_Id := Component_List (Type_Definition (Def));
4671 Left : constant Entity_Id := Defining_Identifier (First (Param_Specs));
4672 Right : constant Entity_Id :=
4673 Defining_Identifier (Next (First (Param_Specs)));
4674 Decls : constant List_Id := New_List;
4675 Stmts : constant List_Id := New_List;
4677 Subp_Body : Node_Id;
4679 begin
4680 pragma Assert (not Is_Tagged_Type (Typ));
4682 -- In order to reuse the expander routines Make_Eq_If and Make_Eq_Case
4683 -- the name of the formals must be X and Y; otherwise we generate two
4684 -- renaming declarations for such purpose.
4686 if Chars (Left) /= Name_X then
4687 Append_To (Decls,
4688 Make_Object_Renaming_Declaration (Loc,
4689 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
4690 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
4691 Name => Make_Identifier (Loc, Chars (Left))));
4692 end if;
4694 if Chars (Right) /= Name_Y then
4695 Append_To (Decls,
4696 Make_Object_Renaming_Declaration (Loc,
4697 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
4698 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
4699 Name => Make_Identifier (Loc, Chars (Right))));
4700 end if;
4702 -- Unchecked_Unions require additional machinery to support equality.
4703 -- Two extra parameters (A and B) are added to the equality function
4704 -- parameter list for each discriminant of the type, in order to
4705 -- capture the inferred values of the discriminants in equality calls.
4706 -- The names of the parameters match the names of the corresponding
4707 -- discriminant, with an added suffix.
4709 if Is_Unchecked_Union (Typ) then
4710 declare
4711 A : Entity_Id;
4712 B : Entity_Id;
4713 Discr : Entity_Id;
4714 Discr_Type : Entity_Id;
4715 New_Discrs : Elist_Id;
4717 begin
4718 New_Discrs := New_Elmt_List;
4720 Discr := First_Discriminant (Typ);
4721 while Present (Discr) loop
4722 Discr_Type := Etype (Discr);
4724 A :=
4725 Make_Defining_Identifier (Loc,
4726 Chars => New_External_Name (Chars (Discr), 'A'));
4728 B :=
4729 Make_Defining_Identifier (Loc,
4730 Chars => New_External_Name (Chars (Discr), 'B'));
4732 -- Add new parameters to the parameter list
4734 Append_To (Param_Specs,
4735 Make_Parameter_Specification (Loc,
4736 Defining_Identifier => A,
4737 Parameter_Type =>
4738 New_Occurrence_Of (Discr_Type, Loc)));
4740 Append_To (Param_Specs,
4741 Make_Parameter_Specification (Loc,
4742 Defining_Identifier => B,
4743 Parameter_Type =>
4744 New_Occurrence_Of (Discr_Type, Loc)));
4746 Append_Elmt (A, New_Discrs);
4748 -- Generate the following code to compare each of the inferred
4749 -- discriminants:
4751 -- if a /= b then
4752 -- return False;
4753 -- end if;
4755 Append_To (Stmts,
4756 Make_If_Statement (Loc,
4757 Condition =>
4758 Make_Op_Ne (Loc,
4759 Left_Opnd => New_Occurrence_Of (A, Loc),
4760 Right_Opnd => New_Occurrence_Of (B, Loc)),
4761 Then_Statements => New_List (
4762 Make_Simple_Return_Statement (Loc,
4763 Expression =>
4764 New_Occurrence_Of (Standard_False, Loc)))));
4765 Next_Discriminant (Discr);
4766 end loop;
4768 -- Generate component-by-component comparison. Note that we must
4769 -- propagate the inferred discriminants formals to act as the case
4770 -- statement switch. Their value is added when an equality call on
4771 -- unchecked unions is expanded.
4773 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps, New_Discrs));
4774 end;
4776 -- Normal case (not unchecked union)
4778 else
4779 Append_To (Stmts,
4780 Make_Eq_If (Typ, Discriminant_Specifications (Def)));
4781 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps));
4782 end if;
4784 Append_To (Stmts,
4785 Make_Simple_Return_Statement (Loc,
4786 Expression => New_Occurrence_Of (Standard_True, Loc)));
4788 Subp_Body :=
4789 Make_Subprogram_Body (Loc,
4790 Specification =>
4791 Make_Function_Specification (Loc,
4792 Defining_Unit_Name => Body_Id,
4793 Parameter_Specifications => Param_Specs,
4794 Result_Definition =>
4795 New_Occurrence_Of (Standard_Boolean, Loc)),
4796 Declarations => Decls,
4797 Handled_Statement_Sequence =>
4798 Make_Handled_Sequence_Of_Statements (Loc,
4799 Statements => Stmts));
4801 return Subp_Body;
4802 end Build_Variant_Record_Equality;
4804 -----------------------------
4805 -- Check_Stream_Attributes --
4806 -----------------------------
4808 procedure Check_Stream_Attributes (Typ : Entity_Id) is
4809 Comp : Entity_Id;
4810 Par_Read : constant Boolean :=
4811 Stream_Attribute_Available (Typ, TSS_Stream_Read)
4812 and then not Has_Specified_Stream_Read (Typ);
4813 Par_Write : constant Boolean :=
4814 Stream_Attribute_Available (Typ, TSS_Stream_Write)
4815 and then not Has_Specified_Stream_Write (Typ);
4817 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type);
4818 -- Check that Comp has a user-specified Nam stream attribute
4820 ----------------
4821 -- Check_Attr --
4822 ----------------
4824 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type) is
4825 begin
4826 -- Move this check to sem???
4828 if not Stream_Attribute_Available (Etype (Comp), TSS_Nam) then
4829 Error_Msg_Name_1 := Nam;
4830 Error_Msg_N
4831 ("|component& in limited extension must have% attribute", Comp);
4832 end if;
4833 end Check_Attr;
4835 -- Start of processing for Check_Stream_Attributes
4837 begin
4838 if Par_Read or else Par_Write then
4839 Comp := First_Component (Typ);
4840 while Present (Comp) loop
4841 if Comes_From_Source (Comp)
4842 and then Original_Record_Component (Comp) = Comp
4843 and then Is_Limited_Type (Etype (Comp))
4844 then
4845 if Par_Read then
4846 Check_Attr (Name_Read, TSS_Stream_Read);
4847 end if;
4849 if Par_Write then
4850 Check_Attr (Name_Write, TSS_Stream_Write);
4851 end if;
4852 end if;
4854 Next_Component (Comp);
4855 end loop;
4856 end if;
4857 end Check_Stream_Attributes;
4859 ----------------------
4860 -- Clean_Task_Names --
4861 ----------------------
4863 procedure Clean_Task_Names
4864 (Typ : Entity_Id;
4865 Proc_Id : Entity_Id)
4867 begin
4868 if Has_Task (Typ)
4869 and then not Restriction_Active (No_Implicit_Heap_Allocations)
4870 and then not Global_Discard_Names
4871 and then Tagged_Type_Expansion
4872 then
4873 Set_Uses_Sec_Stack (Proc_Id);
4874 end if;
4875 end Clean_Task_Names;
4877 -------------------------------
4878 -- Copy_Discr_Checking_Funcs --
4879 -------------------------------
4881 procedure Copy_Discr_Checking_Funcs (N : Node_Id) is
4882 Typ : constant Entity_Id := Defining_Identifier (N);
4883 Comp : Entity_Id := First_Component (Typ);
4884 Old_Comp : Entity_Id := First_Component
4885 (Base_Type (Underlying_Type (Etype (Typ))));
4886 begin
4887 while Present (Comp) loop
4888 if Chars (Comp) = Chars (Old_Comp) then
4889 Set_Discriminant_Checking_Func
4890 (Comp, Discriminant_Checking_Func (Old_Comp));
4891 end if;
4893 Next_Component (Old_Comp);
4894 Next_Component (Comp);
4895 end loop;
4896 end Copy_Discr_Checking_Funcs;
4898 ----------------------------------------
4899 -- Ensure_Activation_Chain_And_Master --
4900 ----------------------------------------
4902 procedure Ensure_Activation_Chain_And_Master (Obj_Decl : Node_Id) is
4903 Def_Id : constant Entity_Id := Defining_Identifier (Obj_Decl);
4904 Expr : constant Node_Id := Expression (Obj_Decl);
4905 Expr_Q : Node_Id;
4906 Typ : constant Entity_Id := Etype (Def_Id);
4908 begin
4909 pragma Assert (Nkind (Obj_Decl) = N_Object_Declaration);
4911 if Might_Have_Tasks (Typ) then
4912 Build_Activation_Chain_Entity (Obj_Decl);
4914 if Has_Task (Typ) then
4915 Build_Master_Entity (Def_Id);
4917 -- Handle objects initialized with BIP function calls
4919 elsif Present (Expr) then
4920 if Nkind (Expr) = N_Qualified_Expression then
4921 Expr_Q := Expression (Expr);
4922 else
4923 Expr_Q := Expr;
4924 end if;
4926 if Is_Build_In_Place_Function_Call (Expr_Q)
4927 or else Present (Unqual_BIP_Iface_Function_Call (Expr_Q))
4928 or else
4929 (Nkind (Expr_Q) = N_Reference
4930 and then
4931 Is_Build_In_Place_Function_Call (Prefix (Expr_Q)))
4932 then
4933 Build_Master_Entity (Def_Id);
4934 end if;
4935 end if;
4936 end if;
4937 end Ensure_Activation_Chain_And_Master;
4939 ------------------------------
4940 -- Expand_Freeze_Array_Type --
4941 ------------------------------
4943 procedure Expand_Freeze_Array_Type (N : Node_Id) is
4944 Typ : constant Entity_Id := Entity (N);
4945 Base : constant Entity_Id := Base_Type (Typ);
4946 Comp_Typ : constant Entity_Id := Component_Type (Typ);
4948 begin
4949 if not Is_Bit_Packed_Array (Typ) then
4951 -- If the component contains tasks, so does the array type. This may
4952 -- not be indicated in the array type because the component may have
4953 -- been a private type at the point of definition. Same if component
4954 -- type is controlled or contains protected objects.
4956 Propagate_Concurrent_Flags (Base, Comp_Typ);
4957 Set_Has_Controlled_Component
4958 (Base, Has_Controlled_Component (Comp_Typ)
4959 or else Is_Controlled (Comp_Typ));
4961 if No (Init_Proc (Base)) then
4963 -- If this is an anonymous array created for a declaration with
4964 -- an initial value, its init_proc will never be called. The
4965 -- initial value itself may have been expanded into assignments,
4966 -- in which case the object declaration is carries the
4967 -- No_Initialization flag.
4969 if Is_Itype (Base)
4970 and then Nkind (Associated_Node_For_Itype (Base)) =
4971 N_Object_Declaration
4972 and then
4973 (Present (Expression (Associated_Node_For_Itype (Base)))
4974 or else No_Initialization (Associated_Node_For_Itype (Base)))
4975 then
4976 null;
4978 -- We do not need an init proc for string or wide [wide] string,
4979 -- since the only time these need initialization in normalize or
4980 -- initialize scalars mode, and these types are treated specially
4981 -- and do not need initialization procedures.
4983 elsif Is_Standard_String_Type (Base) then
4984 null;
4986 -- Otherwise we have to build an init proc for the subtype
4988 else
4989 Build_Array_Init_Proc (Base, N);
4990 end if;
4991 end if;
4993 if Typ = Base and then Has_Controlled_Component (Base) then
4994 Build_Controlling_Procs (Base);
4996 if not Is_Limited_Type (Comp_Typ)
4997 and then Number_Dimensions (Typ) = 1
4998 then
4999 Build_Slice_Assignment (Typ);
5000 end if;
5001 end if;
5003 -- For packed case, default initialization, except if the component type
5004 -- is itself a packed structure with an initialization procedure, or
5005 -- initialize/normalize scalars active, and we have a base type, or the
5006 -- type is public, because in that case a client might specify
5007 -- Normalize_Scalars and there better be a public Init_Proc for it.
5009 elsif (Present (Init_Proc (Component_Type (Base)))
5010 and then No (Base_Init_Proc (Base)))
5011 or else (Init_Or_Norm_Scalars and then Base = Typ)
5012 or else Is_Public (Typ)
5013 then
5014 Build_Array_Init_Proc (Base, N);
5015 end if;
5016 end Expand_Freeze_Array_Type;
5018 -----------------------------------
5019 -- Expand_Freeze_Class_Wide_Type --
5020 -----------------------------------
5022 procedure Expand_Freeze_Class_Wide_Type (N : Node_Id) is
5023 function Is_C_Derivation (Typ : Entity_Id) return Boolean;
5024 -- Given a type, determine whether it is derived from a C or C++ root
5026 ---------------------
5027 -- Is_C_Derivation --
5028 ---------------------
5030 function Is_C_Derivation (Typ : Entity_Id) return Boolean is
5031 T : Entity_Id;
5033 begin
5034 T := Typ;
5035 loop
5036 if Is_CPP_Class (T)
5037 or else Convention (T) = Convention_C
5038 or else Convention (T) = Convention_CPP
5039 then
5040 return True;
5041 end if;
5043 exit when T = Etype (T);
5045 T := Etype (T);
5046 end loop;
5048 return False;
5049 end Is_C_Derivation;
5051 -- Local variables
5053 Typ : constant Entity_Id := Entity (N);
5054 Root : constant Entity_Id := Root_Type (Typ);
5056 -- Start of processing for Expand_Freeze_Class_Wide_Type
5058 begin
5059 -- Certain run-time configurations and targets do not provide support
5060 -- for controlled types.
5062 if Restriction_Active (No_Finalization) then
5063 return;
5065 -- Do not create TSS routine Finalize_Address when dispatching calls are
5066 -- disabled since the core of the routine is a dispatching call.
5068 elsif Restriction_Active (No_Dispatching_Calls) then
5069 return;
5071 -- Do not create TSS routine Finalize_Address for concurrent class-wide
5072 -- types. Ignore C, C++, CIL and Java types since it is assumed that the
5073 -- non-Ada side will handle their destruction.
5075 elsif Is_Concurrent_Type (Root)
5076 or else Is_C_Derivation (Root)
5077 or else Convention (Typ) = Convention_CPP
5078 then
5079 return;
5081 -- Do not create TSS routine Finalize_Address when compiling in CodePeer
5082 -- mode since the routine contains an Unchecked_Conversion.
5084 elsif CodePeer_Mode then
5085 return;
5086 end if;
5088 -- Create the body of TSS primitive Finalize_Address. This automatically
5089 -- sets the TSS entry for the class-wide type.
5091 Make_Finalize_Address_Body (Typ);
5092 end Expand_Freeze_Class_Wide_Type;
5094 ------------------------------------
5095 -- Expand_Freeze_Enumeration_Type --
5096 ------------------------------------
5098 procedure Expand_Freeze_Enumeration_Type (N : Node_Id) is
5099 Typ : constant Entity_Id := Entity (N);
5100 Loc : constant Source_Ptr := Sloc (Typ);
5102 Arr : Entity_Id;
5103 Ent : Entity_Id;
5104 Fent : Entity_Id;
5105 Is_Contiguous : Boolean;
5106 Index_Typ : Entity_Id;
5107 Ityp : Entity_Id;
5108 Last_Repval : Uint;
5109 Lst : List_Id;
5110 Num : Nat;
5111 Pos_Expr : Node_Id;
5113 Func : Entity_Id;
5114 pragma Warnings (Off, Func);
5116 begin
5117 -- Various optimizations possible if given representation is contiguous
5119 Is_Contiguous := True;
5121 Ent := First_Literal (Typ);
5122 Last_Repval := Enumeration_Rep (Ent);
5123 Num := 1;
5124 Next_Literal (Ent);
5126 while Present (Ent) loop
5127 if Enumeration_Rep (Ent) - Last_Repval /= 1 then
5128 Is_Contiguous := False;
5129 else
5130 Last_Repval := Enumeration_Rep (Ent);
5131 end if;
5133 Num := Num + 1;
5134 Next_Literal (Ent);
5135 end loop;
5137 if Is_Contiguous then
5138 Set_Has_Contiguous_Rep (Typ);
5140 -- Now build a subtype declaration
5142 -- subtype typI is new Natural range 0 .. num - 1
5144 Index_Typ :=
5145 Make_Defining_Identifier (Loc,
5146 Chars => New_External_Name (Chars (Typ), 'I'));
5148 Append_Freeze_Action (Typ,
5149 Make_Subtype_Declaration (Loc,
5150 Defining_Identifier => Index_Typ,
5151 Subtype_Indication =>
5152 Make_Subtype_Indication (Loc,
5153 Subtype_Mark =>
5154 New_Occurrence_Of (Standard_Natural, Loc),
5155 Constraint =>
5156 Make_Range_Constraint (Loc,
5157 Range_Expression =>
5158 Make_Range (Loc,
5159 Low_Bound =>
5160 Make_Integer_Literal (Loc, 0),
5161 High_Bound =>
5162 Make_Integer_Literal (Loc, Num - 1))))));
5164 Set_Enum_Pos_To_Rep (Typ, Index_Typ);
5166 else
5167 -- Build list of literal references
5169 Lst := New_List;
5170 Ent := First_Literal (Typ);
5171 while Present (Ent) loop
5172 Append_To (Lst, New_Occurrence_Of (Ent, Sloc (Ent)));
5173 Next_Literal (Ent);
5174 end loop;
5176 -- Now build an array declaration
5178 -- typA : constant array (Natural range 0 .. num - 1) of typ :=
5179 -- (v, v, v, v, v, ....)
5181 Arr :=
5182 Make_Defining_Identifier (Loc,
5183 Chars => New_External_Name (Chars (Typ), 'A'));
5185 Append_Freeze_Action (Typ,
5186 Make_Object_Declaration (Loc,
5187 Defining_Identifier => Arr,
5188 Constant_Present => True,
5190 Object_Definition =>
5191 Make_Constrained_Array_Definition (Loc,
5192 Discrete_Subtype_Definitions => New_List (
5193 Make_Subtype_Indication (Loc,
5194 Subtype_Mark =>
5195 New_Occurrence_Of (Standard_Natural, Loc),
5196 Constraint =>
5197 Make_Range_Constraint (Loc,
5198 Range_Expression =>
5199 Make_Range (Loc,
5200 Low_Bound =>
5201 Make_Integer_Literal (Loc, 0),
5202 High_Bound =>
5203 Make_Integer_Literal (Loc, Num - 1))))),
5205 Component_Definition =>
5206 Make_Component_Definition (Loc,
5207 Aliased_Present => False,
5208 Subtype_Indication => New_Occurrence_Of (Typ, Loc))),
5210 Expression =>
5211 Make_Aggregate (Loc,
5212 Expressions => Lst)));
5214 Set_Enum_Pos_To_Rep (Typ, Arr);
5215 end if;
5217 -- Now we build the function that converts representation values to
5218 -- position values. This function has the form:
5220 -- function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
5221 -- begin
5222 -- case ityp!(A) is
5223 -- when enum-lit'Enum_Rep => return posval;
5224 -- when enum-lit'Enum_Rep => return posval;
5225 -- ...
5226 -- when others =>
5227 -- [raise Constraint_Error when F "invalid data"]
5228 -- return -1;
5229 -- end case;
5230 -- end;
5232 -- Note: the F parameter determines whether the others case (no valid
5233 -- representation) raises Constraint_Error or returns a unique value
5234 -- of minus one. The latter case is used, e.g. in 'Valid code.
5236 -- Note: the reason we use Enum_Rep values in the case here is to avoid
5237 -- the code generator making inappropriate assumptions about the range
5238 -- of the values in the case where the value is invalid. ityp is a
5239 -- signed or unsigned integer type of appropriate width.
5241 -- Note: if exceptions are not supported, then we suppress the raise
5242 -- and return -1 unconditionally (this is an erroneous program in any
5243 -- case and there is no obligation to raise Constraint_Error here). We
5244 -- also do this if pragma Restrictions (No_Exceptions) is active.
5246 -- Is this right??? What about No_Exception_Propagation???
5248 -- The underlying type is signed. Reset the Is_Unsigned_Type explicitly
5249 -- because it might have been inherited from the parent type.
5251 if Enumeration_Rep (First_Literal (Typ)) < 0 then
5252 Set_Is_Unsigned_Type (Typ, False);
5253 end if;
5255 Ityp := Integer_Type_For (Esize (Typ), Is_Unsigned_Type (Typ));
5257 -- The body of the function is a case statement. First collect case
5258 -- alternatives, or optimize the contiguous case.
5260 Lst := New_List;
5262 -- If representation is contiguous, Pos is computed by subtracting
5263 -- the representation of the first literal.
5265 if Is_Contiguous then
5266 Ent := First_Literal (Typ);
5268 if Enumeration_Rep (Ent) = Last_Repval then
5270 -- Another special case: for a single literal, Pos is zero
5272 Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
5274 else
5275 Pos_Expr :=
5276 Convert_To (Standard_Integer,
5277 Make_Op_Subtract (Loc,
5278 Left_Opnd =>
5279 Unchecked_Convert_To
5280 (Ityp, Make_Identifier (Loc, Name_uA)),
5281 Right_Opnd =>
5282 Make_Integer_Literal (Loc,
5283 Intval => Enumeration_Rep (First_Literal (Typ)))));
5284 end if;
5286 Append_To (Lst,
5287 Make_Case_Statement_Alternative (Loc,
5288 Discrete_Choices => New_List (
5289 Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
5290 Low_Bound =>
5291 Make_Integer_Literal (Loc,
5292 Intval => Enumeration_Rep (Ent)),
5293 High_Bound =>
5294 Make_Integer_Literal (Loc, Intval => Last_Repval))),
5296 Statements => New_List (
5297 Make_Simple_Return_Statement (Loc,
5298 Expression => Pos_Expr))));
5300 else
5301 Ent := First_Literal (Typ);
5302 while Present (Ent) loop
5303 Append_To (Lst,
5304 Make_Case_Statement_Alternative (Loc,
5305 Discrete_Choices => New_List (
5306 Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
5307 Intval => Enumeration_Rep (Ent))),
5309 Statements => New_List (
5310 Make_Simple_Return_Statement (Loc,
5311 Expression =>
5312 Make_Integer_Literal (Loc,
5313 Intval => Enumeration_Pos (Ent))))));
5315 Next_Literal (Ent);
5316 end loop;
5317 end if;
5319 -- In normal mode, add the others clause with the test.
5320 -- If Predicates_Ignored is True, validity checks do not apply to
5321 -- the subtype.
5323 if not No_Exception_Handlers_Set
5324 and then not Predicates_Ignored (Typ)
5325 then
5326 Append_To (Lst,
5327 Make_Case_Statement_Alternative (Loc,
5328 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
5329 Statements => New_List (
5330 Make_Raise_Constraint_Error (Loc,
5331 Condition => Make_Identifier (Loc, Name_uF),
5332 Reason => CE_Invalid_Data),
5333 Make_Simple_Return_Statement (Loc,
5334 Expression => Make_Integer_Literal (Loc, -1)))));
5336 -- If either of the restrictions No_Exceptions_Handlers/Propagation is
5337 -- active then return -1 (we cannot usefully raise Constraint_Error in
5338 -- this case). See description above for further details.
5340 else
5341 Append_To (Lst,
5342 Make_Case_Statement_Alternative (Loc,
5343 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
5344 Statements => New_List (
5345 Make_Simple_Return_Statement (Loc,
5346 Expression => Make_Integer_Literal (Loc, -1)))));
5347 end if;
5349 -- Now we can build the function body
5351 Fent :=
5352 Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
5354 Func :=
5355 Make_Subprogram_Body (Loc,
5356 Specification =>
5357 Make_Function_Specification (Loc,
5358 Defining_Unit_Name => Fent,
5359 Parameter_Specifications => New_List (
5360 Make_Parameter_Specification (Loc,
5361 Defining_Identifier =>
5362 Make_Defining_Identifier (Loc, Name_uA),
5363 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
5364 Make_Parameter_Specification (Loc,
5365 Defining_Identifier =>
5366 Make_Defining_Identifier (Loc, Name_uF),
5367 Parameter_Type =>
5368 New_Occurrence_Of (Standard_Boolean, Loc))),
5370 Result_Definition => New_Occurrence_Of (Standard_Integer, Loc)),
5372 Declarations => Empty_List,
5374 Handled_Statement_Sequence =>
5375 Make_Handled_Sequence_Of_Statements (Loc,
5376 Statements => New_List (
5377 Make_Case_Statement (Loc,
5378 Expression =>
5379 Unchecked_Convert_To
5380 (Ityp, Make_Identifier (Loc, Name_uA)),
5381 Alternatives => Lst))));
5383 Set_TSS (Typ, Fent);
5385 -- Set Pure flag (it will be reset if the current context is not Pure).
5386 -- We also pretend there was a pragma Pure_Function so that for purposes
5387 -- of optimization and constant-folding, we will consider the function
5388 -- Pure even if we are not in a Pure context).
5390 Set_Is_Pure (Fent);
5391 Set_Has_Pragma_Pure_Function (Fent);
5393 -- Unless we are in -gnatD mode, where we are debugging generated code,
5394 -- this is an internal entity for which we don't need debug info.
5396 if not Debug_Generated_Code then
5397 Set_Debug_Info_Off (Fent);
5398 end if;
5400 Set_Is_Inlined (Fent);
5402 exception
5403 when RE_Not_Available =>
5404 return;
5405 end Expand_Freeze_Enumeration_Type;
5407 -------------------------------
5408 -- Expand_Freeze_Record_Type --
5409 -------------------------------
5411 procedure Expand_Freeze_Record_Type (N : Node_Id) is
5413 procedure Build_Class_Condition_Subprograms (Typ : Entity_Id);
5414 -- Create internal subprograms of Typ primitives that have class-wide
5415 -- preconditions or postconditions; they are invoked by the caller to
5416 -- evaluate the conditions.
5418 procedure Build_Variant_Record_Equality (Typ : Entity_Id);
5419 -- Create An Equality function for the untagged variant record Typ and
5420 -- attach it to the TSS list.
5422 procedure Register_Dispatch_Table_Wrappers (Typ : Entity_Id);
5423 -- Register dispatch-table wrappers in the dispatch table of Typ
5425 ---------------------------------------
5426 -- Build_Class_Condition_Subprograms --
5427 ---------------------------------------
5429 procedure Build_Class_Condition_Subprograms (Typ : Entity_Id) is
5430 Prim_List : constant Elist_Id := Primitive_Operations (Typ);
5431 Prim_Elmt : Elmt_Id := First_Elmt (Prim_List);
5432 Prim : Entity_Id;
5434 begin
5435 while Present (Prim_Elmt) loop
5436 Prim := Node (Prim_Elmt);
5438 -- Primitive with class-wide preconditions
5440 if Comes_From_Source (Prim)
5441 and then Has_Significant_Contract (Prim)
5442 and then
5443 (Present (Class_Preconditions (Prim))
5444 or else Present (Ignored_Class_Preconditions (Prim)))
5445 then
5446 if Expander_Active then
5447 Make_Class_Precondition_Subps (Prim);
5448 end if;
5450 -- Wrapper of a primitive that has or inherits class-wide
5451 -- preconditions.
5453 elsif Is_Primitive_Wrapper (Prim)
5454 and then
5455 (Present (Nearest_Class_Condition_Subprogram
5456 (Spec_Id => Prim,
5457 Kind => Class_Precondition))
5458 or else
5459 Present (Nearest_Class_Condition_Subprogram
5460 (Spec_Id => Prim,
5461 Kind => Ignored_Class_Precondition)))
5462 then
5463 if Expander_Active then
5464 Make_Class_Precondition_Subps (Prim);
5465 end if;
5466 end if;
5468 Next_Elmt (Prim_Elmt);
5469 end loop;
5470 end Build_Class_Condition_Subprograms;
5472 -----------------------------------
5473 -- Build_Variant_Record_Equality --
5474 -----------------------------------
5476 procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
5477 Loc : constant Source_Ptr := Sloc (Typ);
5478 F : constant Entity_Id :=
5479 Make_Defining_Identifier (Loc,
5480 Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
5481 begin
5482 -- For a variant record with restriction No_Implicit_Conditionals
5483 -- in effect we skip building the procedure. This is safe because
5484 -- if we can see the restriction, so can any caller, and calls to
5485 -- equality test routines are not allowed for variant records if
5486 -- this restriction is active.
5488 if Restriction_Active (No_Implicit_Conditionals) then
5489 return;
5490 end if;
5492 -- Derived Unchecked_Union types no longer inherit the equality
5493 -- function of their parent.
5495 if Is_Derived_Type (Typ)
5496 and then not Is_Unchecked_Union (Typ)
5497 and then not Has_New_Non_Standard_Rep (Typ)
5498 then
5499 declare
5500 Parent_Eq : constant Entity_Id :=
5501 TSS (Root_Type (Typ), TSS_Composite_Equality);
5502 begin
5503 if Present (Parent_Eq) then
5504 Copy_TSS (Parent_Eq, Typ);
5505 return;
5506 end if;
5507 end;
5508 end if;
5510 Discard_Node (
5511 Build_Variant_Record_Equality
5512 (Typ => Typ,
5513 Body_Id => F,
5514 Param_Specs => New_List (
5515 Make_Parameter_Specification (Loc,
5516 Defining_Identifier =>
5517 Make_Defining_Identifier (Loc, Name_X),
5518 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
5520 Make_Parameter_Specification (Loc,
5521 Defining_Identifier =>
5522 Make_Defining_Identifier (Loc, Name_Y),
5523 Parameter_Type => New_Occurrence_Of (Typ, Loc)))));
5525 Set_TSS (Typ, F);
5526 Set_Is_Pure (F);
5528 if not Debug_Generated_Code then
5529 Set_Debug_Info_Off (F);
5530 end if;
5531 end Build_Variant_Record_Equality;
5533 --------------------------------------
5534 -- Register_Dispatch_Table_Wrappers --
5535 --------------------------------------
5537 procedure Register_Dispatch_Table_Wrappers (Typ : Entity_Id) is
5538 Elmt : Elmt_Id := First_Elmt (Primitive_Operations (Typ));
5539 Subp : Entity_Id;
5541 begin
5542 while Present (Elmt) loop
5543 Subp := Node (Elmt);
5545 if Is_Dispatch_Table_Wrapper (Subp) then
5546 Append_Freeze_Actions (Typ,
5547 Register_Primitive (Sloc (Subp), Subp));
5548 end if;
5550 Next_Elmt (Elmt);
5551 end loop;
5552 end Register_Dispatch_Table_Wrappers;
5554 -- Local variables
5556 Typ : constant Node_Id := Entity (N);
5557 Typ_Decl : constant Node_Id := Parent (Typ);
5559 Comp : Entity_Id;
5560 Comp_Typ : Entity_Id;
5561 Predef_List : List_Id;
5563 Wrapper_Decl_List : List_Id;
5564 Wrapper_Body_List : List_Id := No_List;
5566 Renamed_Eq : Node_Id := Empty;
5567 -- Defining unit name for the predefined equality function in the case
5568 -- where the type has a primitive operation that is a renaming of
5569 -- predefined equality (but only if there is also an overriding
5570 -- user-defined equality function). Used to pass this entity from
5571 -- Make_Predefined_Primitive_Specs to Predefined_Primitive_Bodies.
5573 -- Start of processing for Expand_Freeze_Record_Type
5575 begin
5576 -- Build discriminant checking functions if not a derived type (for
5577 -- derived types that are not tagged types, always use the discriminant
5578 -- checking functions of the parent type). However, for untagged types
5579 -- the derivation may have taken place before the parent was frozen, so
5580 -- we copy explicitly the discriminant checking functions from the
5581 -- parent into the components of the derived type.
5583 Build_Or_Copy_Discr_Checking_Funcs (Typ_Decl);
5585 if Is_Derived_Type (Typ)
5586 and then Is_Limited_Type (Typ)
5587 and then Is_Tagged_Type (Typ)
5588 then
5589 Check_Stream_Attributes (Typ);
5590 end if;
5592 -- Update task, protected, and controlled component flags, because some
5593 -- of the component types may have been private at the point of the
5594 -- record declaration. Detect anonymous access-to-controlled components.
5596 Comp := First_Component (Typ);
5597 while Present (Comp) loop
5598 Comp_Typ := Etype (Comp);
5600 Propagate_Concurrent_Flags (Typ, Comp_Typ);
5602 -- Do not set Has_Controlled_Component on a class-wide equivalent
5603 -- type. See Make_CW_Equivalent_Type.
5605 if not Is_Class_Wide_Equivalent_Type (Typ)
5606 and then
5607 (Has_Controlled_Component (Comp_Typ)
5608 or else (Chars (Comp) /= Name_uParent
5609 and then Is_Controlled (Comp_Typ)))
5610 then
5611 Set_Has_Controlled_Component (Typ);
5612 end if;
5614 Next_Component (Comp);
5615 end loop;
5617 -- Handle constructors of untagged CPP_Class types
5619 if not Is_Tagged_Type (Typ) and then Is_CPP_Class (Typ) then
5620 Set_CPP_Constructors (Typ);
5621 end if;
5623 -- Creation of the Dispatch Table. Note that a Dispatch Table is built
5624 -- for regular tagged types as well as for Ada types deriving from a C++
5625 -- Class, but not for tagged types directly corresponding to C++ classes
5626 -- In the later case we assume that it is created in the C++ side and we
5627 -- just use it.
5629 if Is_Tagged_Type (Typ) then
5631 -- Add the _Tag component
5633 if Underlying_Type (Etype (Typ)) = Typ then
5634 Expand_Tagged_Root (Typ);
5635 end if;
5637 if Is_CPP_Class (Typ) then
5638 Set_All_DT_Position (Typ);
5640 -- Create the tag entities with a minimum decoration
5642 if Tagged_Type_Expansion then
5643 Append_Freeze_Actions (Typ, Make_Tags (Typ));
5644 end if;
5646 Set_CPP_Constructors (Typ);
5648 else
5649 if not Building_Static_DT (Typ) then
5651 -- Usually inherited primitives are not delayed but the first
5652 -- Ada extension of a CPP_Class is an exception since the
5653 -- address of the inherited subprogram has to be inserted in
5654 -- the new Ada Dispatch Table and this is a freezing action.
5656 -- Similarly, if this is an inherited operation whose parent is
5657 -- not frozen yet, it is not in the DT of the parent, and we
5658 -- generate an explicit freeze node for the inherited operation
5659 -- so it is properly inserted in the DT of the current type.
5661 declare
5662 Elmt : Elmt_Id;
5663 Subp : Entity_Id;
5665 begin
5666 Elmt := First_Elmt (Primitive_Operations (Typ));
5667 while Present (Elmt) loop
5668 Subp := Node (Elmt);
5670 if Present (Alias (Subp)) then
5671 if Is_CPP_Class (Etype (Typ)) then
5672 Set_Has_Delayed_Freeze (Subp);
5674 elsif Has_Delayed_Freeze (Alias (Subp))
5675 and then not Is_Frozen (Alias (Subp))
5676 then
5677 Set_Is_Frozen (Subp, False);
5678 Set_Has_Delayed_Freeze (Subp);
5679 end if;
5680 end if;
5682 Next_Elmt (Elmt);
5683 end loop;
5684 end;
5685 end if;
5687 -- Unfreeze momentarily the type to add the predefined primitives
5688 -- operations. The reason we unfreeze is so that these predefined
5689 -- operations will indeed end up as primitive operations (which
5690 -- must be before the freeze point).
5692 Set_Is_Frozen (Typ, False);
5694 -- Do not add the spec of predefined primitives in case of
5695 -- CPP tagged type derivations that have convention CPP.
5697 if Is_CPP_Class (Root_Type (Typ))
5698 and then Convention (Typ) = Convention_CPP
5699 then
5700 null;
5702 -- Do not add the spec of the predefined primitives if we are
5703 -- compiling under restriction No_Dispatching_Calls.
5705 elsif not Restriction_Active (No_Dispatching_Calls) then
5706 Make_Predefined_Primitive_Specs (Typ, Predef_List, Renamed_Eq);
5707 Insert_List_Before_And_Analyze (N, Predef_List);
5708 end if;
5710 -- Ada 2005 (AI-391): For a nonabstract null extension, create
5711 -- wrapper functions for each nonoverridden inherited function
5712 -- with a controlling result of the type. The wrapper for such
5713 -- a function returns an extension aggregate that invokes the
5714 -- parent function.
5716 if Ada_Version >= Ada_2005
5717 and then not Is_Abstract_Type (Typ)
5718 and then Is_Null_Extension (Typ)
5719 then
5720 Make_Controlling_Function_Wrappers
5721 (Typ, Wrapper_Decl_List, Wrapper_Body_List);
5722 Insert_List_Before_And_Analyze (N, Wrapper_Decl_List);
5723 end if;
5725 -- Ada 2005 (AI-251): For a nonabstract type extension, build
5726 -- null procedure declarations for each set of homographic null
5727 -- procedures that are inherited from interface types but not
5728 -- overridden. This is done to ensure that the dispatch table
5729 -- entry associated with such null primitives are properly filled.
5731 if Ada_Version >= Ada_2005
5732 and then Etype (Typ) /= Typ
5733 and then not Is_Abstract_Type (Typ)
5734 and then Has_Interfaces (Typ)
5735 then
5736 Insert_Actions (N, Make_Null_Procedure_Specs (Typ));
5737 end if;
5739 Set_Is_Frozen (Typ);
5741 if not Is_Derived_Type (Typ)
5742 or else Is_Tagged_Type (Etype (Typ))
5743 then
5744 Set_All_DT_Position (Typ);
5746 -- If this is a type derived from an untagged private type whose
5747 -- full view is tagged, the type is marked tagged for layout
5748 -- reasons, but it has no dispatch table.
5750 elsif Is_Derived_Type (Typ)
5751 and then Is_Private_Type (Etype (Typ))
5752 and then not Is_Tagged_Type (Etype (Typ))
5753 then
5754 return;
5755 end if;
5757 -- Create and decorate the tags. Suppress their creation when
5758 -- not Tagged_Type_Expansion because the dispatching mechanism is
5759 -- handled internally by the virtual target.
5761 if Tagged_Type_Expansion then
5762 Append_Freeze_Actions (Typ, Make_Tags (Typ));
5764 -- Generate dispatch table of locally defined tagged type.
5765 -- Dispatch tables of library level tagged types are built
5766 -- later (see Build_Static_Dispatch_Tables).
5768 if not Building_Static_DT (Typ) then
5769 Append_Freeze_Actions (Typ, Make_DT (Typ));
5771 -- Register dispatch table wrappers in the dispatch table.
5772 -- It could not be done when these wrappers were built
5773 -- because, at that stage, the dispatch table was not
5774 -- available.
5776 Register_Dispatch_Table_Wrappers (Typ);
5777 end if;
5778 end if;
5780 -- If the type has unknown discriminants, propagate dispatching
5781 -- information to its underlying record view, which does not get
5782 -- its own dispatch table.
5784 if Is_Derived_Type (Typ)
5785 and then Has_Unknown_Discriminants (Typ)
5786 and then Present (Underlying_Record_View (Typ))
5787 then
5788 declare
5789 Rep : constant Entity_Id := Underlying_Record_View (Typ);
5790 begin
5791 Set_Access_Disp_Table
5792 (Rep, Access_Disp_Table (Typ));
5793 Set_Dispatch_Table_Wrappers
5794 (Rep, Dispatch_Table_Wrappers (Typ));
5795 Set_Direct_Primitive_Operations
5796 (Rep, Direct_Primitive_Operations (Typ));
5797 end;
5798 end if;
5800 -- Make sure that the primitives Initialize, Adjust and Finalize
5801 -- are Frozen before other TSS subprograms. We don't want them
5802 -- Frozen inside.
5804 if Is_Controlled (Typ) then
5805 if not Is_Limited_Type (Typ) then
5806 Append_Freeze_Actions (Typ,
5807 Freeze_Entity (Find_Prim_Op (Typ, Name_Adjust), Typ));
5808 end if;
5810 Append_Freeze_Actions (Typ,
5811 Freeze_Entity (Find_Prim_Op (Typ, Name_Initialize), Typ));
5813 Append_Freeze_Actions (Typ,
5814 Freeze_Entity (Find_Prim_Op (Typ, Name_Finalize), Typ));
5815 end if;
5817 -- Freeze rest of primitive operations. There is no need to handle
5818 -- the predefined primitives if we are compiling under restriction
5819 -- No_Dispatching_Calls.
5821 if not Restriction_Active (No_Dispatching_Calls) then
5822 Append_Freeze_Actions (Typ, Predefined_Primitive_Freeze (Typ));
5823 end if;
5824 end if;
5826 -- In the untagged case, ever since Ada 83 an equality function must
5827 -- be provided for variant records that are not unchecked unions.
5828 -- In Ada 2012 the equality function composes, and thus must be built
5829 -- explicitly just as for tagged records.
5831 elsif Has_Discriminants (Typ)
5832 and then not Is_Limited_Type (Typ)
5833 then
5834 declare
5835 Comps : constant Node_Id :=
5836 Component_List (Type_Definition (Typ_Decl));
5837 begin
5838 if Present (Comps)
5839 and then Present (Variant_Part (Comps))
5840 then
5841 Build_Variant_Record_Equality (Typ);
5842 end if;
5843 end;
5845 -- Otherwise create primitive equality operation (AI05-0123)
5847 -- This is done unconditionally to ensure that tools can be linked
5848 -- properly with user programs compiled with older language versions.
5849 -- In addition, this is needed because "=" composes for bounded strings
5850 -- in all language versions (see Exp_Ch4.Expand_Composite_Equality).
5852 elsif Comes_From_Source (Typ)
5853 and then Convention (Typ) = Convention_Ada
5854 and then not Is_Limited_Type (Typ)
5855 then
5856 Build_Untagged_Equality (Typ);
5857 end if;
5859 -- Before building the record initialization procedure, if we are
5860 -- dealing with a concurrent record value type, then we must go through
5861 -- the discriminants, exchanging discriminals between the concurrent
5862 -- type and the concurrent record value type. See the section "Handling
5863 -- of Discriminants" in the Einfo spec for details.
5865 if Is_Concurrent_Record_Type (Typ)
5866 and then Has_Discriminants (Typ)
5867 then
5868 declare
5869 Ctyp : constant Entity_Id :=
5870 Corresponding_Concurrent_Type (Typ);
5871 Conc_Discr : Entity_Id;
5872 Rec_Discr : Entity_Id;
5873 Temp : Entity_Id;
5875 begin
5876 Conc_Discr := First_Discriminant (Ctyp);
5877 Rec_Discr := First_Discriminant (Typ);
5878 while Present (Conc_Discr) loop
5879 Temp := Discriminal (Conc_Discr);
5880 Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
5881 Set_Discriminal (Rec_Discr, Temp);
5883 Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
5884 Set_Discriminal_Link (Discriminal (Rec_Discr), Rec_Discr);
5886 Next_Discriminant (Conc_Discr);
5887 Next_Discriminant (Rec_Discr);
5888 end loop;
5889 end;
5890 end if;
5892 if Has_Controlled_Component (Typ) then
5893 Build_Controlling_Procs (Typ);
5894 end if;
5896 Adjust_Discriminants (Typ);
5898 -- Do not need init for interfaces on virtual targets since they're
5899 -- abstract.
5901 if Tagged_Type_Expansion or else not Is_Interface (Typ) then
5902 Build_Record_Init_Proc (Typ_Decl, Typ);
5903 end if;
5905 -- For tagged type that are not interfaces, build bodies of primitive
5906 -- operations. Note: do this after building the record initialization
5907 -- procedure, since the primitive operations may need the initialization
5908 -- routine. There is no need to add predefined primitives of interfaces
5909 -- because all their predefined primitives are abstract.
5911 if Is_Tagged_Type (Typ) and then not Is_Interface (Typ) then
5913 -- Do not add the body of predefined primitives in case of CPP tagged
5914 -- type derivations that have convention CPP.
5916 if Is_CPP_Class (Root_Type (Typ))
5917 and then Convention (Typ) = Convention_CPP
5918 then
5919 null;
5921 -- Do not add the body of the predefined primitives if we are
5922 -- compiling under restriction No_Dispatching_Calls or if we are
5923 -- compiling a CPP tagged type.
5925 elsif not Restriction_Active (No_Dispatching_Calls) then
5927 -- Create the body of TSS primitive Finalize_Address. This must
5928 -- be done before the bodies of all predefined primitives are
5929 -- created. If Typ is limited, Stream_Input and Stream_Read may
5930 -- produce build-in-place allocations and for those the expander
5931 -- needs Finalize_Address.
5933 Make_Finalize_Address_Body (Typ);
5934 Predef_List := Predefined_Primitive_Bodies (Typ, Renamed_Eq);
5935 Append_Freeze_Actions (Typ, Predef_List);
5936 end if;
5938 -- Ada 2005 (AI-391): If any wrappers were created for nonoverridden
5939 -- inherited functions, then add their bodies to the freeze actions.
5941 Append_Freeze_Actions (Typ, Wrapper_Body_List);
5943 -- Create extra formals for the primitive operations of the type.
5944 -- This must be done before analyzing the body of the initialization
5945 -- procedure, because a self-referential type might call one of these
5946 -- primitives in the body of the init_proc itself.
5948 declare
5949 Elmt : Elmt_Id;
5950 Subp : Entity_Id;
5952 begin
5953 Elmt := First_Elmt (Primitive_Operations (Typ));
5954 while Present (Elmt) loop
5955 Subp := Node (Elmt);
5956 if not Has_Foreign_Convention (Subp)
5957 and then not Is_Predefined_Dispatching_Operation (Subp)
5958 then
5959 Create_Extra_Formals (Subp);
5960 end if;
5962 Next_Elmt (Elmt);
5963 end loop;
5964 end;
5965 end if;
5967 -- Build internal subprograms of primitives with class-wide
5968 -- pre/postconditions.
5970 if Is_Tagged_Type (Typ) then
5971 Build_Class_Condition_Subprograms (Typ);
5972 end if;
5973 end Expand_Freeze_Record_Type;
5975 ------------------------------------
5976 -- Expand_N_Full_Type_Declaration --
5977 ------------------------------------
5979 procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
5980 procedure Build_Master (Ptr_Typ : Entity_Id);
5981 -- Create the master associated with Ptr_Typ
5983 ------------------
5984 -- Build_Master --
5985 ------------------
5987 procedure Build_Master (Ptr_Typ : Entity_Id) is
5988 Desig_Typ : Entity_Id := Designated_Type (Ptr_Typ);
5990 begin
5991 -- If the designated type is an incomplete view coming from a
5992 -- limited-with'ed package, we need to use the nonlimited view in
5993 -- case it has tasks.
5995 if Is_Incomplete_Type (Desig_Typ)
5996 and then Present (Non_Limited_View (Desig_Typ))
5997 then
5998 Desig_Typ := Non_Limited_View (Desig_Typ);
5999 end if;
6001 -- Anonymous access types are created for the components of the
6002 -- record parameter for an entry declaration. No master is created
6003 -- for such a type.
6005 if Has_Task (Desig_Typ) then
6006 Build_Master_Entity (Ptr_Typ);
6007 Build_Master_Renaming (Ptr_Typ);
6009 -- Create a class-wide master because a Master_Id must be generated
6010 -- for access-to-limited-class-wide types whose root may be extended
6011 -- with task components.
6013 -- Note: This code covers access-to-limited-interfaces because they
6014 -- can be used to reference tasks implementing them.
6016 -- Suppress the master creation for access types created for entry
6017 -- formal parameters (parameter block component types). Seems like
6018 -- suppression should be more general for compiler-generated types,
6019 -- but testing Comes_From_Source may be too general in this case
6020 -- (affects some test output)???
6022 elsif not Is_Param_Block_Component_Type (Ptr_Typ)
6023 and then Is_Limited_Class_Wide_Type (Desig_Typ)
6024 then
6025 Build_Class_Wide_Master (Ptr_Typ);
6026 end if;
6027 end Build_Master;
6029 -- Local declarations
6031 Def_Id : constant Entity_Id := Defining_Identifier (N);
6032 B_Id : constant Entity_Id := Base_Type (Def_Id);
6033 FN : Node_Id;
6034 Par_Id : Entity_Id;
6036 -- Start of processing for Expand_N_Full_Type_Declaration
6038 begin
6039 if Is_Access_Type (Def_Id) then
6040 Build_Master (Def_Id);
6042 if Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
6043 Expand_Access_Protected_Subprogram_Type (N);
6044 end if;
6046 -- Array of anonymous access-to-task pointers
6048 elsif Ada_Version >= Ada_2005
6049 and then Is_Array_Type (Def_Id)
6050 and then Is_Access_Type (Component_Type (Def_Id))
6051 and then Ekind (Component_Type (Def_Id)) = E_Anonymous_Access_Type
6052 then
6053 Build_Master (Component_Type (Def_Id));
6055 elsif Has_Task (Def_Id) then
6056 Expand_Previous_Access_Type (Def_Id);
6058 -- Check the components of a record type or array of records for
6059 -- anonymous access-to-task pointers.
6061 elsif Ada_Version >= Ada_2005
6062 and then (Is_Record_Type (Def_Id)
6063 or else
6064 (Is_Array_Type (Def_Id)
6065 and then Is_Record_Type (Component_Type (Def_Id))))
6066 then
6067 declare
6068 Comp : Entity_Id;
6069 First : Boolean;
6070 M_Id : Entity_Id := Empty;
6071 Typ : Entity_Id;
6073 begin
6074 if Is_Array_Type (Def_Id) then
6075 Comp := First_Entity (Component_Type (Def_Id));
6076 else
6077 Comp := First_Entity (Def_Id);
6078 end if;
6080 -- Examine all components looking for anonymous access-to-task
6081 -- types.
6083 First := True;
6084 while Present (Comp) loop
6085 Typ := Etype (Comp);
6087 if Ekind (Typ) = E_Anonymous_Access_Type
6088 and then Might_Have_Tasks
6089 (Available_View (Designated_Type (Typ)))
6090 and then No (Master_Id (Typ))
6091 then
6092 -- Ensure that the record or array type have a _master
6094 if First then
6095 Build_Master_Entity (Def_Id);
6096 Build_Master_Renaming (Typ);
6097 M_Id := Master_Id (Typ);
6099 First := False;
6101 -- Reuse the same master to service any additional types
6103 else
6104 pragma Assert (Present (M_Id));
6105 Set_Master_Id (Typ, M_Id);
6106 end if;
6107 end if;
6109 Next_Entity (Comp);
6110 end loop;
6111 end;
6112 end if;
6114 Par_Id := Etype (B_Id);
6116 -- The parent type is private then we need to inherit any TSS operations
6117 -- from the full view.
6119 if Is_Private_Type (Par_Id)
6120 and then Present (Full_View (Par_Id))
6121 then
6122 Par_Id := Base_Type (Full_View (Par_Id));
6123 end if;
6125 if Nkind (Type_Definition (N)) = N_Derived_Type_Definition
6126 and then not Is_Tagged_Type (Def_Id)
6127 and then Present (Freeze_Node (Par_Id))
6128 and then Present (TSS_Elist (Freeze_Node (Par_Id)))
6129 then
6130 Ensure_Freeze_Node (B_Id);
6131 FN := Freeze_Node (B_Id);
6133 if No (TSS_Elist (FN)) then
6134 Set_TSS_Elist (FN, New_Elmt_List);
6135 end if;
6137 declare
6138 T_E : constant Elist_Id := TSS_Elist (FN);
6139 Elmt : Elmt_Id;
6141 begin
6142 Elmt := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
6143 while Present (Elmt) loop
6144 if Chars (Node (Elmt)) /= Name_uInit then
6145 Append_Elmt (Node (Elmt), T_E);
6146 end if;
6148 Next_Elmt (Elmt);
6149 end loop;
6151 -- If the derived type itself is private with a full view, then
6152 -- associate the full view with the inherited TSS_Elist as well.
6154 if Is_Private_Type (B_Id)
6155 and then Present (Full_View (B_Id))
6156 then
6157 Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
6158 Set_TSS_Elist
6159 (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
6160 end if;
6161 end;
6162 end if;
6163 end Expand_N_Full_Type_Declaration;
6165 ---------------------------------
6166 -- Expand_N_Object_Declaration --
6167 ---------------------------------
6169 procedure Expand_N_Object_Declaration (N : Node_Id) is
6170 Loc : constant Source_Ptr := Sloc (N);
6171 Def_Id : constant Entity_Id := Defining_Identifier (N);
6172 Expr : constant Node_Id := Expression (N);
6173 Obj_Def : constant Node_Id := Object_Definition (N);
6174 Typ : constant Entity_Id := Etype (Def_Id);
6175 Base_Typ : constant Entity_Id := Base_Type (Typ);
6176 Expr_Q : Node_Id;
6178 function Build_Equivalent_Aggregate return Boolean;
6179 -- If the object has a constrained discriminated type and no initial
6180 -- value, it may be possible to build an equivalent aggregate instead,
6181 -- and prevent an actual call to the initialization procedure.
6183 procedure Count_Default_Sized_Task_Stacks
6184 (Typ : Entity_Id;
6185 Pri_Stacks : out Int;
6186 Sec_Stacks : out Int);
6187 -- Count the number of default-sized primary and secondary task stacks
6188 -- required for task objects contained within type Typ. If the number of
6189 -- task objects contained within the type is not known at compile time
6190 -- the procedure will return the stack counts of zero.
6192 procedure Default_Initialize_Object (After : Node_Id);
6193 -- Generate all default initialization actions for object Def_Id. Any
6194 -- new code is inserted after node After.
6196 function Rewrite_As_Renaming return Boolean;
6197 -- Indicate whether to rewrite a declaration with initialization into an
6198 -- object renaming declaration (see below).
6200 --------------------------------
6201 -- Build_Equivalent_Aggregate --
6202 --------------------------------
6204 function Build_Equivalent_Aggregate return Boolean is
6205 Aggr : Node_Id;
6206 Comp : Entity_Id;
6207 Discr : Elmt_Id;
6208 Full_Type : Entity_Id;
6210 begin
6211 Full_Type := Typ;
6213 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
6214 Full_Type := Full_View (Typ);
6215 end if;
6217 -- Only perform this transformation if Elaboration_Code is forbidden
6218 -- or undesirable, and if this is a global entity of a constrained
6219 -- record type.
6221 -- If Initialize_Scalars might be active this transformation cannot
6222 -- be performed either, because it will lead to different semantics
6223 -- or because elaboration code will in fact be created.
6225 if Ekind (Full_Type) /= E_Record_Subtype
6226 or else not Has_Discriminants (Full_Type)
6227 or else not Is_Constrained (Full_Type)
6228 or else Is_Controlled (Full_Type)
6229 or else Is_Limited_Type (Full_Type)
6230 or else not Restriction_Active (No_Initialize_Scalars)
6231 then
6232 return False;
6233 end if;
6235 if Ekind (Current_Scope) = E_Package
6236 and then
6237 (Restriction_Active (No_Elaboration_Code)
6238 or else Is_Preelaborated (Current_Scope))
6239 then
6240 -- Building a static aggregate is possible if the discriminants
6241 -- have static values and the other components have static
6242 -- defaults or none.
6244 Discr := First_Elmt (Discriminant_Constraint (Full_Type));
6245 while Present (Discr) loop
6246 if not Is_OK_Static_Expression (Node (Discr)) then
6247 return False;
6248 end if;
6250 Next_Elmt (Discr);
6251 end loop;
6253 -- Check that initialized components are OK, and that non-
6254 -- initialized components do not require a call to their own
6255 -- initialization procedure.
6257 Comp := First_Component (Full_Type);
6258 while Present (Comp) loop
6259 if Present (Expression (Parent (Comp)))
6260 and then
6261 not Is_OK_Static_Expression (Expression (Parent (Comp)))
6262 then
6263 return False;
6265 elsif Has_Non_Null_Base_Init_Proc (Etype (Comp)) then
6266 return False;
6268 end if;
6270 Next_Component (Comp);
6271 end loop;
6273 -- Everything is static, assemble the aggregate, discriminant
6274 -- values first.
6276 Aggr :=
6277 Make_Aggregate (Loc,
6278 Expressions => New_List,
6279 Component_Associations => New_List);
6281 Discr := First_Elmt (Discriminant_Constraint (Full_Type));
6282 while Present (Discr) loop
6283 Append_To (Expressions (Aggr), New_Copy (Node (Discr)));
6284 Next_Elmt (Discr);
6285 end loop;
6287 -- Now collect values of initialized components
6289 Comp := First_Component (Full_Type);
6290 while Present (Comp) loop
6291 if Present (Expression (Parent (Comp))) then
6292 Append_To (Component_Associations (Aggr),
6293 Make_Component_Association (Loc,
6294 Choices => New_List (New_Occurrence_Of (Comp, Loc)),
6295 Expression => New_Copy_Tree
6296 (Expression (Parent (Comp)))));
6297 end if;
6299 Next_Component (Comp);
6300 end loop;
6302 -- Finally, box-initialize remaining components
6304 Append_To (Component_Associations (Aggr),
6305 Make_Component_Association (Loc,
6306 Choices => New_List (Make_Others_Choice (Loc)),
6307 Expression => Empty));
6308 Set_Box_Present (Last (Component_Associations (Aggr)));
6309 Set_Expression (N, Aggr);
6311 if Typ /= Full_Type then
6312 Analyze_And_Resolve (Aggr, Full_View (Base_Type (Full_Type)));
6313 Rewrite (Aggr, Unchecked_Convert_To (Typ, Aggr));
6314 Analyze_And_Resolve (Aggr, Typ);
6315 else
6316 Analyze_And_Resolve (Aggr, Full_Type);
6317 end if;
6319 return True;
6321 else
6322 return False;
6323 end if;
6324 end Build_Equivalent_Aggregate;
6326 -------------------------------------
6327 -- Count_Default_Sized_Task_Stacks --
6328 -------------------------------------
6330 procedure Count_Default_Sized_Task_Stacks
6331 (Typ : Entity_Id;
6332 Pri_Stacks : out Int;
6333 Sec_Stacks : out Int)
6335 Component : Entity_Id;
6337 begin
6338 -- To calculate the number of default-sized task stacks required for
6339 -- an object of Typ, a depth-first recursive traversal of the AST
6340 -- from the Typ entity node is undertaken. Only type nodes containing
6341 -- task objects are visited.
6343 Pri_Stacks := 0;
6344 Sec_Stacks := 0;
6346 if not Has_Task (Typ) then
6347 return;
6348 end if;
6350 case Ekind (Typ) is
6351 when E_Task_Subtype
6352 | E_Task_Type
6354 -- A task type is found marking the bottom of the descent. If
6355 -- the type has no representation aspect for the corresponding
6356 -- stack then that stack is using the default size.
6358 if Present (Get_Rep_Item (Typ, Name_Storage_Size)) then
6359 Pri_Stacks := 0;
6360 else
6361 Pri_Stacks := 1;
6362 end if;
6364 if Present (Get_Rep_Item (Typ, Name_Secondary_Stack_Size)) then
6365 Sec_Stacks := 0;
6366 else
6367 Sec_Stacks := 1;
6368 end if;
6370 when E_Array_Subtype
6371 | E_Array_Type
6373 -- First find the number of default stacks contained within an
6374 -- array component.
6376 Count_Default_Sized_Task_Stacks
6377 (Component_Type (Typ),
6378 Pri_Stacks,
6379 Sec_Stacks);
6381 -- Then multiply the result by the size of the array
6383 declare
6384 Quantity : constant Int := Number_Of_Elements_In_Array (Typ);
6385 -- Number_Of_Elements_In_Array is non-trival, consequently
6386 -- its result is captured as an optimization.
6388 begin
6389 Pri_Stacks := Pri_Stacks * Quantity;
6390 Sec_Stacks := Sec_Stacks * Quantity;
6391 end;
6393 when E_Protected_Subtype
6394 | E_Protected_Type
6395 | E_Record_Subtype
6396 | E_Record_Type
6398 Component := First_Component_Or_Discriminant (Typ);
6400 -- Recursively descend each component of the composite type
6401 -- looking for tasks, but only if the component is marked as
6402 -- having a task.
6404 while Present (Component) loop
6405 if Has_Task (Etype (Component)) then
6406 declare
6407 P : Int;
6408 S : Int;
6410 begin
6411 Count_Default_Sized_Task_Stacks
6412 (Etype (Component), P, S);
6413 Pri_Stacks := Pri_Stacks + P;
6414 Sec_Stacks := Sec_Stacks + S;
6415 end;
6416 end if;
6418 Next_Component_Or_Discriminant (Component);
6419 end loop;
6421 when E_Limited_Private_Subtype
6422 | E_Limited_Private_Type
6423 | E_Record_Subtype_With_Private
6424 | E_Record_Type_With_Private
6426 -- Switch to the full view of the private type to continue
6427 -- search.
6429 Count_Default_Sized_Task_Stacks
6430 (Full_View (Typ), Pri_Stacks, Sec_Stacks);
6432 -- Other types should not contain tasks
6434 when others =>
6435 raise Program_Error;
6436 end case;
6437 end Count_Default_Sized_Task_Stacks;
6439 -------------------------------
6440 -- Default_Initialize_Object --
6441 -------------------------------
6443 procedure Default_Initialize_Object (After : Node_Id) is
6444 function New_Object_Reference return Node_Id;
6445 -- Return a new reference to Def_Id with attributes Assignment_OK and
6446 -- Must_Not_Freeze already set.
6448 function Simple_Initialization_OK
6449 (Init_Typ : Entity_Id) return Boolean;
6450 -- Determine whether object declaration N with entity Def_Id needs
6451 -- simple initialization, assuming that it is of type Init_Typ.
6453 --------------------------
6454 -- New_Object_Reference --
6455 --------------------------
6457 function New_Object_Reference return Node_Id is
6458 Obj_Ref : constant Node_Id := New_Occurrence_Of (Def_Id, Loc);
6460 begin
6461 -- The call to the type init proc or [Deep_]Finalize must not
6462 -- freeze the related object as the call is internally generated.
6463 -- This way legal rep clauses that apply to the object will not be
6464 -- flagged. Note that the initialization call may be removed if
6465 -- pragma Import is encountered or moved to the freeze actions of
6466 -- the object because of an address clause.
6468 Set_Assignment_OK (Obj_Ref);
6469 Set_Must_Not_Freeze (Obj_Ref);
6471 return Obj_Ref;
6472 end New_Object_Reference;
6474 ------------------------------
6475 -- Simple_Initialization_OK --
6476 ------------------------------
6478 function Simple_Initialization_OK
6479 (Init_Typ : Entity_Id) return Boolean
6481 begin
6482 -- Do not consider the object declaration if it comes with an
6483 -- initialization expression, or is internal in which case it
6484 -- will be assigned later.
6486 return
6487 not Is_Internal (Def_Id)
6488 and then not Has_Init_Expression (N)
6489 and then Needs_Simple_Initialization
6490 (Typ => Init_Typ,
6491 Consider_IS =>
6492 Initialize_Scalars
6493 and then No (Following_Address_Clause (N)));
6494 end Simple_Initialization_OK;
6496 -- Local variables
6498 Exceptions_OK : constant Boolean :=
6499 not Restriction_Active (No_Exception_Propagation);
6501 Aggr_Init : Node_Id;
6502 Comp_Init : List_Id := No_List;
6503 Fin_Block : Node_Id;
6504 Fin_Call : Node_Id;
6505 Init_Stmts : List_Id := No_List;
6506 Obj_Init : Node_Id := Empty;
6507 Obj_Ref : Node_Id;
6509 -- Start of processing for Default_Initialize_Object
6511 begin
6512 -- Default initialization is suppressed for objects that are already
6513 -- known to be imported (i.e. whose declaration specifies the Import
6514 -- aspect). Note that for objects with a pragma Import, we generate
6515 -- initialization here, and then remove it downstream when processing
6516 -- the pragma. It is also suppressed for variables for which a pragma
6517 -- Suppress_Initialization has been explicitly given
6519 if Is_Imported (Def_Id) or else Suppress_Initialization (Def_Id) then
6520 return;
6522 -- Nothing to do if the object being initialized is of a task type
6523 -- and restriction No_Tasking is in effect, because this is a direct
6524 -- violation of the restriction.
6526 elsif Is_Task_Type (Base_Typ)
6527 and then Restriction_Active (No_Tasking)
6528 then
6529 return;
6530 end if;
6532 -- The expansion performed by this routine is as follows:
6534 -- begin
6535 -- Abort_Defer;
6536 -- Type_Init_Proc (Obj);
6538 -- begin
6539 -- [Deep_]Initialize (Obj);
6541 -- exception
6542 -- when others =>
6543 -- [Deep_]Finalize (Obj, Self => False);
6544 -- raise;
6545 -- end;
6546 -- at end
6547 -- Abort_Undefer_Direct;
6548 -- end;
6550 -- Initialize the components of the object
6552 if Has_Non_Null_Base_Init_Proc (Typ)
6553 and then not No_Initialization (N)
6554 and then not Initialization_Suppressed (Typ)
6555 then
6556 -- Do not initialize the components if No_Default_Initialization
6557 -- applies as the actual restriction check will occur later when
6558 -- the object is frozen as it is not known yet whether the object
6559 -- is imported or not.
6561 if not Restriction_Active (No_Default_Initialization) then
6563 -- If the values of the components are compile-time known, use
6564 -- their prebuilt aggregate form directly.
6566 Aggr_Init := Static_Initialization (Base_Init_Proc (Typ));
6568 if Present (Aggr_Init) then
6569 Set_Expression (N,
6570 New_Copy_Tree (Aggr_Init, New_Scope => Current_Scope));
6572 -- If type has discriminants, try to build an equivalent
6573 -- aggregate using discriminant values from the declaration.
6574 -- This is a useful optimization, in particular if restriction
6575 -- No_Elaboration_Code is active.
6577 elsif Build_Equivalent_Aggregate then
6578 null;
6580 -- Optimize the default initialization of an array object when
6581 -- pragma Initialize_Scalars or Normalize_Scalars is in effect.
6582 -- Construct an in-place initialization aggregate which may be
6583 -- convert into a fast memset by the backend.
6585 elsif Init_Or_Norm_Scalars
6586 and then Is_Array_Type (Typ)
6588 -- The array must lack atomic components because they are
6589 -- treated as non-static, and as a result the backend will
6590 -- not initialize the memory in one go.
6592 and then not Has_Atomic_Components (Typ)
6594 -- The array must not be packed because the invalid values
6595 -- in System.Scalar_Values are multiples of Storage_Unit.
6597 and then not Is_Packed (Typ)
6599 -- The array must have static non-empty ranges, otherwise
6600 -- the backend cannot initialize the memory in one go.
6602 and then Has_Static_Non_Empty_Array_Bounds (Typ)
6604 -- The optimization is only relevant for arrays of scalar
6605 -- types.
6607 and then Is_Scalar_Type (Component_Type (Typ))
6609 -- Similar to regular array initialization using a type
6610 -- init proc, predicate checks are not performed because the
6611 -- initialization values are intentionally invalid, and may
6612 -- violate the predicate.
6614 and then not Has_Predicates (Component_Type (Typ))
6616 -- The component type must have a single initialization value
6618 and then Simple_Initialization_OK (Component_Type (Typ))
6619 then
6620 Set_No_Initialization (N, False);
6621 Set_Expression (N,
6622 Get_Simple_Init_Val
6623 (Typ => Typ,
6624 N => Obj_Def,
6625 Size => (if Known_Esize (Def_Id) then Esize (Def_Id)
6626 else Uint_0)));
6628 Analyze_And_Resolve
6629 (Expression (N), Typ, Suppress => All_Checks);
6631 -- Otherwise invoke the type init proc, generate:
6632 -- Type_Init_Proc (Obj);
6634 else
6635 Obj_Ref := New_Object_Reference;
6637 if Comes_From_Source (Def_Id) then
6638 Initialization_Warning (Obj_Ref);
6639 end if;
6641 Comp_Init := Build_Initialization_Call (Loc, Obj_Ref, Typ);
6642 end if;
6643 end if;
6645 -- Provide a default value if the object needs simple initialization
6647 elsif Simple_Initialization_OK (Typ) then
6648 Set_No_Initialization (N, False);
6649 Set_Expression (N,
6650 Get_Simple_Init_Val
6651 (Typ => Typ,
6652 N => Obj_Def,
6653 Size =>
6654 (if Known_Esize (Def_Id) then Esize (Def_Id) else Uint_0)));
6656 Analyze_And_Resolve (Expression (N), Typ);
6657 end if;
6659 -- Initialize the object, generate:
6660 -- [Deep_]Initialize (Obj);
6662 if Needs_Finalization (Typ) and then not No_Initialization (N) then
6663 Obj_Init :=
6664 Make_Init_Call
6665 (Obj_Ref => New_Object_Reference,
6666 Typ => Typ);
6667 end if;
6669 -- Build a special finalization block when both the object and its
6670 -- controlled components are to be initialized. The block finalizes
6671 -- the components if the object initialization fails. Generate:
6673 -- begin
6674 -- <Obj_Init>
6676 -- exception
6677 -- when others =>
6678 -- <Fin_Call>
6679 -- raise;
6680 -- end;
6682 if Has_Controlled_Component (Typ)
6683 and then Present (Comp_Init)
6684 and then Present (Obj_Init)
6685 and then Exceptions_OK
6686 then
6687 Init_Stmts := Comp_Init;
6689 Fin_Call :=
6690 Make_Final_Call
6691 (Obj_Ref => New_Object_Reference,
6692 Typ => Typ,
6693 Skip_Self => True);
6695 if Present (Fin_Call) then
6697 -- Do not emit warnings related to the elaboration order when a
6698 -- controlled object is declared before the body of Finalize is
6699 -- seen.
6701 if Legacy_Elaboration_Checks then
6702 Set_No_Elaboration_Check (Fin_Call);
6703 end if;
6705 Fin_Block :=
6706 Make_Block_Statement (Loc,
6707 Declarations => No_List,
6709 Handled_Statement_Sequence =>
6710 Make_Handled_Sequence_Of_Statements (Loc,
6711 Statements => New_List (Obj_Init),
6713 Exception_Handlers => New_List (
6714 Make_Exception_Handler (Loc,
6715 Exception_Choices => New_List (
6716 Make_Others_Choice (Loc)),
6718 Statements => New_List (
6719 Fin_Call,
6720 Make_Raise_Statement (Loc))))));
6722 -- Signal the ABE mechanism that the block carries out
6723 -- initialization actions.
6725 Set_Is_Initialization_Block (Fin_Block);
6727 Append_To (Init_Stmts, Fin_Block);
6728 end if;
6730 -- Otherwise finalization is not required, the initialization calls
6731 -- are passed to the abort block building circuitry, generate:
6733 -- Type_Init_Proc (Obj);
6734 -- [Deep_]Initialize (Obj);
6736 else
6737 if Present (Comp_Init) then
6738 Init_Stmts := Comp_Init;
6739 end if;
6741 if Present (Obj_Init) then
6742 if No (Init_Stmts) then
6743 Init_Stmts := New_List;
6744 end if;
6746 Append_To (Init_Stmts, Obj_Init);
6747 end if;
6748 end if;
6750 -- Build an abort block to protect the initialization calls
6752 if Abort_Allowed
6753 and then Present (Comp_Init)
6754 and then Present (Obj_Init)
6755 then
6756 -- Generate:
6757 -- Abort_Defer;
6759 Prepend_To (Init_Stmts, Build_Runtime_Call (Loc, RE_Abort_Defer));
6761 -- When exceptions are propagated, abort deferral must take place
6762 -- in the presence of initialization or finalization exceptions.
6763 -- Generate:
6765 -- begin
6766 -- Abort_Defer;
6767 -- <Init_Stmts>
6768 -- at end
6769 -- Abort_Undefer_Direct;
6770 -- end;
6772 if Exceptions_OK then
6773 Init_Stmts := New_List (
6774 Build_Abort_Undefer_Block (Loc,
6775 Stmts => Init_Stmts,
6776 Context => N));
6778 -- Otherwise exceptions are not propagated. Generate:
6780 -- Abort_Defer;
6781 -- <Init_Stmts>
6782 -- Abort_Undefer;
6784 else
6785 Append_To (Init_Stmts,
6786 Build_Runtime_Call (Loc, RE_Abort_Undefer));
6787 end if;
6788 end if;
6790 -- Insert the whole initialization sequence into the tree. If the
6791 -- object has a delayed freeze, as will be the case when it has
6792 -- aspect specifications, the initialization sequence is part of
6793 -- the freeze actions.
6795 if Present (Init_Stmts) then
6796 if Has_Delayed_Freeze (Def_Id) then
6797 Append_Freeze_Actions (Def_Id, Init_Stmts);
6798 else
6799 Insert_Actions_After (After, Init_Stmts);
6800 end if;
6801 end if;
6802 end Default_Initialize_Object;
6804 -------------------------
6805 -- Rewrite_As_Renaming --
6806 -------------------------
6808 function Rewrite_As_Renaming return Boolean is
6809 Result : constant Boolean :=
6811 -- If the object declaration appears in the form
6813 -- Obj : Ctrl_Typ := Func (...);
6815 -- where Ctrl_Typ is controlled but not immutably limited type, then
6816 -- the expansion of the function call should use a dereference of the
6817 -- result to reference the value on the secondary stack.
6819 -- Obj : Ctrl_Typ renames Func (...).all;
6821 -- As a result, the call avoids an extra copy. This an optimization,
6822 -- but it is required for passing ACATS tests in some cases where it
6823 -- would otherwise make two copies. The RM allows removing redunant
6824 -- Adjust/Finalize calls, but does not allow insertion of extra ones.
6826 -- This part is disabled for now, because it breaks GNAT Studio
6827 -- builds
6829 (False -- ???
6830 and then Nkind (Expr_Q) = N_Explicit_Dereference
6831 and then not Comes_From_Source (Expr_Q)
6832 and then Nkind (Original_Node (Expr_Q)) = N_Function_Call
6833 and then Nkind (Object_Definition (N)) in N_Has_Entity
6834 and then (Needs_Finalization (Entity (Object_Definition (N)))))
6836 -- If the initializing expression is for a variable with attribute
6837 -- OK_To_Rename set, then transform:
6839 -- Obj : Typ := Expr;
6841 -- into
6843 -- Obj : Typ renames Expr;
6845 -- provided that Obj is not aliased. The aliased case has to be
6846 -- excluded in general because Expr will not be aliased in
6847 -- general.
6849 or else
6850 (not Aliased_Present (N)
6851 and then Is_Entity_Name (Expr_Q)
6852 and then Ekind (Entity (Expr_Q)) = E_Variable
6853 and then OK_To_Rename (Entity (Expr_Q))
6854 and then Is_Entity_Name (Obj_Def));
6855 begin
6856 -- Return False if there are any aspect specifications, because
6857 -- otherwise we duplicate that corresponding implicit attribute
6858 -- definition, and call Insert_Action, which has no place to insert
6859 -- the attribute definition. The attribute definition is stored in
6860 -- Aspect_Rep_Item, which is not a list.
6862 return Result and then No (Aspect_Specifications (N));
6863 end Rewrite_As_Renaming;
6865 -- Local variables
6867 Next_N : constant Node_Id := Next (N);
6869 Adj_Call : Node_Id;
6870 Id_Ref : Node_Id;
6871 Tag_Assign : Node_Id;
6873 Init_After : Node_Id := N;
6874 -- Node after which the initialization actions are to be inserted. This
6875 -- is normally N, except for the case of a shared passive variable, in
6876 -- which case the init proc call must be inserted only after the bodies
6877 -- of the shared variable procedures have been seen.
6879 -- Start of processing for Expand_N_Object_Declaration
6881 begin
6882 -- Don't do anything for deferred constants. All proper actions will be
6883 -- expanded during the full declaration.
6885 if No (Expr) and Constant_Present (N) then
6886 return;
6887 end if;
6889 -- The type of the object cannot be abstract. This is diagnosed at the
6890 -- point the object is frozen, which happens after the declaration is
6891 -- fully expanded, so simply return now.
6893 if Is_Abstract_Type (Typ) then
6894 return;
6895 end if;
6897 -- No action needed for the internal imported dummy object added by
6898 -- Make_DT to compute the offset of the components that reference
6899 -- secondary dispatch tables; required to avoid never-ending loop
6900 -- processing this internal object declaration.
6902 if Tagged_Type_Expansion
6903 and then Is_Internal (Def_Id)
6904 and then Is_Imported (Def_Id)
6905 and then Related_Type (Def_Id) = Implementation_Base_Type (Typ)
6906 then
6907 return;
6908 end if;
6910 -- Make shared memory routines for shared passive variable
6912 if Is_Shared_Passive (Def_Id) then
6913 Init_After := Make_Shared_Var_Procs (N);
6914 end if;
6916 -- If tasks are being declared, make sure we have an activation chain
6917 -- defined for the tasks (has no effect if we already have one), and
6918 -- also that a Master variable is established (and that the appropriate
6919 -- enclosing construct is established as a task master).
6921 Ensure_Activation_Chain_And_Master (N);
6923 -- If No_Implicit_Heap_Allocations or No_Implicit_Task_Allocations
6924 -- restrictions are active then default-sized secondary stacks are
6925 -- generated by the binder and allocated by SS_Init. To provide the
6926 -- binder the number of stacks to generate, the number of default-sized
6927 -- stacks required for task objects contained within the object
6928 -- declaration N is calculated here as it is at this point where
6929 -- unconstrained types become constrained. The result is stored in the
6930 -- enclosing unit's Unit_Record.
6932 -- Note if N is an array object declaration that has an initialization
6933 -- expression, a second object declaration for the initialization
6934 -- expression is created by the compiler. To prevent double counting
6935 -- of the stacks in this scenario, the stacks of the first array are
6936 -- not counted.
6938 if Might_Have_Tasks (Typ)
6939 and then not Restriction_Active (No_Secondary_Stack)
6940 and then (Restriction_Active (No_Implicit_Heap_Allocations)
6941 or else Restriction_Active (No_Implicit_Task_Allocations))
6942 and then not (Ekind (Typ) in E_Array_Type | E_Array_Subtype
6943 and then (Has_Init_Expression (N)))
6944 then
6945 declare
6946 PS_Count, SS_Count : Int := 0;
6947 begin
6948 Count_Default_Sized_Task_Stacks (Typ, PS_Count, SS_Count);
6949 Increment_Primary_Stack_Count (PS_Count);
6950 Increment_Sec_Stack_Count (SS_Count);
6951 end;
6952 end if;
6954 -- Default initialization required, and no expression present
6956 if No (Expr) then
6958 -- If we have a type with a variant part, the initialization proc
6959 -- will contain implicit tests of the discriminant values, which
6960 -- counts as a violation of the restriction No_Implicit_Conditionals.
6962 if Has_Variant_Part (Typ) then
6963 declare
6964 Msg : Boolean;
6966 begin
6967 Check_Restriction (Msg, No_Implicit_Conditionals, Obj_Def);
6969 if Msg then
6970 Error_Msg_N
6971 ("\initialization of variant record tests discriminants",
6972 Obj_Def);
6973 return;
6974 end if;
6975 end;
6976 end if;
6978 -- For the default initialization case, if we have a private type
6979 -- with invariants, and invariant checks are enabled, then insert an
6980 -- invariant check after the object declaration. Note that it is OK
6981 -- to clobber the object with an invalid value since if the exception
6982 -- is raised, then the object will go out of scope. In the case where
6983 -- an array object is initialized with an aggregate, the expression
6984 -- is removed. Check flag Has_Init_Expression to avoid generating a
6985 -- junk invariant check and flag No_Initialization to avoid checking
6986 -- an uninitialized object such as a compiler temporary used for an
6987 -- aggregate.
6989 if Has_Invariants (Base_Typ)
6990 and then Present (Invariant_Procedure (Base_Typ))
6991 and then not Has_Init_Expression (N)
6992 and then not No_Initialization (N)
6993 then
6994 -- If entity has an address clause or aspect, make invariant
6995 -- call into a freeze action for the explicit freeze node for
6996 -- object. Otherwise insert invariant check after declaration.
6998 if Present (Following_Address_Clause (N))
6999 or else Has_Aspect (Def_Id, Aspect_Address)
7000 then
7001 Ensure_Freeze_Node (Def_Id);
7002 Set_Has_Delayed_Freeze (Def_Id);
7003 Set_Is_Frozen (Def_Id, False);
7005 if not Partial_View_Has_Unknown_Discr (Typ) then
7006 Append_Freeze_Action (Def_Id,
7007 Make_Invariant_Call (New_Occurrence_Of (Def_Id, Loc)));
7008 end if;
7010 elsif not Partial_View_Has_Unknown_Discr (Typ) then
7011 Insert_After (N,
7012 Make_Invariant_Call (New_Occurrence_Of (Def_Id, Loc)));
7013 end if;
7014 end if;
7016 Default_Initialize_Object (Init_After);
7018 -- Generate attribute for Persistent_BSS if needed
7020 if Persistent_BSS_Mode
7021 and then Comes_From_Source (N)
7022 and then Is_Potentially_Persistent_Type (Typ)
7023 and then not Has_Init_Expression (N)
7024 and then Is_Library_Level_Entity (Def_Id)
7025 then
7026 declare
7027 Prag : Node_Id;
7028 begin
7029 Prag :=
7030 Make_Linker_Section_Pragma
7031 (Def_Id, Sloc (N), ".persistent.bss");
7032 Insert_After (N, Prag);
7033 Analyze (Prag);
7034 end;
7035 end if;
7037 -- If access type, then we know it is null if not initialized
7039 if Is_Access_Type (Typ) then
7040 Set_Is_Known_Null (Def_Id);
7041 end if;
7043 -- Explicit initialization present
7045 else
7046 -- Obtain actual expression from qualified expression
7048 Expr_Q := Unqualify (Expr);
7050 -- When we have the appropriate type of aggregate in the expression
7051 -- (it has been determined during analysis of the aggregate by
7052 -- setting the delay flag), let's perform in place assignment and
7053 -- thus avoid creating a temporary.
7055 if Is_Delayed_Aggregate (Expr_Q) then
7057 -- An aggregate that must be built in place is not resolved and
7058 -- expanded until the enclosing construct is expanded. This will
7059 -- happen when the aggregate is limited and the declared object
7060 -- has a following address clause; it happens also when generating
7061 -- C code for an aggregate that has an alignment or address clause
7062 -- (see Analyze_Object_Declaration). Resolution is done without
7063 -- expansion because it will take place when the declaration
7064 -- itself is expanded.
7066 if (Is_Limited_Type (Typ) or else Modify_Tree_For_C)
7067 and then not Analyzed (Expr)
7068 then
7069 Expander_Mode_Save_And_Set (False);
7070 Resolve (Expr, Typ);
7071 Expander_Mode_Restore;
7072 end if;
7074 Convert_Aggr_In_Object_Decl (N);
7076 -- Ada 2005 (AI-318-02): If the initialization expression is a call
7077 -- to a build-in-place function, then access to the declared object
7078 -- must be passed to the function. Currently we limit such functions
7079 -- to those with constrained limited result subtypes, but eventually
7080 -- plan to expand the allowed forms of functions that are treated as
7081 -- build-in-place.
7083 elsif Is_Build_In_Place_Function_Call (Expr_Q) then
7084 Make_Build_In_Place_Call_In_Object_Declaration (N, Expr_Q);
7086 -- The previous call expands the expression initializing the
7087 -- built-in-place object into further code that will be analyzed
7088 -- later. No further expansion needed here.
7090 return;
7092 -- This is the same as the previous 'elsif', except that the call has
7093 -- been transformed by other expansion activities into something like
7094 -- F(...)'Reference.
7096 elsif Nkind (Expr_Q) = N_Reference
7097 and then Is_Build_In_Place_Function_Call (Prefix (Expr_Q))
7098 and then not Is_Expanded_Build_In_Place_Call
7099 (Unqual_Conv (Prefix (Expr_Q)))
7100 then
7101 Make_Build_In_Place_Call_In_Anonymous_Context (Prefix (Expr_Q));
7103 -- The previous call expands the expression initializing the
7104 -- built-in-place object into further code that will be analyzed
7105 -- later. No further expansion needed here.
7107 return;
7109 -- Ada 2005 (AI-318-02): Specialization of the previous case for
7110 -- expressions containing a build-in-place function call whose
7111 -- returned object covers interface types, and Expr_Q has calls to
7112 -- Ada.Tags.Displace to displace the pointer to the returned build-
7113 -- in-place object to reference the secondary dispatch table of a
7114 -- covered interface type.
7116 elsif Present (Unqual_BIP_Iface_Function_Call (Expr_Q)) then
7117 Make_Build_In_Place_Iface_Call_In_Object_Declaration (N, Expr_Q);
7119 -- The previous call expands the expression initializing the
7120 -- built-in-place object into further code that will be analyzed
7121 -- later. No further expansion needed here.
7123 return;
7125 -- Ada 2005 (AI-251): Rewrite the expression that initializes a
7126 -- class-wide interface object to ensure that we copy the full
7127 -- object, unless we are targetting a VM where interfaces are handled
7128 -- by VM itself. Note that if the root type of Typ is an ancestor of
7129 -- Expr's type, both types share the same dispatch table and there is
7130 -- no need to displace the pointer.
7132 elsif Is_Interface (Typ)
7134 -- Avoid never-ending recursion because if Equivalent_Type is set
7135 -- then we've done it already and must not do it again.
7137 and then not
7138 (Nkind (Obj_Def) = N_Identifier
7139 and then Present (Equivalent_Type (Entity (Obj_Def))))
7140 then
7141 pragma Assert (Is_Class_Wide_Type (Typ));
7143 -- If the object is a return object of an inherently limited type,
7144 -- which implies build-in-place treatment, bypass the special
7145 -- treatment of class-wide interface initialization below. In this
7146 -- case, the expansion of the return statement will take care of
7147 -- creating the object (via allocator) and initializing it.
7149 if Is_Return_Object (Def_Id) and then Is_Limited_View (Typ) then
7150 null;
7152 elsif Tagged_Type_Expansion then
7153 declare
7154 Iface : constant Entity_Id := Root_Type (Typ);
7155 Expr_N : Node_Id := Expr;
7156 Expr_Typ : Entity_Id;
7157 New_Expr : Node_Id;
7158 Obj_Id : Entity_Id;
7159 Tag_Comp : Node_Id;
7161 begin
7162 -- If the original node of the expression was a conversion
7163 -- to this specific class-wide interface type then restore
7164 -- the original node because we must copy the object before
7165 -- displacing the pointer to reference the secondary tag
7166 -- component. This code must be kept synchronized with the
7167 -- expansion done by routine Expand_Interface_Conversion
7169 if not Comes_From_Source (Expr_N)
7170 and then Nkind (Expr_N) = N_Explicit_Dereference
7171 and then Nkind (Original_Node (Expr_N)) = N_Type_Conversion
7172 and then Etype (Original_Node (Expr_N)) = Typ
7173 then
7174 Rewrite (Expr_N, Original_Node (Expression (N)));
7175 end if;
7177 -- Avoid expansion of redundant interface conversion
7179 if Is_Interface (Etype (Expr_N))
7180 and then Nkind (Expr_N) = N_Type_Conversion
7181 and then Etype (Expr_N) = Typ
7182 then
7183 Expr_N := Expression (Expr_N);
7184 Set_Expression (N, Expr_N);
7185 end if;
7187 Obj_Id := Make_Temporary (Loc, 'D', Expr_N);
7188 Expr_Typ := Base_Type (Etype (Expr_N));
7190 if Is_Class_Wide_Type (Expr_Typ) then
7191 Expr_Typ := Root_Type (Expr_Typ);
7192 end if;
7194 -- Replace
7195 -- CW : I'Class := Obj;
7196 -- by
7197 -- Tmp : T := Obj;
7198 -- type Ityp is not null access I'Class;
7199 -- CW : I'Class renames Ityp (Tmp.I_Tag'Address).all;
7201 if Comes_From_Source (Expr_N)
7202 and then Nkind (Expr_N) = N_Identifier
7203 and then not Is_Interface (Expr_Typ)
7204 and then Interface_Present_In_Ancestor (Expr_Typ, Typ)
7205 and then (Expr_Typ = Etype (Expr_Typ)
7206 or else not
7207 Is_Variable_Size_Record (Etype (Expr_Typ)))
7208 then
7209 -- Copy the object
7211 Insert_Action (N,
7212 Make_Object_Declaration (Loc,
7213 Defining_Identifier => Obj_Id,
7214 Object_Definition =>
7215 New_Occurrence_Of (Expr_Typ, Loc),
7216 Expression => Relocate_Node (Expr_N)));
7218 -- Statically reference the tag associated with the
7219 -- interface
7221 Tag_Comp :=
7222 Make_Selected_Component (Loc,
7223 Prefix => New_Occurrence_Of (Obj_Id, Loc),
7224 Selector_Name =>
7225 New_Occurrence_Of
7226 (Find_Interface_Tag (Expr_Typ, Iface), Loc));
7228 -- Replace
7229 -- IW : I'Class := Obj;
7230 -- by
7231 -- type Equiv_Record is record ... end record;
7232 -- implicit subtype CW is <Class_Wide_Subtype>;
7233 -- Tmp : CW := CW!(Obj);
7234 -- type Ityp is not null access I'Class;
7235 -- IW : I'Class renames
7236 -- Ityp!(Displace (Temp'Address, I'Tag)).all;
7238 else
7239 -- Generate the equivalent record type and update the
7240 -- subtype indication to reference it.
7242 Expand_Subtype_From_Expr
7243 (N => N,
7244 Unc_Type => Typ,
7245 Subtype_Indic => Obj_Def,
7246 Exp => Expr_N);
7248 if not Is_Interface (Etype (Expr_N)) then
7249 New_Expr := Relocate_Node (Expr_N);
7251 -- For interface types we use 'Address which displaces
7252 -- the pointer to the base of the object (if required)
7254 else
7255 New_Expr :=
7256 Unchecked_Convert_To (Etype (Obj_Def),
7257 Make_Explicit_Dereference (Loc,
7258 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
7259 Make_Attribute_Reference (Loc,
7260 Prefix => Relocate_Node (Expr_N),
7261 Attribute_Name => Name_Address))));
7262 end if;
7264 -- Copy the object
7266 if not Is_Limited_Record (Expr_Typ) then
7267 Insert_Action (N,
7268 Make_Object_Declaration (Loc,
7269 Defining_Identifier => Obj_Id,
7270 Object_Definition =>
7271 New_Occurrence_Of (Etype (Obj_Def), Loc),
7272 Expression => New_Expr));
7274 -- Rename limited type object since they cannot be copied
7275 -- This case occurs when the initialization expression
7276 -- has been previously expanded into a temporary object.
7278 else pragma Assert (not Comes_From_Source (Expr_Q));
7279 Insert_Action (N,
7280 Make_Object_Renaming_Declaration (Loc,
7281 Defining_Identifier => Obj_Id,
7282 Subtype_Mark =>
7283 New_Occurrence_Of (Etype (Obj_Def), Loc),
7284 Name =>
7285 Unchecked_Convert_To
7286 (Etype (Obj_Def), New_Expr)));
7287 end if;
7289 -- Dynamically reference the tag associated with the
7290 -- interface.
7292 Tag_Comp :=
7293 Make_Function_Call (Loc,
7294 Name => New_Occurrence_Of (RTE (RE_Displace), Loc),
7295 Parameter_Associations => New_List (
7296 Make_Attribute_Reference (Loc,
7297 Prefix => New_Occurrence_Of (Obj_Id, Loc),
7298 Attribute_Name => Name_Address),
7299 New_Occurrence_Of
7300 (Node (First_Elmt (Access_Disp_Table (Iface))),
7301 Loc)));
7302 end if;
7304 Rewrite (N,
7305 Make_Object_Renaming_Declaration (Loc,
7306 Defining_Identifier => Make_Temporary (Loc, 'D'),
7307 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
7308 Name =>
7309 Convert_Tag_To_Interface (Typ, Tag_Comp)));
7311 -- If the original entity comes from source, then mark the
7312 -- new entity as needing debug information, even though it's
7313 -- defined by a generated renaming that does not come from
7314 -- source, so that Materialize_Entity will be set on the
7315 -- entity when Debug_Renaming_Declaration is called during
7316 -- analysis.
7318 if Comes_From_Source (Def_Id) then
7319 Set_Debug_Info_Needed (Defining_Identifier (N));
7320 end if;
7322 Analyze (N, Suppress => All_Checks);
7324 -- Replace internal identifier of rewritten node by the
7325 -- identifier found in the sources. We also have to exchange
7326 -- entities containing their defining identifiers to ensure
7327 -- the correct replacement of the object declaration by this
7328 -- object renaming declaration because these identifiers
7329 -- were previously added by Enter_Name to the current scope.
7330 -- We must preserve the homonym chain of the source entity
7331 -- as well. We must also preserve the kind of the entity,
7332 -- which may be a constant. Preserve entity chain because
7333 -- itypes may have been generated already, and the full
7334 -- chain must be preserved for final freezing. Finally,
7335 -- preserve Comes_From_Source setting, so that debugging
7336 -- and cross-referencing information is properly kept, and
7337 -- preserve source location, to prevent spurious errors when
7338 -- entities are declared (they must have their own Sloc).
7340 declare
7341 New_Id : constant Entity_Id := Defining_Identifier (N);
7342 Next_Temp : constant Entity_Id := Next_Entity (New_Id);
7343 Save_CFS : constant Boolean :=
7344 Comes_From_Source (Def_Id);
7345 Save_SP : constant Node_Id := SPARK_Pragma (Def_Id);
7346 Save_SPI : constant Boolean :=
7347 SPARK_Pragma_Inherited (Def_Id);
7349 begin
7350 Link_Entities (New_Id, Next_Entity (Def_Id));
7351 Link_Entities (Def_Id, Next_Temp);
7353 Set_Chars (Defining_Identifier (N), Chars (Def_Id));
7354 Set_Homonym (Defining_Identifier (N), Homonym (Def_Id));
7355 Mutate_Ekind (Defining_Identifier (N), Ekind (Def_Id));
7356 Set_Sloc (Defining_Identifier (N), Sloc (Def_Id));
7358 Set_Comes_From_Source (Def_Id, False);
7360 -- ??? This is extremely dangerous!!! Exchanging entities
7361 -- is very low level, and as a result it resets flags and
7362 -- fields which belong to the original Def_Id. Several of
7363 -- these attributes are saved and restored, but there may
7364 -- be many more that need to be preserverd.
7366 Exchange_Entities (Defining_Identifier (N), Def_Id);
7368 -- Restore clobbered attributes
7370 Set_Comes_From_Source (Def_Id, Save_CFS);
7371 Set_SPARK_Pragma (Def_Id, Save_SP);
7372 Set_SPARK_Pragma_Inherited (Def_Id, Save_SPI);
7373 end;
7374 end;
7375 end if;
7377 return;
7379 -- Common case of explicit object initialization
7381 else
7382 -- In most cases, we must check that the initial value meets any
7383 -- constraint imposed by the declared type. However, there is one
7384 -- very important exception to this rule. If the entity has an
7385 -- unconstrained nominal subtype, then it acquired its constraints
7386 -- from the expression in the first place, and not only does this
7387 -- mean that the constraint check is not needed, but an attempt to
7388 -- perform the constraint check can cause order of elaboration
7389 -- problems.
7391 if not Is_Constr_Subt_For_U_Nominal (Typ) then
7393 -- If this is an allocator for an aggregate that has been
7394 -- allocated in place, delay checks until assignments are
7395 -- made, because the discriminants are not initialized.
7397 if Nkind (Expr) = N_Allocator
7398 and then No_Initialization (Expr)
7399 then
7400 null;
7402 -- Otherwise apply a constraint check now if no prev error
7404 elsif Nkind (Expr) /= N_Error then
7405 Apply_Constraint_Check (Expr, Typ);
7407 -- Deal with possible range check
7409 if Do_Range_Check (Expr) then
7411 -- If assignment checks are suppressed, turn off flag
7413 if Suppress_Assignment_Checks (N) then
7414 Set_Do_Range_Check (Expr, False);
7416 -- Otherwise generate the range check
7418 else
7419 Generate_Range_Check
7420 (Expr, Typ, CE_Range_Check_Failed);
7421 end if;
7422 end if;
7423 end if;
7424 end if;
7426 -- If the type is controlled and not inherently limited, then
7427 -- the target is adjusted after the copy and attached to the
7428 -- finalization list. However, no adjustment is done in the case
7429 -- where the object was initialized by a call to a function whose
7430 -- result is built in place, since no copy occurred. Similarly, no
7431 -- adjustment is required if we are going to rewrite the object
7432 -- declaration into a renaming declaration.
7434 if Needs_Finalization (Typ)
7435 and then not Is_Limited_View (Typ)
7436 and then not Rewrite_As_Renaming
7437 then
7438 Adj_Call :=
7439 Make_Adjust_Call (
7440 Obj_Ref => New_Occurrence_Of (Def_Id, Loc),
7441 Typ => Base_Typ);
7443 -- Guard against a missing [Deep_]Adjust when the base type
7444 -- was not properly frozen.
7446 if Present (Adj_Call) then
7447 Insert_Action_After (Init_After, Adj_Call);
7448 end if;
7449 end if;
7451 -- For tagged types, when an init value is given, the tag has to
7452 -- be re-initialized separately in order to avoid the propagation
7453 -- of a wrong tag coming from a view conversion unless the type
7454 -- is class wide (in this case the tag comes from the init value).
7455 -- Suppress the tag assignment when not Tagged_Type_Expansion
7456 -- because tags are represented implicitly in objects. Ditto for
7457 -- types that are CPP_CLASS, and for initializations that are
7458 -- aggregates, because they have to have the right tag.
7460 -- The re-assignment of the tag has to be done even if the object
7461 -- is a constant. The assignment must be analyzed after the
7462 -- declaration. If an address clause follows, this is handled as
7463 -- part of the freeze actions for the object, otherwise insert
7464 -- tag assignment here.
7466 Tag_Assign := Make_Tag_Assignment (N);
7468 if Present (Tag_Assign) then
7469 if Present (Following_Address_Clause (N)) then
7470 Ensure_Freeze_Node (Def_Id);
7472 else
7473 Insert_Action_After (Init_After, Tag_Assign);
7474 end if;
7476 -- Handle C++ constructor calls. Note that we do not check that
7477 -- Typ is a tagged type since the equivalent Ada type of a C++
7478 -- class that has no virtual methods is an untagged limited
7479 -- record type.
7481 elsif Is_CPP_Constructor_Call (Expr) then
7483 -- The call to the initialization procedure does NOT freeze the
7484 -- object being initialized.
7486 Id_Ref := New_Occurrence_Of (Def_Id, Loc);
7487 Set_Must_Not_Freeze (Id_Ref);
7488 Set_Assignment_OK (Id_Ref);
7490 Insert_Actions_After (Init_After,
7491 Build_Initialization_Call (Loc, Id_Ref, Typ,
7492 Constructor_Ref => Expr));
7494 -- We remove here the original call to the constructor
7495 -- to avoid its management in the backend
7497 Set_Expression (N, Empty);
7498 return;
7500 -- Handle initialization of limited tagged types
7502 elsif Is_Tagged_Type (Typ)
7503 and then Is_Class_Wide_Type (Typ)
7504 and then Is_Limited_Record (Typ)
7505 and then not Is_Limited_Interface (Typ)
7506 then
7507 -- Given that the type is limited we cannot perform a copy. If
7508 -- Expr_Q is the reference to a variable we mark the variable
7509 -- as OK_To_Rename to expand this declaration into a renaming
7510 -- declaration (see below).
7512 if Is_Entity_Name (Expr_Q) then
7513 Set_OK_To_Rename (Entity (Expr_Q));
7515 -- If we cannot convert the expression into a renaming we must
7516 -- consider it an internal error because the backend does not
7517 -- have support to handle it. But avoid crashing on a raise
7518 -- expression or conditional expression.
7520 elsif Nkind (Original_Node (Expr_Q)) not in
7521 N_Raise_Expression | N_If_Expression | N_Case_Expression
7522 then
7523 raise Program_Error;
7524 end if;
7526 -- For discrete types, set the Is_Known_Valid flag if the
7527 -- initializing value is known to be valid. Only do this for
7528 -- source assignments, since otherwise we can end up turning
7529 -- on the known valid flag prematurely from inserted code.
7531 elsif Comes_From_Source (N)
7532 and then Is_Discrete_Type (Typ)
7533 and then Expr_Known_Valid (Expr)
7534 and then Safe_To_Capture_Value (N, Def_Id)
7535 then
7536 Set_Is_Known_Valid (Def_Id);
7538 elsif Is_Access_Type (Typ) then
7540 -- For access types set the Is_Known_Non_Null flag if the
7541 -- initializing value is known to be non-null. We can also set
7542 -- Can_Never_Be_Null if this is a constant.
7544 if Known_Non_Null (Expr) then
7545 Set_Is_Known_Non_Null (Def_Id, True);
7547 if Constant_Present (N) then
7548 Set_Can_Never_Be_Null (Def_Id);
7549 end if;
7550 end if;
7551 end if;
7553 -- If validity checking on copies, validate initial expression.
7554 -- But skip this if declaration is for a generic type, since it
7555 -- makes no sense to validate generic types. Not clear if this
7556 -- can happen for legal programs, but it definitely can arise
7557 -- from previous instantiation errors.
7559 if Validity_Checks_On
7560 and then Comes_From_Source (N)
7561 and then Validity_Check_Copies
7562 and then not Is_Generic_Type (Etype (Def_Id))
7563 then
7564 Ensure_Valid (Expr);
7565 if Safe_To_Capture_Value (N, Def_Id) then
7566 Set_Is_Known_Valid (Def_Id);
7567 end if;
7568 end if;
7569 end if;
7571 -- Cases where the back end cannot handle the initialization
7572 -- directly. In such cases, we expand an assignment that will
7573 -- be appropriately handled by Expand_N_Assignment_Statement.
7575 -- The exclusion of the unconstrained case is wrong, but for now it
7576 -- is too much trouble ???
7578 if (Is_Possibly_Unaligned_Slice (Expr)
7579 or else (Is_Possibly_Unaligned_Object (Expr)
7580 and then not Represented_As_Scalar (Etype (Expr))))
7581 and then not (Is_Array_Type (Etype (Expr))
7582 and then not Is_Constrained (Etype (Expr)))
7583 then
7584 declare
7585 Stat : constant Node_Id :=
7586 Make_Assignment_Statement (Loc,
7587 Name => New_Occurrence_Of (Def_Id, Loc),
7588 Expression => Relocate_Node (Expr));
7589 begin
7590 Set_Expression (N, Empty);
7591 Set_No_Initialization (N);
7592 Set_Assignment_OK (Name (Stat));
7593 Set_No_Ctrl_Actions (Stat);
7594 Insert_After_And_Analyze (Init_After, Stat);
7595 end;
7596 end if;
7597 end if;
7599 if Nkind (Obj_Def) = N_Access_Definition
7600 and then not Is_Local_Anonymous_Access (Etype (Def_Id))
7601 then
7602 -- An Ada 2012 stand-alone object of an anonymous access type
7604 declare
7605 Loc : constant Source_Ptr := Sloc (N);
7607 Level : constant Entity_Id :=
7608 Make_Defining_Identifier (Sloc (N),
7609 Chars =>
7610 New_External_Name (Chars (Def_Id), Suffix => "L"));
7612 Level_Decl : Node_Id;
7613 Level_Expr : Node_Id;
7615 begin
7616 Mutate_Ekind (Level, Ekind (Def_Id));
7617 Set_Etype (Level, Standard_Natural);
7618 Set_Scope (Level, Scope (Def_Id));
7620 -- Set accessibility level of null
7622 if No (Expr) then
7623 Level_Expr :=
7624 Make_Integer_Literal
7625 (Loc, Scope_Depth (Standard_Standard));
7627 -- When the expression of the object is a function which returns
7628 -- an anonymous access type the master of the call is the object
7629 -- being initialized instead of the type.
7631 elsif Nkind (Expr) = N_Function_Call
7632 and then Ekind (Etype (Name (Expr))) = E_Anonymous_Access_Type
7633 then
7634 Level_Expr := Accessibility_Level
7635 (Def_Id, Object_Decl_Level);
7637 -- General case
7639 else
7640 Level_Expr := Accessibility_Level (Expr, Dynamic_Level);
7641 end if;
7643 Level_Decl :=
7644 Make_Object_Declaration (Loc,
7645 Defining_Identifier => Level,
7646 Object_Definition =>
7647 New_Occurrence_Of (Standard_Natural, Loc),
7648 Expression => Level_Expr,
7649 Constant_Present => Constant_Present (N),
7650 Has_Init_Expression => True);
7652 Insert_Action_After (Init_After, Level_Decl);
7654 Set_Extra_Accessibility (Def_Id, Level);
7655 end;
7656 end if;
7658 -- If the object is default initialized and its type is subject to
7659 -- pragma Default_Initial_Condition, add a runtime check to verify
7660 -- the assumption of the pragma (SPARK RM 7.3.3). Generate:
7662 -- <Base_Typ>DIC (<Base_Typ> (Def_Id));
7664 -- Note that the check is generated for source objects only
7666 if Comes_From_Source (Def_Id)
7667 and then Has_DIC (Typ)
7668 and then Present (DIC_Procedure (Typ))
7669 and then not Has_Null_Body (DIC_Procedure (Typ))
7670 and then not Has_Init_Expression (N)
7671 and then not Is_Imported (Def_Id)
7672 then
7673 declare
7674 DIC_Call : constant Node_Id :=
7675 Build_DIC_Call
7676 (Loc, New_Occurrence_Of (Def_Id, Loc), Typ);
7677 begin
7678 if Present (Next_N) then
7679 Insert_Before_And_Analyze (Next_N, DIC_Call);
7681 -- The object declaration is the last node in a declarative or a
7682 -- statement list.
7684 else
7685 Append_To (List_Containing (N), DIC_Call);
7686 Analyze (DIC_Call);
7687 end if;
7688 end;
7689 end if;
7691 -- Final transformation - turn the object declaration into a renaming
7692 -- if appropriate. If this is the completion of a deferred constant
7693 -- declaration, then this transformation generates what would be
7694 -- illegal code if written by hand, but that's OK.
7696 if Present (Expr) then
7697 if Rewrite_As_Renaming then
7698 Rewrite (N,
7699 Make_Object_Renaming_Declaration (Loc,
7700 Defining_Identifier => Defining_Identifier (N),
7701 Subtype_Mark => Obj_Def,
7702 Name => Expr_Q));
7704 -- We do not analyze this renaming declaration, because all its
7705 -- components have already been analyzed, and if we were to go
7706 -- ahead and analyze it, we would in effect be trying to generate
7707 -- another declaration of X, which won't do.
7709 Set_Renamed_Object (Defining_Identifier (N), Expr_Q);
7710 Set_Analyzed (N);
7712 -- We do need to deal with debug issues for this renaming
7714 -- First, if entity comes from source, then mark it as needing
7715 -- debug information, even though it is defined by a generated
7716 -- renaming that does not come from source.
7718 Set_Debug_Info_Defining_Id (N);
7720 -- Now call the routine to generate debug info for the renaming
7722 declare
7723 Decl : constant Node_Id := Debug_Renaming_Declaration (N);
7724 begin
7725 if Present (Decl) then
7726 Insert_Action (N, Decl);
7727 end if;
7728 end;
7729 end if;
7730 end if;
7732 -- Exception on library entity not available
7734 exception
7735 when RE_Not_Available =>
7736 return;
7737 end Expand_N_Object_Declaration;
7739 ---------------------------------
7740 -- Expand_N_Subtype_Indication --
7741 ---------------------------------
7743 -- Add a check on the range of the subtype and deal with validity checking
7745 procedure Expand_N_Subtype_Indication (N : Node_Id) is
7746 Ran : constant Node_Id := Range_Expression (Constraint (N));
7747 Typ : constant Entity_Id := Entity (Subtype_Mark (N));
7749 begin
7750 if Nkind (Constraint (N)) = N_Range_Constraint then
7751 Validity_Check_Range (Range_Expression (Constraint (N)));
7752 end if;
7754 -- Do not duplicate the work of Process_Range_Expr_In_Decl in Sem_Ch3
7756 if Nkind (Parent (N)) in N_Constrained_Array_Definition | N_Slice
7757 and then Nkind (Parent (Parent (N))) not in
7758 N_Full_Type_Declaration | N_Object_Declaration
7759 then
7760 Apply_Range_Check (Ran, Typ);
7761 end if;
7762 end Expand_N_Subtype_Indication;
7764 ---------------------------
7765 -- Expand_N_Variant_Part --
7766 ---------------------------
7768 -- Note: this procedure no longer has any effect. It used to be that we
7769 -- would replace the choices in the last variant by a when others, and
7770 -- also expanded static predicates in variant choices here, but both of
7771 -- those activities were being done too early, since we can't check the
7772 -- choices until the statically predicated subtypes are frozen, which can
7773 -- happen as late as the free point of the record, and we can't change the
7774 -- last choice to an others before checking the choices, which is now done
7775 -- at the freeze point of the record.
7777 procedure Expand_N_Variant_Part (N : Node_Id) is
7778 begin
7779 null;
7780 end Expand_N_Variant_Part;
7782 ---------------------------------
7783 -- Expand_Previous_Access_Type --
7784 ---------------------------------
7786 procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
7787 Ptr_Typ : Entity_Id;
7789 begin
7790 -- Find all access types in the current scope whose designated type is
7791 -- Def_Id and build master renamings for them.
7793 Ptr_Typ := First_Entity (Current_Scope);
7794 while Present (Ptr_Typ) loop
7795 if Is_Access_Type (Ptr_Typ)
7796 and then Designated_Type (Ptr_Typ) = Def_Id
7797 and then No (Master_Id (Ptr_Typ))
7798 then
7799 -- Ensure that the designated type has a master
7801 Build_Master_Entity (Def_Id);
7803 -- Private and incomplete types complicate the insertion of master
7804 -- renamings because the access type may precede the full view of
7805 -- the designated type. For this reason, the master renamings are
7806 -- inserted relative to the designated type.
7808 Build_Master_Renaming (Ptr_Typ, Ins_Nod => Parent (Def_Id));
7809 end if;
7811 Next_Entity (Ptr_Typ);
7812 end loop;
7813 end Expand_Previous_Access_Type;
7815 -----------------------------
7816 -- Expand_Record_Extension --
7817 -----------------------------
7819 -- Add a field _parent at the beginning of the record extension. This is
7820 -- used to implement inheritance. Here are some examples of expansion:
7822 -- 1. no discriminants
7823 -- type T2 is new T1 with null record;
7824 -- gives
7825 -- type T2 is new T1 with record
7826 -- _Parent : T1;
7827 -- end record;
7829 -- 2. renamed discriminants
7830 -- type T2 (B, C : Int) is new T1 (A => B) with record
7831 -- _Parent : T1 (A => B);
7832 -- D : Int;
7833 -- end;
7835 -- 3. inherited discriminants
7836 -- type T2 is new T1 with record -- discriminant A inherited
7837 -- _Parent : T1 (A);
7838 -- D : Int;
7839 -- end;
7841 procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
7842 Indic : constant Node_Id := Subtype_Indication (Def);
7843 Loc : constant Source_Ptr := Sloc (Def);
7844 Rec_Ext_Part : Node_Id := Record_Extension_Part (Def);
7845 Par_Subtype : Entity_Id;
7846 Comp_List : Node_Id;
7847 Comp_Decl : Node_Id;
7848 Parent_N : Node_Id;
7849 D : Entity_Id;
7850 List_Constr : constant List_Id := New_List;
7852 begin
7853 -- Expand_Record_Extension is called directly from the semantics, so
7854 -- we must check to see whether expansion is active before proceeding,
7855 -- because this affects the visibility of selected components in bodies
7856 -- of instances. Within a generic we still need to set Parent_Subtype
7857 -- link because the visibility of inherited components will have to be
7858 -- verified in subsequent instances.
7860 if not Expander_Active then
7861 if Inside_A_Generic and then Ekind (T) = E_Record_Type then
7862 Set_Parent_Subtype (T, Etype (T));
7863 end if;
7864 return;
7865 end if;
7867 -- This may be a derivation of an untagged private type whose full
7868 -- view is tagged, in which case the Derived_Type_Definition has no
7869 -- extension part. Build an empty one now.
7871 if No (Rec_Ext_Part) then
7872 Rec_Ext_Part :=
7873 Make_Record_Definition (Loc,
7874 End_Label => Empty,
7875 Component_List => Empty,
7876 Null_Present => True);
7878 Set_Record_Extension_Part (Def, Rec_Ext_Part);
7879 Mark_Rewrite_Insertion (Rec_Ext_Part);
7880 end if;
7882 Comp_List := Component_List (Rec_Ext_Part);
7884 Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
7886 -- If the derived type inherits its discriminants the type of the
7887 -- _parent field must be constrained by the inherited discriminants
7889 if Has_Discriminants (T)
7890 and then Nkind (Indic) /= N_Subtype_Indication
7891 and then not Is_Constrained (Entity (Indic))
7892 then
7893 D := First_Discriminant (T);
7894 while Present (D) loop
7895 Append_To (List_Constr, New_Occurrence_Of (D, Loc));
7896 Next_Discriminant (D);
7897 end loop;
7899 Par_Subtype :=
7900 Process_Subtype (
7901 Make_Subtype_Indication (Loc,
7902 Subtype_Mark => New_Occurrence_Of (Entity (Indic), Loc),
7903 Constraint =>
7904 Make_Index_Or_Discriminant_Constraint (Loc,
7905 Constraints => List_Constr)),
7906 Def);
7908 -- Otherwise the original subtype_indication is just what is needed
7910 else
7911 Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
7912 end if;
7914 Set_Parent_Subtype (T, Par_Subtype);
7916 Comp_Decl :=
7917 Make_Component_Declaration (Loc,
7918 Defining_Identifier => Parent_N,
7919 Component_Definition =>
7920 Make_Component_Definition (Loc,
7921 Aliased_Present => False,
7922 Subtype_Indication => New_Occurrence_Of (Par_Subtype, Loc)));
7924 if Null_Present (Rec_Ext_Part) then
7925 Set_Component_List (Rec_Ext_Part,
7926 Make_Component_List (Loc,
7927 Component_Items => New_List (Comp_Decl),
7928 Variant_Part => Empty,
7929 Null_Present => False));
7930 Set_Null_Present (Rec_Ext_Part, False);
7932 elsif Null_Present (Comp_List)
7933 or else Is_Empty_List (Component_Items (Comp_List))
7934 then
7935 Set_Component_Items (Comp_List, New_List (Comp_Decl));
7936 Set_Null_Present (Comp_List, False);
7938 else
7939 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
7940 end if;
7942 Analyze (Comp_Decl);
7943 end Expand_Record_Extension;
7945 ------------------------
7946 -- Expand_Tagged_Root --
7947 ------------------------
7949 procedure Expand_Tagged_Root (T : Entity_Id) is
7950 Def : constant Node_Id := Type_Definition (Parent (T));
7951 Comp_List : Node_Id;
7952 Comp_Decl : Node_Id;
7953 Sloc_N : Source_Ptr;
7955 begin
7956 if Null_Present (Def) then
7957 Set_Component_List (Def,
7958 Make_Component_List (Sloc (Def),
7959 Component_Items => Empty_List,
7960 Variant_Part => Empty,
7961 Null_Present => True));
7962 end if;
7964 Comp_List := Component_List (Def);
7966 if Null_Present (Comp_List)
7967 or else Is_Empty_List (Component_Items (Comp_List))
7968 then
7969 Sloc_N := Sloc (Comp_List);
7970 else
7971 Sloc_N := Sloc (First (Component_Items (Comp_List)));
7972 end if;
7974 Comp_Decl :=
7975 Make_Component_Declaration (Sloc_N,
7976 Defining_Identifier => First_Tag_Component (T),
7977 Component_Definition =>
7978 Make_Component_Definition (Sloc_N,
7979 Aliased_Present => False,
7980 Subtype_Indication => New_Occurrence_Of (RTE (RE_Tag), Sloc_N)));
7982 if Null_Present (Comp_List)
7983 or else Is_Empty_List (Component_Items (Comp_List))
7984 then
7985 Set_Component_Items (Comp_List, New_List (Comp_Decl));
7986 Set_Null_Present (Comp_List, False);
7988 else
7989 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
7990 end if;
7992 -- We don't Analyze the whole expansion because the tag component has
7993 -- already been analyzed previously. Here we just insure that the tree
7994 -- is coherent with the semantic decoration
7996 Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
7998 exception
7999 when RE_Not_Available =>
8000 return;
8001 end Expand_Tagged_Root;
8003 ------------------------------
8004 -- Freeze_Stream_Operations --
8005 ------------------------------
8007 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
8008 Names : constant array (1 .. 4) of TSS_Name_Type :=
8009 (TSS_Stream_Input,
8010 TSS_Stream_Output,
8011 TSS_Stream_Read,
8012 TSS_Stream_Write);
8013 Stream_Op : Entity_Id;
8015 begin
8016 -- Primitive operations of tagged types are frozen when the dispatch
8017 -- table is constructed.
8019 if not Comes_From_Source (Typ) or else Is_Tagged_Type (Typ) then
8020 return;
8021 end if;
8023 for J in Names'Range loop
8024 Stream_Op := TSS (Typ, Names (J));
8026 if Present (Stream_Op)
8027 and then Is_Subprogram (Stream_Op)
8028 and then Nkind (Unit_Declaration_Node (Stream_Op)) =
8029 N_Subprogram_Declaration
8030 and then not Is_Frozen (Stream_Op)
8031 then
8032 Append_Freeze_Actions (Typ, Freeze_Entity (Stream_Op, N));
8033 end if;
8034 end loop;
8035 end Freeze_Stream_Operations;
8037 -----------------
8038 -- Freeze_Type --
8039 -----------------
8041 -- Full type declarations are expanded at the point at which the type is
8042 -- frozen. The formal N is the Freeze_Node for the type. Any statements or
8043 -- declarations generated by the freezing (e.g. the procedure generated
8044 -- for initialization) are chained in the Actions field list of the freeze
8045 -- node using Append_Freeze_Actions.
8047 -- WARNING: This routine manages Ghost regions. Return statements must be
8048 -- replaced by gotos which jump to the end of the routine and restore the
8049 -- Ghost mode.
8051 function Freeze_Type (N : Node_Id) return Boolean is
8052 procedure Process_RACW_Types (Typ : Entity_Id);
8053 -- Validate and generate stubs for all RACW types associated with type
8054 -- Typ.
8056 procedure Process_Pending_Access_Types (Typ : Entity_Id);
8057 -- Associate type Typ's Finalize_Address primitive with the finalization
8058 -- masters of pending access-to-Typ types.
8060 ------------------------
8061 -- Process_RACW_Types --
8062 ------------------------
8064 procedure Process_RACW_Types (Typ : Entity_Id) is
8065 List : constant Elist_Id := Access_Types_To_Process (N);
8066 E : Elmt_Id;
8067 Seen : Boolean := False;
8069 begin
8070 if Present (List) then
8071 E := First_Elmt (List);
8072 while Present (E) loop
8073 if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
8074 Validate_RACW_Primitives (Node (E));
8075 Seen := True;
8076 end if;
8078 Next_Elmt (E);
8079 end loop;
8080 end if;
8082 -- If there are RACWs designating this type, make stubs now
8084 if Seen then
8085 Remote_Types_Tagged_Full_View_Encountered (Typ);
8086 end if;
8087 end Process_RACW_Types;
8089 ----------------------------------
8090 -- Process_Pending_Access_Types --
8091 ----------------------------------
8093 procedure Process_Pending_Access_Types (Typ : Entity_Id) is
8094 E : Elmt_Id;
8096 begin
8097 -- Finalize_Address is not generated in CodePeer mode because the
8098 -- body contains address arithmetic. This processing is disabled.
8100 if CodePeer_Mode then
8101 null;
8103 -- Certain itypes are generated for contexts that cannot allocate
8104 -- objects and should not set primitive Finalize_Address.
8106 elsif Is_Itype (Typ)
8107 and then Nkind (Associated_Node_For_Itype (Typ)) =
8108 N_Explicit_Dereference
8109 then
8110 null;
8112 -- When an access type is declared after the incomplete view of a
8113 -- Taft-amendment type, the access type is considered pending in
8114 -- case the full view of the Taft-amendment type is controlled. If
8115 -- this is indeed the case, associate the Finalize_Address routine
8116 -- of the full view with the finalization masters of all pending
8117 -- access types. This scenario applies to anonymous access types as
8118 -- well.
8120 elsif Needs_Finalization (Typ)
8121 and then Present (Pending_Access_Types (Typ))
8122 then
8123 E := First_Elmt (Pending_Access_Types (Typ));
8124 while Present (E) loop
8126 -- Generate:
8127 -- Set_Finalize_Address
8128 -- (Ptr_Typ, <Typ>FD'Unrestricted_Access);
8130 Append_Freeze_Action (Typ,
8131 Make_Set_Finalize_Address_Call
8132 (Loc => Sloc (N),
8133 Ptr_Typ => Node (E)));
8135 Next_Elmt (E);
8136 end loop;
8137 end if;
8138 end Process_Pending_Access_Types;
8140 -- Local variables
8142 Def_Id : constant Entity_Id := Entity (N);
8144 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
8145 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
8146 -- Save the Ghost-related attributes to restore on exit
8148 Result : Boolean := False;
8150 -- Start of processing for Freeze_Type
8152 begin
8153 -- The type being frozen may be subject to pragma Ghost. Set the mode
8154 -- now to ensure that any nodes generated during freezing are properly
8155 -- marked as Ghost.
8157 Set_Ghost_Mode (Def_Id);
8159 -- Process any remote access-to-class-wide types designating the type
8160 -- being frozen.
8162 Process_RACW_Types (Def_Id);
8164 -- Freeze processing for record types
8166 if Is_Record_Type (Def_Id) then
8167 if Ekind (Def_Id) = E_Record_Type then
8168 Expand_Freeze_Record_Type (N);
8169 elsif Is_Class_Wide_Type (Def_Id) then
8170 Expand_Freeze_Class_Wide_Type (N);
8171 end if;
8173 -- Freeze processing for array types
8175 elsif Is_Array_Type (Def_Id) then
8176 Expand_Freeze_Array_Type (N);
8178 -- Freeze processing for access types
8180 -- For pool-specific access types, find out the pool object used for
8181 -- this type, needs actual expansion of it in some cases. Here are the
8182 -- different cases :
8184 -- 1. Rep Clause "for Def_Id'Storage_Size use 0;"
8185 -- ---> don't use any storage pool
8187 -- 2. Rep Clause : for Def_Id'Storage_Size use Expr.
8188 -- Expand:
8189 -- Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
8191 -- 3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
8192 -- ---> Storage Pool is the specified one
8194 -- See GNAT Pool packages in the Run-Time for more details
8196 elsif Ekind (Def_Id) in E_Access_Type | E_General_Access_Type then
8197 declare
8198 Loc : constant Source_Ptr := Sloc (N);
8199 Desig_Type : constant Entity_Id := Designated_Type (Def_Id);
8201 Freeze_Action_Typ : Entity_Id;
8202 Pool_Object : Entity_Id;
8204 begin
8205 -- Case 1
8207 -- Rep Clause "for Def_Id'Storage_Size use 0;"
8208 -- ---> don't use any storage pool
8210 if No_Pool_Assigned (Def_Id) then
8211 null;
8213 -- Case 2
8215 -- Rep Clause : for Def_Id'Storage_Size use Expr.
8216 -- ---> Expand:
8217 -- Def_Id__Pool : Stack_Bounded_Pool
8218 -- (Expr, DT'Size, DT'Alignment);
8220 elsif Has_Storage_Size_Clause (Def_Id) then
8221 declare
8222 DT_Align : Node_Id;
8223 DT_Size : Node_Id;
8225 begin
8226 -- For unconstrained composite types we give a size of zero
8227 -- so that the pool knows that it needs a special algorithm
8228 -- for variable size object allocation.
8230 if Is_Composite_Type (Desig_Type)
8231 and then not Is_Constrained (Desig_Type)
8232 then
8233 DT_Size := Make_Integer_Literal (Loc, 0);
8234 DT_Align := Make_Integer_Literal (Loc, Maximum_Alignment);
8236 else
8237 DT_Size :=
8238 Make_Attribute_Reference (Loc,
8239 Prefix => New_Occurrence_Of (Desig_Type, Loc),
8240 Attribute_Name => Name_Max_Size_In_Storage_Elements);
8242 DT_Align :=
8243 Make_Attribute_Reference (Loc,
8244 Prefix => New_Occurrence_Of (Desig_Type, Loc),
8245 Attribute_Name => Name_Alignment);
8246 end if;
8248 Pool_Object :=
8249 Make_Defining_Identifier (Loc,
8250 Chars => New_External_Name (Chars (Def_Id), 'P'));
8252 -- We put the code associated with the pools in the entity
8253 -- that has the later freeze node, usually the access type
8254 -- but it can also be the designated_type; because the pool
8255 -- code requires both those types to be frozen
8257 if Is_Frozen (Desig_Type)
8258 and then (No (Freeze_Node (Desig_Type))
8259 or else Analyzed (Freeze_Node (Desig_Type)))
8260 then
8261 Freeze_Action_Typ := Def_Id;
8263 -- A Taft amendment type cannot get the freeze actions
8264 -- since the full view is not there.
8266 elsif Is_Incomplete_Or_Private_Type (Desig_Type)
8267 and then No (Full_View (Desig_Type))
8268 then
8269 Freeze_Action_Typ := Def_Id;
8271 else
8272 Freeze_Action_Typ := Desig_Type;
8273 end if;
8275 Append_Freeze_Action (Freeze_Action_Typ,
8276 Make_Object_Declaration (Loc,
8277 Defining_Identifier => Pool_Object,
8278 Object_Definition =>
8279 Make_Subtype_Indication (Loc,
8280 Subtype_Mark =>
8281 New_Occurrence_Of
8282 (RTE (RE_Stack_Bounded_Pool), Loc),
8284 Constraint =>
8285 Make_Index_Or_Discriminant_Constraint (Loc,
8286 Constraints => New_List (
8288 -- First discriminant is the Pool Size
8290 New_Occurrence_Of (
8291 Storage_Size_Variable (Def_Id), Loc),
8293 -- Second discriminant is the element size
8295 DT_Size,
8297 -- Third discriminant is the alignment
8299 DT_Align)))));
8300 end;
8302 Set_Associated_Storage_Pool (Def_Id, Pool_Object);
8304 -- Case 3
8306 -- Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
8307 -- ---> Storage Pool is the specified one
8309 -- When compiling in Ada 2012 mode, ensure that the accessibility
8310 -- level of the subpool access type is not deeper than that of the
8311 -- pool_with_subpools.
8313 elsif Ada_Version >= Ada_2012
8314 and then Present (Associated_Storage_Pool (Def_Id))
8315 and then RTU_Loaded (System_Storage_Pools_Subpools)
8316 then
8317 declare
8318 Loc : constant Source_Ptr := Sloc (Def_Id);
8319 Pool : constant Entity_Id :=
8320 Associated_Storage_Pool (Def_Id);
8322 begin
8323 -- It is known that the accessibility level of the access
8324 -- type is deeper than that of the pool.
8326 if Type_Access_Level (Def_Id)
8327 > Static_Accessibility_Level (Pool, Object_Decl_Level)
8328 and then Is_Class_Wide_Type (Etype (Pool))
8329 and then not Accessibility_Checks_Suppressed (Def_Id)
8330 and then not Accessibility_Checks_Suppressed (Pool)
8331 then
8332 -- When the pool is of a class-wide type, it may or may
8333 -- not support subpools depending on the path of
8334 -- derivation. Generate:
8336 -- if Def_Id in RSPWS'Class then
8337 -- raise Program_Error;
8338 -- end if;
8340 Append_Freeze_Action (Def_Id,
8341 Make_If_Statement (Loc,
8342 Condition =>
8343 Make_In (Loc,
8344 Left_Opnd => New_Occurrence_Of (Pool, Loc),
8345 Right_Opnd =>
8346 New_Occurrence_Of
8347 (Class_Wide_Type
8348 (RTE
8349 (RE_Root_Storage_Pool_With_Subpools)),
8350 Loc)),
8351 Then_Statements => New_List (
8352 Make_Raise_Program_Error (Loc,
8353 Reason => PE_Accessibility_Check_Failed))));
8354 end if;
8355 end;
8356 end if;
8358 -- For access-to-controlled types (including class-wide types and
8359 -- Taft-amendment types, which potentially have controlled
8360 -- components), expand the list controller object that will store
8361 -- the dynamically allocated objects. Don't do this transformation
8362 -- for expander-generated access types, except do it for types
8363 -- that are the full view of types derived from other private
8364 -- types and for access types used to implement indirect temps.
8365 -- Also suppress the list controller in the case of a designated
8366 -- type with convention Java, since this is used when binding to
8367 -- Java API specs, where there's no equivalent of a finalization
8368 -- list and we don't want to pull in the finalization support if
8369 -- not needed.
8371 if not Comes_From_Source (Def_Id)
8372 and then not Has_Private_Declaration (Def_Id)
8373 and then not Old_Attr_Util.Indirect_Temps
8374 .Is_Access_Type_For_Indirect_Temp (Def_Id)
8375 then
8376 null;
8378 -- An exception is made for types defined in the run-time because
8379 -- Ada.Tags.Tag itself is such a type and cannot afford this
8380 -- unnecessary overhead that would generates a loop in the
8381 -- expansion scheme. Another exception is if Restrictions
8382 -- (No_Finalization) is active, since then we know nothing is
8383 -- controlled.
8385 elsif Restriction_Active (No_Finalization)
8386 or else In_Runtime (Def_Id)
8387 then
8388 null;
8390 -- Create a finalization master for an access-to-controlled type
8391 -- or an access-to-incomplete type. It is assumed that the full
8392 -- view will be controlled.
8394 elsif Needs_Finalization (Desig_Type)
8395 or else (Is_Incomplete_Type (Desig_Type)
8396 and then No (Full_View (Desig_Type)))
8397 then
8398 Build_Finalization_Master (Def_Id);
8400 -- Create a finalization master when the designated type contains
8401 -- a private component. It is assumed that the full view will be
8402 -- controlled.
8404 elsif Has_Private_Component (Desig_Type) then
8405 Build_Finalization_Master
8406 (Typ => Def_Id,
8407 For_Private => True,
8408 Context_Scope => Scope (Def_Id),
8409 Insertion_Node => Declaration_Node (Desig_Type));
8410 end if;
8411 end;
8413 -- Freeze processing for enumeration types
8415 elsif Ekind (Def_Id) = E_Enumeration_Type then
8417 -- We only have something to do if we have a non-standard
8418 -- representation (i.e. at least one literal whose pos value
8419 -- is not the same as its representation)
8421 if Has_Non_Standard_Rep (Def_Id) then
8422 Expand_Freeze_Enumeration_Type (N);
8423 end if;
8425 -- Private types that are completed by a derivation from a private
8426 -- type have an internally generated full view, that needs to be
8427 -- frozen. This must be done explicitly because the two views share
8428 -- the freeze node, and the underlying full view is not visible when
8429 -- the freeze node is analyzed.
8431 elsif Is_Private_Type (Def_Id)
8432 and then Is_Derived_Type (Def_Id)
8433 and then Present (Full_View (Def_Id))
8434 and then Is_Itype (Full_View (Def_Id))
8435 and then Has_Private_Declaration (Full_View (Def_Id))
8436 and then Freeze_Node (Full_View (Def_Id)) = N
8437 then
8438 Set_Entity (N, Full_View (Def_Id));
8439 Result := Freeze_Type (N);
8440 Set_Entity (N, Def_Id);
8442 -- All other types require no expander action. There are such cases
8443 -- (e.g. task types and protected types). In such cases, the freeze
8444 -- nodes are there for use by Gigi.
8446 end if;
8448 -- Complete the initialization of all pending access types' finalization
8449 -- masters now that the designated type has been is frozen and primitive
8450 -- Finalize_Address generated.
8452 Process_Pending_Access_Types (Def_Id);
8453 Freeze_Stream_Operations (N, Def_Id);
8455 -- Generate the [spec and] body of the invariant procedure tasked with
8456 -- the runtime verification of all invariants that pertain to the type.
8457 -- This includes invariants on the partial and full view, inherited
8458 -- class-wide invariants from parent types or interfaces, and invariants
8459 -- on array elements or record components.
8461 if Is_Interface (Def_Id) then
8463 -- Interfaces are treated as the partial view of a private type in
8464 -- order to achieve uniformity with the general case. As a result, an
8465 -- interface receives only a "partial" invariant procedure which is
8466 -- never called.
8468 if Has_Own_Invariants (Def_Id) then
8469 Build_Invariant_Procedure_Body
8470 (Typ => Def_Id,
8471 Partial_Invariant => Is_Interface (Def_Id));
8472 end if;
8474 -- Non-interface types
8476 -- Do not generate invariant procedure within other assertion
8477 -- subprograms, which may involve local declarations of local
8478 -- subtypes to which these checks do not apply.
8480 else
8481 if Has_Invariants (Def_Id) then
8482 if not Predicate_Check_In_Scope (Def_Id)
8483 or else (Ekind (Current_Scope) = E_Function
8484 and then Is_Predicate_Function (Current_Scope))
8485 then
8486 null;
8487 else
8488 Build_Invariant_Procedure_Body (Def_Id);
8489 end if;
8490 end if;
8492 -- Generate the [spec and] body of the procedure tasked with the
8493 -- run-time verification of pragma Default_Initial_Condition's
8494 -- expression.
8496 if Has_DIC (Def_Id) then
8497 Build_DIC_Procedure_Body (Def_Id);
8498 end if;
8499 end if;
8501 Restore_Ghost_Region (Saved_GM, Saved_IGR);
8503 return Result;
8505 exception
8506 when RE_Not_Available =>
8507 Restore_Ghost_Region (Saved_GM, Saved_IGR);
8509 return False;
8510 end Freeze_Type;
8512 -------------------------
8513 -- Get_Simple_Init_Val --
8514 -------------------------
8516 function Get_Simple_Init_Val
8517 (Typ : Entity_Id;
8518 N : Node_Id;
8519 Size : Uint := No_Uint) return Node_Id
8521 IV_Attribute : constant Boolean :=
8522 Nkind (N) = N_Attribute_Reference
8523 and then Attribute_Name (N) = Name_Invalid_Value;
8525 Loc : constant Source_Ptr := Sloc (N);
8527 procedure Extract_Subtype_Bounds
8528 (Lo_Bound : out Uint;
8529 Hi_Bound : out Uint);
8530 -- Inspect subtype Typ as well its ancestor subtypes and derived types
8531 -- to determine the best known information about the bounds of the type.
8532 -- The output parameters are set as follows:
8534 -- * Lo_Bound - Set to No_Unit when there is no information available,
8535 -- or to the known low bound.
8537 -- * Hi_Bound - Set to No_Unit when there is no information available,
8538 -- or to the known high bound.
8540 function Simple_Init_Array_Type return Node_Id;
8541 -- Build an expression to initialize array type Typ
8543 function Simple_Init_Defaulted_Type return Node_Id;
8544 -- Build an expression to initialize type Typ which is subject to
8545 -- aspect Default_Value.
8547 function Simple_Init_Initialize_Scalars_Type
8548 (Size_To_Use : Uint) return Node_Id;
8549 -- Build an expression to initialize scalar type Typ which is subject to
8550 -- pragma Initialize_Scalars. Size_To_Use is the size of the object.
8552 function Simple_Init_Normalize_Scalars_Type
8553 (Size_To_Use : Uint) return Node_Id;
8554 -- Build an expression to initialize scalar type Typ which is subject to
8555 -- pragma Normalize_Scalars. Size_To_Use is the size of the object.
8557 function Simple_Init_Private_Type return Node_Id;
8558 -- Build an expression to initialize private type Typ
8560 function Simple_Init_Scalar_Type return Node_Id;
8561 -- Build an expression to initialize scalar type Typ
8563 ----------------------------
8564 -- Extract_Subtype_Bounds --
8565 ----------------------------
8567 procedure Extract_Subtype_Bounds
8568 (Lo_Bound : out Uint;
8569 Hi_Bound : out Uint)
8571 ST1 : Entity_Id;
8572 ST2 : Entity_Id;
8573 Lo : Node_Id;
8574 Hi : Node_Id;
8575 Lo_Val : Uint;
8576 Hi_Val : Uint;
8578 begin
8579 Lo_Bound := No_Uint;
8580 Hi_Bound := No_Uint;
8582 -- Loop to climb ancestor subtypes and derived types
8584 ST1 := Typ;
8585 loop
8586 if not Is_Discrete_Type (ST1) then
8587 return;
8588 end if;
8590 Lo := Type_Low_Bound (ST1);
8591 Hi := Type_High_Bound (ST1);
8593 if Compile_Time_Known_Value (Lo) then
8594 Lo_Val := Expr_Value (Lo);
8596 if No (Lo_Bound) or else Lo_Bound < Lo_Val then
8597 Lo_Bound := Lo_Val;
8598 end if;
8599 end if;
8601 if Compile_Time_Known_Value (Hi) then
8602 Hi_Val := Expr_Value (Hi);
8604 if No (Hi_Bound) or else Hi_Bound > Hi_Val then
8605 Hi_Bound := Hi_Val;
8606 end if;
8607 end if;
8609 ST2 := Ancestor_Subtype (ST1);
8611 if No (ST2) then
8612 ST2 := Etype (ST1);
8613 end if;
8615 exit when ST1 = ST2;
8616 ST1 := ST2;
8617 end loop;
8618 end Extract_Subtype_Bounds;
8620 ----------------------------
8621 -- Simple_Init_Array_Type --
8622 ----------------------------
8624 function Simple_Init_Array_Type return Node_Id is
8625 Comp_Typ : constant Entity_Id := Component_Type (Typ);
8627 function Simple_Init_Dimension (Index : Node_Id) return Node_Id;
8628 -- Initialize a single array dimension with index constraint Index
8630 --------------------
8631 -- Simple_Init_Dimension --
8632 --------------------
8634 function Simple_Init_Dimension (Index : Node_Id) return Node_Id is
8635 begin
8636 -- Process the current dimension
8638 if Present (Index) then
8640 -- Build a suitable "others" aggregate for the next dimension,
8641 -- or initialize the component itself. Generate:
8643 -- (others => ...)
8645 return
8646 Make_Aggregate (Loc,
8647 Component_Associations => New_List (
8648 Make_Component_Association (Loc,
8649 Choices => New_List (Make_Others_Choice (Loc)),
8650 Expression =>
8651 Simple_Init_Dimension (Next_Index (Index)))));
8653 -- Otherwise all dimensions have been processed. Initialize the
8654 -- component itself.
8656 else
8657 return
8658 Get_Simple_Init_Val
8659 (Typ => Comp_Typ,
8660 N => N,
8661 Size => Esize (Comp_Typ));
8662 end if;
8663 end Simple_Init_Dimension;
8665 -- Start of processing for Simple_Init_Array_Type
8667 begin
8668 return Simple_Init_Dimension (First_Index (Typ));
8669 end Simple_Init_Array_Type;
8671 --------------------------------
8672 -- Simple_Init_Defaulted_Type --
8673 --------------------------------
8675 function Simple_Init_Defaulted_Type return Node_Id is
8676 Subtyp : Entity_Id := First_Subtype (Typ);
8678 begin
8679 -- When the first subtype is private, retrieve the expression of the
8680 -- Default_Value from the underlying type.
8682 if Is_Private_Type (Subtyp) then
8683 Subtyp := Full_View (Subtyp);
8684 end if;
8686 -- Use the Sloc of the context node when constructing the initial
8687 -- value because the expression of Default_Value may come from a
8688 -- different unit. Updating the Sloc will result in accurate error
8689 -- diagnostics.
8691 return
8692 OK_Convert_To
8693 (Typ => Typ,
8694 Expr =>
8695 New_Copy_Tree
8696 (Source => Default_Aspect_Value (Subtyp),
8697 New_Sloc => Loc));
8698 end Simple_Init_Defaulted_Type;
8700 -----------------------------------------
8701 -- Simple_Init_Initialize_Scalars_Type --
8702 -----------------------------------------
8704 function Simple_Init_Initialize_Scalars_Type
8705 (Size_To_Use : Uint) return Node_Id
8707 Float_Typ : Entity_Id;
8708 Hi_Bound : Uint;
8709 Lo_Bound : Uint;
8710 Scal_Typ : Scalar_Id;
8712 begin
8713 Extract_Subtype_Bounds (Lo_Bound, Hi_Bound);
8715 -- Float types
8717 if Is_Floating_Point_Type (Typ) then
8718 Float_Typ := Root_Type (Typ);
8720 if Float_Typ = Standard_Short_Float then
8721 Scal_Typ := Name_Short_Float;
8722 elsif Float_Typ = Standard_Float then
8723 Scal_Typ := Name_Float;
8724 elsif Float_Typ = Standard_Long_Float then
8725 Scal_Typ := Name_Long_Float;
8726 else pragma Assert (Float_Typ = Standard_Long_Long_Float);
8727 Scal_Typ := Name_Long_Long_Float;
8728 end if;
8730 -- If zero is invalid, it is a convenient value to use that is for
8731 -- sure an appropriate invalid value in all situations.
8733 elsif Present (Lo_Bound) and then Lo_Bound > Uint_0 then
8734 return Make_Integer_Literal (Loc, 0);
8736 -- Unsigned types
8738 elsif Is_Unsigned_Type (Typ) then
8739 if Size_To_Use <= 8 then
8740 Scal_Typ := Name_Unsigned_8;
8741 elsif Size_To_Use <= 16 then
8742 Scal_Typ := Name_Unsigned_16;
8743 elsif Size_To_Use <= 32 then
8744 Scal_Typ := Name_Unsigned_32;
8745 elsif Size_To_Use <= 64 then
8746 Scal_Typ := Name_Unsigned_64;
8747 else
8748 Scal_Typ := Name_Unsigned_128;
8749 end if;
8751 -- Signed types
8753 else
8754 if Size_To_Use <= 8 then
8755 Scal_Typ := Name_Signed_8;
8756 elsif Size_To_Use <= 16 then
8757 Scal_Typ := Name_Signed_16;
8758 elsif Size_To_Use <= 32 then
8759 Scal_Typ := Name_Signed_32;
8760 elsif Size_To_Use <= 64 then
8761 Scal_Typ := Name_Signed_64;
8762 else
8763 Scal_Typ := Name_Signed_128;
8764 end if;
8765 end if;
8767 -- Use the values specified by pragma Initialize_Scalars or the ones
8768 -- provided by the binder. Higher precedence is given to the pragma.
8770 return Invalid_Scalar_Value (Loc, Scal_Typ);
8771 end Simple_Init_Initialize_Scalars_Type;
8773 ----------------------------------------
8774 -- Simple_Init_Normalize_Scalars_Type --
8775 ----------------------------------------
8777 function Simple_Init_Normalize_Scalars_Type
8778 (Size_To_Use : Uint) return Node_Id
8780 Signed_Size : constant Uint := UI_Min (Uint_63, Size_To_Use - 1);
8782 Expr : Node_Id;
8783 Hi_Bound : Uint;
8784 Lo_Bound : Uint;
8786 begin
8787 Extract_Subtype_Bounds (Lo_Bound, Hi_Bound);
8789 -- If zero is invalid, it is a convenient value to use that is for
8790 -- sure an appropriate invalid value in all situations.
8792 if Present (Lo_Bound) and then Lo_Bound > Uint_0 then
8793 Expr := Make_Integer_Literal (Loc, 0);
8795 -- Cases where all one bits is the appropriate invalid value
8797 -- For modular types, all 1 bits is either invalid or valid. If it
8798 -- is valid, then there is nothing that can be done since there are
8799 -- no invalid values (we ruled out zero already).
8801 -- For signed integer types that have no negative values, either
8802 -- there is room for negative values, or there is not. If there
8803 -- is, then all 1-bits may be interpreted as minus one, which is
8804 -- certainly invalid. Alternatively it is treated as the largest
8805 -- positive value, in which case the observation for modular types
8806 -- still applies.
8808 -- For float types, all 1-bits is a NaN (not a number), which is
8809 -- certainly an appropriately invalid value.
8811 elsif Is_Enumeration_Type (Typ)
8812 or else Is_Floating_Point_Type (Typ)
8813 or else Is_Unsigned_Type (Typ)
8814 then
8815 Expr := Make_Integer_Literal (Loc, 2 ** Size_To_Use - 1);
8817 -- Resolve as Long_Long_Long_Unsigned, because the largest number
8818 -- we can generate is out of range of universal integer.
8820 Analyze_And_Resolve (Expr, Standard_Long_Long_Long_Unsigned);
8822 -- Case of signed types
8824 else
8825 -- Normally we like to use the most negative number. The one
8826 -- exception is when this number is in the known subtype range and
8827 -- the largest positive number is not in the known subtype range.
8829 -- For this exceptional case, use largest positive value
8831 if Present (Lo_Bound) and then Present (Hi_Bound)
8832 and then Lo_Bound <= (-(2 ** Signed_Size))
8833 and then Hi_Bound < 2 ** Signed_Size
8834 then
8835 Expr := Make_Integer_Literal (Loc, 2 ** Signed_Size - 1);
8837 -- Normal case of largest negative value
8839 else
8840 Expr := Make_Integer_Literal (Loc, -(2 ** Signed_Size));
8841 end if;
8842 end if;
8844 return Expr;
8845 end Simple_Init_Normalize_Scalars_Type;
8847 ------------------------------
8848 -- Simple_Init_Private_Type --
8849 ------------------------------
8851 function Simple_Init_Private_Type return Node_Id is
8852 Under_Typ : constant Entity_Id := Underlying_Type (Typ);
8853 Expr : Node_Id;
8855 begin
8856 -- The availability of the underlying view must be checked by routine
8857 -- Needs_Simple_Initialization.
8859 pragma Assert (Present (Under_Typ));
8861 Expr := Get_Simple_Init_Val (Under_Typ, N, Size);
8863 -- If the initial value is null or an aggregate, qualify it with the
8864 -- underlying type in order to provide a proper context.
8866 if Nkind (Expr) in N_Aggregate | N_Null then
8867 Expr :=
8868 Make_Qualified_Expression (Loc,
8869 Subtype_Mark => New_Occurrence_Of (Under_Typ, Loc),
8870 Expression => Expr);
8871 end if;
8873 Expr := Unchecked_Convert_To (Typ, Expr);
8875 -- Do not truncate the result when scalar types are involved and
8876 -- Initialize/Normalize_Scalars is in effect.
8878 if Nkind (Expr) = N_Unchecked_Type_Conversion
8879 and then Is_Scalar_Type (Under_Typ)
8880 then
8881 Set_No_Truncation (Expr);
8882 end if;
8884 return Expr;
8885 end Simple_Init_Private_Type;
8887 -----------------------------
8888 -- Simple_Init_Scalar_Type --
8889 -----------------------------
8891 function Simple_Init_Scalar_Type return Node_Id is
8892 Expr : Node_Id;
8893 Size_To_Use : Uint;
8895 begin
8896 pragma Assert (Init_Or_Norm_Scalars or IV_Attribute);
8898 -- Determine the size of the object. This is either the size provided
8899 -- by the caller, or the Esize of the scalar type.
8901 if No (Size) or else Size <= Uint_0 then
8902 Size_To_Use := UI_Max (Uint_1, Esize (Typ));
8903 else
8904 Size_To_Use := Size;
8905 end if;
8907 -- The maximum size to use is System_Max_Integer_Size bits. This
8908 -- will create values of type Long_Long_Long_Unsigned and the range
8909 -- must fit this type.
8911 if Present (Size_To_Use)
8912 and then Size_To_Use > System_Max_Integer_Size
8913 then
8914 Size_To_Use := UI_From_Int (System_Max_Integer_Size);
8915 end if;
8917 if Normalize_Scalars and then not IV_Attribute then
8918 Expr := Simple_Init_Normalize_Scalars_Type (Size_To_Use);
8919 else
8920 Expr := Simple_Init_Initialize_Scalars_Type (Size_To_Use);
8921 end if;
8923 -- The final expression is obtained by doing an unchecked conversion
8924 -- of this result to the base type of the required subtype. Use the
8925 -- base type to prevent the unchecked conversion from chopping bits,
8926 -- and then we set Kill_Range_Check to preserve the "bad" value.
8928 Expr := Unchecked_Convert_To (Base_Type (Typ), Expr);
8930 -- Ensure that the expression is not truncated since the "bad" bits
8931 -- are desired, and also kill the range checks.
8933 if Nkind (Expr) = N_Unchecked_Type_Conversion then
8934 Set_Kill_Range_Check (Expr);
8935 Set_No_Truncation (Expr);
8936 end if;
8938 return Expr;
8939 end Simple_Init_Scalar_Type;
8941 -- Start of processing for Get_Simple_Init_Val
8943 begin
8944 if Is_Private_Type (Typ) then
8945 return Simple_Init_Private_Type;
8947 elsif Is_Scalar_Type (Typ) then
8948 if Has_Default_Aspect (Typ) then
8949 return Simple_Init_Defaulted_Type;
8950 else
8951 return Simple_Init_Scalar_Type;
8952 end if;
8954 -- Array type with Initialize or Normalize_Scalars
8956 elsif Is_Array_Type (Typ) then
8957 pragma Assert (Init_Or_Norm_Scalars);
8958 return Simple_Init_Array_Type;
8960 -- Access type is initialized to null
8962 elsif Is_Access_Type (Typ) then
8963 return Make_Null (Loc);
8965 -- No other possibilities should arise, since we should only be calling
8966 -- Get_Simple_Init_Val if Needs_Simple_Initialization returned True,
8967 -- indicating one of the above cases held.
8969 else
8970 raise Program_Error;
8971 end if;
8973 exception
8974 when RE_Not_Available =>
8975 return Empty;
8976 end Get_Simple_Init_Val;
8978 ------------------------------
8979 -- Has_New_Non_Standard_Rep --
8980 ------------------------------
8982 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
8983 begin
8984 if not Is_Derived_Type (T) then
8985 return Has_Non_Standard_Rep (T)
8986 or else Has_Non_Standard_Rep (Root_Type (T));
8988 -- If Has_Non_Standard_Rep is not set on the derived type, the
8989 -- representation is fully inherited.
8991 elsif not Has_Non_Standard_Rep (T) then
8992 return False;
8994 else
8995 return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
8997 -- May need a more precise check here: the First_Rep_Item may be a
8998 -- stream attribute, which does not affect the representation of the
8999 -- type ???
9001 end if;
9002 end Has_New_Non_Standard_Rep;
9004 ----------------------
9005 -- Inline_Init_Proc --
9006 ----------------------
9008 function Inline_Init_Proc (Typ : Entity_Id) return Boolean is
9009 begin
9010 -- The initialization proc of protected records is not worth inlining.
9011 -- In addition, when compiled for another unit for inlining purposes,
9012 -- it may make reference to entities that have not been elaborated yet.
9013 -- The initialization proc of records that need finalization contains
9014 -- a nested clean-up procedure that makes it impractical to inline as
9015 -- well, except for simple controlled types themselves. And similar
9016 -- considerations apply to task types.
9018 if Is_Concurrent_Type (Typ) then
9019 return False;
9021 elsif Needs_Finalization (Typ) and then not Is_Controlled (Typ) then
9022 return False;
9024 elsif Has_Task (Typ) then
9025 return False;
9027 else
9028 return True;
9029 end if;
9030 end Inline_Init_Proc;
9032 ----------------
9033 -- In_Runtime --
9034 ----------------
9036 function In_Runtime (E : Entity_Id) return Boolean is
9037 S1 : Entity_Id;
9039 begin
9040 S1 := Scope (E);
9041 while Scope (S1) /= Standard_Standard loop
9042 S1 := Scope (S1);
9043 end loop;
9045 return Is_RTU (S1, System) or else Is_RTU (S1, Ada);
9046 end In_Runtime;
9048 package body Initialization_Control is
9050 ------------------------
9051 -- Requires_Late_Init --
9052 ------------------------
9054 function Requires_Late_Init
9055 (Decl : Node_Id;
9056 Rec_Type : Entity_Id) return Boolean
9058 References_Current_Instance : Boolean := False;
9059 Has_Access_Discriminant : Boolean := False;
9060 Has_Internal_Call : Boolean := False;
9062 function Find_Access_Discriminant
9063 (N : Node_Id) return Traverse_Result;
9064 -- Look for a name denoting an access discriminant
9066 function Find_Current_Instance
9067 (N : Node_Id) return Traverse_Result;
9068 -- Look for a reference to the current instance of the type
9070 function Find_Internal_Call
9071 (N : Node_Id) return Traverse_Result;
9072 -- Look for an internal protected function call
9074 ------------------------------
9075 -- Find_Access_Discriminant --
9076 ------------------------------
9078 function Find_Access_Discriminant
9079 (N : Node_Id) return Traverse_Result is
9080 begin
9081 if Is_Entity_Name (N)
9082 and then Denotes_Discriminant (N)
9083 and then Is_Access_Type (Etype (N))
9084 then
9085 Has_Access_Discriminant := True;
9086 return Abandon;
9087 else
9088 return OK;
9089 end if;
9090 end Find_Access_Discriminant;
9092 ---------------------------
9093 -- Find_Current_Instance --
9094 ---------------------------
9096 function Find_Current_Instance
9097 (N : Node_Id) return Traverse_Result is
9098 begin
9099 if Is_Entity_Name (N)
9100 and then Present (Entity (N))
9101 and then Is_Current_Instance (N)
9102 then
9103 References_Current_Instance := True;
9104 return Abandon;
9105 else
9106 return OK;
9107 end if;
9108 end Find_Current_Instance;
9110 ------------------------
9111 -- Find_Internal_Call --
9112 ------------------------
9114 function Find_Internal_Call (N : Node_Id) return Traverse_Result is
9116 function Call_Scope (N : Node_Id) return Entity_Id;
9117 -- Return the scope enclosing a given call node N
9119 ----------------
9120 -- Call_Scope --
9121 ----------------
9123 function Call_Scope (N : Node_Id) return Entity_Id is
9124 Nam : constant Node_Id := Name (N);
9125 begin
9126 if Nkind (Nam) = N_Selected_Component then
9127 return Scope (Entity (Prefix (Nam)));
9128 else
9129 return Scope (Entity (Nam));
9130 end if;
9131 end Call_Scope;
9133 begin
9134 if Nkind (N) = N_Function_Call
9135 and then Call_Scope (N)
9136 = Corresponding_Concurrent_Type (Rec_Type)
9137 then
9138 Has_Internal_Call := True;
9139 return Abandon;
9140 else
9141 return OK;
9142 end if;
9143 end Find_Internal_Call;
9145 procedure Search_Access_Discriminant is new
9146 Traverse_Proc (Find_Access_Discriminant);
9148 procedure Search_Current_Instance is new
9149 Traverse_Proc (Find_Current_Instance);
9151 procedure Search_Internal_Call is new
9152 Traverse_Proc (Find_Internal_Call);
9154 -- Start of processing for Requires_Late_Init
9156 begin
9157 -- A component of an object is said to require late initialization
9158 -- if:
9160 -- it has an access discriminant value constrained by a per-object
9161 -- expression;
9163 if Has_Access_Constraint (Defining_Identifier (Decl))
9164 and then No (Expression (Decl))
9165 then
9166 return True;
9168 elsif Present (Expression (Decl)) then
9170 -- it has an initialization expression that includes a name
9171 -- denoting an access discriminant;
9173 Search_Access_Discriminant (Expression (Decl));
9175 if Has_Access_Discriminant then
9176 return True;
9177 end if;
9179 -- or it has an initialization expression that includes a
9180 -- reference to the current instance of the type either by
9181 -- name...
9183 Search_Current_Instance (Expression (Decl));
9185 if References_Current_Instance then
9186 return True;
9187 end if;
9189 -- ...or implicitly as the target object of a call.
9191 if Is_Protected_Record_Type (Rec_Type) then
9192 Search_Internal_Call (Expression (Decl));
9194 if Has_Internal_Call then
9195 return True;
9196 end if;
9197 end if;
9198 end if;
9200 return False;
9201 end Requires_Late_Init;
9203 -----------------------------
9204 -- Has_Late_Init_Component --
9205 -----------------------------
9207 function Has_Late_Init_Component
9208 (Tagged_Rec_Type : Entity_Id) return Boolean
9210 Comp_Id : Entity_Id :=
9211 First_Component (Implementation_Base_Type (Tagged_Rec_Type));
9212 begin
9213 while Present (Comp_Id) loop
9214 if Requires_Late_Init (Decl => Parent (Comp_Id),
9215 Rec_Type => Tagged_Rec_Type)
9216 then
9217 return True; -- found a component that requires late init
9219 elsif Chars (Comp_Id) = Name_uParent
9220 and then Has_Late_Init_Component (Etype (Comp_Id))
9221 then
9222 return True; -- an ancestor type has a late init component
9223 end if;
9225 Next_Component (Comp_Id);
9226 end loop;
9228 return False;
9229 end Has_Late_Init_Component;
9231 ------------------------
9232 -- Tag_Init_Condition --
9233 ------------------------
9235 function Tag_Init_Condition
9236 (Loc : Source_Ptr;
9237 Init_Control_Formal : Entity_Id) return Node_Id is
9238 begin
9239 return Make_Op_Eq (Loc,
9240 New_Occurrence_Of (Init_Control_Formal, Loc),
9241 Make_Mode_Literal (Loc, Full_Init));
9242 end Tag_Init_Condition;
9244 --------------------------
9245 -- Early_Init_Condition --
9246 --------------------------
9248 function Early_Init_Condition
9249 (Loc : Source_Ptr;
9250 Init_Control_Formal : Entity_Id) return Node_Id is
9251 begin
9252 return Make_Op_Ne (Loc,
9253 New_Occurrence_Of (Init_Control_Formal, Loc),
9254 Make_Mode_Literal (Loc, Late_Init_Only));
9255 end Early_Init_Condition;
9257 -------------------------
9258 -- Late_Init_Condition --
9259 -------------------------
9261 function Late_Init_Condition
9262 (Loc : Source_Ptr;
9263 Init_Control_Formal : Entity_Id) return Node_Id is
9264 begin
9265 return Make_Op_Ne (Loc,
9266 New_Occurrence_Of (Init_Control_Formal, Loc),
9267 Make_Mode_Literal (Loc, Early_Init_Only));
9268 end Late_Init_Condition;
9270 end Initialization_Control;
9272 ----------------------------
9273 -- Initialization_Warning --
9274 ----------------------------
9276 procedure Initialization_Warning (E : Entity_Id) is
9277 Warning_Needed : Boolean;
9279 begin
9280 Warning_Needed := False;
9282 if Ekind (Current_Scope) = E_Package
9283 and then Static_Elaboration_Desired (Current_Scope)
9284 then
9285 if Is_Type (E) then
9286 if Is_Record_Type (E) then
9287 if Has_Discriminants (E)
9288 or else Is_Limited_Type (E)
9289 or else Has_Non_Standard_Rep (E)
9290 then
9291 Warning_Needed := True;
9293 else
9294 -- Verify that at least one component has an initialization
9295 -- expression. No need for a warning on a type if all its
9296 -- components have no initialization.
9298 declare
9299 Comp : Entity_Id;
9301 begin
9302 Comp := First_Component (E);
9303 while Present (Comp) loop
9304 pragma Assert
9305 (Nkind (Parent (Comp)) = N_Component_Declaration);
9307 if Present (Expression (Parent (Comp))) then
9308 Warning_Needed := True;
9309 exit;
9310 end if;
9312 Next_Component (Comp);
9313 end loop;
9314 end;
9315 end if;
9317 if Warning_Needed then
9318 Error_Msg_N
9319 ("objects of the type cannot be initialized statically "
9320 & "by default??", Parent (E));
9321 end if;
9322 end if;
9324 else
9325 Error_Msg_N ("object cannot be initialized statically??", E);
9326 end if;
9327 end if;
9328 end Initialization_Warning;
9330 ------------------
9331 -- Init_Formals --
9332 ------------------
9334 function Init_Formals (Typ : Entity_Id; Proc_Id : Entity_Id) return List_Id
9336 Loc : constant Source_Ptr := Sloc (Typ);
9337 Unc_Arr : constant Boolean :=
9338 Is_Array_Type (Typ) and then not Is_Constrained (Typ);
9339 With_Prot : constant Boolean :=
9340 Has_Protected (Typ)
9341 or else (Is_Record_Type (Typ)
9342 and then Is_Protected_Record_Type (Typ));
9343 With_Task : constant Boolean :=
9344 not Global_No_Tasking
9345 and then
9346 (Has_Task (Typ)
9347 or else (Is_Record_Type (Typ)
9348 and then Is_Task_Record_Type (Typ)));
9349 Formals : List_Id;
9351 begin
9352 -- The first parameter is always _Init : [in] out Typ. Note that we need
9353 -- it to be in/out in the case of an unconstrained array, because of the
9354 -- need to have the bounds, and in the case of protected or task record
9355 -- value, because there are default record fields that may be referenced
9356 -- in the generated initialization routine.
9358 Formals := New_List (
9359 Make_Parameter_Specification (Loc,
9360 Defining_Identifier => Make_Defining_Identifier (Loc, Name_uInit),
9361 In_Present => Unc_Arr or else With_Prot or else With_Task,
9362 Out_Present => True,
9363 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
9365 -- For task record value, or type that contains tasks, add two more
9366 -- formals, _Master : Master_Id and _Chain : in out Activation_Chain
9367 -- We also add these parameters for the task record type case.
9369 if With_Task then
9370 Append_To (Formals,
9371 Make_Parameter_Specification (Loc,
9372 Defining_Identifier =>
9373 Make_Defining_Identifier (Loc, Name_uMaster),
9374 Parameter_Type =>
9375 New_Occurrence_Of (Standard_Integer, Loc)));
9377 Set_Has_Master_Entity (Proc_Id);
9379 -- Add _Chain (not done for sequential elaboration policy, see
9380 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
9382 if Partition_Elaboration_Policy /= 'S' then
9383 Append_To (Formals,
9384 Make_Parameter_Specification (Loc,
9385 Defining_Identifier =>
9386 Make_Defining_Identifier (Loc, Name_uChain),
9387 In_Present => True,
9388 Out_Present => True,
9389 Parameter_Type =>
9390 New_Occurrence_Of (RTE (RE_Activation_Chain), Loc)));
9391 end if;
9393 Append_To (Formals,
9394 Make_Parameter_Specification (Loc,
9395 Defining_Identifier =>
9396 Make_Defining_Identifier (Loc, Name_uTask_Name),
9397 In_Present => True,
9398 Parameter_Type => New_Occurrence_Of (Standard_String, Loc)));
9399 end if;
9401 -- Due to certain edge cases such as arrays with null-excluding
9402 -- components being built with the secondary stack it becomes necessary
9403 -- to add a formal to the Init_Proc which controls whether we raise
9404 -- Constraint_Errors on generated calls for internal object
9405 -- declarations.
9407 if Needs_Conditional_Null_Excluding_Check (Typ) then
9408 Append_To (Formals,
9409 Make_Parameter_Specification (Loc,
9410 Defining_Identifier =>
9411 Make_Defining_Identifier (Loc,
9412 New_External_Name (Chars
9413 (Component_Type (Typ)), "_skip_null_excluding_check")),
9414 Expression => New_Occurrence_Of (Standard_False, Loc),
9415 In_Present => True,
9416 Parameter_Type =>
9417 New_Occurrence_Of (Standard_Boolean, Loc)));
9418 end if;
9420 return Formals;
9422 exception
9423 when RE_Not_Available =>
9424 return Empty_List;
9425 end Init_Formals;
9427 -------------------------
9428 -- Init_Secondary_Tags --
9429 -------------------------
9431 procedure Init_Secondary_Tags
9432 (Typ : Entity_Id;
9433 Target : Node_Id;
9434 Init_Tags_List : List_Id;
9435 Stmts_List : List_Id;
9436 Fixed_Comps : Boolean := True;
9437 Variable_Comps : Boolean := True)
9439 Loc : constant Source_Ptr := Sloc (Target);
9441 -- Inherit the C++ tag of the secondary dispatch table of Typ associated
9442 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
9444 procedure Initialize_Tag
9445 (Typ : Entity_Id;
9446 Iface : Entity_Id;
9447 Tag_Comp : Entity_Id;
9448 Iface_Tag : Node_Id);
9449 -- Initialize the tag of the secondary dispatch table of Typ associated
9450 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
9451 -- Compiling under the CPP full ABI compatibility mode, if the ancestor
9452 -- of Typ CPP tagged type we generate code to inherit the contents of
9453 -- the dispatch table directly from the ancestor.
9455 --------------------
9456 -- Initialize_Tag --
9457 --------------------
9459 procedure Initialize_Tag
9460 (Typ : Entity_Id;
9461 Iface : Entity_Id;
9462 Tag_Comp : Entity_Id;
9463 Iface_Tag : Node_Id)
9465 Comp_Typ : Entity_Id;
9466 Offset_To_Top_Comp : Entity_Id := Empty;
9468 begin
9469 -- Initialize pointer to secondary DT associated with the interface
9471 if not Is_Ancestor (Iface, Typ, Use_Full_View => True) then
9472 Append_To (Init_Tags_List,
9473 Make_Assignment_Statement (Loc,
9474 Name =>
9475 Make_Selected_Component (Loc,
9476 Prefix => New_Copy_Tree (Target),
9477 Selector_Name => New_Occurrence_Of (Tag_Comp, Loc)),
9478 Expression =>
9479 New_Occurrence_Of (Iface_Tag, Loc)));
9480 end if;
9482 Comp_Typ := Scope (Tag_Comp);
9484 -- Initialize the entries of the table of interfaces. We generate a
9485 -- different call when the parent of the type has variable size
9486 -- components.
9488 if Comp_Typ /= Etype (Comp_Typ)
9489 and then Is_Variable_Size_Record (Etype (Comp_Typ))
9490 and then Chars (Tag_Comp) /= Name_uTag
9491 then
9492 pragma Assert (Present (DT_Offset_To_Top_Func (Tag_Comp)));
9494 -- Issue error if Set_Dynamic_Offset_To_Top is not available in a
9495 -- configurable run-time environment.
9497 if not RTE_Available (RE_Set_Dynamic_Offset_To_Top) then
9498 Error_Msg_CRT
9499 ("variable size record with interface types", Typ);
9500 return;
9501 end if;
9503 -- Generate:
9504 -- Set_Dynamic_Offset_To_Top
9505 -- (This => Init,
9506 -- Prim_T => Typ'Tag,
9507 -- Interface_T => Iface'Tag,
9508 -- Offset_Value => n,
9509 -- Offset_Func => Fn'Unrestricted_Access)
9511 Append_To (Stmts_List,
9512 Make_Procedure_Call_Statement (Loc,
9513 Name =>
9514 New_Occurrence_Of (RTE (RE_Set_Dynamic_Offset_To_Top), Loc),
9515 Parameter_Associations => New_List (
9516 Make_Attribute_Reference (Loc,
9517 Prefix => New_Copy_Tree (Target),
9518 Attribute_Name => Name_Address),
9520 Unchecked_Convert_To (RTE (RE_Tag),
9521 New_Occurrence_Of
9522 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc)),
9524 Unchecked_Convert_To (RTE (RE_Tag),
9525 New_Occurrence_Of
9526 (Node (First_Elmt (Access_Disp_Table (Iface))),
9527 Loc)),
9529 Unchecked_Convert_To
9530 (RTE (RE_Storage_Offset),
9531 Make_Op_Minus (Loc,
9532 Make_Attribute_Reference (Loc,
9533 Prefix =>
9534 Make_Selected_Component (Loc,
9535 Prefix => New_Copy_Tree (Target),
9536 Selector_Name =>
9537 New_Occurrence_Of (Tag_Comp, Loc)),
9538 Attribute_Name => Name_Position))),
9540 Unchecked_Convert_To (RTE (RE_Offset_To_Top_Function_Ptr),
9541 Make_Attribute_Reference (Loc,
9542 Prefix => New_Occurrence_Of
9543 (DT_Offset_To_Top_Func (Tag_Comp), Loc),
9544 Attribute_Name => Name_Unrestricted_Access)))));
9546 -- In this case the next component stores the value of the offset
9547 -- to the top.
9549 Offset_To_Top_Comp := Next_Entity (Tag_Comp);
9550 pragma Assert (Present (Offset_To_Top_Comp));
9552 Append_To (Init_Tags_List,
9553 Make_Assignment_Statement (Loc,
9554 Name =>
9555 Make_Selected_Component (Loc,
9556 Prefix => New_Copy_Tree (Target),
9557 Selector_Name =>
9558 New_Occurrence_Of (Offset_To_Top_Comp, Loc)),
9560 Expression =>
9561 Make_Op_Minus (Loc,
9562 Make_Attribute_Reference (Loc,
9563 Prefix =>
9564 Make_Selected_Component (Loc,
9565 Prefix => New_Copy_Tree (Target),
9566 Selector_Name => New_Occurrence_Of (Tag_Comp, Loc)),
9567 Attribute_Name => Name_Position))));
9569 -- Normal case: No discriminants in the parent type
9571 else
9572 -- Don't need to set any value if the offset-to-top field is
9573 -- statically set or if this interface shares the primary
9574 -- dispatch table.
9576 if not Building_Static_Secondary_DT (Typ)
9577 and then not Is_Ancestor (Iface, Typ, Use_Full_View => True)
9578 then
9579 Append_To (Stmts_List,
9580 Build_Set_Static_Offset_To_Top (Loc,
9581 Iface_Tag => New_Occurrence_Of (Iface_Tag, Loc),
9582 Offset_Value =>
9583 Unchecked_Convert_To (RTE (RE_Storage_Offset),
9584 Make_Op_Minus (Loc,
9585 Make_Attribute_Reference (Loc,
9586 Prefix =>
9587 Make_Selected_Component (Loc,
9588 Prefix => New_Copy_Tree (Target),
9589 Selector_Name =>
9590 New_Occurrence_Of (Tag_Comp, Loc)),
9591 Attribute_Name => Name_Position)))));
9592 end if;
9594 -- Generate:
9595 -- Register_Interface_Offset
9596 -- (Prim_T => Typ'Tag,
9597 -- Interface_T => Iface'Tag,
9598 -- Is_Constant => True,
9599 -- Offset_Value => n,
9600 -- Offset_Func => null);
9602 if not Building_Static_Secondary_DT (Typ)
9603 and then RTE_Available (RE_Register_Interface_Offset)
9604 then
9605 Append_To (Stmts_List,
9606 Make_Procedure_Call_Statement (Loc,
9607 Name =>
9608 New_Occurrence_Of
9609 (RTE (RE_Register_Interface_Offset), Loc),
9610 Parameter_Associations => New_List (
9611 Unchecked_Convert_To (RTE (RE_Tag),
9612 New_Occurrence_Of
9613 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc)),
9615 Unchecked_Convert_To (RTE (RE_Tag),
9616 New_Occurrence_Of
9617 (Node (First_Elmt (Access_Disp_Table (Iface))), Loc)),
9619 New_Occurrence_Of (Standard_True, Loc),
9621 Unchecked_Convert_To (RTE (RE_Storage_Offset),
9622 Make_Op_Minus (Loc,
9623 Make_Attribute_Reference (Loc,
9624 Prefix =>
9625 Make_Selected_Component (Loc,
9626 Prefix => New_Copy_Tree (Target),
9627 Selector_Name =>
9628 New_Occurrence_Of (Tag_Comp, Loc)),
9629 Attribute_Name => Name_Position))),
9631 Make_Null (Loc))));
9632 end if;
9633 end if;
9634 end Initialize_Tag;
9636 -- Local variables
9638 Full_Typ : Entity_Id;
9639 Ifaces_List : Elist_Id;
9640 Ifaces_Comp_List : Elist_Id;
9641 Ifaces_Tag_List : Elist_Id;
9642 Iface_Elmt : Elmt_Id;
9643 Iface_Comp_Elmt : Elmt_Id;
9644 Iface_Tag_Elmt : Elmt_Id;
9645 Tag_Comp : Node_Id;
9646 In_Variable_Pos : Boolean;
9648 -- Start of processing for Init_Secondary_Tags
9650 begin
9651 -- Handle private types
9653 if Present (Full_View (Typ)) then
9654 Full_Typ := Full_View (Typ);
9655 else
9656 Full_Typ := Typ;
9657 end if;
9659 Collect_Interfaces_Info
9660 (Full_Typ, Ifaces_List, Ifaces_Comp_List, Ifaces_Tag_List);
9662 Iface_Elmt := First_Elmt (Ifaces_List);
9663 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
9664 Iface_Tag_Elmt := First_Elmt (Ifaces_Tag_List);
9665 while Present (Iface_Elmt) loop
9666 Tag_Comp := Node (Iface_Comp_Elmt);
9668 -- Check if parent of record type has variable size components
9670 In_Variable_Pos := Scope (Tag_Comp) /= Etype (Scope (Tag_Comp))
9671 and then Is_Variable_Size_Record (Etype (Scope (Tag_Comp)));
9673 -- If we are compiling under the CPP full ABI compatibility mode and
9674 -- the ancestor is a CPP_Pragma tagged type then we generate code to
9675 -- initialize the secondary tag components from tags that reference
9676 -- secondary tables filled with copy of parent slots.
9678 if Is_CPP_Class (Root_Type (Full_Typ)) then
9680 -- Reject interface components located at variable offset in
9681 -- C++ derivations. This is currently unsupported.
9683 if not Fixed_Comps and then In_Variable_Pos then
9685 -- Locate the first dynamic component of the record. Done to
9686 -- improve the text of the warning.
9688 declare
9689 Comp : Entity_Id;
9690 Comp_Typ : Entity_Id;
9692 begin
9693 Comp := First_Entity (Typ);
9694 while Present (Comp) loop
9695 Comp_Typ := Etype (Comp);
9697 if Ekind (Comp) /= E_Discriminant
9698 and then not Is_Tag (Comp)
9699 then
9700 exit when
9701 (Is_Record_Type (Comp_Typ)
9702 and then
9703 Is_Variable_Size_Record (Base_Type (Comp_Typ)))
9704 or else
9705 (Is_Array_Type (Comp_Typ)
9706 and then Is_Variable_Size_Array (Comp_Typ));
9707 end if;
9709 Next_Entity (Comp);
9710 end loop;
9712 pragma Assert (Present (Comp));
9714 -- Move this check to sem???
9715 Error_Msg_Node_2 := Comp;
9716 Error_Msg_NE
9717 ("parent type & with dynamic component & cannot be parent"
9718 & " of 'C'P'P derivation if new interfaces are present",
9719 Typ, Scope (Original_Record_Component (Comp)));
9721 Error_Msg_Sloc :=
9722 Sloc (Scope (Original_Record_Component (Comp)));
9723 Error_Msg_NE
9724 ("type derived from 'C'P'P type & defined #",
9725 Typ, Scope (Original_Record_Component (Comp)));
9727 -- Avoid duplicated warnings
9729 exit;
9730 end;
9732 -- Initialize secondary tags
9734 else
9735 Initialize_Tag
9736 (Typ => Full_Typ,
9737 Iface => Node (Iface_Elmt),
9738 Tag_Comp => Tag_Comp,
9739 Iface_Tag => Node (Iface_Tag_Elmt));
9740 end if;
9742 -- Otherwise generate code to initialize the tag
9744 else
9745 if (In_Variable_Pos and then Variable_Comps)
9746 or else (not In_Variable_Pos and then Fixed_Comps)
9747 then
9748 Initialize_Tag
9749 (Typ => Full_Typ,
9750 Iface => Node (Iface_Elmt),
9751 Tag_Comp => Tag_Comp,
9752 Iface_Tag => Node (Iface_Tag_Elmt));
9753 end if;
9754 end if;
9756 Next_Elmt (Iface_Elmt);
9757 Next_Elmt (Iface_Comp_Elmt);
9758 Next_Elmt (Iface_Tag_Elmt);
9759 end loop;
9760 end Init_Secondary_Tags;
9762 ----------------------------
9763 -- Is_Null_Statement_List --
9764 ----------------------------
9766 function Is_Null_Statement_List (Stmts : List_Id) return Boolean is
9767 Stmt : Node_Id;
9769 begin
9770 -- We must skip SCIL nodes because they may have been added to the list
9771 -- by Insert_Actions.
9773 Stmt := First_Non_SCIL_Node (Stmts);
9774 while Present (Stmt) loop
9775 if Nkind (Stmt) = N_Case_Statement then
9776 declare
9777 Alt : Node_Id;
9778 begin
9779 Alt := First (Alternatives (Stmt));
9780 while Present (Alt) loop
9781 if not Is_Null_Statement_List (Statements (Alt)) then
9782 return False;
9783 end if;
9785 Next (Alt);
9786 end loop;
9787 end;
9789 elsif Nkind (Stmt) /= N_Null_Statement then
9790 return False;
9791 end if;
9793 Stmt := Next_Non_SCIL_Node (Stmt);
9794 end loop;
9796 return True;
9797 end Is_Null_Statement_List;
9799 ----------------------------------------
9800 -- Make_Controlling_Function_Wrappers --
9801 ----------------------------------------
9803 procedure Make_Controlling_Function_Wrappers
9804 (Tag_Typ : Entity_Id;
9805 Decl_List : out List_Id;
9806 Body_List : out List_Id)
9808 Loc : constant Source_Ptr := Sloc (Tag_Typ);
9810 function Make_Wrapper_Specification (Subp : Entity_Id) return Node_Id;
9811 -- Returns a function specification with the same profile as Subp
9813 --------------------------------
9814 -- Make_Wrapper_Specification --
9815 --------------------------------
9817 function Make_Wrapper_Specification (Subp : Entity_Id) return Node_Id is
9818 begin
9819 return
9820 Make_Function_Specification (Loc,
9821 Defining_Unit_Name =>
9822 Make_Defining_Identifier (Loc,
9823 Chars => Chars (Subp)),
9824 Parameter_Specifications =>
9825 Copy_Parameter_List (Subp),
9826 Result_Definition =>
9827 New_Occurrence_Of (Etype (Subp), Loc));
9828 end Make_Wrapper_Specification;
9830 Prim_Elmt : Elmt_Id;
9831 Subp : Entity_Id;
9832 Actual_List : List_Id;
9833 Formal : Entity_Id;
9834 Par_Formal : Entity_Id;
9835 Ext_Aggr : Node_Id;
9836 Formal_Node : Node_Id;
9837 Func_Body : Node_Id;
9838 Func_Decl : Node_Id;
9839 Func_Id : Entity_Id;
9841 -- Start of processing for Make_Controlling_Function_Wrappers
9843 begin
9844 Decl_List := New_List;
9845 Body_List := New_List;
9847 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
9848 while Present (Prim_Elmt) loop
9849 Subp := Node (Prim_Elmt);
9851 -- If a primitive function with a controlling result of the type has
9852 -- not been overridden by the user, then we must create a wrapper
9853 -- function here that effectively overrides it and invokes the
9854 -- (non-abstract) parent function. This can only occur for a null
9855 -- extension. Note that functions with anonymous controlling access
9856 -- results don't qualify and must be overridden. We also exclude
9857 -- Input attributes, since each type will have its own version of
9858 -- Input constructed by the expander. The test for Comes_From_Source
9859 -- is needed to distinguish inherited operations from renamings
9860 -- (which also have Alias set). We exclude internal entities with
9861 -- Interface_Alias to avoid generating duplicated wrappers since
9862 -- the primitive which covers the interface is also available in
9863 -- the list of primitive operations.
9865 -- The function may be abstract, or require_Overriding may be set
9866 -- for it, because tests for null extensions may already have reset
9867 -- the Is_Abstract_Subprogram_Flag. If Requires_Overriding is not
9868 -- set, functions that need wrappers are recognized by having an
9869 -- alias that returns the parent type.
9871 if Comes_From_Source (Subp)
9872 or else No (Alias (Subp))
9873 or else Present (Interface_Alias (Subp))
9874 or else Ekind (Subp) /= E_Function
9875 or else not Has_Controlling_Result (Subp)
9876 or else Is_Access_Type (Etype (Subp))
9877 or else Is_Abstract_Subprogram (Alias (Subp))
9878 or else Is_TSS (Subp, TSS_Stream_Input)
9879 then
9880 goto Next_Prim;
9882 elsif Is_Abstract_Subprogram (Subp)
9883 or else Requires_Overriding (Subp)
9884 or else
9885 (Is_Null_Extension (Etype (Subp))
9886 and then Etype (Alias (Subp)) /= Etype (Subp))
9887 then
9888 -- If there is a non-overloadable homonym in the current
9889 -- scope, the implicit declaration remains invisible.
9890 -- We check the current entity with the same name, or its
9891 -- homonym in case the derivation takes place after the
9892 -- hiding object declaration.
9894 if Present (Current_Entity (Subp)) then
9895 declare
9896 Curr : constant Entity_Id := Current_Entity (Subp);
9897 Prev : constant Entity_Id := Homonym (Curr);
9898 begin
9899 if (Comes_From_Source (Curr)
9900 and then Scope (Curr) = Current_Scope
9901 and then not Is_Overloadable (Curr))
9902 or else
9903 (Present (Prev)
9904 and then Comes_From_Source (Prev)
9905 and then Scope (Prev) = Current_Scope
9906 and then not Is_Overloadable (Prev))
9907 then
9908 goto Next_Prim;
9909 end if;
9910 end;
9911 end if;
9913 Func_Decl :=
9914 Make_Subprogram_Declaration (Loc,
9915 Specification => Make_Wrapper_Specification (Subp));
9917 Append_To (Decl_List, Func_Decl);
9919 -- Build a wrapper body that calls the parent function. The body
9920 -- contains a single return statement that returns an extension
9921 -- aggregate whose ancestor part is a call to the parent function,
9922 -- passing the formals as actuals (with any controlling arguments
9923 -- converted to the types of the corresponding formals of the
9924 -- parent function, which might be anonymous access types), and
9925 -- having a null extension.
9927 Formal := First_Formal (Subp);
9928 Par_Formal := First_Formal (Alias (Subp));
9929 Formal_Node :=
9930 First (Parameter_Specifications (Specification (Func_Decl)));
9932 if Present (Formal) then
9933 Actual_List := New_List;
9935 while Present (Formal) loop
9936 if Is_Controlling_Formal (Formal) then
9937 Append_To (Actual_List,
9938 Make_Type_Conversion (Loc,
9939 Subtype_Mark =>
9940 New_Occurrence_Of (Etype (Par_Formal), Loc),
9941 Expression =>
9942 New_Occurrence_Of
9943 (Defining_Identifier (Formal_Node), Loc)));
9944 else
9945 Append_To
9946 (Actual_List,
9947 New_Occurrence_Of
9948 (Defining_Identifier (Formal_Node), Loc));
9949 end if;
9951 Next_Formal (Formal);
9952 Next_Formal (Par_Formal);
9953 Next (Formal_Node);
9954 end loop;
9955 else
9956 Actual_List := No_List;
9957 end if;
9959 Ext_Aggr :=
9960 Make_Extension_Aggregate (Loc,
9961 Ancestor_Part =>
9962 Make_Function_Call (Loc,
9963 Name =>
9964 New_Occurrence_Of (Alias (Subp), Loc),
9965 Parameter_Associations => Actual_List),
9966 Null_Record_Present => True);
9968 -- GNATprove will use expression of an expression function as an
9969 -- implicit postcondition. GNAT will not benefit from expression
9970 -- function (and would struggle if we add an expression function
9971 -- to freezing actions).
9973 if GNATprove_Mode then
9974 Func_Body :=
9975 Make_Expression_Function (Loc,
9976 Specification =>
9977 Make_Wrapper_Specification (Subp),
9978 Expression => Ext_Aggr);
9979 else
9980 Func_Body :=
9981 Make_Subprogram_Body (Loc,
9982 Specification =>
9983 Make_Wrapper_Specification (Subp),
9984 Declarations => Empty_List,
9985 Handled_Statement_Sequence =>
9986 Make_Handled_Sequence_Of_Statements (Loc,
9987 Statements => New_List (
9988 Make_Simple_Return_Statement (Loc,
9989 Expression => Ext_Aggr))));
9990 end if;
9992 Append_To (Body_List, Func_Body);
9994 -- Replace the inherited function with the wrapper function in the
9995 -- primitive operations list. We add the minimum decoration needed
9996 -- to override interface primitives.
9998 Func_Id := Defining_Unit_Name (Specification (Func_Decl));
10000 Mutate_Ekind (Func_Id, E_Function);
10001 Set_Is_Wrapper (Func_Id);
10003 -- Corresponding_Spec will be set again to the same value during
10004 -- analysis, but we need this information earlier.
10005 -- Expand_N_Freeze_Entity needs to know whether a subprogram body
10006 -- is a wrapper's body in order to get check suppression right.
10008 Set_Corresponding_Spec (Func_Body, Func_Id);
10010 Override_Dispatching_Operation (Tag_Typ, Subp, New_Op => Func_Id);
10011 end if;
10013 <<Next_Prim>>
10014 Next_Elmt (Prim_Elmt);
10015 end loop;
10016 end Make_Controlling_Function_Wrappers;
10018 ------------------
10019 -- Make_Eq_Body --
10020 ------------------
10022 function Make_Eq_Body
10023 (Typ : Entity_Id;
10024 Eq_Name : Name_Id) return Node_Id
10026 Loc : constant Source_Ptr := Sloc (Parent (Typ));
10027 Decl : Node_Id;
10028 Def : constant Node_Id := Parent (Typ);
10029 Stmts : constant List_Id := New_List;
10030 Variant_Case : Boolean := Has_Discriminants (Typ);
10031 Comps : Node_Id := Empty;
10032 Typ_Def : Node_Id := Type_Definition (Def);
10034 begin
10035 Decl :=
10036 Predef_Spec_Or_Body (Loc,
10037 Tag_Typ => Typ,
10038 Name => Eq_Name,
10039 Profile => New_List (
10040 Make_Parameter_Specification (Loc,
10041 Defining_Identifier =>
10042 Make_Defining_Identifier (Loc, Name_X),
10043 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
10045 Make_Parameter_Specification (Loc,
10046 Defining_Identifier =>
10047 Make_Defining_Identifier (Loc, Name_Y),
10048 Parameter_Type => New_Occurrence_Of (Typ, Loc))),
10050 Ret_Type => Standard_Boolean,
10051 For_Body => True);
10053 if Variant_Case then
10054 if Nkind (Typ_Def) = N_Derived_Type_Definition then
10055 Typ_Def := Record_Extension_Part (Typ_Def);
10056 end if;
10058 if Present (Typ_Def) then
10059 Comps := Component_List (Typ_Def);
10060 end if;
10062 Variant_Case :=
10063 Present (Comps) and then Present (Variant_Part (Comps));
10064 end if;
10066 if Variant_Case then
10067 Append_To (Stmts,
10068 Make_Eq_If (Typ, Discriminant_Specifications (Def)));
10069 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps));
10070 Append_To (Stmts,
10071 Make_Simple_Return_Statement (Loc,
10072 Expression => New_Occurrence_Of (Standard_True, Loc)));
10074 else
10075 Append_To (Stmts,
10076 Make_Simple_Return_Statement (Loc,
10077 Expression =>
10078 Expand_Record_Equality
10079 (Typ,
10080 Typ => Typ,
10081 Lhs => Make_Identifier (Loc, Name_X),
10082 Rhs => Make_Identifier (Loc, Name_Y))));
10083 end if;
10085 Set_Handled_Statement_Sequence
10086 (Decl, Make_Handled_Sequence_Of_Statements (Loc, Stmts));
10087 return Decl;
10088 end Make_Eq_Body;
10090 ------------------
10091 -- Make_Eq_Case --
10092 ------------------
10094 -- <Make_Eq_If shared components>
10096 -- case X.D1 is
10097 -- when V1 => <Make_Eq_Case> on subcomponents
10098 -- ...
10099 -- when Vn => <Make_Eq_Case> on subcomponents
10100 -- end case;
10102 function Make_Eq_Case
10103 (E : Entity_Id;
10104 CL : Node_Id;
10105 Discrs : Elist_Id := New_Elmt_List) return List_Id
10107 Loc : constant Source_Ptr := Sloc (E);
10108 Result : constant List_Id := New_List;
10109 Variant : Node_Id;
10110 Alt_List : List_Id;
10112 function Corresponding_Formal (C : Node_Id) return Entity_Id;
10113 -- Given the discriminant that controls a given variant of an unchecked
10114 -- union, find the formal of the equality function that carries the
10115 -- inferred value of the discriminant.
10117 function External_Name (E : Entity_Id) return Name_Id;
10118 -- The value of a given discriminant is conveyed in the corresponding
10119 -- formal parameter of the equality routine. The name of this formal
10120 -- parameter carries a one-character suffix which is removed here.
10122 --------------------------
10123 -- Corresponding_Formal --
10124 --------------------------
10126 function Corresponding_Formal (C : Node_Id) return Entity_Id is
10127 Discr : constant Entity_Id := Entity (Name (Variant_Part (C)));
10128 Elm : Elmt_Id;
10130 begin
10131 Elm := First_Elmt (Discrs);
10132 while Present (Elm) loop
10133 if Chars (Discr) = External_Name (Node (Elm)) then
10134 return Node (Elm);
10135 end if;
10137 Next_Elmt (Elm);
10138 end loop;
10140 -- A formal of the proper name must be found
10142 raise Program_Error;
10143 end Corresponding_Formal;
10145 -------------------
10146 -- External_Name --
10147 -------------------
10149 function External_Name (E : Entity_Id) return Name_Id is
10150 begin
10151 Get_Name_String (Chars (E));
10152 Name_Len := Name_Len - 1;
10153 return Name_Find;
10154 end External_Name;
10156 -- Start of processing for Make_Eq_Case
10158 begin
10159 Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
10161 if No (Variant_Part (CL)) then
10162 return Result;
10163 end if;
10165 Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
10167 if No (Variant) then
10168 return Result;
10169 end if;
10171 Alt_List := New_List;
10172 while Present (Variant) loop
10173 Append_To (Alt_List,
10174 Make_Case_Statement_Alternative (Loc,
10175 Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
10176 Statements =>
10177 Make_Eq_Case (E, Component_List (Variant), Discrs)));
10178 Next_Non_Pragma (Variant);
10179 end loop;
10181 -- If we have an Unchecked_Union, use one of the parameters of the
10182 -- enclosing equality routine that captures the discriminant, to use
10183 -- as the expression in the generated case statement.
10185 if Is_Unchecked_Union (E) then
10186 Append_To (Result,
10187 Make_Case_Statement (Loc,
10188 Expression =>
10189 New_Occurrence_Of (Corresponding_Formal (CL), Loc),
10190 Alternatives => Alt_List));
10192 else
10193 Append_To (Result,
10194 Make_Case_Statement (Loc,
10195 Expression =>
10196 Make_Selected_Component (Loc,
10197 Prefix => Make_Identifier (Loc, Name_X),
10198 Selector_Name => New_Copy (Name (Variant_Part (CL)))),
10199 Alternatives => Alt_List));
10200 end if;
10202 return Result;
10203 end Make_Eq_Case;
10205 ----------------
10206 -- Make_Eq_If --
10207 ----------------
10209 -- Generates:
10211 -- if
10212 -- X.C1 /= Y.C1
10213 -- or else
10214 -- X.C2 /= Y.C2
10215 -- ...
10216 -- then
10217 -- return False;
10218 -- end if;
10220 -- or a null statement if the list L is empty
10222 -- Equality may be user-defined for a given component type, in which case
10223 -- a function call is constructed instead of an operator node. This is an
10224 -- Ada 2012 change in the composability of equality for untagged composite
10225 -- types.
10227 function Make_Eq_If
10228 (E : Entity_Id;
10229 L : List_Id) return Node_Id
10231 Loc : constant Source_Ptr := Sloc (E);
10233 C : Node_Id;
10234 Cond : Node_Id;
10235 Field_Name : Name_Id;
10236 Next_Test : Node_Id;
10237 Typ : Entity_Id;
10239 begin
10240 if No (L) then
10241 return Make_Null_Statement (Loc);
10243 else
10244 Cond := Empty;
10246 C := First_Non_Pragma (L);
10247 while Present (C) loop
10248 Typ := Etype (Defining_Identifier (C));
10249 Field_Name := Chars (Defining_Identifier (C));
10251 -- The tags must not be compared: they are not part of the value.
10252 -- Ditto for parent interfaces because their equality operator is
10253 -- abstract.
10255 -- Note also that in the following, we use Make_Identifier for
10256 -- the component names. Use of New_Occurrence_Of to identify the
10257 -- components would be incorrect because the wrong entities for
10258 -- discriminants could be picked up in the private type case.
10260 if Field_Name = Name_uParent
10261 and then Is_Interface (Typ)
10262 then
10263 null;
10265 elsif Field_Name /= Name_uTag then
10266 declare
10267 Lhs : constant Node_Id :=
10268 Make_Selected_Component (Loc,
10269 Prefix => Make_Identifier (Loc, Name_X),
10270 Selector_Name => Make_Identifier (Loc, Field_Name));
10272 Rhs : constant Node_Id :=
10273 Make_Selected_Component (Loc,
10274 Prefix => Make_Identifier (Loc, Name_Y),
10275 Selector_Name => Make_Identifier (Loc, Field_Name));
10276 Eq_Call : Node_Id;
10278 begin
10279 -- Build equality code with a user-defined operator, if
10280 -- available, and with the predefined "=" otherwise. For
10281 -- compatibility with older Ada versions, we also use the
10282 -- predefined operation if the component-type equality is
10283 -- abstract, rather than raising Program_Error.
10285 if Ada_Version < Ada_2012 then
10286 Next_Test := Make_Op_Ne (Loc, Lhs, Rhs);
10288 else
10289 Eq_Call := Build_Eq_Call (Typ, Loc, Lhs, Rhs);
10291 if No (Eq_Call) then
10292 Next_Test := Make_Op_Ne (Loc, Lhs, Rhs);
10294 -- If a component has a defined abstract equality, its
10295 -- application raises Program_Error on that component
10296 -- and therefore on the current variant.
10298 elsif Nkind (Eq_Call) = N_Raise_Program_Error then
10299 Set_Etype (Eq_Call, Standard_Boolean);
10300 Next_Test := Make_Op_Not (Loc, Eq_Call);
10302 else
10303 Next_Test := Make_Op_Not (Loc, Eq_Call);
10304 end if;
10305 end if;
10306 end;
10308 Evolve_Or_Else (Cond, Next_Test);
10309 end if;
10311 Next_Non_Pragma (C);
10312 end loop;
10314 if No (Cond) then
10315 return Make_Null_Statement (Loc);
10317 else
10318 return
10319 Make_Implicit_If_Statement (E,
10320 Condition => Cond,
10321 Then_Statements => New_List (
10322 Make_Simple_Return_Statement (Loc,
10323 Expression => New_Occurrence_Of (Standard_False, Loc))));
10324 end if;
10325 end if;
10326 end Make_Eq_If;
10328 -------------------
10329 -- Make_Neq_Body --
10330 -------------------
10332 function Make_Neq_Body (Tag_Typ : Entity_Id) return Node_Id is
10334 function Is_Predefined_Neq_Renaming (Prim : Node_Id) return Boolean;
10335 -- Returns true if Prim is a renaming of an unresolved predefined
10336 -- inequality operation.
10338 --------------------------------
10339 -- Is_Predefined_Neq_Renaming --
10340 --------------------------------
10342 function Is_Predefined_Neq_Renaming (Prim : Node_Id) return Boolean is
10343 begin
10344 return Chars (Prim) /= Name_Op_Ne
10345 and then Present (Alias (Prim))
10346 and then Comes_From_Source (Prim)
10347 and then Is_Intrinsic_Subprogram (Alias (Prim))
10348 and then Chars (Alias (Prim)) = Name_Op_Ne;
10349 end Is_Predefined_Neq_Renaming;
10351 -- Local variables
10353 Loc : constant Source_Ptr := Sloc (Parent (Tag_Typ));
10354 Decl : Node_Id;
10355 Eq_Prim : Entity_Id;
10356 Left_Op : Entity_Id;
10357 Renaming_Prim : Entity_Id;
10358 Right_Op : Entity_Id;
10359 Target : Entity_Id;
10361 -- Start of processing for Make_Neq_Body
10363 begin
10364 -- For a call on a renaming of a dispatching subprogram that is
10365 -- overridden, if the overriding occurred before the renaming, then
10366 -- the body executed is that of the overriding declaration, even if the
10367 -- overriding declaration is not visible at the place of the renaming;
10368 -- otherwise, the inherited or predefined subprogram is called, see
10369 -- (RM 8.5.4(8)).
10371 -- Stage 1: Search for a renaming of the inequality primitive and also
10372 -- search for an overriding of the equality primitive located before the
10373 -- renaming declaration.
10375 declare
10376 Elmt : Elmt_Id;
10377 Prim : Node_Id;
10379 begin
10380 Eq_Prim := Empty;
10381 Renaming_Prim := Empty;
10383 Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
10384 while Present (Elmt) loop
10385 Prim := Node (Elmt);
10387 if Is_User_Defined_Equality (Prim) and then No (Alias (Prim)) then
10388 if No (Renaming_Prim) then
10389 pragma Assert (No (Eq_Prim));
10390 Eq_Prim := Prim;
10391 end if;
10393 elsif Is_Predefined_Neq_Renaming (Prim) then
10394 Renaming_Prim := Prim;
10395 end if;
10397 Next_Elmt (Elmt);
10398 end loop;
10399 end;
10401 -- No further action needed if no renaming was found
10403 if No (Renaming_Prim) then
10404 return Empty;
10405 end if;
10407 -- Stage 2: Replace the renaming declaration by a subprogram declaration
10408 -- (required to add its body)
10410 Decl := Parent (Parent (Renaming_Prim));
10411 Rewrite (Decl,
10412 Make_Subprogram_Declaration (Loc,
10413 Specification => Specification (Decl)));
10414 Set_Analyzed (Decl);
10416 -- Remove the decoration of intrinsic renaming subprogram
10418 Set_Is_Intrinsic_Subprogram (Renaming_Prim, False);
10419 Set_Convention (Renaming_Prim, Convention_Ada);
10420 Set_Alias (Renaming_Prim, Empty);
10421 Set_Has_Completion (Renaming_Prim, False);
10423 -- Stage 3: Build the corresponding body
10425 Left_Op := First_Formal (Renaming_Prim);
10426 Right_Op := Next_Formal (Left_Op);
10428 Decl :=
10429 Predef_Spec_Or_Body (Loc,
10430 Tag_Typ => Tag_Typ,
10431 Name => Chars (Renaming_Prim),
10432 Profile => New_List (
10433 Make_Parameter_Specification (Loc,
10434 Defining_Identifier =>
10435 Make_Defining_Identifier (Loc, Chars (Left_Op)),
10436 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
10438 Make_Parameter_Specification (Loc,
10439 Defining_Identifier =>
10440 Make_Defining_Identifier (Loc, Chars (Right_Op)),
10441 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
10443 Ret_Type => Standard_Boolean,
10444 For_Body => True);
10446 -- If the overriding of the equality primitive occurred before the
10447 -- renaming, then generate:
10449 -- function <Neq_Name> (X : Y : Typ) return Boolean is
10450 -- begin
10451 -- return not Oeq (X, Y);
10452 -- end;
10454 if Present (Eq_Prim) then
10455 Target := Eq_Prim;
10457 -- Otherwise build a nested subprogram which performs the predefined
10458 -- evaluation of the equality operator. That is, generate:
10460 -- function <Neq_Name> (X : Y : Typ) return Boolean is
10461 -- function Oeq (X : Y) return Boolean is
10462 -- begin
10463 -- <<body of default implementation>>
10464 -- end;
10465 -- begin
10466 -- return not Oeq (X, Y);
10467 -- end;
10469 else
10470 declare
10471 Local_Subp : Node_Id;
10472 begin
10473 Local_Subp := Make_Eq_Body (Tag_Typ, Name_Op_Eq);
10474 Set_Declarations (Decl, New_List (Local_Subp));
10475 Target := Defining_Entity (Local_Subp);
10476 end;
10477 end if;
10479 Set_Handled_Statement_Sequence
10480 (Decl,
10481 Make_Handled_Sequence_Of_Statements (Loc, New_List (
10482 Make_Simple_Return_Statement (Loc,
10483 Expression =>
10484 Make_Op_Not (Loc,
10485 Make_Function_Call (Loc,
10486 Name => New_Occurrence_Of (Target, Loc),
10487 Parameter_Associations => New_List (
10488 Make_Identifier (Loc, Chars (Left_Op)),
10489 Make_Identifier (Loc, Chars (Right_Op)))))))));
10491 return Decl;
10492 end Make_Neq_Body;
10494 -------------------------------
10495 -- Make_Null_Procedure_Specs --
10496 -------------------------------
10498 function Make_Null_Procedure_Specs (Tag_Typ : Entity_Id) return List_Id is
10499 Decl_List : constant List_Id := New_List;
10500 Loc : constant Source_Ptr := Sloc (Tag_Typ);
10501 Formal : Entity_Id;
10502 New_Param_Spec : Node_Id;
10503 New_Spec : Node_Id;
10504 Parent_Subp : Entity_Id;
10505 Prim_Elmt : Elmt_Id;
10506 Subp : Entity_Id;
10508 begin
10509 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
10510 while Present (Prim_Elmt) loop
10511 Subp := Node (Prim_Elmt);
10513 -- If a null procedure inherited from an interface has not been
10514 -- overridden, then we build a null procedure declaration to
10515 -- override the inherited procedure.
10517 Parent_Subp := Alias (Subp);
10519 if Present (Parent_Subp)
10520 and then Is_Null_Interface_Primitive (Parent_Subp)
10521 then
10522 -- The null procedure spec is copied from the inherited procedure,
10523 -- except for the IS NULL (which must be added) and the overriding
10524 -- indicators (which must be removed, if present).
10526 New_Spec :=
10527 Copy_Subprogram_Spec (Subprogram_Specification (Subp), Loc);
10529 Set_Null_Present (New_Spec, True);
10530 Set_Must_Override (New_Spec, False);
10531 Set_Must_Not_Override (New_Spec, False);
10533 Formal := First_Formal (Subp);
10534 New_Param_Spec := First (Parameter_Specifications (New_Spec));
10536 while Present (Formal) loop
10538 -- For controlling arguments we must change their parameter
10539 -- type to reference the tagged type (instead of the interface
10540 -- type).
10542 if Is_Controlling_Formal (Formal) then
10543 if Nkind (Parameter_Type (Parent (Formal))) = N_Identifier
10544 then
10545 Set_Parameter_Type (New_Param_Spec,
10546 New_Occurrence_Of (Tag_Typ, Loc));
10548 else pragma Assert
10549 (Nkind (Parameter_Type (Parent (Formal))) =
10550 N_Access_Definition);
10551 Set_Subtype_Mark (Parameter_Type (New_Param_Spec),
10552 New_Occurrence_Of (Tag_Typ, Loc));
10553 end if;
10554 end if;
10556 Next_Formal (Formal);
10557 Next (New_Param_Spec);
10558 end loop;
10560 Append_To (Decl_List,
10561 Make_Subprogram_Declaration (Loc,
10562 Specification => New_Spec));
10563 end if;
10565 Next_Elmt (Prim_Elmt);
10566 end loop;
10568 return Decl_List;
10569 end Make_Null_Procedure_Specs;
10571 ---------------------------------------
10572 -- Make_Predefined_Primitive_Eq_Spec --
10573 ---------------------------------------
10575 procedure Make_Predefined_Primitive_Eq_Spec
10576 (Tag_Typ : Entity_Id;
10577 Predef_List : List_Id;
10578 Renamed_Eq : out Entity_Id)
10580 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
10581 -- Returns true if Prim is a renaming of an unresolved predefined
10582 -- equality operation.
10584 -------------------------------
10585 -- Is_Predefined_Eq_Renaming --
10586 -------------------------------
10588 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
10589 begin
10590 return Chars (Prim) /= Name_Op_Eq
10591 and then Present (Alias (Prim))
10592 and then Comes_From_Source (Prim)
10593 and then Is_Intrinsic_Subprogram (Alias (Prim))
10594 and then Chars (Alias (Prim)) = Name_Op_Eq;
10595 end Is_Predefined_Eq_Renaming;
10597 -- Local variables
10599 Loc : constant Source_Ptr := Sloc (Tag_Typ);
10601 Eq_Name : Name_Id := Name_Op_Eq;
10602 Eq_Needed : Boolean := True;
10603 Eq_Spec : Node_Id;
10604 Prim : Elmt_Id;
10606 Has_Predef_Eq_Renaming : Boolean := False;
10607 -- Set to True if Tag_Typ has a primitive that renames the predefined
10608 -- equality operator. Used to implement (RM 8-5-4(8)).
10610 -- Start of processing for Make_Predefined_Primitive_Specs
10612 begin
10613 Renamed_Eq := Empty;
10615 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
10616 while Present (Prim) loop
10618 -- If a primitive is encountered that renames the predefined equality
10619 -- operator before reaching any explicit equality primitive, then we
10620 -- still need to create a predefined equality function, because calls
10621 -- to it can occur via the renaming. A new name is created for the
10622 -- equality to avoid conflicting with any user-defined equality.
10623 -- (Note that this doesn't account for renamings of equality nested
10624 -- within subpackages???)
10626 if Is_Predefined_Eq_Renaming (Node (Prim)) then
10627 Has_Predef_Eq_Renaming := True;
10628 Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
10630 -- User-defined equality
10632 elsif Is_User_Defined_Equality (Node (Prim)) then
10633 if No (Alias (Node (Prim)))
10634 or else Nkind (Unit_Declaration_Node (Node (Prim))) =
10635 N_Subprogram_Renaming_Declaration
10636 then
10637 Eq_Needed := False;
10638 exit;
10640 -- If the parent is not an interface type and has an abstract
10641 -- equality function explicitly defined in the sources, then the
10642 -- inherited equality is abstract as well, and no body can be
10643 -- created for it.
10645 elsif not Is_Interface (Etype (Tag_Typ))
10646 and then Present (Alias (Node (Prim)))
10647 and then Comes_From_Source (Alias (Node (Prim)))
10648 and then Is_Abstract_Subprogram (Alias (Node (Prim)))
10649 then
10650 Eq_Needed := False;
10651 exit;
10653 -- If the type has an equality function corresponding with a
10654 -- primitive defined in an interface type, the inherited equality
10655 -- is abstract as well, and no body can be created for it.
10657 elsif Present (Alias (Node (Prim)))
10658 and then Comes_From_Source (Ultimate_Alias (Node (Prim)))
10659 and then
10660 Is_Interface
10661 (Find_Dispatching_Type (Ultimate_Alias (Node (Prim))))
10662 then
10663 Eq_Needed := False;
10664 exit;
10665 end if;
10666 end if;
10668 Next_Elmt (Prim);
10669 end loop;
10671 -- If a renaming of predefined equality was found but there was no
10672 -- user-defined equality (so Eq_Needed is still true), then set the name
10673 -- back to Name_Op_Eq. But in the case where a user-defined equality was
10674 -- located after such a renaming, then the predefined equality function
10675 -- is still needed, so Eq_Needed must be set back to True.
10677 if Eq_Name /= Name_Op_Eq then
10678 if Eq_Needed then
10679 Eq_Name := Name_Op_Eq;
10680 else
10681 Eq_Needed := True;
10682 end if;
10683 end if;
10685 if Eq_Needed then
10686 Eq_Spec := Predef_Spec_Or_Body (Loc,
10687 Tag_Typ => Tag_Typ,
10688 Name => Eq_Name,
10689 Profile => New_List (
10690 Make_Parameter_Specification (Loc,
10691 Defining_Identifier =>
10692 Make_Defining_Identifier (Loc, Name_X),
10693 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
10695 Make_Parameter_Specification (Loc,
10696 Defining_Identifier =>
10697 Make_Defining_Identifier (Loc, Name_Y),
10698 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
10699 Ret_Type => Standard_Boolean);
10700 Append_To (Predef_List, Eq_Spec);
10702 if Has_Predef_Eq_Renaming then
10703 Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
10705 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
10706 while Present (Prim) loop
10708 -- Any renamings of equality that appeared before an overriding
10709 -- equality must be updated to refer to the entity for the
10710 -- predefined equality, otherwise calls via the renaming would
10711 -- get incorrectly resolved to call the user-defined equality
10712 -- function.
10714 if Is_Predefined_Eq_Renaming (Node (Prim)) then
10715 Set_Alias (Node (Prim), Renamed_Eq);
10717 -- Exit upon encountering a user-defined equality
10719 elsif Chars (Node (Prim)) = Name_Op_Eq
10720 and then No (Alias (Node (Prim)))
10721 then
10722 exit;
10723 end if;
10725 Next_Elmt (Prim);
10726 end loop;
10727 end if;
10728 end if;
10729 end Make_Predefined_Primitive_Eq_Spec;
10731 -------------------------------------
10732 -- Make_Predefined_Primitive_Specs --
10733 -------------------------------------
10735 procedure Make_Predefined_Primitive_Specs
10736 (Tag_Typ : Entity_Id;
10737 Predef_List : out List_Id;
10738 Renamed_Eq : out Entity_Id)
10740 Loc : constant Source_Ptr := Sloc (Tag_Typ);
10741 Res : constant List_Id := New_List;
10743 use Exp_Put_Image;
10745 begin
10746 Renamed_Eq := Empty;
10748 -- Spec of _Size
10750 Append_To (Res, Predef_Spec_Or_Body (Loc,
10751 Tag_Typ => Tag_Typ,
10752 Name => Name_uSize,
10753 Profile => New_List (
10754 Make_Parameter_Specification (Loc,
10755 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
10756 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
10758 Ret_Type => Standard_Long_Long_Integer));
10760 -- Spec of Put_Image
10762 if (not No_Run_Time_Mode)
10763 and then RTE_Available (RE_Root_Buffer_Type)
10764 then
10765 -- No_Run_Time_Mode implies that the declaration of Tag_Typ
10766 -- (like any tagged type) will be rejected. Given this, avoid
10767 -- cascading errors associated with the Tag_Typ's TSS_Put_Image
10768 -- procedure.
10770 Append_To (Res, Predef_Spec_Or_Body (Loc,
10771 Tag_Typ => Tag_Typ,
10772 Name => Make_TSS_Name (Tag_Typ, TSS_Put_Image),
10773 Profile => Build_Put_Image_Profile (Loc, Tag_Typ)));
10774 end if;
10776 -- Specs for dispatching stream attributes
10778 declare
10779 Stream_Op_TSS_Names :
10780 constant array (Positive range <>) of TSS_Name_Type :=
10781 (TSS_Stream_Read,
10782 TSS_Stream_Write,
10783 TSS_Stream_Input,
10784 TSS_Stream_Output);
10786 begin
10787 for Op in Stream_Op_TSS_Names'Range loop
10788 if Stream_Operation_OK (Tag_Typ, Stream_Op_TSS_Names (Op)) then
10789 Append_To (Res,
10790 Predef_Stream_Attr_Spec (Loc, Tag_Typ,
10791 Stream_Op_TSS_Names (Op)));
10792 end if;
10793 end loop;
10794 end;
10796 -- Spec of "=" is expanded if the type is not limited and if a user
10797 -- defined "=" was not already declared for the non-full view of a
10798 -- private extension.
10800 if not Is_Limited_Type (Tag_Typ) then
10801 Make_Predefined_Primitive_Eq_Spec (Tag_Typ, Res, Renamed_Eq);
10803 -- Spec for dispatching assignment
10805 Append_To (Res, Predef_Spec_Or_Body (Loc,
10806 Tag_Typ => Tag_Typ,
10807 Name => Name_uAssign,
10808 Profile => New_List (
10809 Make_Parameter_Specification (Loc,
10810 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
10811 Out_Present => True,
10812 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
10814 Make_Parameter_Specification (Loc,
10815 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
10816 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)))));
10817 end if;
10819 -- Ada 2005: Generate declarations for the following primitive
10820 -- operations for limited interfaces and synchronized types that
10821 -- implement a limited interface.
10823 -- Disp_Asynchronous_Select
10824 -- Disp_Conditional_Select
10825 -- Disp_Get_Prim_Op_Kind
10826 -- Disp_Get_Task_Id
10827 -- Disp_Requeue
10828 -- Disp_Timed_Select
10830 -- Disable the generation of these bodies if Ravenscar or ZFP is active
10832 if Ada_Version >= Ada_2005
10833 and then not Restriction_Active (No_Select_Statements)
10834 and then RTE_Available (RE_Select_Specific_Data)
10835 then
10836 -- These primitives are defined abstract in interface types
10838 if Is_Interface (Tag_Typ)
10839 and then Is_Limited_Record (Tag_Typ)
10840 then
10841 Append_To (Res,
10842 Make_Abstract_Subprogram_Declaration (Loc,
10843 Specification =>
10844 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
10846 Append_To (Res,
10847 Make_Abstract_Subprogram_Declaration (Loc,
10848 Specification =>
10849 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
10851 Append_To (Res,
10852 Make_Abstract_Subprogram_Declaration (Loc,
10853 Specification =>
10854 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
10856 Append_To (Res,
10857 Make_Abstract_Subprogram_Declaration (Loc,
10858 Specification =>
10859 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
10861 Append_To (Res,
10862 Make_Abstract_Subprogram_Declaration (Loc,
10863 Specification =>
10864 Make_Disp_Requeue_Spec (Tag_Typ)));
10866 Append_To (Res,
10867 Make_Abstract_Subprogram_Declaration (Loc,
10868 Specification =>
10869 Make_Disp_Timed_Select_Spec (Tag_Typ)));
10871 -- If ancestor is an interface type, declare non-abstract primitives
10872 -- to override the abstract primitives of the interface type.
10874 -- In VM targets we define these primitives in all root tagged types
10875 -- that are not interface types. Done because in VM targets we don't
10876 -- have secondary dispatch tables and any derivation of Tag_Typ may
10877 -- cover limited interfaces (which always have these primitives since
10878 -- they may be ancestors of synchronized interface types).
10880 elsif (not Is_Interface (Tag_Typ)
10881 and then Is_Interface (Etype (Tag_Typ))
10882 and then Is_Limited_Record (Etype (Tag_Typ)))
10883 or else
10884 (Is_Concurrent_Record_Type (Tag_Typ)
10885 and then Has_Interfaces (Tag_Typ))
10886 or else
10887 (not Tagged_Type_Expansion
10888 and then not Is_Interface (Tag_Typ)
10889 and then Tag_Typ = Root_Type (Tag_Typ))
10890 then
10891 Append_To (Res,
10892 Make_Subprogram_Declaration (Loc,
10893 Specification =>
10894 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
10896 Append_To (Res,
10897 Make_Subprogram_Declaration (Loc,
10898 Specification =>
10899 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
10901 Append_To (Res,
10902 Make_Subprogram_Declaration (Loc,
10903 Specification =>
10904 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
10906 Append_To (Res,
10907 Make_Subprogram_Declaration (Loc,
10908 Specification =>
10909 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
10911 Append_To (Res,
10912 Make_Subprogram_Declaration (Loc,
10913 Specification =>
10914 Make_Disp_Requeue_Spec (Tag_Typ)));
10916 Append_To (Res,
10917 Make_Subprogram_Declaration (Loc,
10918 Specification =>
10919 Make_Disp_Timed_Select_Spec (Tag_Typ)));
10920 end if;
10921 end if;
10923 -- All tagged types receive their own Deep_Adjust and Deep_Finalize
10924 -- regardless of whether they are controlled or may contain controlled
10925 -- components.
10927 -- Do not generate the routines if finalization is disabled
10929 if Restriction_Active (No_Finalization) then
10930 null;
10932 else
10933 if not Is_Limited_Type (Tag_Typ) then
10934 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
10935 end if;
10937 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
10938 end if;
10940 Predef_List := Res;
10941 end Make_Predefined_Primitive_Specs;
10943 -------------------------
10944 -- Make_Tag_Assignment --
10945 -------------------------
10947 function Make_Tag_Assignment (N : Node_Id) return Node_Id is
10948 Loc : constant Source_Ptr := Sloc (N);
10949 Def_If : constant Entity_Id := Defining_Identifier (N);
10950 Expr : constant Node_Id := Expression (N);
10951 Typ : constant Entity_Id := Etype (Def_If);
10952 Full_Typ : constant Entity_Id := Underlying_Type (Typ);
10953 New_Ref : Node_Id;
10955 begin
10956 -- This expansion activity is called during analysis.
10958 if Is_Tagged_Type (Typ)
10959 and then not Is_Class_Wide_Type (Typ)
10960 and then not Is_CPP_Class (Typ)
10961 and then Tagged_Type_Expansion
10962 and then Nkind (Expr) /= N_Aggregate
10963 and then (Nkind (Expr) /= N_Qualified_Expression
10964 or else Nkind (Expression (Expr)) /= N_Aggregate)
10965 then
10966 New_Ref :=
10967 Make_Selected_Component (Loc,
10968 Prefix => New_Occurrence_Of (Def_If, Loc),
10969 Selector_Name =>
10970 New_Occurrence_Of (First_Tag_Component (Full_Typ), Loc));
10971 Set_Assignment_OK (New_Ref);
10973 return
10974 Make_Assignment_Statement (Loc,
10975 Name => New_Ref,
10976 Expression =>
10977 Unchecked_Convert_To (RTE (RE_Tag),
10978 New_Occurrence_Of (Node
10979 (First_Elmt (Access_Disp_Table (Full_Typ))), Loc)));
10980 else
10981 return Empty;
10982 end if;
10983 end Make_Tag_Assignment;
10985 ----------------------
10986 -- Predef_Deep_Spec --
10987 ----------------------
10989 function Predef_Deep_Spec
10990 (Loc : Source_Ptr;
10991 Tag_Typ : Entity_Id;
10992 Name : TSS_Name_Type;
10993 For_Body : Boolean := False) return Node_Id
10995 Formals : List_Id;
10997 begin
10998 -- V : in out Tag_Typ
11000 Formals := New_List (
11001 Make_Parameter_Specification (Loc,
11002 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
11003 In_Present => True,
11004 Out_Present => True,
11005 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)));
11007 -- F : Boolean := True
11009 if Name = TSS_Deep_Adjust
11010 or else Name = TSS_Deep_Finalize
11011 then
11012 Append_To (Formals,
11013 Make_Parameter_Specification (Loc,
11014 Defining_Identifier => Make_Defining_Identifier (Loc, Name_F),
11015 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
11016 Expression => New_Occurrence_Of (Standard_True, Loc)));
11017 end if;
11019 return
11020 Predef_Spec_Or_Body (Loc,
11021 Name => Make_TSS_Name (Tag_Typ, Name),
11022 Tag_Typ => Tag_Typ,
11023 Profile => Formals,
11024 For_Body => For_Body);
11026 exception
11027 when RE_Not_Available =>
11028 return Empty;
11029 end Predef_Deep_Spec;
11031 -------------------------
11032 -- Predef_Spec_Or_Body --
11033 -------------------------
11035 function Predef_Spec_Or_Body
11036 (Loc : Source_Ptr;
11037 Tag_Typ : Entity_Id;
11038 Name : Name_Id;
11039 Profile : List_Id;
11040 Ret_Type : Entity_Id := Empty;
11041 For_Body : Boolean := False) return Node_Id
11043 Id : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
11044 Spec : Node_Id;
11046 begin
11047 Set_Is_Public (Id, Is_Public (Tag_Typ));
11049 -- The internal flag is set to mark these declarations because they have
11050 -- specific properties. First, they are primitives even if they are not
11051 -- defined in the type scope (the freezing point is not necessarily in
11052 -- the same scope). Second, the predefined equality can be overridden by
11053 -- a user-defined equality, no body will be generated in this case.
11055 Set_Is_Internal (Id);
11057 if not Debug_Generated_Code then
11058 Set_Debug_Info_Off (Id);
11059 end if;
11061 if No (Ret_Type) then
11062 Spec :=
11063 Make_Procedure_Specification (Loc,
11064 Defining_Unit_Name => Id,
11065 Parameter_Specifications => Profile);
11066 else
11067 Spec :=
11068 Make_Function_Specification (Loc,
11069 Defining_Unit_Name => Id,
11070 Parameter_Specifications => Profile,
11071 Result_Definition => New_Occurrence_Of (Ret_Type, Loc));
11072 end if;
11074 -- Declare an abstract subprogram for primitive subprograms of an
11075 -- interface type (except for "=").
11077 if Is_Interface (Tag_Typ) then
11078 if Name /= Name_Op_Eq then
11079 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
11081 -- The equality function (if any) for an interface type is defined
11082 -- to be nonabstract, so we create an expression function for it that
11083 -- always returns False. Note that the function can never actually be
11084 -- invoked because interface types are abstract, so there aren't any
11085 -- objects of such types (and their equality operation will always
11086 -- dispatch).
11088 else
11089 return Make_Expression_Function
11090 (Loc, Spec, New_Occurrence_Of (Standard_False, Loc));
11091 end if;
11093 -- If body case, return empty subprogram body. Note that this is ill-
11094 -- formed, because there is not even a null statement, and certainly not
11095 -- a return in the function case. The caller is expected to do surgery
11096 -- on the body to add the appropriate stuff.
11098 elsif For_Body then
11099 return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
11101 -- For the case of an Input attribute predefined for an abstract type,
11102 -- generate an abstract specification. This will never be called, but we
11103 -- need the slot allocated in the dispatching table so that attributes
11104 -- typ'Class'Input and typ'Class'Output will work properly.
11106 elsif Is_TSS (Name, TSS_Stream_Input)
11107 and then Is_Abstract_Type (Tag_Typ)
11108 then
11109 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
11111 -- Normal spec case, where we return a subprogram declaration
11113 else
11114 return Make_Subprogram_Declaration (Loc, Spec);
11115 end if;
11116 end Predef_Spec_Or_Body;
11118 -----------------------------
11119 -- Predef_Stream_Attr_Spec --
11120 -----------------------------
11122 function Predef_Stream_Attr_Spec
11123 (Loc : Source_Ptr;
11124 Tag_Typ : Entity_Id;
11125 Name : TSS_Name_Type) return Node_Id
11127 Ret_Type : Entity_Id;
11129 begin
11130 if Name = TSS_Stream_Input then
11131 Ret_Type := Tag_Typ;
11132 else
11133 Ret_Type := Empty;
11134 end if;
11136 return
11137 Predef_Spec_Or_Body
11138 (Loc,
11139 Name => Make_TSS_Name (Tag_Typ, Name),
11140 Tag_Typ => Tag_Typ,
11141 Profile => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
11142 Ret_Type => Ret_Type,
11143 For_Body => False);
11144 end Predef_Stream_Attr_Spec;
11146 ----------------------------------
11147 -- Predefined_Primitive_Eq_Body --
11148 ----------------------------------
11150 procedure Predefined_Primitive_Eq_Body
11151 (Tag_Typ : Entity_Id;
11152 Predef_List : List_Id;
11153 Renamed_Eq : Entity_Id)
11155 Decl : Node_Id;
11156 Eq_Needed : Boolean;
11157 Eq_Name : Name_Id;
11158 Prim : Elmt_Id;
11160 begin
11161 -- See if we have a predefined "=" operator
11163 if Present (Renamed_Eq) then
11164 Eq_Needed := True;
11165 Eq_Name := Chars (Renamed_Eq);
11167 -- If the parent is an interface type then it has defined all the
11168 -- predefined primitives abstract and we need to check if the type
11169 -- has some user defined "=" function which matches the profile of
11170 -- the Ada predefined equality operator to avoid generating it.
11172 elsif Is_Interface (Etype (Tag_Typ)) then
11173 Eq_Needed := True;
11174 Eq_Name := Name_Op_Eq;
11176 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
11177 while Present (Prim) loop
11178 if Is_User_Defined_Equality (Node (Prim))
11179 and then not Is_Internal (Node (Prim))
11180 then
11181 Eq_Needed := False;
11182 Eq_Name := No_Name;
11183 exit;
11184 end if;
11186 Next_Elmt (Prim);
11187 end loop;
11189 else
11190 Eq_Needed := False;
11191 Eq_Name := No_Name;
11193 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
11194 while Present (Prim) loop
11195 if Is_User_Defined_Equality (Node (Prim))
11196 and then Is_Internal (Node (Prim))
11197 then
11198 Eq_Needed := True;
11199 Eq_Name := Name_Op_Eq;
11200 exit;
11201 end if;
11203 Next_Elmt (Prim);
11204 end loop;
11205 end if;
11207 -- If equality is needed, we will have its name
11209 pragma Assert (Eq_Needed = Present (Eq_Name));
11211 -- Body for equality
11213 if Eq_Needed then
11214 Decl := Make_Eq_Body (Tag_Typ, Eq_Name);
11215 Append_To (Predef_List, Decl);
11216 end if;
11218 -- Body for inequality (if required)
11220 Decl := Make_Neq_Body (Tag_Typ);
11222 if Present (Decl) then
11223 Append_To (Predef_List, Decl);
11224 end if;
11225 end Predefined_Primitive_Eq_Body;
11227 ---------------------------------
11228 -- Predefined_Primitive_Bodies --
11229 ---------------------------------
11231 function Predefined_Primitive_Bodies
11232 (Tag_Typ : Entity_Id;
11233 Renamed_Eq : Entity_Id) return List_Id
11235 Loc : constant Source_Ptr := Sloc (Tag_Typ);
11236 Res : constant List_Id := New_List;
11237 Adj_Call : Node_Id;
11238 Decl : Node_Id;
11239 Fin_Call : Node_Id;
11240 Ent : Entity_Id;
11242 pragma Warnings (Off, Ent);
11244 use Exp_Put_Image;
11246 begin
11247 pragma Assert (not Is_Interface (Tag_Typ));
11249 -- Body of _Size
11251 Decl := Predef_Spec_Or_Body (Loc,
11252 Tag_Typ => Tag_Typ,
11253 Name => Name_uSize,
11254 Profile => New_List (
11255 Make_Parameter_Specification (Loc,
11256 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
11257 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
11259 Ret_Type => Standard_Long_Long_Integer,
11260 For_Body => True);
11262 Set_Handled_Statement_Sequence (Decl,
11263 Make_Handled_Sequence_Of_Statements (Loc, New_List (
11264 Make_Simple_Return_Statement (Loc,
11265 Expression =>
11266 Make_Attribute_Reference (Loc,
11267 Prefix => Make_Identifier (Loc, Name_X),
11268 Attribute_Name => Name_Size)))));
11270 Append_To (Res, Decl);
11272 -- Body of Put_Image
11274 if No (TSS (Tag_Typ, TSS_Put_Image))
11275 and then (not No_Run_Time_Mode)
11276 and then RTE_Available (RE_Root_Buffer_Type)
11277 then
11278 Build_Record_Put_Image_Procedure (Loc, Tag_Typ, Decl, Ent);
11279 Append_To (Res, Decl);
11280 end if;
11282 -- Bodies for Dispatching stream IO routines. We need these only for
11283 -- non-limited types (in the limited case there is no dispatching).
11284 -- We also skip them if dispatching or finalization are not available
11285 -- or if stream operations are prohibited by restriction No_Streams or
11286 -- from use of pragma/aspect No_Tagged_Streams.
11288 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Read)
11289 and then No (TSS (Tag_Typ, TSS_Stream_Read))
11290 then
11291 Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
11292 Append_To (Res, Decl);
11293 end if;
11295 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Write)
11296 and then No (TSS (Tag_Typ, TSS_Stream_Write))
11297 then
11298 Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
11299 Append_To (Res, Decl);
11300 end if;
11302 -- Skip body of _Input for the abstract case, since the corresponding
11303 -- spec is abstract (see Predef_Spec_Or_Body).
11305 if not Is_Abstract_Type (Tag_Typ)
11306 and then Stream_Operation_OK (Tag_Typ, TSS_Stream_Input)
11307 and then No (TSS (Tag_Typ, TSS_Stream_Input))
11308 then
11309 Build_Record_Or_Elementary_Input_Function
11310 (Loc, Tag_Typ, Decl, Ent);
11311 Append_To (Res, Decl);
11312 end if;
11314 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Output)
11315 and then No (TSS (Tag_Typ, TSS_Stream_Output))
11316 then
11317 Build_Record_Or_Elementary_Output_Procedure (Loc, Tag_Typ, Decl, Ent);
11318 Append_To (Res, Decl);
11319 end if;
11321 -- Ada 2005: Generate bodies for the following primitive operations for
11322 -- limited interfaces and synchronized types that implement a limited
11323 -- interface.
11325 -- disp_asynchronous_select
11326 -- disp_conditional_select
11327 -- disp_get_prim_op_kind
11328 -- disp_get_task_id
11329 -- disp_timed_select
11331 -- The interface versions will have null bodies
11333 -- Disable the generation of these bodies if Ravenscar or ZFP is active
11335 -- In VM targets we define these primitives in all root tagged types
11336 -- that are not interface types. Done because in VM targets we don't
11337 -- have secondary dispatch tables and any derivation of Tag_Typ may
11338 -- cover limited interfaces (which always have these primitives since
11339 -- they may be ancestors of synchronized interface types).
11341 if Ada_Version >= Ada_2005
11342 and then
11343 ((Is_Interface (Etype (Tag_Typ))
11344 and then Is_Limited_Record (Etype (Tag_Typ)))
11345 or else
11346 (Is_Concurrent_Record_Type (Tag_Typ)
11347 and then Has_Interfaces (Tag_Typ))
11348 or else
11349 (not Tagged_Type_Expansion
11350 and then Tag_Typ = Root_Type (Tag_Typ)))
11351 and then not Restriction_Active (No_Select_Statements)
11352 and then RTE_Available (RE_Select_Specific_Data)
11353 then
11354 Append_To (Res, Make_Disp_Asynchronous_Select_Body (Tag_Typ));
11355 Append_To (Res, Make_Disp_Conditional_Select_Body (Tag_Typ));
11356 Append_To (Res, Make_Disp_Get_Prim_Op_Kind_Body (Tag_Typ));
11357 Append_To (Res, Make_Disp_Get_Task_Id_Body (Tag_Typ));
11358 Append_To (Res, Make_Disp_Requeue_Body (Tag_Typ));
11359 Append_To (Res, Make_Disp_Timed_Select_Body (Tag_Typ));
11360 end if;
11362 if not Is_Limited_Type (Tag_Typ) then
11363 -- Body for equality and inequality
11365 Predefined_Primitive_Eq_Body (Tag_Typ, Res, Renamed_Eq);
11367 -- Body for dispatching assignment
11369 Decl :=
11370 Predef_Spec_Or_Body (Loc,
11371 Tag_Typ => Tag_Typ,
11372 Name => Name_uAssign,
11373 Profile => New_List (
11374 Make_Parameter_Specification (Loc,
11375 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
11376 Out_Present => True,
11377 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
11379 Make_Parameter_Specification (Loc,
11380 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
11381 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
11382 For_Body => True);
11384 Set_Handled_Statement_Sequence (Decl,
11385 Make_Handled_Sequence_Of_Statements (Loc, New_List (
11386 Make_Assignment_Statement (Loc,
11387 Name => Make_Identifier (Loc, Name_X),
11388 Expression => Make_Identifier (Loc, Name_Y)))));
11390 Append_To (Res, Decl);
11391 end if;
11393 -- Generate empty bodies of routines Deep_Adjust and Deep_Finalize for
11394 -- tagged types which do not contain controlled components.
11396 -- Do not generate the routines if finalization is disabled
11398 if Restriction_Active (No_Finalization) then
11399 null;
11401 elsif not Has_Controlled_Component (Tag_Typ) then
11402 if not Is_Limited_Type (Tag_Typ) then
11403 Adj_Call := Empty;
11404 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
11406 if Is_Controlled (Tag_Typ) then
11407 Adj_Call :=
11408 Make_Adjust_Call (
11409 Obj_Ref => Make_Identifier (Loc, Name_V),
11410 Typ => Tag_Typ);
11411 end if;
11413 if No (Adj_Call) then
11414 Adj_Call := Make_Null_Statement (Loc);
11415 end if;
11417 Set_Handled_Statement_Sequence (Decl,
11418 Make_Handled_Sequence_Of_Statements (Loc,
11419 Statements => New_List (Adj_Call)));
11421 Append_To (Res, Decl);
11422 end if;
11424 Fin_Call := Empty;
11425 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
11427 if Is_Controlled (Tag_Typ) then
11428 Fin_Call :=
11429 Make_Final_Call
11430 (Obj_Ref => Make_Identifier (Loc, Name_V),
11431 Typ => Tag_Typ);
11432 end if;
11434 if No (Fin_Call) then
11435 Fin_Call := Make_Null_Statement (Loc);
11436 end if;
11438 Set_Handled_Statement_Sequence (Decl,
11439 Make_Handled_Sequence_Of_Statements (Loc,
11440 Statements => New_List (Fin_Call)));
11442 Append_To (Res, Decl);
11443 end if;
11445 return Res;
11446 end Predefined_Primitive_Bodies;
11448 ---------------------------------
11449 -- Predefined_Primitive_Freeze --
11450 ---------------------------------
11452 function Predefined_Primitive_Freeze
11453 (Tag_Typ : Entity_Id) return List_Id
11455 Res : constant List_Id := New_List;
11456 Prim : Elmt_Id;
11457 Frnodes : List_Id;
11459 begin
11460 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
11461 while Present (Prim) loop
11462 if Is_Predefined_Dispatching_Operation (Node (Prim)) then
11463 Frnodes := Freeze_Entity (Node (Prim), Tag_Typ);
11465 if Present (Frnodes) then
11466 Append_List_To (Res, Frnodes);
11467 end if;
11468 end if;
11470 Next_Elmt (Prim);
11471 end loop;
11473 return Res;
11474 end Predefined_Primitive_Freeze;
11476 -------------------------
11477 -- Stream_Operation_OK --
11478 -------------------------
11480 function Stream_Operation_OK
11481 (Typ : Entity_Id;
11482 Operation : TSS_Name_Type) return Boolean
11484 Has_Predefined_Or_Specified_Stream_Attribute : Boolean := False;
11486 begin
11487 -- Special case of a limited type extension: a default implementation
11488 -- of the stream attributes Read or Write exists if that attribute
11489 -- has been specified or is available for an ancestor type; a default
11490 -- implementation of the attribute Output (resp. Input) exists if the
11491 -- attribute has been specified or Write (resp. Read) is available for
11492 -- an ancestor type. The last condition only applies under Ada 2005.
11494 if Is_Limited_Type (Typ) and then Is_Tagged_Type (Typ) then
11495 if Operation = TSS_Stream_Read then
11496 Has_Predefined_Or_Specified_Stream_Attribute :=
11497 Has_Specified_Stream_Read (Typ);
11499 elsif Operation = TSS_Stream_Write then
11500 Has_Predefined_Or_Specified_Stream_Attribute :=
11501 Has_Specified_Stream_Write (Typ);
11503 elsif Operation = TSS_Stream_Input then
11504 Has_Predefined_Or_Specified_Stream_Attribute :=
11505 Has_Specified_Stream_Input (Typ)
11506 or else
11507 (Ada_Version >= Ada_2005
11508 and then Stream_Operation_OK (Typ, TSS_Stream_Read));
11510 elsif Operation = TSS_Stream_Output then
11511 Has_Predefined_Or_Specified_Stream_Attribute :=
11512 Has_Specified_Stream_Output (Typ)
11513 or else
11514 (Ada_Version >= Ada_2005
11515 and then Stream_Operation_OK (Typ, TSS_Stream_Write));
11516 end if;
11518 -- Case of inherited TSS_Stream_Read or TSS_Stream_Write
11520 if not Has_Predefined_Or_Specified_Stream_Attribute
11521 and then Is_Derived_Type (Typ)
11522 and then (Operation = TSS_Stream_Read
11523 or else Operation = TSS_Stream_Write)
11524 then
11525 Has_Predefined_Or_Specified_Stream_Attribute :=
11526 Present
11527 (Find_Inherited_TSS (Base_Type (Etype (Typ)), Operation));
11528 end if;
11529 end if;
11531 -- If the type is not limited, or else is limited but the attribute is
11532 -- explicitly specified or is predefined for the type, then return True,
11533 -- unless other conditions prevail, such as restrictions prohibiting
11534 -- streams or dispatching operations. We also return True for limited
11535 -- interfaces, because they may be extended by nonlimited types and
11536 -- permit inheritance in this case (addresses cases where an abstract
11537 -- extension doesn't get 'Input declared, as per comments below, but
11538 -- 'Class'Input must still be allowed). Note that attempts to apply
11539 -- stream attributes to a limited interface or its class-wide type
11540 -- (or limited extensions thereof) will still get properly rejected
11541 -- by Check_Stream_Attribute.
11543 -- We exclude the Input operation from being a predefined subprogram in
11544 -- the case where the associated type is an abstract extension, because
11545 -- the attribute is not callable in that case, per 13.13.2(49/2). Also,
11546 -- we don't want an abstract version created because types derived from
11547 -- the abstract type may not even have Input available (for example if
11548 -- derived from a private view of the abstract type that doesn't have
11549 -- a visible Input).
11551 -- Do not generate stream routines for type Finalization_Master because
11552 -- a master may never appear in types and therefore cannot be read or
11553 -- written.
11555 return
11556 (not Is_Limited_Type (Typ)
11557 or else Is_Interface (Typ)
11558 or else Has_Predefined_Or_Specified_Stream_Attribute)
11559 and then
11560 (Operation /= TSS_Stream_Input
11561 or else not Is_Abstract_Type (Typ)
11562 or else not Is_Derived_Type (Typ))
11563 and then not Has_Unknown_Discriminants (Typ)
11564 and then not Is_Concurrent_Interface (Typ)
11565 and then not Restriction_Active (No_Streams)
11566 and then not Restriction_Active (No_Dispatch)
11567 and then No (No_Tagged_Streams_Pragma (Typ))
11568 and then not No_Run_Time_Mode
11569 and then RTE_Available (RE_Tag)
11570 and then No (Type_Without_Stream_Operation (Typ))
11571 and then RTE_Available (RE_Root_Stream_Type)
11572 and then not Is_RTE (Typ, RE_Finalization_Master);
11573 end Stream_Operation_OK;
11575 end Exp_Ch3;