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