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