2009-04-20 Rafael Avila de Espindola <espindola@google.com>
[official-gcc.git] / gcc / ada / exp_ch3.adb
blob4442a78e01da4bd699cc41e06a32bd531b5e8df3
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-2008, 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_Disp; use Exp_Disp;
38 with Exp_Dist; use Exp_Dist;
39 with Exp_Smem; use Exp_Smem;
40 with Exp_Strm; use Exp_Strm;
41 with Exp_Tss; use Exp_Tss;
42 with Exp_Util; use Exp_Util;
43 with Freeze; use Freeze;
44 with Nlists; use Nlists;
45 with Namet; use Namet;
46 with Nmake; use Nmake;
47 with Opt; use Opt;
48 with Restrict; use Restrict;
49 with Rident; use Rident;
50 with Rtsfind; use Rtsfind;
51 with Sem; use Sem;
52 with Sem_Aux; use Sem_Aux;
53 with Sem_Attr; use Sem_Attr;
54 with Sem_Cat; use Sem_Cat;
55 with Sem_Ch3; use Sem_Ch3;
56 with Sem_Ch8; use Sem_Ch8;
57 with Sem_Disp; use Sem_Disp;
58 with Sem_Eval; use Sem_Eval;
59 with Sem_Mech; use Sem_Mech;
60 with Sem_Res; use Sem_Res;
61 with Sem_Type; use Sem_Type;
62 with Sem_Util; use Sem_Util;
63 with Sinfo; use Sinfo;
64 with Stand; use Stand;
65 with Snames; use Snames;
66 with Targparm; use Targparm;
67 with Tbuild; use Tbuild;
68 with Ttypes; use Ttypes;
69 with Validsw; use Validsw;
71 package body Exp_Ch3 is
73 -----------------------
74 -- Local Subprograms --
75 -----------------------
77 function Add_Final_Chain (Def_Id : Entity_Id) return Entity_Id;
78 -- Add the declaration of a finalization list to the freeze actions for
79 -- Def_Id, and return its defining identifier.
81 procedure Adjust_Discriminants (Rtype : Entity_Id);
82 -- This is used when freezing a record type. It attempts to construct
83 -- more restrictive subtypes for discriminants so that the max size of
84 -- the record can be calculated more accurately. See the body of this
85 -- procedure for details.
87 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id);
88 -- Build initialization procedure for given array type. Nod is a node
89 -- used for attachment of any actions required in its construction.
90 -- It also supplies the source location used for the procedure.
92 function Build_Discriminant_Formals
93 (Rec_Id : Entity_Id;
94 Use_Dl : Boolean) return List_Id;
95 -- This function uses the discriminants of a type to build a list of
96 -- formal parameters, used in the following function. If the flag Use_Dl
97 -- is set, the list is built using the already defined discriminals
98 -- of the type. Otherwise new identifiers are created, with the source
99 -- 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 function Build_Master_Renaming
118 (N : Node_Id;
119 T : Entity_Id) return Entity_Id;
120 -- If the designated type of an access type is a task type or contains
121 -- tasks, we make sure that a _Master variable is declared in the current
122 -- scope, and then declare a renaming for it:
124 -- atypeM : Master_Id renames _Master;
126 -- where atyp is the name of the access type. This declaration is used when
127 -- an allocator for the access type is expanded. The node is the full
128 -- declaration of the designated type that contains tasks. The renaming
129 -- declaration is inserted before N, and after the Master declaration.
131 procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id);
132 -- Build record initialization procedure. N is the type declaration
133 -- node, and Pe is the corresponding entity for the record type.
135 procedure Build_Slice_Assignment (Typ : Entity_Id);
136 -- Build assignment procedure for one-dimensional arrays of controlled
137 -- types. Other array and slice assignments are expanded in-line, but
138 -- the code expansion for controlled components (when control actions
139 -- are active) can lead to very large blocks that GCC3 handles poorly.
141 procedure Build_Variant_Record_Equality (Typ : Entity_Id);
142 -- Create An Equality function for the non-tagged variant record 'Typ'
143 -- and attach it to the TSS list
145 procedure Check_Stream_Attributes (Typ : Entity_Id);
146 -- Check that if a limited extension has a parent with user-defined stream
147 -- attributes, and does not itself have user-defined stream-attributes,
148 -- then any limited component of the extension also has the corresponding
149 -- user-defined stream attributes.
151 procedure Clean_Task_Names
152 (Typ : Entity_Id;
153 Proc_Id : Entity_Id);
154 -- If an initialization procedure includes calls to generate names
155 -- for task subcomponents, indicate that secondary stack cleanup is
156 -- needed after an initialization. Typ is the component type, and Proc_Id
157 -- the initialization procedure for the enclosing composite type.
159 procedure Expand_Tagged_Root (T : Entity_Id);
160 -- Add a field _Tag at the beginning of the record. This field carries
161 -- the value of the access to the Dispatch table. This procedure is only
162 -- called on root type, the _Tag field being inherited by the descendants.
164 procedure Expand_Record_Controller (T : Entity_Id);
165 -- T must be a record type that Has_Controlled_Component. Add a field
166 -- _controller of type Record_Controller or Limited_Record_Controller
167 -- in the record T.
169 procedure Freeze_Array_Type (N : Node_Id);
170 -- Freeze an array type. Deals with building the initialization procedure,
171 -- creating the packed array type for a packed array and also with the
172 -- creation of the controlling procedures for the controlled case. The
173 -- argument N is the N_Freeze_Entity node for the type.
175 procedure Freeze_Enumeration_Type (N : Node_Id);
176 -- Freeze enumeration type with non-standard representation. Builds the
177 -- array and function needed to convert between enumeration pos and
178 -- enumeration representation values. N is the N_Freeze_Entity node
179 -- for the type.
181 procedure Freeze_Record_Type (N : Node_Id);
182 -- Freeze record type. Builds all necessary discriminant checking
183 -- and other ancillary functions, and builds dispatch tables where
184 -- needed. The argument N is the N_Freeze_Entity node. This processing
185 -- applies only to E_Record_Type entities, not to class wide types,
186 -- record subtypes, or private types.
188 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id);
189 -- Treat user-defined stream operations as renaming_as_body if the
190 -- subprogram they rename is not frozen when the type is frozen.
192 procedure Initialization_Warning (E : Entity_Id);
193 -- If static elaboration of the package is requested, indicate
194 -- when a type does meet the conditions for static initialization. If
195 -- E is a type, it has components that have no static initialization.
196 -- if E is an entity, its initial expression is not compile-time known.
198 function Init_Formals (Typ : Entity_Id) return List_Id;
199 -- This function builds the list of formals for an initialization routine.
200 -- The first formal is always _Init with the given type. For task value
201 -- record types and types containing tasks, three additional formals are
202 -- added:
204 -- _Master : Master_Id
205 -- _Chain : in out Activation_Chain
206 -- _Task_Name : String
208 -- The caller must append additional entries for discriminants if required.
210 function In_Runtime (E : Entity_Id) return Boolean;
211 -- Check if E is defined in the RTL (in a child of Ada or System). Used
212 -- to avoid to bring in the overhead of _Input, _Output for tagged types.
214 function Is_Variable_Size_Record (E : Entity_Id) return Boolean;
215 -- Returns true if E has variable size components
217 function Make_Eq_Case
218 (E : Entity_Id;
219 CL : Node_Id;
220 Discr : Entity_Id := Empty) return List_Id;
221 -- Building block for variant record equality. Defined to share the code
222 -- between the tagged and non-tagged case. Given a Component_List node CL,
223 -- it generates an 'if' followed by a 'case' statement that compares all
224 -- components of local temporaries named X and Y (that are declared as
225 -- formals at some upper level). E provides the Sloc to be used for the
226 -- generated code. Discr is used as the case statement switch in the case
227 -- of Unchecked_Union equality.
229 function Make_Eq_If
230 (E : Entity_Id;
231 L : List_Id) return Node_Id;
232 -- Building block for variant record equality. Defined to share the code
233 -- between the tagged and non-tagged case. Given the list of components
234 -- (or discriminants) L, it generates a return statement that compares all
235 -- components of local temporaries named X and Y (that are declared as
236 -- formals at some upper level). E provides the Sloc to be used for the
237 -- generated code.
239 procedure Make_Predefined_Primitive_Specs
240 (Tag_Typ : Entity_Id;
241 Predef_List : out List_Id;
242 Renamed_Eq : out Entity_Id);
243 -- Create a list with the specs of the predefined primitive operations.
244 -- For tagged types that are interfaces all these primitives are defined
245 -- abstract.
247 -- The following entries are present for all tagged types, and provide
248 -- the results of the corresponding attribute applied to the object.
249 -- Dispatching is required in general, since the result of the attribute
250 -- will vary with the actual object subtype.
252 -- _alignment provides result of 'Alignment attribute
253 -- _size provides result of 'Size attribute
254 -- typSR provides result of 'Read attribute
255 -- typSW provides result of 'Write attribute
256 -- typSI provides result of 'Input attribute
257 -- typSO provides result of 'Output attribute
259 -- The following entries are additionally present for non-limited tagged
260 -- types, and implement additional dispatching operations for predefined
261 -- operations:
263 -- _equality implements "=" operator
264 -- _assign implements assignment operation
265 -- typDF implements deep finalization
266 -- typDA implements deep adjust
268 -- The latter two are empty procedures unless the type contains some
269 -- controlled components that require finalization actions (the deep
270 -- in the name refers to the fact that the action applies to components).
272 -- The list is returned in Predef_List. The Parameter Renamed_Eq either
273 -- returns the value Empty, or else the defining unit name for the
274 -- predefined equality function in the case where the type has a primitive
275 -- operation that is a renaming of predefined equality (but only if there
276 -- is also an overriding user-defined equality function). The returned
277 -- Renamed_Eq will be passed to the corresponding parameter of
278 -- Predefined_Primitive_Bodies.
280 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean;
281 -- returns True if there are representation clauses for type T that are not
282 -- inherited. If the result is false, the init_proc and the discriminant
283 -- checking functions of the parent can be reused by a derived type.
285 procedure Make_Controlling_Function_Wrappers
286 (Tag_Typ : Entity_Id;
287 Decl_List : out List_Id;
288 Body_List : out List_Id);
289 -- Ada 2005 (AI-391): Makes specs and bodies for the wrapper functions
290 -- associated with inherited functions with controlling results which
291 -- are not overridden. The body of each wrapper function consists solely
292 -- of a return statement whose expression is an extension aggregate
293 -- invoking the inherited subprogram's parent subprogram and extended
294 -- with a null association list.
296 procedure Make_Null_Procedure_Specs
297 (Tag_Typ : Entity_Id;
298 Decl_List : out List_Id);
299 -- Ada 2005 (AI-251): Makes specs for null procedures associated with any
300 -- null procedures inherited from an interface type that have not been
301 -- overridden. Only one null procedure will be created for a given set of
302 -- inherited null procedures with homographic profiles.
304 function Predef_Spec_Or_Body
305 (Loc : Source_Ptr;
306 Tag_Typ : Entity_Id;
307 Name : Name_Id;
308 Profile : List_Id;
309 Ret_Type : Entity_Id := Empty;
310 For_Body : Boolean := False) return Node_Id;
311 -- This function generates the appropriate expansion for a predefined
312 -- primitive operation specified by its name, parameter profile and
313 -- return type (Empty means this is a procedure). If For_Body is false,
314 -- then the returned node is a subprogram declaration. If For_Body is
315 -- true, then the returned node is a empty subprogram body containing
316 -- no declarations and no statements.
318 function Predef_Stream_Attr_Spec
319 (Loc : Source_Ptr;
320 Tag_Typ : Entity_Id;
321 Name : TSS_Name_Type;
322 For_Body : Boolean := False) return Node_Id;
323 -- Specialized version of Predef_Spec_Or_Body that apply to read, write,
324 -- input and output attribute whose specs are constructed in Exp_Strm.
326 function Predef_Deep_Spec
327 (Loc : Source_Ptr;
328 Tag_Typ : Entity_Id;
329 Name : TSS_Name_Type;
330 For_Body : Boolean := False) return Node_Id;
331 -- Specialized version of Predef_Spec_Or_Body that apply to _deep_adjust
332 -- and _deep_finalize
334 function Predefined_Primitive_Bodies
335 (Tag_Typ : Entity_Id;
336 Renamed_Eq : Entity_Id) return List_Id;
337 -- Create the bodies of the predefined primitives that are described in
338 -- Predefined_Primitive_Specs. When not empty, Renamed_Eq must denote
339 -- the defining unit name of the type's predefined equality as returned
340 -- by Make_Predefined_Primitive_Specs.
342 function Predefined_Primitive_Freeze (Tag_Typ : Entity_Id) return List_Id;
343 -- Freeze entities of all predefined primitive operations. This is needed
344 -- because the bodies of these operations do not normally do any freezing.
346 function Stream_Operation_OK
347 (Typ : Entity_Id;
348 Operation : TSS_Name_Type) return Boolean;
349 -- Check whether the named stream operation must be emitted for a given
350 -- type. The rules for inheritance of stream attributes by type extensions
351 -- are enforced by this function. Furthermore, various restrictions prevent
352 -- the generation of these operations, as a useful optimization or for
353 -- certification purposes.
355 ---------------------
356 -- Add_Final_Chain --
357 ---------------------
359 function Add_Final_Chain (Def_Id : Entity_Id) return Entity_Id is
360 Loc : constant Source_Ptr := Sloc (Def_Id);
361 Flist : Entity_Id;
363 begin
364 Flist :=
365 Make_Defining_Identifier (Loc,
366 New_External_Name (Chars (Def_Id), 'L'));
368 Append_Freeze_Action (Def_Id,
369 Make_Object_Declaration (Loc,
370 Defining_Identifier => Flist,
371 Object_Definition =>
372 New_Reference_To (RTE (RE_List_Controller), Loc)));
374 return Flist;
375 end Add_Final_Chain;
377 --------------------------
378 -- Adjust_Discriminants --
379 --------------------------
381 -- This procedure attempts to define subtypes for discriminants that are
382 -- more restrictive than those declared. Such a replacement is possible if
383 -- we can demonstrate that values outside the restricted range would cause
384 -- constraint errors in any case. The advantage of restricting the
385 -- discriminant types in this way is that the maximum size of the variant
386 -- record can be calculated more conservatively.
388 -- An example of a situation in which we can perform this type of
389 -- restriction is the following:
391 -- subtype B is range 1 .. 10;
392 -- type Q is array (B range <>) of Integer;
394 -- type V (N : Natural) is record
395 -- C : Q (1 .. N);
396 -- end record;
398 -- In this situation, we can restrict the upper bound of N to 10, since
399 -- any larger value would cause a constraint error in any case.
401 -- There are many situations in which such restriction is possible, but
402 -- for now, we just look for cases like the above, where the component
403 -- in question is a one dimensional array whose upper bound is one of
404 -- the record discriminants. Also the component must not be part of
405 -- any variant part, since then the component does not always exist.
407 procedure Adjust_Discriminants (Rtype : Entity_Id) is
408 Loc : constant Source_Ptr := Sloc (Rtype);
409 Comp : Entity_Id;
410 Ctyp : Entity_Id;
411 Ityp : Entity_Id;
412 Lo : Node_Id;
413 Hi : Node_Id;
414 P : Node_Id;
415 Loval : Uint;
416 Discr : Entity_Id;
417 Dtyp : Entity_Id;
418 Dhi : Node_Id;
419 Dhiv : Uint;
420 Ahi : Node_Id;
421 Ahiv : Uint;
422 Tnn : Entity_Id;
424 begin
425 Comp := First_Component (Rtype);
426 while Present (Comp) loop
428 -- If our parent is a variant, quit, we do not look at components
429 -- that are in variant parts, because they may not always exist.
431 P := Parent (Comp); -- component declaration
432 P := Parent (P); -- component list
434 exit when Nkind (Parent (P)) = N_Variant;
436 -- We are looking for a one dimensional array type
438 Ctyp := Etype (Comp);
440 if not Is_Array_Type (Ctyp)
441 or else Number_Dimensions (Ctyp) > 1
442 then
443 goto Continue;
444 end if;
446 -- The lower bound must be constant, and the upper bound is a
447 -- discriminant (which is a discriminant of the current record).
449 Ityp := Etype (First_Index (Ctyp));
450 Lo := Type_Low_Bound (Ityp);
451 Hi := Type_High_Bound (Ityp);
453 if not Compile_Time_Known_Value (Lo)
454 or else Nkind (Hi) /= N_Identifier
455 or else No (Entity (Hi))
456 or else Ekind (Entity (Hi)) /= E_Discriminant
457 then
458 goto Continue;
459 end if;
461 -- We have an array with appropriate bounds
463 Loval := Expr_Value (Lo);
464 Discr := Entity (Hi);
465 Dtyp := Etype (Discr);
467 -- See if the discriminant has a known upper bound
469 Dhi := Type_High_Bound (Dtyp);
471 if not Compile_Time_Known_Value (Dhi) then
472 goto Continue;
473 end if;
475 Dhiv := Expr_Value (Dhi);
477 -- See if base type of component array has known upper bound
479 Ahi := Type_High_Bound (Etype (First_Index (Base_Type (Ctyp))));
481 if not Compile_Time_Known_Value (Ahi) then
482 goto Continue;
483 end if;
485 Ahiv := Expr_Value (Ahi);
487 -- The condition for doing the restriction is that the high bound
488 -- of the discriminant is greater than the low bound of the array,
489 -- and is also greater than the high bound of the base type index.
491 if Dhiv > Loval and then Dhiv > Ahiv then
493 -- We can reset the upper bound of the discriminant type to
494 -- whichever is larger, the low bound of the component, or
495 -- the high bound of the base type array index.
497 -- We build a subtype that is declared as
499 -- subtype Tnn is discr_type range discr_type'First .. max;
501 -- And insert this declaration into the tree. The type of the
502 -- discriminant is then reset to this more restricted subtype.
504 Tnn := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
506 Insert_Action (Declaration_Node (Rtype),
507 Make_Subtype_Declaration (Loc,
508 Defining_Identifier => Tnn,
509 Subtype_Indication =>
510 Make_Subtype_Indication (Loc,
511 Subtype_Mark => New_Occurrence_Of (Dtyp, Loc),
512 Constraint =>
513 Make_Range_Constraint (Loc,
514 Range_Expression =>
515 Make_Range (Loc,
516 Low_Bound =>
517 Make_Attribute_Reference (Loc,
518 Attribute_Name => Name_First,
519 Prefix => New_Occurrence_Of (Dtyp, Loc)),
520 High_Bound =>
521 Make_Integer_Literal (Loc,
522 Intval => UI_Max (Loval, Ahiv)))))));
524 Set_Etype (Discr, Tnn);
525 end if;
527 <<Continue>>
528 Next_Component (Comp);
529 end loop;
530 end Adjust_Discriminants;
532 ---------------------------
533 -- Build_Array_Init_Proc --
534 ---------------------------
536 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id) is
537 Loc : constant Source_Ptr := Sloc (Nod);
538 Comp_Type : constant Entity_Id := Component_Type (A_Type);
539 Index_List : List_Id;
540 Proc_Id : Entity_Id;
541 Body_Stmts : List_Id;
542 Has_Default_Init : Boolean;
544 function Init_Component return List_Id;
545 -- Create one statement to initialize one array component, designated
546 -- by a full set of indices.
548 function Init_One_Dimension (N : Int) return List_Id;
549 -- Create loop to initialize one dimension of the array. The single
550 -- statement in the loop body initializes the inner dimensions if any,
551 -- or else the single component. Note that this procedure is called
552 -- recursively, with N being the dimension to be initialized. A call
553 -- with N greater than the number of dimensions simply generates the
554 -- component initialization, terminating the recursion.
556 --------------------
557 -- Init_Component --
558 --------------------
560 function Init_Component return List_Id is
561 Comp : Node_Id;
563 begin
564 Comp :=
565 Make_Indexed_Component (Loc,
566 Prefix => Make_Identifier (Loc, Name_uInit),
567 Expressions => Index_List);
569 if Needs_Simple_Initialization (Comp_Type) then
570 Set_Assignment_OK (Comp);
571 return New_List (
572 Make_Assignment_Statement (Loc,
573 Name => Comp,
574 Expression =>
575 Get_Simple_Init_Val
576 (Comp_Type, Nod, Component_Size (A_Type))));
578 else
579 Clean_Task_Names (Comp_Type, Proc_Id);
580 return
581 Build_Initialization_Call
582 (Loc, Comp, Comp_Type,
583 In_Init_Proc => True,
584 Enclos_Type => A_Type);
585 end if;
586 end Init_Component;
588 ------------------------
589 -- Init_One_Dimension --
590 ------------------------
592 function Init_One_Dimension (N : Int) return List_Id is
593 Index : Entity_Id;
595 begin
596 -- If the component does not need initializing, then there is nothing
597 -- to do here, so we return a null body. This occurs when generating
598 -- the dummy Init_Proc needed for Initialize_Scalars processing.
600 if not Has_Non_Null_Base_Init_Proc (Comp_Type)
601 and then not Needs_Simple_Initialization (Comp_Type)
602 and then not Has_Task (Comp_Type)
603 then
604 return New_List (Make_Null_Statement (Loc));
606 -- If all dimensions dealt with, we simply initialize the component
608 elsif N > Number_Dimensions (A_Type) then
609 return Init_Component;
611 -- Here we generate the required loop
613 else
614 Index :=
615 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
617 Append (New_Reference_To (Index, Loc), Index_List);
619 return New_List (
620 Make_Implicit_Loop_Statement (Nod,
621 Identifier => Empty,
622 Iteration_Scheme =>
623 Make_Iteration_Scheme (Loc,
624 Loop_Parameter_Specification =>
625 Make_Loop_Parameter_Specification (Loc,
626 Defining_Identifier => Index,
627 Discrete_Subtype_Definition =>
628 Make_Attribute_Reference (Loc,
629 Prefix => Make_Identifier (Loc, Name_uInit),
630 Attribute_Name => Name_Range,
631 Expressions => New_List (
632 Make_Integer_Literal (Loc, N))))),
633 Statements => Init_One_Dimension (N + 1)));
634 end if;
635 end Init_One_Dimension;
637 -- Start of processing for Build_Array_Init_Proc
639 begin
640 -- Nothing to generate in the following cases:
642 -- 1. Initialization is suppressed for the type
643 -- 2. The type is a value type, in the CIL sense.
644 -- 3. An initialization already exists for the base type
646 if Suppress_Init_Proc (A_Type)
647 or else Is_Value_Type (Comp_Type)
648 or else Present (Base_Init_Proc (A_Type))
649 then
650 return;
651 end if;
653 Index_List := New_List;
655 -- We need an initialization procedure if any of the following is true:
657 -- 1. The component type has an initialization procedure
658 -- 2. The component type needs simple initialization
659 -- 3. Tasks are present
660 -- 4. The type is marked as a public entity
662 -- The reason for the public entity test is to deal properly with the
663 -- Initialize_Scalars pragma. This pragma can be set in the client and
664 -- not in the declaring package, this means the client will make a call
665 -- to the initialization procedure (because one of conditions 1-3 must
666 -- apply in this case), and we must generate a procedure (even if it is
667 -- null) to satisfy the call in this case.
669 -- Exception: do not build an array init_proc for a type whose root
670 -- type is Standard.String or Standard.Wide_[Wide_]String, since there
671 -- is no place to put the code, and in any case we handle initialization
672 -- of such types (in the Initialize_Scalars case, that's the only time
673 -- the issue arises) in a special manner anyway which does not need an
674 -- init_proc.
676 Has_Default_Init := Has_Non_Null_Base_Init_Proc (Comp_Type)
677 or else Needs_Simple_Initialization (Comp_Type)
678 or else Has_Task (Comp_Type);
680 if Has_Default_Init
681 or else (not Restriction_Active (No_Initialize_Scalars)
682 and then Is_Public (A_Type)
683 and then Root_Type (A_Type) /= Standard_String
684 and then Root_Type (A_Type) /= Standard_Wide_String
685 and then Root_Type (A_Type) /= Standard_Wide_Wide_String)
686 then
687 Proc_Id :=
688 Make_Defining_Identifier (Loc,
689 Chars => Make_Init_Proc_Name (A_Type));
691 -- If No_Default_Initialization restriction is active, then we don't
692 -- want to build an init_proc, but we need to mark that an init_proc
693 -- would be needed if this restriction was not active (so that we can
694 -- detect attempts to call it), so set a dummy init_proc in place.
695 -- This is only done though when actual default initialization is
696 -- needed (and not done when only Is_Public is True), since otherwise
697 -- objects such as arrays of scalars could be wrongly flagged as
698 -- violating the restriction.
700 if Restriction_Active (No_Default_Initialization) then
701 if Has_Default_Init then
702 Set_Init_Proc (A_Type, Proc_Id);
703 end if;
705 return;
706 end if;
708 Body_Stmts := Init_One_Dimension (1);
710 Discard_Node (
711 Make_Subprogram_Body (Loc,
712 Specification =>
713 Make_Procedure_Specification (Loc,
714 Defining_Unit_Name => Proc_Id,
715 Parameter_Specifications => Init_Formals (A_Type)),
716 Declarations => New_List,
717 Handled_Statement_Sequence =>
718 Make_Handled_Sequence_Of_Statements (Loc,
719 Statements => Body_Stmts)));
721 Set_Ekind (Proc_Id, E_Procedure);
722 Set_Is_Public (Proc_Id, Is_Public (A_Type));
723 Set_Is_Internal (Proc_Id);
724 Set_Has_Completion (Proc_Id);
726 if not Debug_Generated_Code then
727 Set_Debug_Info_Off (Proc_Id);
728 end if;
730 -- Set inlined unless controlled stuff or tasks around, in which
731 -- case we do not want to inline, because nested stuff may cause
732 -- difficulties in inter-unit inlining, and furthermore there is
733 -- in any case no point in inlining such complex init procs.
735 if not Has_Task (Proc_Id)
736 and then not Needs_Finalization (Proc_Id)
737 then
738 Set_Is_Inlined (Proc_Id);
739 end if;
741 -- Associate Init_Proc with type, and determine if the procedure
742 -- is null (happens because of the Initialize_Scalars pragma case,
743 -- where we have to generate a null procedure in case it is called
744 -- by a client with Initialize_Scalars set). Such procedures have
745 -- to be generated, but do not have to be called, so we mark them
746 -- as null to suppress the call.
748 Set_Init_Proc (A_Type, Proc_Id);
750 if List_Length (Body_Stmts) = 1
751 and then Nkind (First (Body_Stmts)) = N_Null_Statement
752 then
753 Set_Is_Null_Init_Proc (Proc_Id);
755 else
756 -- Try to build a static aggregate to initialize statically
757 -- objects of the type. This can only be done for constrained
758 -- one-dimensional arrays with static bounds.
760 Set_Static_Initialization
761 (Proc_Id,
762 Build_Equivalent_Array_Aggregate (First_Subtype (A_Type)));
763 end if;
764 end if;
765 end Build_Array_Init_Proc;
767 -----------------------------
768 -- Build_Class_Wide_Master --
769 -----------------------------
771 procedure Build_Class_Wide_Master (T : Entity_Id) is
772 Loc : constant Source_Ptr := Sloc (T);
773 M_Id : Entity_Id;
774 Decl : Node_Id;
775 P : Node_Id;
776 Par : Node_Id;
778 begin
779 -- Nothing to do if there is no task hierarchy
781 if Restriction_Active (No_Task_Hierarchy) then
782 return;
783 end if;
785 -- Find declaration that created the access type: either a type
786 -- declaration, or an object declaration with an access definition,
787 -- in which case the type is anonymous.
789 if Is_Itype (T) then
790 P := Associated_Node_For_Itype (T);
791 else
792 P := Parent (T);
793 end if;
795 -- Nothing to do if we already built a master entity for this scope
797 if not Has_Master_Entity (Scope (T)) then
799 -- First build the master entity
800 -- _Master : constant Master_Id := Current_Master.all;
801 -- and insert it just before the current declaration.
803 Decl :=
804 Make_Object_Declaration (Loc,
805 Defining_Identifier =>
806 Make_Defining_Identifier (Loc, Name_uMaster),
807 Constant_Present => True,
808 Object_Definition => New_Reference_To (Standard_Integer, Loc),
809 Expression =>
810 Make_Explicit_Dereference (Loc,
811 New_Reference_To (RTE (RE_Current_Master), Loc)));
813 Insert_Action (P, Decl);
814 Analyze (Decl);
815 Set_Has_Master_Entity (Scope (T));
817 -- Now mark the containing scope as a task master. Masters
818 -- associated with return statements are already marked at
819 -- this stage (see Analyze_Subprogram_Body).
821 if Ekind (Current_Scope) /= E_Return_Statement then
822 Par := P;
823 while Nkind (Par) /= N_Compilation_Unit loop
824 Par := Parent (Par);
826 -- If we fall off the top, we are at the outer level, and the
827 -- environment task is our effective master, so nothing to mark.
829 if Nkind_In
830 (Par, N_Task_Body, N_Block_Statement, N_Subprogram_Body)
831 then
832 Set_Is_Task_Master (Par, True);
833 exit;
834 end if;
835 end loop;
836 end if;
837 end if;
839 -- Now define the renaming of the master_id
841 M_Id :=
842 Make_Defining_Identifier (Loc,
843 New_External_Name (Chars (T), 'M'));
845 Decl :=
846 Make_Object_Renaming_Declaration (Loc,
847 Defining_Identifier => M_Id,
848 Subtype_Mark => New_Reference_To (Standard_Integer, Loc),
849 Name => Make_Identifier (Loc, Name_uMaster));
850 Insert_Before (P, Decl);
851 Analyze (Decl);
853 Set_Master_Id (T, M_Id);
855 exception
856 when RE_Not_Available =>
857 return;
858 end Build_Class_Wide_Master;
860 --------------------------------
861 -- Build_Discr_Checking_Funcs --
862 --------------------------------
864 procedure Build_Discr_Checking_Funcs (N : Node_Id) is
865 Rec_Id : Entity_Id;
866 Loc : Source_Ptr;
867 Enclosing_Func_Id : Entity_Id;
868 Sequence : Nat := 1;
869 Type_Def : Node_Id;
870 V : Node_Id;
872 function Build_Case_Statement
873 (Case_Id : Entity_Id;
874 Variant : Node_Id) return Node_Id;
875 -- Build a case statement containing only two alternatives. The first
876 -- alternative corresponds exactly to the discrete choices given on the
877 -- variant with contains the components that we are generating the
878 -- checks for. If the discriminant is one of these return False. The
879 -- second alternative is an OTHERS choice that will return True
880 -- indicating the discriminant did not match.
882 function Build_Dcheck_Function
883 (Case_Id : Entity_Id;
884 Variant : Node_Id) return Entity_Id;
885 -- Build the discriminant checking function for a given variant
887 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id);
888 -- Builds the discriminant checking function for each variant of the
889 -- given variant part of the record type.
891 --------------------------
892 -- Build_Case_Statement --
893 --------------------------
895 function Build_Case_Statement
896 (Case_Id : Entity_Id;
897 Variant : Node_Id) return Node_Id
899 Alt_List : constant List_Id := New_List;
900 Actuals_List : List_Id;
901 Case_Node : Node_Id;
902 Case_Alt_Node : Node_Id;
903 Choice : Node_Id;
904 Choice_List : List_Id;
905 D : Entity_Id;
906 Return_Node : Node_Id;
908 begin
909 Case_Node := New_Node (N_Case_Statement, Loc);
911 -- Replace the discriminant which controls the variant, with the name
912 -- of the formal of the checking function.
914 Set_Expression (Case_Node,
915 Make_Identifier (Loc, Chars (Case_Id)));
917 Choice := First (Discrete_Choices (Variant));
919 if Nkind (Choice) = N_Others_Choice then
920 Choice_List := New_Copy_List (Others_Discrete_Choices (Choice));
921 else
922 Choice_List := New_Copy_List (Discrete_Choices (Variant));
923 end if;
925 if not Is_Empty_List (Choice_List) then
926 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
927 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
929 -- In case this is a nested variant, we need to return the result
930 -- of the discriminant checking function for the immediately
931 -- enclosing variant.
933 if Present (Enclosing_Func_Id) then
934 Actuals_List := New_List;
936 D := First_Discriminant (Rec_Id);
937 while Present (D) loop
938 Append (Make_Identifier (Loc, Chars (D)), Actuals_List);
939 Next_Discriminant (D);
940 end loop;
942 Return_Node :=
943 Make_Simple_Return_Statement (Loc,
944 Expression =>
945 Make_Function_Call (Loc,
946 Name =>
947 New_Reference_To (Enclosing_Func_Id, Loc),
948 Parameter_Associations =>
949 Actuals_List));
951 else
952 Return_Node :=
953 Make_Simple_Return_Statement (Loc,
954 Expression =>
955 New_Reference_To (Standard_False, Loc));
956 end if;
958 Set_Statements (Case_Alt_Node, New_List (Return_Node));
959 Append (Case_Alt_Node, Alt_List);
960 end if;
962 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
963 Choice_List := New_List (New_Node (N_Others_Choice, Loc));
964 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
966 Return_Node :=
967 Make_Simple_Return_Statement (Loc,
968 Expression =>
969 New_Reference_To (Standard_True, Loc));
971 Set_Statements (Case_Alt_Node, New_List (Return_Node));
972 Append (Case_Alt_Node, Alt_List);
974 Set_Alternatives (Case_Node, Alt_List);
975 return Case_Node;
976 end Build_Case_Statement;
978 ---------------------------
979 -- Build_Dcheck_Function --
980 ---------------------------
982 function Build_Dcheck_Function
983 (Case_Id : Entity_Id;
984 Variant : Node_Id) return Entity_Id
986 Body_Node : Node_Id;
987 Func_Id : Entity_Id;
988 Parameter_List : List_Id;
989 Spec_Node : Node_Id;
991 begin
992 Body_Node := New_Node (N_Subprogram_Body, Loc);
993 Sequence := Sequence + 1;
995 Func_Id :=
996 Make_Defining_Identifier (Loc,
997 Chars => New_External_Name (Chars (Rec_Id), 'D', Sequence));
999 Spec_Node := New_Node (N_Function_Specification, Loc);
1000 Set_Defining_Unit_Name (Spec_Node, Func_Id);
1002 Parameter_List := Build_Discriminant_Formals (Rec_Id, False);
1004 Set_Parameter_Specifications (Spec_Node, Parameter_List);
1005 Set_Result_Definition (Spec_Node,
1006 New_Reference_To (Standard_Boolean, Loc));
1007 Set_Specification (Body_Node, Spec_Node);
1008 Set_Declarations (Body_Node, New_List);
1010 Set_Handled_Statement_Sequence (Body_Node,
1011 Make_Handled_Sequence_Of_Statements (Loc,
1012 Statements => New_List (
1013 Build_Case_Statement (Case_Id, Variant))));
1015 Set_Ekind (Func_Id, E_Function);
1016 Set_Mechanism (Func_Id, Default_Mechanism);
1017 Set_Is_Inlined (Func_Id, True);
1018 Set_Is_Pure (Func_Id, True);
1019 Set_Is_Public (Func_Id, Is_Public (Rec_Id));
1020 Set_Is_Internal (Func_Id, True);
1022 if not Debug_Generated_Code then
1023 Set_Debug_Info_Off (Func_Id);
1024 end if;
1026 Analyze (Body_Node);
1028 Append_Freeze_Action (Rec_Id, Body_Node);
1029 Set_Dcheck_Function (Variant, Func_Id);
1030 return Func_Id;
1031 end Build_Dcheck_Function;
1033 ----------------------------
1034 -- Build_Dcheck_Functions --
1035 ----------------------------
1037 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id) is
1038 Component_List_Node : Node_Id;
1039 Decl : Entity_Id;
1040 Discr_Name : Entity_Id;
1041 Func_Id : Entity_Id;
1042 Variant : Node_Id;
1043 Saved_Enclosing_Func_Id : Entity_Id;
1045 begin
1046 -- Build the discriminant-checking function for each variant, and
1047 -- label all components of that variant with the function's name.
1048 -- We only Generate a discriminant-checking function when the
1049 -- variant is not empty, to prevent the creation of dead code.
1050 -- The exception to that is when Frontend_Layout_On_Target is set,
1051 -- because the variant record size function generated in package
1052 -- Layout needs to generate calls to all discriminant-checking
1053 -- functions, including those for empty variants.
1055 Discr_Name := Entity (Name (Variant_Part_Node));
1056 Variant := First_Non_Pragma (Variants (Variant_Part_Node));
1058 while Present (Variant) loop
1059 Component_List_Node := Component_List (Variant);
1061 if not Null_Present (Component_List_Node)
1062 or else Frontend_Layout_On_Target
1063 then
1064 Func_Id := Build_Dcheck_Function (Discr_Name, Variant);
1065 Decl :=
1066 First_Non_Pragma (Component_Items (Component_List_Node));
1068 while Present (Decl) loop
1069 Set_Discriminant_Checking_Func
1070 (Defining_Identifier (Decl), Func_Id);
1072 Next_Non_Pragma (Decl);
1073 end loop;
1075 if Present (Variant_Part (Component_List_Node)) then
1076 Saved_Enclosing_Func_Id := Enclosing_Func_Id;
1077 Enclosing_Func_Id := Func_Id;
1078 Build_Dcheck_Functions (Variant_Part (Component_List_Node));
1079 Enclosing_Func_Id := Saved_Enclosing_Func_Id;
1080 end if;
1081 end if;
1083 Next_Non_Pragma (Variant);
1084 end loop;
1085 end Build_Dcheck_Functions;
1087 -- Start of processing for Build_Discr_Checking_Funcs
1089 begin
1090 -- Only build if not done already
1092 if not Discr_Check_Funcs_Built (N) then
1093 Type_Def := Type_Definition (N);
1095 if Nkind (Type_Def) = N_Record_Definition then
1096 if No (Component_List (Type_Def)) then -- null record.
1097 return;
1098 else
1099 V := Variant_Part (Component_List (Type_Def));
1100 end if;
1102 else pragma Assert (Nkind (Type_Def) = N_Derived_Type_Definition);
1103 if No (Component_List (Record_Extension_Part (Type_Def))) then
1104 return;
1105 else
1106 V := Variant_Part
1107 (Component_List (Record_Extension_Part (Type_Def)));
1108 end if;
1109 end if;
1111 Rec_Id := Defining_Identifier (N);
1113 if Present (V) and then not Is_Unchecked_Union (Rec_Id) then
1114 Loc := Sloc (N);
1115 Enclosing_Func_Id := Empty;
1116 Build_Dcheck_Functions (V);
1117 end if;
1119 Set_Discr_Check_Funcs_Built (N);
1120 end if;
1121 end Build_Discr_Checking_Funcs;
1123 --------------------------------
1124 -- Build_Discriminant_Formals --
1125 --------------------------------
1127 function Build_Discriminant_Formals
1128 (Rec_Id : Entity_Id;
1129 Use_Dl : Boolean) return List_Id
1131 Loc : Source_Ptr := Sloc (Rec_Id);
1132 Parameter_List : constant List_Id := New_List;
1133 D : Entity_Id;
1134 Formal : Entity_Id;
1135 Param_Spec_Node : Node_Id;
1137 begin
1138 if Has_Discriminants (Rec_Id) then
1139 D := First_Discriminant (Rec_Id);
1140 while Present (D) loop
1141 Loc := Sloc (D);
1143 if Use_Dl then
1144 Formal := Discriminal (D);
1145 else
1146 Formal := Make_Defining_Identifier (Loc, Chars (D));
1147 end if;
1149 Param_Spec_Node :=
1150 Make_Parameter_Specification (Loc,
1151 Defining_Identifier => Formal,
1152 Parameter_Type =>
1153 New_Reference_To (Etype (D), Loc));
1154 Append (Param_Spec_Node, Parameter_List);
1155 Next_Discriminant (D);
1156 end loop;
1157 end if;
1159 return Parameter_List;
1160 end Build_Discriminant_Formals;
1162 --------------------------------------
1163 -- Build_Equivalent_Array_Aggregate --
1164 --------------------------------------
1166 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id is
1167 Loc : constant Source_Ptr := Sloc (T);
1168 Comp_Type : constant Entity_Id := Component_Type (T);
1169 Index_Type : constant Entity_Id := Etype (First_Index (T));
1170 Proc : constant Entity_Id := Base_Init_Proc (T);
1171 Lo, Hi : Node_Id;
1172 Aggr : Node_Id;
1173 Expr : Node_Id;
1175 begin
1176 if not Is_Constrained (T)
1177 or else Number_Dimensions (T) > 1
1178 or else No (Proc)
1179 then
1180 Initialization_Warning (T);
1181 return Empty;
1182 end if;
1184 Lo := Type_Low_Bound (Index_Type);
1185 Hi := Type_High_Bound (Index_Type);
1187 if not Compile_Time_Known_Value (Lo)
1188 or else not Compile_Time_Known_Value (Hi)
1189 then
1190 Initialization_Warning (T);
1191 return Empty;
1192 end if;
1194 if Is_Record_Type (Comp_Type)
1195 and then Present (Base_Init_Proc (Comp_Type))
1196 then
1197 Expr := Static_Initialization (Base_Init_Proc (Comp_Type));
1199 if No (Expr) then
1200 Initialization_Warning (T);
1201 return Empty;
1202 end if;
1204 else
1205 Initialization_Warning (T);
1206 return Empty;
1207 end if;
1209 Aggr := Make_Aggregate (Loc, No_List, New_List);
1210 Set_Etype (Aggr, T);
1211 Set_Aggregate_Bounds (Aggr,
1212 Make_Range (Loc,
1213 Low_Bound => New_Copy (Lo),
1214 High_Bound => New_Copy (Hi)));
1215 Set_Parent (Aggr, Parent (Proc));
1217 Append_To (Component_Associations (Aggr),
1218 Make_Component_Association (Loc,
1219 Choices =>
1220 New_List (
1221 Make_Range (Loc,
1222 Low_Bound => New_Copy (Lo),
1223 High_Bound => New_Copy (Hi))),
1224 Expression => Expr));
1226 if Static_Array_Aggregate (Aggr) then
1227 return Aggr;
1228 else
1229 Initialization_Warning (T);
1230 return Empty;
1231 end if;
1232 end Build_Equivalent_Array_Aggregate;
1234 ---------------------------------------
1235 -- Build_Equivalent_Record_Aggregate --
1236 ---------------------------------------
1238 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id is
1239 Agg : Node_Id;
1240 Comp : Entity_Id;
1242 -- Start of processing for Build_Equivalent_Record_Aggregate
1244 begin
1245 if not Is_Record_Type (T)
1246 or else Has_Discriminants (T)
1247 or else Is_Limited_Type (T)
1248 or else Has_Non_Standard_Rep (T)
1249 then
1250 Initialization_Warning (T);
1251 return Empty;
1252 end if;
1254 Comp := First_Component (T);
1256 -- A null record needs no warning
1258 if No (Comp) then
1259 return Empty;
1260 end if;
1262 while Present (Comp) loop
1264 -- Array components are acceptable if initialized by a positional
1265 -- aggregate with static components.
1267 if Is_Array_Type (Etype (Comp)) then
1268 declare
1269 Comp_Type : constant Entity_Id := Component_Type (Etype (Comp));
1271 begin
1272 if Nkind (Parent (Comp)) /= N_Component_Declaration
1273 or else No (Expression (Parent (Comp)))
1274 or else Nkind (Expression (Parent (Comp))) /= N_Aggregate
1275 then
1276 Initialization_Warning (T);
1277 return Empty;
1279 elsif Is_Scalar_Type (Component_Type (Etype (Comp)))
1280 and then
1281 (not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1282 or else not Compile_Time_Known_Value
1283 (Type_High_Bound (Comp_Type)))
1284 then
1285 Initialization_Warning (T);
1286 return Empty;
1288 elsif
1289 not Static_Array_Aggregate (Expression (Parent (Comp)))
1290 then
1291 Initialization_Warning (T);
1292 return Empty;
1293 end if;
1294 end;
1296 elsif Is_Scalar_Type (Etype (Comp)) then
1297 if Nkind (Parent (Comp)) /= N_Component_Declaration
1298 or else No (Expression (Parent (Comp)))
1299 or else not Compile_Time_Known_Value (Expression (Parent (Comp)))
1300 then
1301 Initialization_Warning (T);
1302 return Empty;
1303 end if;
1305 -- For now, other types are excluded
1307 else
1308 Initialization_Warning (T);
1309 return Empty;
1310 end if;
1312 Next_Component (Comp);
1313 end loop;
1315 -- All components have static initialization. Build positional
1316 -- aggregate from the given expressions or defaults.
1318 Agg := Make_Aggregate (Sloc (T), New_List, New_List);
1319 Set_Parent (Agg, Parent (T));
1321 Comp := First_Component (T);
1322 while Present (Comp) loop
1323 Append
1324 (New_Copy_Tree (Expression (Parent (Comp))), Expressions (Agg));
1325 Next_Component (Comp);
1326 end loop;
1328 Analyze_And_Resolve (Agg, T);
1329 return Agg;
1330 end Build_Equivalent_Record_Aggregate;
1332 -------------------------------
1333 -- Build_Initialization_Call --
1334 -------------------------------
1336 -- References to a discriminant inside the record type declaration can
1337 -- appear either in the subtype_indication to constrain a record or an
1338 -- array, or as part of a larger expression given for the initial value
1339 -- of a component. In both of these cases N appears in the record
1340 -- initialization procedure and needs to be replaced by the formal
1341 -- parameter of the initialization procedure which corresponds to that
1342 -- discriminant.
1344 -- In the example below, references to discriminants D1 and D2 in proc_1
1345 -- are replaced by references to formals with the same name
1346 -- (discriminals)
1348 -- A similar replacement is done for calls to any record initialization
1349 -- procedure for any components that are themselves of a record type.
1351 -- type R (D1, D2 : Integer) is record
1352 -- X : Integer := F * D1;
1353 -- Y : Integer := F * D2;
1354 -- end record;
1356 -- procedure proc_1 (Out_2 : out R; D1 : Integer; D2 : Integer) is
1357 -- begin
1358 -- Out_2.D1 := D1;
1359 -- Out_2.D2 := D2;
1360 -- Out_2.X := F * D1;
1361 -- Out_2.Y := F * D2;
1362 -- end;
1364 function Build_Initialization_Call
1365 (Loc : Source_Ptr;
1366 Id_Ref : Node_Id;
1367 Typ : Entity_Id;
1368 In_Init_Proc : Boolean := False;
1369 Enclos_Type : Entity_Id := Empty;
1370 Discr_Map : Elist_Id := New_Elmt_List;
1371 With_Default_Init : Boolean := False) return List_Id
1373 First_Arg : Node_Id;
1374 Args : List_Id;
1375 Decls : List_Id;
1376 Decl : Node_Id;
1377 Discr : Entity_Id;
1378 Arg : Node_Id;
1379 Proc : constant Entity_Id := Base_Init_Proc (Typ);
1380 Init_Type : constant Entity_Id := Etype (First_Formal (Proc));
1381 Full_Init_Type : constant Entity_Id := Underlying_Type (Init_Type);
1382 Res : constant List_Id := New_List;
1383 Full_Type : Entity_Id := Typ;
1384 Controller_Typ : Entity_Id;
1386 begin
1387 -- Nothing to do if the Init_Proc is null, unless Initialize_Scalars
1388 -- is active (in which case we make the call anyway, since in the
1389 -- actual compiled client it may be non null).
1390 -- Also nothing to do for value types.
1392 if (Is_Null_Init_Proc (Proc) and then not Init_Or_Norm_Scalars)
1393 or else Is_Value_Type (Typ)
1394 or else Is_Value_Type (Component_Type (Typ))
1395 then
1396 return Empty_List;
1397 end if;
1399 -- Go to full view if private type. In the case of successive
1400 -- private derivations, this can require more than one step.
1402 while Is_Private_Type (Full_Type)
1403 and then Present (Full_View (Full_Type))
1404 loop
1405 Full_Type := Full_View (Full_Type);
1406 end loop;
1408 -- If Typ is derived, the procedure is the initialization procedure for
1409 -- the root type. Wrap the argument in an conversion to make it type
1410 -- honest. Actually it isn't quite type honest, because there can be
1411 -- conflicts of views in the private type case. That is why we set
1412 -- Conversion_OK in the conversion node.
1414 if (Is_Record_Type (Typ)
1415 or else Is_Array_Type (Typ)
1416 or else Is_Private_Type (Typ))
1417 and then Init_Type /= Base_Type (Typ)
1418 then
1419 First_Arg := OK_Convert_To (Etype (Init_Type), Id_Ref);
1420 Set_Etype (First_Arg, Init_Type);
1422 else
1423 First_Arg := Id_Ref;
1424 end if;
1426 Args := New_List (Convert_Concurrent (First_Arg, Typ));
1428 -- In the tasks case, add _Master as the value of the _Master parameter
1429 -- and _Chain as the value of the _Chain parameter. At the outer level,
1430 -- these will be variables holding the corresponding values obtained
1431 -- from GNARL. At inner levels, they will be the parameters passed down
1432 -- through the outer routines.
1434 if Has_Task (Full_Type) then
1435 if Restriction_Active (No_Task_Hierarchy) then
1437 -- See comments in System.Tasking.Initialization.Init_RTS
1438 -- for the value 3 (should be rtsfindable constant ???)
1440 Append_To (Args, Make_Integer_Literal (Loc, 3));
1442 else
1443 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1444 end if;
1446 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1448 -- Ada 2005 (AI-287): In case of default initialized components
1449 -- with tasks, we generate a null string actual parameter.
1450 -- This is just a workaround that must be improved later???
1452 if With_Default_Init then
1453 Append_To (Args,
1454 Make_String_Literal (Loc,
1455 Strval => ""));
1457 else
1458 Decls :=
1459 Build_Task_Image_Decls (Loc, Id_Ref, Enclos_Type, In_Init_Proc);
1460 Decl := Last (Decls);
1462 Append_To (Args,
1463 New_Occurrence_Of (Defining_Identifier (Decl), Loc));
1464 Append_List (Decls, Res);
1465 end if;
1467 else
1468 Decls := No_List;
1469 Decl := Empty;
1470 end if;
1472 -- Add discriminant values if discriminants are present
1474 if Has_Discriminants (Full_Init_Type) then
1475 Discr := First_Discriminant (Full_Init_Type);
1477 while Present (Discr) loop
1479 -- If this is a discriminated concurrent type, the init_proc
1480 -- for the corresponding record is being called. Use that type
1481 -- directly to find the discriminant value, to handle properly
1482 -- intervening renamed discriminants.
1484 declare
1485 T : Entity_Id := Full_Type;
1487 begin
1488 if Is_Protected_Type (T) then
1489 T := Corresponding_Record_Type (T);
1491 elsif Is_Private_Type (T)
1492 and then Present (Underlying_Full_View (T))
1493 and then Is_Protected_Type (Underlying_Full_View (T))
1494 then
1495 T := Corresponding_Record_Type (Underlying_Full_View (T));
1496 end if;
1498 Arg :=
1499 Get_Discriminant_Value (
1500 Discr,
1502 Discriminant_Constraint (Full_Type));
1503 end;
1505 if In_Init_Proc then
1507 -- Replace any possible references to the discriminant in the
1508 -- call to the record initialization procedure with references
1509 -- to the appropriate formal parameter.
1511 if Nkind (Arg) = N_Identifier
1512 and then Ekind (Entity (Arg)) = E_Discriminant
1513 then
1514 Arg := New_Reference_To (Discriminal (Entity (Arg)), Loc);
1516 -- Case of access discriminants. We replace the reference
1517 -- to the type by a reference to the actual object
1519 elsif Nkind (Arg) = N_Attribute_Reference
1520 and then Is_Access_Type (Etype (Arg))
1521 and then Is_Entity_Name (Prefix (Arg))
1522 and then Is_Type (Entity (Prefix (Arg)))
1523 then
1524 Arg :=
1525 Make_Attribute_Reference (Loc,
1526 Prefix => New_Copy (Prefix (Id_Ref)),
1527 Attribute_Name => Name_Unrestricted_Access);
1529 -- Otherwise make a copy of the default expression. Note that
1530 -- we use the current Sloc for this, because we do not want the
1531 -- call to appear to be at the declaration point. Within the
1532 -- expression, replace discriminants with their discriminals.
1534 else
1535 Arg :=
1536 New_Copy_Tree (Arg, Map => Discr_Map, New_Sloc => Loc);
1537 end if;
1539 else
1540 if Is_Constrained (Full_Type) then
1541 Arg := Duplicate_Subexpr_No_Checks (Arg);
1542 else
1543 -- The constraints come from the discriminant default exps,
1544 -- they must be reevaluated, so we use New_Copy_Tree but we
1545 -- ensure the proper Sloc (for any embedded calls).
1547 Arg := New_Copy_Tree (Arg, New_Sloc => Loc);
1548 end if;
1549 end if;
1551 -- Ada 2005 (AI-287): In case of default initialized components,
1552 -- we need to generate the corresponding selected component node
1553 -- to access the discriminant value. In other cases this is not
1554 -- required because we are inside the init proc and we use the
1555 -- corresponding formal.
1557 if With_Default_Init
1558 and then Nkind (Id_Ref) = N_Selected_Component
1559 and then Nkind (Arg) = N_Identifier
1560 then
1561 Append_To (Args,
1562 Make_Selected_Component (Loc,
1563 Prefix => New_Copy_Tree (Prefix (Id_Ref)),
1564 Selector_Name => Arg));
1565 else
1566 Append_To (Args, Arg);
1567 end if;
1569 Next_Discriminant (Discr);
1570 end loop;
1571 end if;
1573 -- If this is a call to initialize the parent component of a derived
1574 -- tagged type, indicate that the tag should not be set in the parent.
1576 if Is_Tagged_Type (Full_Init_Type)
1577 and then not Is_CPP_Class (Full_Init_Type)
1578 and then Nkind (Id_Ref) = N_Selected_Component
1579 and then Chars (Selector_Name (Id_Ref)) = Name_uParent
1580 then
1581 Append_To (Args, New_Occurrence_Of (Standard_False, Loc));
1582 end if;
1584 Append_To (Res,
1585 Make_Procedure_Call_Statement (Loc,
1586 Name => New_Occurrence_Of (Proc, Loc),
1587 Parameter_Associations => Args));
1589 if Needs_Finalization (Typ)
1590 and then Nkind (Id_Ref) = N_Selected_Component
1591 then
1592 if Chars (Selector_Name (Id_Ref)) /= Name_uParent then
1593 Append_List_To (Res,
1594 Make_Init_Call (
1595 Ref => New_Copy_Tree (First_Arg),
1596 Typ => Typ,
1597 Flist_Ref =>
1598 Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1599 With_Attach => Make_Integer_Literal (Loc, 1)));
1601 -- If the enclosing type is an extension with new controlled
1602 -- components, it has his own record controller. If the parent
1603 -- also had a record controller, attach it to the new one.
1605 -- Build_Init_Statements relies on the fact that in this specific
1606 -- case the last statement of the result is the attach call to
1607 -- the controller. If this is changed, it must be synchronized.
1609 elsif Present (Enclos_Type)
1610 and then Has_New_Controlled_Component (Enclos_Type)
1611 and then Has_Controlled_Component (Typ)
1612 then
1613 if Is_Inherently_Limited_Type (Typ) then
1614 Controller_Typ := RTE (RE_Limited_Record_Controller);
1615 else
1616 Controller_Typ := RTE (RE_Record_Controller);
1617 end if;
1619 Append_List_To (Res,
1620 Make_Init_Call (
1621 Ref =>
1622 Make_Selected_Component (Loc,
1623 Prefix => New_Copy_Tree (First_Arg),
1624 Selector_Name => Make_Identifier (Loc, Name_uController)),
1625 Typ => Controller_Typ,
1626 Flist_Ref => Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1627 With_Attach => Make_Integer_Literal (Loc, 1)));
1628 end if;
1629 end if;
1631 return Res;
1633 exception
1634 when RE_Not_Available =>
1635 return Empty_List;
1636 end Build_Initialization_Call;
1638 ---------------------------
1639 -- Build_Master_Renaming --
1640 ---------------------------
1642 function Build_Master_Renaming
1643 (N : Node_Id;
1644 T : Entity_Id) return Entity_Id
1646 Loc : constant Source_Ptr := Sloc (N);
1647 M_Id : Entity_Id;
1648 Decl : Node_Id;
1650 begin
1651 -- Nothing to do if there is no task hierarchy
1653 if Restriction_Active (No_Task_Hierarchy) then
1654 return Empty;
1655 end if;
1657 M_Id :=
1658 Make_Defining_Identifier (Loc,
1659 New_External_Name (Chars (T), 'M'));
1661 Decl :=
1662 Make_Object_Renaming_Declaration (Loc,
1663 Defining_Identifier => M_Id,
1664 Subtype_Mark => New_Reference_To (RTE (RE_Master_Id), Loc),
1665 Name => Make_Identifier (Loc, Name_uMaster));
1666 Insert_Before (N, Decl);
1667 Analyze (Decl);
1668 return M_Id;
1670 exception
1671 when RE_Not_Available =>
1672 return Empty;
1673 end Build_Master_Renaming;
1675 ---------------------------
1676 -- Build_Master_Renaming --
1677 ---------------------------
1679 procedure Build_Master_Renaming (N : Node_Id; T : Entity_Id) is
1680 M_Id : Entity_Id;
1682 begin
1683 -- Nothing to do if there is no task hierarchy
1685 if Restriction_Active (No_Task_Hierarchy) then
1686 return;
1687 end if;
1689 M_Id := Build_Master_Renaming (N, T);
1690 Set_Master_Id (T, M_Id);
1692 exception
1693 when RE_Not_Available =>
1694 return;
1695 end Build_Master_Renaming;
1697 ----------------------------
1698 -- Build_Record_Init_Proc --
1699 ----------------------------
1701 procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id) is
1702 Loc : Source_Ptr := Sloc (N);
1703 Discr_Map : constant Elist_Id := New_Elmt_List;
1704 Proc_Id : Entity_Id;
1705 Rec_Type : Entity_Id;
1706 Set_Tag : Entity_Id := Empty;
1708 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id;
1709 -- Build a assignment statement node which assigns to record component
1710 -- its default expression if defined. The assignment left hand side is
1711 -- marked Assignment_OK so that initialization of limited private
1712 -- records works correctly, Return also the adjustment call for
1713 -- controlled objects
1715 procedure Build_Discriminant_Assignments (Statement_List : List_Id);
1716 -- If the record has discriminants, adds assignment statements to
1717 -- statement list to initialize the discriminant values from the
1718 -- arguments of the initialization procedure.
1720 function Build_Init_Statements (Comp_List : Node_Id) return List_Id;
1721 -- Build a list representing a sequence of statements which initialize
1722 -- components of the given component list. This may involve building
1723 -- case statements for the variant parts.
1725 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id;
1726 -- Given a non-tagged type-derivation that declares discriminants,
1727 -- such as
1729 -- type R (R1, R2 : Integer) is record ... end record;
1731 -- type D (D1 : Integer) is new R (1, D1);
1733 -- we make the _init_proc of D be
1735 -- procedure _init_proc(X : D; D1 : Integer) is
1736 -- begin
1737 -- _init_proc( R(X), 1, D1);
1738 -- end _init_proc;
1740 -- This function builds the call statement in this _init_proc.
1742 procedure Build_Init_Procedure;
1743 -- Build the tree corresponding to the procedure specification and body
1744 -- of the initialization procedure (by calling all the preceding
1745 -- auxiliary routines), and install it as the _init TSS.
1747 procedure Build_Offset_To_Top_Functions;
1748 -- Ada 2005 (AI-251): Build the tree corresponding to the procedure spec
1749 -- and body of the Offset_To_Top function that is generated when the
1750 -- parent of a type with discriminants has secondary dispatch tables.
1752 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id);
1753 -- Add range checks to components of discriminated records. S is a
1754 -- subtype indication of a record component. Check_List is a list
1755 -- to which the check actions are appended.
1757 function Component_Needs_Simple_Initialization
1758 (T : Entity_Id) return Boolean;
1759 -- Determines if a component needs simple initialization, given its type
1760 -- T. This is the same as Needs_Simple_Initialization except for the
1761 -- following difference: the types Tag and Interface_Tag, that are
1762 -- access types which would normally require simple initialization to
1763 -- null, do not require initialization as components, since they are
1764 -- explicitly initialized by other means.
1766 procedure Constrain_Array
1767 (SI : Node_Id;
1768 Check_List : List_Id);
1769 -- Called from Build_Record_Checks.
1770 -- Apply a list of index constraints to an unconstrained array type.
1771 -- The first parameter is the entity for the resulting subtype.
1772 -- Check_List is a list to which the check actions are appended.
1774 procedure Constrain_Index
1775 (Index : Node_Id;
1776 S : Node_Id;
1777 Check_List : List_Id);
1778 -- Process an index constraint in a constrained array declaration.
1779 -- The constraint can be a subtype name, or a range with or without
1780 -- an explicit subtype mark. The index is the corresponding index of the
1781 -- unconstrained array. S is the range expression. Check_List is a list
1782 -- to which the check actions are appended (called from
1783 -- Build_Record_Checks).
1785 function Parent_Subtype_Renaming_Discrims return Boolean;
1786 -- Returns True for base types N that rename discriminants, else False
1788 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean;
1789 -- Determines whether a record initialization procedure needs to be
1790 -- generated for the given record type.
1792 ----------------------
1793 -- Build_Assignment --
1794 ----------------------
1796 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id is
1797 Exp : Node_Id := N;
1798 Lhs : Node_Id;
1799 Typ : constant Entity_Id := Underlying_Type (Etype (Id));
1800 Kind : Node_Kind := Nkind (N);
1801 Res : List_Id;
1803 begin
1804 Loc := Sloc (N);
1805 Lhs :=
1806 Make_Selected_Component (Loc,
1807 Prefix => Make_Identifier (Loc, Name_uInit),
1808 Selector_Name => New_Occurrence_Of (Id, Loc));
1809 Set_Assignment_OK (Lhs);
1811 -- Case of an access attribute applied to the current instance.
1812 -- Replace the reference to the type by a reference to the actual
1813 -- object. (Note that this handles the case of the top level of
1814 -- the expression being given by such an attribute, but does not
1815 -- cover uses nested within an initial value expression. Nested
1816 -- uses are unlikely to occur in practice, but are theoretically
1817 -- possible. It is not clear how to handle them without fully
1818 -- traversing the expression. ???
1820 if Kind = N_Attribute_Reference
1821 and then (Attribute_Name (N) = Name_Unchecked_Access
1822 or else
1823 Attribute_Name (N) = Name_Unrestricted_Access)
1824 and then Is_Entity_Name (Prefix (N))
1825 and then Is_Type (Entity (Prefix (N)))
1826 and then Entity (Prefix (N)) = Rec_Type
1827 then
1828 Exp :=
1829 Make_Attribute_Reference (Loc,
1830 Prefix => Make_Identifier (Loc, Name_uInit),
1831 Attribute_Name => Name_Unrestricted_Access);
1832 end if;
1834 -- Take a copy of Exp to ensure that later copies of this component
1835 -- declaration in derived types see the original tree, not a node
1836 -- rewritten during expansion of the init_proc.
1838 Exp := New_Copy_Tree (Exp);
1840 Res := New_List (
1841 Make_Assignment_Statement (Loc,
1842 Name => Lhs,
1843 Expression => Exp));
1845 Set_No_Ctrl_Actions (First (Res));
1847 -- Adjust the tag if tagged (because of possible view conversions).
1848 -- Suppress the tag adjustment when VM_Target because VM tags are
1849 -- represented implicitly in objects.
1851 if Is_Tagged_Type (Typ) and then VM_Target = No_VM then
1852 Append_To (Res,
1853 Make_Assignment_Statement (Loc,
1854 Name =>
1855 Make_Selected_Component (Loc,
1856 Prefix => New_Copy_Tree (Lhs),
1857 Selector_Name =>
1858 New_Reference_To (First_Tag_Component (Typ), Loc)),
1860 Expression =>
1861 Unchecked_Convert_To (RTE (RE_Tag),
1862 New_Reference_To
1863 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc))));
1864 end if;
1866 -- Adjust the component if controlled except if it is an aggregate
1867 -- that will be expanded inline
1869 if Kind = N_Qualified_Expression then
1870 Kind := Nkind (Expression (N));
1871 end if;
1873 if Needs_Finalization (Typ)
1874 and then not (Kind = N_Aggregate or else Kind = N_Extension_Aggregate)
1875 and then not Is_Inherently_Limited_Type (Typ)
1876 then
1877 Append_List_To (Res,
1878 Make_Adjust_Call (
1879 Ref => New_Copy_Tree (Lhs),
1880 Typ => Etype (Id),
1881 Flist_Ref =>
1882 Find_Final_List (Etype (Id), New_Copy_Tree (Lhs)),
1883 With_Attach => Make_Integer_Literal (Loc, 1)));
1884 end if;
1886 return Res;
1888 exception
1889 when RE_Not_Available =>
1890 return Empty_List;
1891 end Build_Assignment;
1893 ------------------------------------
1894 -- Build_Discriminant_Assignments --
1895 ------------------------------------
1897 procedure Build_Discriminant_Assignments (Statement_List : List_Id) is
1898 D : Entity_Id;
1899 Is_Tagged : constant Boolean := Is_Tagged_Type (Rec_Type);
1901 begin
1902 if Has_Discriminants (Rec_Type)
1903 and then not Is_Unchecked_Union (Rec_Type)
1904 then
1905 D := First_Discriminant (Rec_Type);
1907 while Present (D) loop
1908 -- Don't generate the assignment for discriminants in derived
1909 -- tagged types if the discriminant is a renaming of some
1910 -- ancestor discriminant. This initialization will be done
1911 -- when initializing the _parent field of the derived record.
1913 if Is_Tagged and then
1914 Present (Corresponding_Discriminant (D))
1915 then
1916 null;
1918 else
1919 Loc := Sloc (D);
1920 Append_List_To (Statement_List,
1921 Build_Assignment (D,
1922 New_Reference_To (Discriminal (D), Loc)));
1923 end if;
1925 Next_Discriminant (D);
1926 end loop;
1927 end if;
1928 end Build_Discriminant_Assignments;
1930 --------------------------
1931 -- Build_Init_Call_Thru --
1932 --------------------------
1934 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id is
1935 Parent_Proc : constant Entity_Id :=
1936 Base_Init_Proc (Etype (Rec_Type));
1938 Parent_Type : constant Entity_Id :=
1939 Etype (First_Formal (Parent_Proc));
1941 Uparent_Type : constant Entity_Id :=
1942 Underlying_Type (Parent_Type);
1944 First_Discr_Param : Node_Id;
1946 Parent_Discr : Entity_Id;
1947 First_Arg : Node_Id;
1948 Args : List_Id;
1949 Arg : Node_Id;
1950 Res : List_Id;
1952 begin
1953 -- First argument (_Init) is the object to be initialized.
1954 -- ??? not sure where to get a reasonable Loc for First_Arg
1956 First_Arg :=
1957 OK_Convert_To (Parent_Type,
1958 New_Reference_To (Defining_Identifier (First (Parameters)), Loc));
1960 Set_Etype (First_Arg, Parent_Type);
1962 Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
1964 -- In the tasks case,
1965 -- add _Master as the value of the _Master parameter
1966 -- add _Chain as the value of the _Chain parameter.
1967 -- add _Task_Name as the value of the _Task_Name parameter.
1968 -- At the outer level, these will be variables holding the
1969 -- corresponding values obtained from GNARL or the expander.
1971 -- At inner levels, they will be the parameters passed down through
1972 -- the outer routines.
1974 First_Discr_Param := Next (First (Parameters));
1976 if Has_Task (Rec_Type) then
1977 if Restriction_Active (No_Task_Hierarchy) then
1979 -- See comments in System.Tasking.Initialization.Init_RTS
1980 -- for the value 3.
1982 Append_To (Args, Make_Integer_Literal (Loc, 3));
1983 else
1984 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1985 end if;
1987 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1988 Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
1989 First_Discr_Param := Next (Next (Next (First_Discr_Param)));
1990 end if;
1992 -- Append discriminant values
1994 if Has_Discriminants (Uparent_Type) then
1995 pragma Assert (not Is_Tagged_Type (Uparent_Type));
1997 Parent_Discr := First_Discriminant (Uparent_Type);
1998 while Present (Parent_Discr) loop
2000 -- Get the initial value for this discriminant
2001 -- ??? needs to be cleaned up to use parent_Discr_Constr
2002 -- directly.
2004 declare
2005 Discr_Value : Elmt_Id :=
2006 First_Elmt
2007 (Stored_Constraint (Rec_Type));
2009 Discr : Entity_Id :=
2010 First_Stored_Discriminant (Uparent_Type);
2011 begin
2012 while Original_Record_Component (Parent_Discr) /= Discr loop
2013 Next_Stored_Discriminant (Discr);
2014 Next_Elmt (Discr_Value);
2015 end loop;
2017 Arg := Node (Discr_Value);
2018 end;
2020 -- Append it to the list
2022 if Nkind (Arg) = N_Identifier
2023 and then Ekind (Entity (Arg)) = E_Discriminant
2024 then
2025 Append_To (Args,
2026 New_Reference_To (Discriminal (Entity (Arg)), Loc));
2028 -- Case of access discriminants. We replace the reference
2029 -- to the type by a reference to the actual object.
2031 -- Is above comment right??? Use of New_Copy below seems mighty
2032 -- suspicious ???
2034 else
2035 Append_To (Args, New_Copy (Arg));
2036 end if;
2038 Next_Discriminant (Parent_Discr);
2039 end loop;
2040 end if;
2042 Res :=
2043 New_List (
2044 Make_Procedure_Call_Statement (Loc,
2045 Name => New_Occurrence_Of (Parent_Proc, Loc),
2046 Parameter_Associations => Args));
2048 return Res;
2049 end Build_Init_Call_Thru;
2051 -----------------------------------
2052 -- Build_Offset_To_Top_Functions --
2053 -----------------------------------
2055 procedure Build_Offset_To_Top_Functions is
2057 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id);
2058 -- Generate:
2059 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2060 -- begin
2061 -- return O.Iface_Comp'Position;
2062 -- end Fxx;
2064 ----------------------------------
2065 -- Build_Offset_To_Top_Function --
2066 ----------------------------------
2068 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id) is
2069 Body_Node : Node_Id;
2070 Func_Id : Entity_Id;
2071 Spec_Node : Node_Id;
2073 begin
2074 Func_Id :=
2075 Make_Defining_Identifier (Loc,
2076 Chars => New_Internal_Name ('F'));
2078 Set_DT_Offset_To_Top_Func (Iface_Comp, Func_Id);
2080 -- Generate
2081 -- function Fxx (O : in Rec_Typ) return Storage_Offset;
2083 Spec_Node := New_Node (N_Function_Specification, Loc);
2084 Set_Defining_Unit_Name (Spec_Node, Func_Id);
2085 Set_Parameter_Specifications (Spec_Node, New_List (
2086 Make_Parameter_Specification (Loc,
2087 Defining_Identifier => Make_Defining_Identifier (Loc, Name_uO),
2088 In_Present => True,
2089 Parameter_Type => New_Reference_To (Rec_Type, Loc))));
2090 Set_Result_Definition (Spec_Node,
2091 New_Reference_To (RTE (RE_Storage_Offset), Loc));
2093 -- Generate
2094 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2095 -- begin
2096 -- return O.Iface_Comp'Position;
2097 -- end Fxx;
2099 Body_Node := New_Node (N_Subprogram_Body, Loc);
2100 Set_Specification (Body_Node, Spec_Node);
2101 Set_Declarations (Body_Node, New_List);
2102 Set_Handled_Statement_Sequence (Body_Node,
2103 Make_Handled_Sequence_Of_Statements (Loc,
2104 Statements => New_List (
2105 Make_Simple_Return_Statement (Loc,
2106 Expression =>
2107 Make_Attribute_Reference (Loc,
2108 Prefix =>
2109 Make_Selected_Component (Loc,
2110 Prefix => Make_Identifier (Loc, Name_uO),
2111 Selector_Name => New_Reference_To
2112 (Iface_Comp, Loc)),
2113 Attribute_Name => Name_Position)))));
2115 Set_Ekind (Func_Id, E_Function);
2116 Set_Mechanism (Func_Id, Default_Mechanism);
2117 Set_Is_Internal (Func_Id, True);
2119 if not Debug_Generated_Code then
2120 Set_Debug_Info_Off (Func_Id);
2121 end if;
2123 Analyze (Body_Node);
2125 Append_Freeze_Action (Rec_Type, Body_Node);
2126 end Build_Offset_To_Top_Function;
2128 -- Local variables
2130 Ifaces_Comp_List : Elist_Id;
2131 Iface_Comp_Elmt : Elmt_Id;
2132 Iface_Comp : Node_Id;
2134 -- Start of processing for Build_Offset_To_Top_Functions
2136 begin
2137 -- Offset_To_Top_Functions are built only for derivations of types
2138 -- with discriminants that cover interface types.
2139 -- Nothing is needed either in case of virtual machines, since
2140 -- interfaces are handled directly by the VM.
2142 if not Is_Tagged_Type (Rec_Type)
2143 or else Etype (Rec_Type) = Rec_Type
2144 or else not Has_Discriminants (Etype (Rec_Type))
2145 or else VM_Target /= No_VM
2146 then
2147 return;
2148 end if;
2150 Collect_Interface_Components (Rec_Type, Ifaces_Comp_List);
2152 -- For each interface type with secondary dispatch table we generate
2153 -- the Offset_To_Top_Functions (required to displace the pointer in
2154 -- interface conversions)
2156 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
2157 while Present (Iface_Comp_Elmt) loop
2158 Iface_Comp := Node (Iface_Comp_Elmt);
2159 pragma Assert (Is_Interface (Related_Type (Iface_Comp)));
2161 -- If the interface is a parent of Rec_Type it shares the primary
2162 -- dispatch table and hence there is no need to build the function
2164 if not Is_Ancestor (Related_Type (Iface_Comp), Rec_Type) then
2165 Build_Offset_To_Top_Function (Iface_Comp);
2166 end if;
2168 Next_Elmt (Iface_Comp_Elmt);
2169 end loop;
2170 end Build_Offset_To_Top_Functions;
2172 --------------------------
2173 -- Build_Init_Procedure --
2174 --------------------------
2176 procedure Build_Init_Procedure is
2177 Body_Node : Node_Id;
2178 Handled_Stmt_Node : Node_Id;
2179 Parameters : List_Id;
2180 Proc_Spec_Node : Node_Id;
2181 Body_Stmts : List_Id;
2182 Record_Extension_Node : Node_Id;
2183 Init_Tags_List : List_Id;
2185 begin
2186 Body_Stmts := New_List;
2187 Body_Node := New_Node (N_Subprogram_Body, Loc);
2188 Set_Ekind (Proc_Id, E_Procedure);
2190 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2191 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2193 Parameters := Init_Formals (Rec_Type);
2194 Append_List_To (Parameters,
2195 Build_Discriminant_Formals (Rec_Type, True));
2197 -- For tagged types, we add a flag to indicate whether the routine
2198 -- is called to initialize a parent component in the init_proc of
2199 -- a type extension. If the flag is false, we do not set the tag
2200 -- because it has been set already in the extension.
2202 if Is_Tagged_Type (Rec_Type)
2203 and then not Is_CPP_Class (Rec_Type)
2204 then
2205 Set_Tag :=
2206 Make_Defining_Identifier (Loc,
2207 Chars => New_Internal_Name ('P'));
2209 Append_To (Parameters,
2210 Make_Parameter_Specification (Loc,
2211 Defining_Identifier => Set_Tag,
2212 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
2213 Expression => New_Occurrence_Of (Standard_True, Loc)));
2214 end if;
2216 Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
2217 Set_Specification (Body_Node, Proc_Spec_Node);
2218 Set_Declarations (Body_Node, New_List);
2220 if Parent_Subtype_Renaming_Discrims then
2222 -- N is a Derived_Type_Definition that renames the parameters
2223 -- of the ancestor type. We initialize it by expanding our
2224 -- discriminants and call the ancestor _init_proc with a
2225 -- type-converted object
2227 Append_List_To (Body_Stmts,
2228 Build_Init_Call_Thru (Parameters));
2230 elsif Nkind (Type_Definition (N)) = N_Record_Definition then
2231 Build_Discriminant_Assignments (Body_Stmts);
2233 if not Null_Present (Type_Definition (N)) then
2234 Append_List_To (Body_Stmts,
2235 Build_Init_Statements (
2236 Component_List (Type_Definition (N))));
2237 end if;
2239 else
2240 -- N is a Derived_Type_Definition with a possible non-empty
2241 -- extension. The initialization of a type extension consists
2242 -- in the initialization of the components in the extension.
2244 Build_Discriminant_Assignments (Body_Stmts);
2246 Record_Extension_Node :=
2247 Record_Extension_Part (Type_Definition (N));
2249 if not Null_Present (Record_Extension_Node) then
2250 declare
2251 Stmts : constant List_Id :=
2252 Build_Init_Statements (
2253 Component_List (Record_Extension_Node));
2255 begin
2256 -- The parent field must be initialized first because
2257 -- the offset of the new discriminants may depend on it
2259 Prepend_To (Body_Stmts, Remove_Head (Stmts));
2260 Append_List_To (Body_Stmts, Stmts);
2261 end;
2262 end if;
2263 end if;
2265 -- Add here the assignment to instantiate the Tag
2267 -- The assignment corresponds to the code:
2269 -- _Init._Tag := Typ'Tag;
2271 -- Suppress the tag assignment when VM_Target because VM tags are
2272 -- represented implicitly in objects. It is also suppressed in case
2273 -- of CPP_Class types because in this case the tag is initialized in
2274 -- the C++ side.
2276 if Is_Tagged_Type (Rec_Type)
2277 and then not Is_CPP_Class (Rec_Type)
2278 and then VM_Target = No_VM
2279 and then not No_Run_Time_Mode
2280 then
2281 -- Initialize the primary tag
2283 Init_Tags_List := New_List (
2284 Make_Assignment_Statement (Loc,
2285 Name =>
2286 Make_Selected_Component (Loc,
2287 Prefix => Make_Identifier (Loc, Name_uInit),
2288 Selector_Name =>
2289 New_Reference_To (First_Tag_Component (Rec_Type), Loc)),
2291 Expression =>
2292 New_Reference_To
2293 (Node (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2295 -- Ada 2005 (AI-251): Initialize the secondary tags components
2296 -- located at fixed positions (tags whose position depends on
2297 -- variable size components are initialized later ---see below).
2299 if Ada_Version >= Ada_05
2300 and then not Is_Interface (Rec_Type)
2301 and then Has_Interfaces (Rec_Type)
2302 then
2303 Init_Secondary_Tags
2304 (Typ => Rec_Type,
2305 Target => Make_Identifier (Loc, Name_uInit),
2306 Stmts_List => Init_Tags_List,
2307 Fixed_Comps => True,
2308 Variable_Comps => False);
2309 end if;
2311 -- The tag must be inserted before the assignments to other
2312 -- components, because the initial value of the component may
2313 -- depend on the tag (eg. through a dispatching operation on
2314 -- an access to the current type). The tag assignment is not done
2315 -- when initializing the parent component of a type extension,
2316 -- because in that case the tag is set in the extension.
2318 -- Extensions of imported C++ classes add a final complication,
2319 -- because we cannot inhibit tag setting in the constructor for
2320 -- the parent. In that case we insert the tag initialization
2321 -- after the calls to initialize the parent.
2323 if not Is_CPP_Class (Root_Type (Rec_Type)) then
2324 Prepend_To (Body_Stmts,
2325 Make_If_Statement (Loc,
2326 Condition => New_Occurrence_Of (Set_Tag, Loc),
2327 Then_Statements => Init_Tags_List));
2329 -- CPP_Class derivation: In this case the dispatch table of the
2330 -- parent was built in the C++ side and we copy the table of the
2331 -- parent to initialize the new dispatch table.
2333 else
2334 declare
2335 Nod : Node_Id;
2337 begin
2338 -- We assume the first init_proc call is for the parent
2340 Nod := First (Body_Stmts);
2341 while Present (Next (Nod))
2342 and then (Nkind (Nod) /= N_Procedure_Call_Statement
2343 or else not Is_Init_Proc (Name (Nod)))
2344 loop
2345 Nod := Next (Nod);
2346 end loop;
2348 -- Generate:
2349 -- ancestor_constructor (_init.parent);
2350 -- if Arg2 then
2351 -- inherit_prim_ops (_init._tag, new_dt, num_prims);
2352 -- _init._tag := new_dt;
2353 -- end if;
2355 Prepend_To (Init_Tags_List,
2356 Build_Inherit_Prims (Loc,
2357 Typ => Rec_Type,
2358 Old_Tag_Node =>
2359 Make_Selected_Component (Loc,
2360 Prefix =>
2361 Make_Identifier (Loc,
2362 Chars => Name_uInit),
2363 Selector_Name =>
2364 New_Reference_To
2365 (First_Tag_Component (Rec_Type), Loc)),
2366 New_Tag_Node =>
2367 New_Reference_To
2368 (Node (First_Elmt (Access_Disp_Table (Rec_Type))),
2369 Loc),
2370 Num_Prims =>
2371 UI_To_Int
2372 (DT_Entry_Count (First_Tag_Component (Rec_Type)))));
2374 Insert_After (Nod,
2375 Make_If_Statement (Loc,
2376 Condition => New_Occurrence_Of (Set_Tag, Loc),
2377 Then_Statements => Init_Tags_List));
2379 -- We have inherited table of the parent from the CPP side.
2380 -- Now we fill the slots associated with Ada primitives.
2381 -- This needs more work to avoid its execution each time
2382 -- an object is initialized???
2384 declare
2385 E : Elmt_Id;
2386 Prim : Node_Id;
2388 begin
2389 E := First_Elmt (Primitive_Operations (Rec_Type));
2390 while Present (E) loop
2391 Prim := Node (E);
2393 if not Is_Imported (Prim)
2394 and then Convention (Prim) = Convention_CPP
2395 and then not Present (Interface_Alias (Prim))
2396 then
2397 Append_List_To (Init_Tags_List,
2398 Register_Primitive (Loc, Prim => Prim));
2399 end if;
2401 Next_Elmt (E);
2402 end loop;
2403 end;
2404 end;
2405 end if;
2407 -- Ada 2005 (AI-251): Initialize the secondary tag components
2408 -- located at variable positions. We delay the generation of this
2409 -- code until here because the value of the attribute 'Position
2410 -- applied to variable size components of the parent type that
2411 -- depend on discriminants is only safely read at runtime after
2412 -- the parent components have been initialized.
2414 if Ada_Version >= Ada_05
2415 and then not Is_Interface (Rec_Type)
2416 and then Has_Interfaces (Rec_Type)
2417 and then Has_Discriminants (Etype (Rec_Type))
2418 and then Is_Variable_Size_Record (Etype (Rec_Type))
2419 then
2420 Init_Tags_List := New_List;
2422 Init_Secondary_Tags
2423 (Typ => Rec_Type,
2424 Target => Make_Identifier (Loc, Name_uInit),
2425 Stmts_List => Init_Tags_List,
2426 Fixed_Comps => False,
2427 Variable_Comps => True);
2429 if Is_Non_Empty_List (Init_Tags_List) then
2430 Append_List_To (Body_Stmts, Init_Tags_List);
2431 end if;
2432 end if;
2433 end if;
2435 Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
2436 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2437 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2438 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2440 if not Debug_Generated_Code then
2441 Set_Debug_Info_Off (Proc_Id);
2442 end if;
2444 -- Associate Init_Proc with type, and determine if the procedure
2445 -- is null (happens because of the Initialize_Scalars pragma case,
2446 -- where we have to generate a null procedure in case it is called
2447 -- by a client with Initialize_Scalars set). Such procedures have
2448 -- to be generated, but do not have to be called, so we mark them
2449 -- as null to suppress the call.
2451 Set_Init_Proc (Rec_Type, Proc_Id);
2453 if List_Length (Body_Stmts) = 1
2454 and then Nkind (First (Body_Stmts)) = N_Null_Statement
2455 and then VM_Target /= CLI_Target
2456 then
2457 -- Even though the init proc may be null at this time it might get
2458 -- some stuff added to it later by the CIL backend, so always keep
2459 -- it when VM_Target = CLI_Target.
2461 Set_Is_Null_Init_Proc (Proc_Id);
2462 end if;
2463 end Build_Init_Procedure;
2465 ---------------------------
2466 -- Build_Init_Statements --
2467 ---------------------------
2469 function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
2470 Check_List : constant List_Id := New_List;
2471 Alt_List : List_Id;
2472 Decl : Node_Id;
2473 Id : Entity_Id;
2474 Names : Node_Id;
2475 Statement_List : List_Id;
2476 Stmts : List_Id;
2477 Typ : Entity_Id;
2478 Variant : Node_Id;
2480 Per_Object_Constraint_Components : Boolean;
2482 function Has_Access_Constraint (E : Entity_Id) return Boolean;
2483 -- Components with access discriminants that depend on the current
2484 -- instance must be initialized after all other components.
2486 ---------------------------
2487 -- Has_Access_Constraint --
2488 ---------------------------
2490 function Has_Access_Constraint (E : Entity_Id) return Boolean is
2491 Disc : Entity_Id;
2492 T : constant Entity_Id := Etype (E);
2494 begin
2495 if Has_Per_Object_Constraint (E)
2496 and then Has_Discriminants (T)
2497 then
2498 Disc := First_Discriminant (T);
2499 while Present (Disc) loop
2500 if Is_Access_Type (Etype (Disc)) then
2501 return True;
2502 end if;
2504 Next_Discriminant (Disc);
2505 end loop;
2507 return False;
2508 else
2509 return False;
2510 end if;
2511 end Has_Access_Constraint;
2513 -- Start of processing for Build_Init_Statements
2515 begin
2516 if Null_Present (Comp_List) then
2517 return New_List (Make_Null_Statement (Loc));
2518 end if;
2520 Statement_List := New_List;
2522 -- Loop through visible declarations of task types and protected
2523 -- types moving any expanded code from the spec to the body of the
2524 -- init procedure.
2526 if Is_Task_Record_Type (Rec_Type)
2527 or else Is_Protected_Record_Type (Rec_Type)
2528 then
2529 declare
2530 Decl : constant Node_Id :=
2531 Parent (Corresponding_Concurrent_Type (Rec_Type));
2532 Def : Node_Id;
2533 N1 : Node_Id;
2534 N2 : Node_Id;
2536 begin
2537 if Is_Task_Record_Type (Rec_Type) then
2538 Def := Task_Definition (Decl);
2539 else
2540 Def := Protected_Definition (Decl);
2541 end if;
2543 if Present (Def) then
2544 N1 := First (Visible_Declarations (Def));
2545 while Present (N1) loop
2546 N2 := N1;
2547 N1 := Next (N1);
2549 if Nkind (N2) in N_Statement_Other_Than_Procedure_Call
2550 or else Nkind (N2) in N_Raise_xxx_Error
2551 or else Nkind (N2) = N_Procedure_Call_Statement
2552 then
2553 Append_To (Statement_List,
2554 New_Copy_Tree (N2, New_Scope => Proc_Id));
2555 Rewrite (N2, Make_Null_Statement (Sloc (N2)));
2556 Analyze (N2);
2557 end if;
2558 end loop;
2559 end if;
2560 end;
2561 end if;
2563 -- Loop through components, skipping pragmas, in 2 steps. The first
2564 -- step deals with regular components. The second step deals with
2565 -- components have per object constraints, and no explicit initia-
2566 -- lization.
2568 Per_Object_Constraint_Components := False;
2570 -- First step : regular components
2572 Decl := First_Non_Pragma (Component_Items (Comp_List));
2573 while Present (Decl) loop
2574 Loc := Sloc (Decl);
2575 Build_Record_Checks
2576 (Subtype_Indication (Component_Definition (Decl)), Check_List);
2578 Id := Defining_Identifier (Decl);
2579 Typ := Etype (Id);
2581 if Has_Access_Constraint (Id)
2582 and then No (Expression (Decl))
2583 then
2584 -- Skip processing for now and ask for a second pass
2586 Per_Object_Constraint_Components := True;
2588 else
2589 -- Case of explicit initialization
2591 if Present (Expression (Decl)) then
2592 Stmts := Build_Assignment (Id, Expression (Decl));
2594 -- Case of composite component with its own Init_Proc
2596 elsif not Is_Interface (Typ)
2597 and then Has_Non_Null_Base_Init_Proc (Typ)
2598 then
2599 Stmts :=
2600 Build_Initialization_Call
2601 (Loc,
2602 Make_Selected_Component (Loc,
2603 Prefix => Make_Identifier (Loc, Name_uInit),
2604 Selector_Name => New_Occurrence_Of (Id, Loc)),
2605 Typ,
2606 In_Init_Proc => True,
2607 Enclos_Type => Rec_Type,
2608 Discr_Map => Discr_Map);
2610 Clean_Task_Names (Typ, Proc_Id);
2612 -- Case of component needing simple initialization
2614 elsif Component_Needs_Simple_Initialization (Typ) then
2615 Stmts :=
2616 Build_Assignment
2617 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id)));
2619 -- Nothing needed for this case
2621 else
2622 Stmts := No_List;
2623 end if;
2625 if Present (Check_List) then
2626 Append_List_To (Statement_List, Check_List);
2627 end if;
2629 if Present (Stmts) then
2631 -- Add the initialization of the record controller before
2632 -- the _Parent field is attached to it when the attachment
2633 -- can occur. It does not work to simply initialize the
2634 -- controller first: it must be initialized after the parent
2635 -- if the parent holds discriminants that can be used to
2636 -- compute the offset of the controller. We assume here that
2637 -- the last statement of the initialization call is the
2638 -- attachment of the parent (see Build_Initialization_Call)
2640 if Chars (Id) = Name_uController
2641 and then Rec_Type /= Etype (Rec_Type)
2642 and then Has_Controlled_Component (Etype (Rec_Type))
2643 and then Has_New_Controlled_Component (Rec_Type)
2644 and then Present (Last (Statement_List))
2645 then
2646 Insert_List_Before (Last (Statement_List), Stmts);
2647 else
2648 Append_List_To (Statement_List, Stmts);
2649 end if;
2650 end if;
2651 end if;
2653 Next_Non_Pragma (Decl);
2654 end loop;
2656 if Per_Object_Constraint_Components then
2658 -- Second pass: components with per-object constraints
2660 Decl := First_Non_Pragma (Component_Items (Comp_List));
2661 while Present (Decl) loop
2662 Loc := Sloc (Decl);
2663 Id := Defining_Identifier (Decl);
2664 Typ := Etype (Id);
2666 if Has_Access_Constraint (Id)
2667 and then No (Expression (Decl))
2668 then
2669 if Has_Non_Null_Base_Init_Proc (Typ) then
2670 Append_List_To (Statement_List,
2671 Build_Initialization_Call (Loc,
2672 Make_Selected_Component (Loc,
2673 Prefix => Make_Identifier (Loc, Name_uInit),
2674 Selector_Name => New_Occurrence_Of (Id, Loc)),
2675 Typ,
2676 In_Init_Proc => True,
2677 Enclos_Type => Rec_Type,
2678 Discr_Map => Discr_Map));
2680 Clean_Task_Names (Typ, Proc_Id);
2682 elsif Component_Needs_Simple_Initialization (Typ) then
2683 Append_List_To (Statement_List,
2684 Build_Assignment
2685 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id))));
2686 end if;
2687 end if;
2689 Next_Non_Pragma (Decl);
2690 end loop;
2691 end if;
2693 -- Process the variant part
2695 if Present (Variant_Part (Comp_List)) then
2696 Alt_List := New_List;
2697 Variant := First_Non_Pragma (Variants (Variant_Part (Comp_List)));
2698 while Present (Variant) loop
2699 Loc := Sloc (Variant);
2700 Append_To (Alt_List,
2701 Make_Case_Statement_Alternative (Loc,
2702 Discrete_Choices =>
2703 New_Copy_List (Discrete_Choices (Variant)),
2704 Statements =>
2705 Build_Init_Statements (Component_List (Variant))));
2706 Next_Non_Pragma (Variant);
2707 end loop;
2709 -- The expression of the case statement which is a reference
2710 -- to one of the discriminants is replaced by the appropriate
2711 -- formal parameter of the initialization procedure.
2713 Append_To (Statement_List,
2714 Make_Case_Statement (Loc,
2715 Expression =>
2716 New_Reference_To (Discriminal (
2717 Entity (Name (Variant_Part (Comp_List)))), Loc),
2718 Alternatives => Alt_List));
2719 end if;
2721 -- For a task record type, add the task create call and calls
2722 -- to bind any interrupt (signal) entries.
2724 if Is_Task_Record_Type (Rec_Type) then
2726 -- In the case of the restricted run time the ATCB has already
2727 -- been preallocated.
2729 if Restricted_Profile then
2730 Append_To (Statement_List,
2731 Make_Assignment_Statement (Loc,
2732 Name => Make_Selected_Component (Loc,
2733 Prefix => Make_Identifier (Loc, Name_uInit),
2734 Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
2735 Expression => Make_Attribute_Reference (Loc,
2736 Prefix =>
2737 Make_Selected_Component (Loc,
2738 Prefix => Make_Identifier (Loc, Name_uInit),
2739 Selector_Name =>
2740 Make_Identifier (Loc, Name_uATCB)),
2741 Attribute_Name => Name_Unchecked_Access)));
2742 end if;
2744 Append_To (Statement_List, Make_Task_Create_Call (Rec_Type));
2746 -- Generate the statements which map a string entry name to a
2747 -- task entry index. Note that the task may not have entries.
2749 if Entry_Names_OK then
2750 Names := Build_Entry_Names (Rec_Type);
2752 if Present (Names) then
2753 Append_To (Statement_List, Names);
2754 end if;
2755 end if;
2757 declare
2758 Task_Type : constant Entity_Id :=
2759 Corresponding_Concurrent_Type (Rec_Type);
2760 Task_Decl : constant Node_Id := Parent (Task_Type);
2761 Task_Def : constant Node_Id := Task_Definition (Task_Decl);
2762 Vis_Decl : Node_Id;
2763 Ent : Entity_Id;
2765 begin
2766 if Present (Task_Def) then
2767 Vis_Decl := First (Visible_Declarations (Task_Def));
2768 while Present (Vis_Decl) loop
2769 Loc := Sloc (Vis_Decl);
2771 if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
2772 if Get_Attribute_Id (Chars (Vis_Decl)) =
2773 Attribute_Address
2774 then
2775 Ent := Entity (Name (Vis_Decl));
2777 if Ekind (Ent) = E_Entry then
2778 Append_To (Statement_List,
2779 Make_Procedure_Call_Statement (Loc,
2780 Name => New_Reference_To (
2781 RTE (RE_Bind_Interrupt_To_Entry), Loc),
2782 Parameter_Associations => New_List (
2783 Make_Selected_Component (Loc,
2784 Prefix =>
2785 Make_Identifier (Loc, Name_uInit),
2786 Selector_Name =>
2787 Make_Identifier (Loc, Name_uTask_Id)),
2788 Entry_Index_Expression (
2789 Loc, Ent, Empty, Task_Type),
2790 Expression (Vis_Decl))));
2791 end if;
2792 end if;
2793 end if;
2795 Next (Vis_Decl);
2796 end loop;
2797 end if;
2798 end;
2799 end if;
2801 -- For a protected type, add statements generated by
2802 -- Make_Initialize_Protection.
2804 if Is_Protected_Record_Type (Rec_Type) then
2805 Append_List_To (Statement_List,
2806 Make_Initialize_Protection (Rec_Type));
2808 -- Generate the statements which map a string entry name to a
2809 -- protected entry index. Note that the protected type may not
2810 -- have entries.
2812 if Entry_Names_OK then
2813 Names := Build_Entry_Names (Rec_Type);
2815 if Present (Names) then
2816 Append_To (Statement_List, Names);
2817 end if;
2818 end if;
2819 end if;
2821 -- If no initializations when generated for component declarations
2822 -- corresponding to this Statement_List, append a null statement
2823 -- to the Statement_List to make it a valid Ada tree.
2825 if Is_Empty_List (Statement_List) then
2826 Append (New_Node (N_Null_Statement, Loc), Statement_List);
2827 end if;
2829 return Statement_List;
2831 exception
2832 when RE_Not_Available =>
2833 return Empty_List;
2834 end Build_Init_Statements;
2836 -------------------------
2837 -- Build_Record_Checks --
2838 -------------------------
2840 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
2841 Subtype_Mark_Id : Entity_Id;
2843 begin
2844 if Nkind (S) = N_Subtype_Indication then
2845 Find_Type (Subtype_Mark (S));
2846 Subtype_Mark_Id := Entity (Subtype_Mark (S));
2848 -- Remaining processing depends on type
2850 case Ekind (Subtype_Mark_Id) is
2852 when Array_Kind =>
2853 Constrain_Array (S, Check_List);
2855 when others =>
2856 null;
2857 end case;
2858 end if;
2859 end Build_Record_Checks;
2861 -------------------------------------------
2862 -- Component_Needs_Simple_Initialization --
2863 -------------------------------------------
2865 function Component_Needs_Simple_Initialization
2866 (T : Entity_Id) return Boolean
2868 begin
2869 return
2870 Needs_Simple_Initialization (T)
2871 and then not Is_RTE (T, RE_Tag)
2873 -- Ada 2005 (AI-251): Check also the tag of abstract interfaces
2875 and then not Is_RTE (T, RE_Interface_Tag);
2876 end Component_Needs_Simple_Initialization;
2878 ---------------------
2879 -- Constrain_Array --
2880 ---------------------
2882 procedure Constrain_Array
2883 (SI : Node_Id;
2884 Check_List : List_Id)
2886 C : constant Node_Id := Constraint (SI);
2887 Number_Of_Constraints : Nat := 0;
2888 Index : Node_Id;
2889 S, T : Entity_Id;
2891 begin
2892 T := Entity (Subtype_Mark (SI));
2894 if Ekind (T) in Access_Kind then
2895 T := Designated_Type (T);
2896 end if;
2898 S := First (Constraints (C));
2900 while Present (S) loop
2901 Number_Of_Constraints := Number_Of_Constraints + 1;
2902 Next (S);
2903 end loop;
2905 -- In either case, the index constraint must provide a discrete
2906 -- range for each index of the array type and the type of each
2907 -- discrete range must be the same as that of the corresponding
2908 -- index. (RM 3.6.1)
2910 S := First (Constraints (C));
2911 Index := First_Index (T);
2912 Analyze (Index);
2914 -- Apply constraints to each index type
2916 for J in 1 .. Number_Of_Constraints loop
2917 Constrain_Index (Index, S, Check_List);
2918 Next (Index);
2919 Next (S);
2920 end loop;
2922 end Constrain_Array;
2924 ---------------------
2925 -- Constrain_Index --
2926 ---------------------
2928 procedure Constrain_Index
2929 (Index : Node_Id;
2930 S : Node_Id;
2931 Check_List : List_Id)
2933 T : constant Entity_Id := Etype (Index);
2935 begin
2936 if Nkind (S) = N_Range then
2937 Process_Range_Expr_In_Decl (S, T, Check_List);
2938 end if;
2939 end Constrain_Index;
2941 --------------------------------------
2942 -- Parent_Subtype_Renaming_Discrims --
2943 --------------------------------------
2945 function Parent_Subtype_Renaming_Discrims return Boolean is
2946 De : Entity_Id;
2947 Dp : Entity_Id;
2949 begin
2950 if Base_Type (Pe) /= Pe then
2951 return False;
2952 end if;
2954 if Etype (Pe) = Pe
2955 or else not Has_Discriminants (Pe)
2956 or else Is_Constrained (Pe)
2957 or else Is_Tagged_Type (Pe)
2958 then
2959 return False;
2960 end if;
2962 -- If there are no explicit stored discriminants we have inherited
2963 -- the root type discriminants so far, so no renamings occurred.
2965 if First_Discriminant (Pe) = First_Stored_Discriminant (Pe) then
2966 return False;
2967 end if;
2969 -- Check if we have done some trivial renaming of the parent
2970 -- discriminants, i.e. something like
2972 -- type DT (X1,X2: int) is new PT (X1,X2);
2974 De := First_Discriminant (Pe);
2975 Dp := First_Discriminant (Etype (Pe));
2977 while Present (De) loop
2978 pragma Assert (Present (Dp));
2980 if Corresponding_Discriminant (De) /= Dp then
2981 return True;
2982 end if;
2984 Next_Discriminant (De);
2985 Next_Discriminant (Dp);
2986 end loop;
2988 return Present (Dp);
2989 end Parent_Subtype_Renaming_Discrims;
2991 ------------------------
2992 -- Requires_Init_Proc --
2993 ------------------------
2995 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
2996 Comp_Decl : Node_Id;
2997 Id : Entity_Id;
2998 Typ : Entity_Id;
3000 begin
3001 -- Definitely do not need one if specifically suppressed
3003 if Suppress_Init_Proc (Rec_Id) then
3004 return False;
3005 end if;
3007 -- If it is a type derived from a type with unknown discriminants,
3008 -- we cannot build an initialization procedure for it.
3010 if Has_Unknown_Discriminants (Rec_Id)
3011 or else Has_Unknown_Discriminants (Etype (Rec_Id))
3012 then
3013 return False;
3014 end if;
3016 -- Otherwise we need to generate an initialization procedure if
3017 -- Is_CPP_Class is False and at least one of the following applies:
3019 -- 1. Discriminants are present, since they need to be initialized
3020 -- with the appropriate discriminant constraint expressions.
3021 -- However, the discriminant of an unchecked union does not
3022 -- count, since the discriminant is not present.
3024 -- 2. The type is a tagged type, since the implicit Tag component
3025 -- needs to be initialized with a pointer to the dispatch table.
3027 -- 3. The type contains tasks
3029 -- 4. One or more components has an initial value
3031 -- 5. One or more components is for a type which itself requires
3032 -- an initialization procedure.
3034 -- 6. One or more components is a type that requires simple
3035 -- initialization (see Needs_Simple_Initialization), except
3036 -- that types Tag and Interface_Tag are excluded, since fields
3037 -- of these types are initialized by other means.
3039 -- 7. The type is the record type built for a task type (since at
3040 -- the very least, Create_Task must be called)
3042 -- 8. The type is the record type built for a protected type (since
3043 -- at least Initialize_Protection must be called)
3045 -- 9. The type is marked as a public entity. The reason we add this
3046 -- case (even if none of the above apply) is to properly handle
3047 -- Initialize_Scalars. If a package is compiled without an IS
3048 -- pragma, and the client is compiled with an IS pragma, then
3049 -- the client will think an initialization procedure is present
3050 -- and call it, when in fact no such procedure is required, but
3051 -- since the call is generated, there had better be a routine
3052 -- at the other end of the call, even if it does nothing!)
3054 -- Note: the reason we exclude the CPP_Class case is because in this
3055 -- case the initialization is performed in the C++ side.
3057 if Is_CPP_Class (Rec_Id) then
3058 return False;
3060 elsif Is_Interface (Rec_Id) then
3061 return False;
3063 elsif (Has_Discriminants (Rec_Id)
3064 and then not Is_Unchecked_Union (Rec_Id))
3065 or else Is_Tagged_Type (Rec_Id)
3066 or else Is_Concurrent_Record_Type (Rec_Id)
3067 or else Has_Task (Rec_Id)
3068 then
3069 return True;
3070 end if;
3072 Id := First_Component (Rec_Id);
3073 while Present (Id) loop
3074 Comp_Decl := Parent (Id);
3075 Typ := Etype (Id);
3077 if Present (Expression (Comp_Decl))
3078 or else Has_Non_Null_Base_Init_Proc (Typ)
3079 or else Component_Needs_Simple_Initialization (Typ)
3080 then
3081 return True;
3082 end if;
3084 Next_Component (Id);
3085 end loop;
3087 -- As explained above, a record initialization procedure is needed
3088 -- for public types in case Initialize_Scalars applies to a client.
3089 -- However, such a procedure is not needed in the case where either
3090 -- of restrictions No_Initialize_Scalars or No_Default_Initialization
3091 -- applies. No_Initialize_Scalars excludes the possibility of using
3092 -- Initialize_Scalars in any partition, and No_Default_Initialization
3093 -- implies that no initialization should ever be done for objects of
3094 -- the type, so is incompatible with Initialize_Scalars.
3096 if not Restriction_Active (No_Initialize_Scalars)
3097 and then not Restriction_Active (No_Default_Initialization)
3098 and then Is_Public (Rec_Id)
3099 then
3100 return True;
3101 end if;
3103 return False;
3104 end Requires_Init_Proc;
3106 -- Start of processing for Build_Record_Init_Proc
3108 begin
3109 -- Check for value type, which means no initialization required
3111 Rec_Type := Defining_Identifier (N);
3113 if Is_Value_Type (Rec_Type) then
3114 return;
3115 end if;
3117 -- This may be full declaration of a private type, in which case
3118 -- the visible entity is a record, and the private entity has been
3119 -- exchanged with it in the private part of the current package.
3120 -- The initialization procedure is built for the record type, which
3121 -- is retrievable from the private entity.
3123 if Is_Incomplete_Or_Private_Type (Rec_Type) then
3124 Rec_Type := Underlying_Type (Rec_Type);
3125 end if;
3127 -- If there are discriminants, build the discriminant map to replace
3128 -- discriminants by their discriminals in complex bound expressions.
3129 -- These only arise for the corresponding records of synchronized types.
3131 if Is_Concurrent_Record_Type (Rec_Type)
3132 and then Has_Discriminants (Rec_Type)
3133 then
3134 declare
3135 Disc : Entity_Id;
3136 begin
3137 Disc := First_Discriminant (Rec_Type);
3138 while Present (Disc) loop
3139 Append_Elmt (Disc, Discr_Map);
3140 Append_Elmt (Discriminal (Disc), Discr_Map);
3141 Next_Discriminant (Disc);
3142 end loop;
3143 end;
3144 end if;
3146 -- Derived types that have no type extension can use the initialization
3147 -- procedure of their parent and do not need a procedure of their own.
3148 -- This is only correct if there are no representation clauses for the
3149 -- type or its parent, and if the parent has in fact been frozen so
3150 -- that its initialization procedure exists.
3152 if Is_Derived_Type (Rec_Type)
3153 and then not Is_Tagged_Type (Rec_Type)
3154 and then not Is_Unchecked_Union (Rec_Type)
3155 and then not Has_New_Non_Standard_Rep (Rec_Type)
3156 and then not Parent_Subtype_Renaming_Discrims
3157 and then Has_Non_Null_Base_Init_Proc (Etype (Rec_Type))
3158 then
3159 Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
3161 -- Otherwise if we need an initialization procedure, then build one,
3162 -- mark it as public and inlinable and as having a completion.
3164 elsif Requires_Init_Proc (Rec_Type)
3165 or else Is_Unchecked_Union (Rec_Type)
3166 then
3167 Proc_Id :=
3168 Make_Defining_Identifier (Loc,
3169 Chars => Make_Init_Proc_Name (Rec_Type));
3171 -- If No_Default_Initialization restriction is active, then we don't
3172 -- want to build an init_proc, but we need to mark that an init_proc
3173 -- would be needed if this restriction was not active (so that we can
3174 -- detect attempts to call it), so set a dummy init_proc in place.
3176 if Restriction_Active (No_Default_Initialization) then
3177 Set_Init_Proc (Rec_Type, Proc_Id);
3178 return;
3179 end if;
3181 Build_Offset_To_Top_Functions;
3182 Build_Init_Procedure;
3183 Set_Is_Public (Proc_Id, Is_Public (Pe));
3185 -- The initialization of protected records is not worth inlining.
3186 -- In addition, when compiled for another unit for inlining purposes,
3187 -- it may make reference to entities that have not been elaborated
3188 -- yet. The initialization of controlled records contains a nested
3189 -- clean-up procedure that makes it impractical to inline as well,
3190 -- and leads to undefined symbols if inlined in a different unit.
3191 -- Similar considerations apply to task types.
3193 if not Is_Concurrent_Type (Rec_Type)
3194 and then not Has_Task (Rec_Type)
3195 and then not Needs_Finalization (Rec_Type)
3196 then
3197 Set_Is_Inlined (Proc_Id);
3198 end if;
3200 Set_Is_Internal (Proc_Id);
3201 Set_Has_Completion (Proc_Id);
3203 if not Debug_Generated_Code then
3204 Set_Debug_Info_Off (Proc_Id);
3205 end if;
3207 declare
3208 Agg : constant Node_Id :=
3209 Build_Equivalent_Record_Aggregate (Rec_Type);
3211 procedure Collect_Itypes (Comp : Node_Id);
3212 -- Generate references to itypes in the aggregate, because
3213 -- the first use of the aggregate may be in a nested scope.
3215 --------------------
3216 -- Collect_Itypes --
3217 --------------------
3219 procedure Collect_Itypes (Comp : Node_Id) is
3220 Ref : Node_Id;
3221 Sub_Aggr : Node_Id;
3222 Typ : constant Entity_Id := Etype (Comp);
3224 begin
3225 if Is_Array_Type (Typ)
3226 and then Is_Itype (Typ)
3227 then
3228 Ref := Make_Itype_Reference (Loc);
3229 Set_Itype (Ref, Typ);
3230 Append_Freeze_Action (Rec_Type, Ref);
3232 Ref := Make_Itype_Reference (Loc);
3233 Set_Itype (Ref, Etype (First_Index (Typ)));
3234 Append_Freeze_Action (Rec_Type, Ref);
3236 Sub_Aggr := First (Expressions (Comp));
3238 -- Recurse on nested arrays
3240 while Present (Sub_Aggr) loop
3241 Collect_Itypes (Sub_Aggr);
3242 Next (Sub_Aggr);
3243 end loop;
3244 end if;
3245 end Collect_Itypes;
3247 begin
3248 -- If there is a static initialization aggregate for the type,
3249 -- generate itype references for the types of its (sub)components,
3250 -- to prevent out-of-scope errors in the resulting tree.
3251 -- The aggregate may have been rewritten as a Raise node, in which
3252 -- case there are no relevant itypes.
3254 if Present (Agg)
3255 and then Nkind (Agg) = N_Aggregate
3256 then
3257 Set_Static_Initialization (Proc_Id, Agg);
3259 declare
3260 Comp : Node_Id;
3261 begin
3262 Comp := First (Component_Associations (Agg));
3263 while Present (Comp) loop
3264 Collect_Itypes (Expression (Comp));
3265 Next (Comp);
3266 end loop;
3267 end;
3268 end if;
3269 end;
3270 end if;
3271 end Build_Record_Init_Proc;
3273 ----------------------------
3274 -- Build_Slice_Assignment --
3275 ----------------------------
3277 -- Generates the following subprogram:
3279 -- procedure Assign
3280 -- (Source, Target : Array_Type,
3281 -- Left_Lo, Left_Hi : Index;
3282 -- Right_Lo, Right_Hi : Index;
3283 -- Rev : Boolean)
3284 -- is
3285 -- Li1 : Index;
3286 -- Ri1 : Index;
3288 -- begin
3290 -- if Left_Hi < Left_Lo then
3291 -- return;
3292 -- end if;
3294 -- if Rev then
3295 -- Li1 := Left_Hi;
3296 -- Ri1 := Right_Hi;
3297 -- else
3298 -- Li1 := Left_Lo;
3299 -- Ri1 := Right_Lo;
3300 -- end if;
3302 -- loop
3303 -- Target (Li1) := Source (Ri1);
3305 -- if Rev then
3306 -- exit when Li1 = Left_Lo;
3307 -- Li1 := Index'pred (Li1);
3308 -- Ri1 := Index'pred (Ri1);
3309 -- else
3310 -- exit when Li1 = Left_Hi;
3311 -- Li1 := Index'succ (Li1);
3312 -- Ri1 := Index'succ (Ri1);
3313 -- end if;
3314 -- end loop;
3315 -- end Assign;
3317 procedure Build_Slice_Assignment (Typ : Entity_Id) is
3318 Loc : constant Source_Ptr := Sloc (Typ);
3319 Index : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
3321 -- Build formal parameters of procedure
3323 Larray : constant Entity_Id :=
3324 Make_Defining_Identifier
3325 (Loc, Chars => New_Internal_Name ('A'));
3326 Rarray : constant Entity_Id :=
3327 Make_Defining_Identifier
3328 (Loc, Chars => New_Internal_Name ('R'));
3329 Left_Lo : constant Entity_Id :=
3330 Make_Defining_Identifier
3331 (Loc, Chars => New_Internal_Name ('L'));
3332 Left_Hi : constant Entity_Id :=
3333 Make_Defining_Identifier
3334 (Loc, Chars => New_Internal_Name ('L'));
3335 Right_Lo : constant Entity_Id :=
3336 Make_Defining_Identifier
3337 (Loc, Chars => New_Internal_Name ('R'));
3338 Right_Hi : constant Entity_Id :=
3339 Make_Defining_Identifier
3340 (Loc, Chars => New_Internal_Name ('R'));
3341 Rev : constant Entity_Id :=
3342 Make_Defining_Identifier
3343 (Loc, Chars => New_Internal_Name ('D'));
3344 Proc_Name : constant Entity_Id :=
3345 Make_Defining_Identifier (Loc,
3346 Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
3348 Lnn : constant Entity_Id :=
3349 Make_Defining_Identifier (Loc, New_Internal_Name ('L'));
3350 Rnn : constant Entity_Id :=
3351 Make_Defining_Identifier (Loc, New_Internal_Name ('R'));
3352 -- Subscripts for left and right sides
3354 Decls : List_Id;
3355 Loops : Node_Id;
3356 Stats : List_Id;
3358 begin
3359 -- Build declarations for indices
3361 Decls := New_List;
3363 Append_To (Decls,
3364 Make_Object_Declaration (Loc,
3365 Defining_Identifier => Lnn,
3366 Object_Definition =>
3367 New_Occurrence_Of (Index, Loc)));
3369 Append_To (Decls,
3370 Make_Object_Declaration (Loc,
3371 Defining_Identifier => Rnn,
3372 Object_Definition =>
3373 New_Occurrence_Of (Index, Loc)));
3375 Stats := New_List;
3377 -- Build test for empty slice case
3379 Append_To (Stats,
3380 Make_If_Statement (Loc,
3381 Condition =>
3382 Make_Op_Lt (Loc,
3383 Left_Opnd => New_Occurrence_Of (Left_Hi, Loc),
3384 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc)),
3385 Then_Statements => New_List (Make_Simple_Return_Statement (Loc))));
3387 -- Build initializations for indices
3389 declare
3390 F_Init : constant List_Id := New_List;
3391 B_Init : constant List_Id := New_List;
3393 begin
3394 Append_To (F_Init,
3395 Make_Assignment_Statement (Loc,
3396 Name => New_Occurrence_Of (Lnn, Loc),
3397 Expression => New_Occurrence_Of (Left_Lo, Loc)));
3399 Append_To (F_Init,
3400 Make_Assignment_Statement (Loc,
3401 Name => New_Occurrence_Of (Rnn, Loc),
3402 Expression => New_Occurrence_Of (Right_Lo, Loc)));
3404 Append_To (B_Init,
3405 Make_Assignment_Statement (Loc,
3406 Name => New_Occurrence_Of (Lnn, Loc),
3407 Expression => New_Occurrence_Of (Left_Hi, Loc)));
3409 Append_To (B_Init,
3410 Make_Assignment_Statement (Loc,
3411 Name => New_Occurrence_Of (Rnn, Loc),
3412 Expression => New_Occurrence_Of (Right_Hi, Loc)));
3414 Append_To (Stats,
3415 Make_If_Statement (Loc,
3416 Condition => New_Occurrence_Of (Rev, Loc),
3417 Then_Statements => B_Init,
3418 Else_Statements => F_Init));
3419 end;
3421 -- Now construct the assignment statement
3423 Loops :=
3424 Make_Loop_Statement (Loc,
3425 Statements => New_List (
3426 Make_Assignment_Statement (Loc,
3427 Name =>
3428 Make_Indexed_Component (Loc,
3429 Prefix => New_Occurrence_Of (Larray, Loc),
3430 Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
3431 Expression =>
3432 Make_Indexed_Component (Loc,
3433 Prefix => New_Occurrence_Of (Rarray, Loc),
3434 Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
3435 End_Label => Empty);
3437 -- Build the exit condition and increment/decrement statements
3439 declare
3440 F_Ass : constant List_Id := New_List;
3441 B_Ass : constant List_Id := New_List;
3443 begin
3444 Append_To (F_Ass,
3445 Make_Exit_Statement (Loc,
3446 Condition =>
3447 Make_Op_Eq (Loc,
3448 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3449 Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
3451 Append_To (F_Ass,
3452 Make_Assignment_Statement (Loc,
3453 Name => New_Occurrence_Of (Lnn, Loc),
3454 Expression =>
3455 Make_Attribute_Reference (Loc,
3456 Prefix =>
3457 New_Occurrence_Of (Index, Loc),
3458 Attribute_Name => Name_Succ,
3459 Expressions => New_List (
3460 New_Occurrence_Of (Lnn, Loc)))));
3462 Append_To (F_Ass,
3463 Make_Assignment_Statement (Loc,
3464 Name => New_Occurrence_Of (Rnn, Loc),
3465 Expression =>
3466 Make_Attribute_Reference (Loc,
3467 Prefix =>
3468 New_Occurrence_Of (Index, Loc),
3469 Attribute_Name => Name_Succ,
3470 Expressions => New_List (
3471 New_Occurrence_Of (Rnn, Loc)))));
3473 Append_To (B_Ass,
3474 Make_Exit_Statement (Loc,
3475 Condition =>
3476 Make_Op_Eq (Loc,
3477 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3478 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
3480 Append_To (B_Ass,
3481 Make_Assignment_Statement (Loc,
3482 Name => New_Occurrence_Of (Lnn, Loc),
3483 Expression =>
3484 Make_Attribute_Reference (Loc,
3485 Prefix =>
3486 New_Occurrence_Of (Index, Loc),
3487 Attribute_Name => Name_Pred,
3488 Expressions => New_List (
3489 New_Occurrence_Of (Lnn, Loc)))));
3491 Append_To (B_Ass,
3492 Make_Assignment_Statement (Loc,
3493 Name => New_Occurrence_Of (Rnn, Loc),
3494 Expression =>
3495 Make_Attribute_Reference (Loc,
3496 Prefix =>
3497 New_Occurrence_Of (Index, Loc),
3498 Attribute_Name => Name_Pred,
3499 Expressions => New_List (
3500 New_Occurrence_Of (Rnn, Loc)))));
3502 Append_To (Statements (Loops),
3503 Make_If_Statement (Loc,
3504 Condition => New_Occurrence_Of (Rev, Loc),
3505 Then_Statements => B_Ass,
3506 Else_Statements => F_Ass));
3507 end;
3509 Append_To (Stats, Loops);
3511 declare
3512 Spec : Node_Id;
3513 Formals : List_Id := New_List;
3515 begin
3516 Formals := New_List (
3517 Make_Parameter_Specification (Loc,
3518 Defining_Identifier => Larray,
3519 Out_Present => True,
3520 Parameter_Type =>
3521 New_Reference_To (Base_Type (Typ), Loc)),
3523 Make_Parameter_Specification (Loc,
3524 Defining_Identifier => Rarray,
3525 Parameter_Type =>
3526 New_Reference_To (Base_Type (Typ), Loc)),
3528 Make_Parameter_Specification (Loc,
3529 Defining_Identifier => Left_Lo,
3530 Parameter_Type =>
3531 New_Reference_To (Index, Loc)),
3533 Make_Parameter_Specification (Loc,
3534 Defining_Identifier => Left_Hi,
3535 Parameter_Type =>
3536 New_Reference_To (Index, Loc)),
3538 Make_Parameter_Specification (Loc,
3539 Defining_Identifier => Right_Lo,
3540 Parameter_Type =>
3541 New_Reference_To (Index, Loc)),
3543 Make_Parameter_Specification (Loc,
3544 Defining_Identifier => Right_Hi,
3545 Parameter_Type =>
3546 New_Reference_To (Index, Loc)));
3548 Append_To (Formals,
3549 Make_Parameter_Specification (Loc,
3550 Defining_Identifier => Rev,
3551 Parameter_Type =>
3552 New_Reference_To (Standard_Boolean, Loc)));
3554 Spec :=
3555 Make_Procedure_Specification (Loc,
3556 Defining_Unit_Name => Proc_Name,
3557 Parameter_Specifications => Formals);
3559 Discard_Node (
3560 Make_Subprogram_Body (Loc,
3561 Specification => Spec,
3562 Declarations => Decls,
3563 Handled_Statement_Sequence =>
3564 Make_Handled_Sequence_Of_Statements (Loc,
3565 Statements => Stats)));
3566 end;
3568 Set_TSS (Typ, Proc_Name);
3569 Set_Is_Pure (Proc_Name);
3570 end Build_Slice_Assignment;
3572 ------------------------------------
3573 -- Build_Variant_Record_Equality --
3574 ------------------------------------
3576 -- Generates:
3578 -- function _Equality (X, Y : T) return Boolean is
3579 -- begin
3580 -- -- Compare discriminants
3582 -- if False or else X.D1 /= Y.D1 or else X.D2 /= Y.D2 then
3583 -- return False;
3584 -- end if;
3586 -- -- Compare components
3588 -- if False or else X.C1 /= Y.C1 or else X.C2 /= Y.C2 then
3589 -- return False;
3590 -- end if;
3592 -- -- Compare variant part
3594 -- case X.D1 is
3595 -- when V1 =>
3596 -- if False or else X.C2 /= Y.C2 or else X.C3 /= Y.C3 then
3597 -- return False;
3598 -- end if;
3599 -- ...
3600 -- when Vn =>
3601 -- if False or else X.Cn /= Y.Cn then
3602 -- return False;
3603 -- end if;
3604 -- end case;
3606 -- return True;
3607 -- end _Equality;
3609 procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
3610 Loc : constant Source_Ptr := Sloc (Typ);
3612 F : constant Entity_Id :=
3613 Make_Defining_Identifier (Loc,
3614 Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
3616 X : constant Entity_Id :=
3617 Make_Defining_Identifier (Loc,
3618 Chars => Name_X);
3620 Y : constant Entity_Id :=
3621 Make_Defining_Identifier (Loc,
3622 Chars => Name_Y);
3624 Def : constant Node_Id := Parent (Typ);
3625 Comps : constant Node_Id := Component_List (Type_Definition (Def));
3626 Stmts : constant List_Id := New_List;
3627 Pspecs : constant List_Id := New_List;
3629 begin
3630 -- Derived Unchecked_Union types no longer inherit the equality function
3631 -- of their parent.
3633 if Is_Derived_Type (Typ)
3634 and then not Is_Unchecked_Union (Typ)
3635 and then not Has_New_Non_Standard_Rep (Typ)
3636 then
3637 declare
3638 Parent_Eq : constant Entity_Id :=
3639 TSS (Root_Type (Typ), TSS_Composite_Equality);
3641 begin
3642 if Present (Parent_Eq) then
3643 Copy_TSS (Parent_Eq, Typ);
3644 return;
3645 end if;
3646 end;
3647 end if;
3649 Discard_Node (
3650 Make_Subprogram_Body (Loc,
3651 Specification =>
3652 Make_Function_Specification (Loc,
3653 Defining_Unit_Name => F,
3654 Parameter_Specifications => Pspecs,
3655 Result_Definition => New_Reference_To (Standard_Boolean, Loc)),
3656 Declarations => New_List,
3657 Handled_Statement_Sequence =>
3658 Make_Handled_Sequence_Of_Statements (Loc,
3659 Statements => Stmts)));
3661 Append_To (Pspecs,
3662 Make_Parameter_Specification (Loc,
3663 Defining_Identifier => X,
3664 Parameter_Type => New_Reference_To (Typ, Loc)));
3666 Append_To (Pspecs,
3667 Make_Parameter_Specification (Loc,
3668 Defining_Identifier => Y,
3669 Parameter_Type => New_Reference_To (Typ, Loc)));
3671 -- Unchecked_Unions require additional machinery to support equality.
3672 -- Two extra parameters (A and B) are added to the equality function
3673 -- parameter list in order to capture the inferred values of the
3674 -- discriminants in later calls.
3676 if Is_Unchecked_Union (Typ) then
3677 declare
3678 Discr_Type : constant Node_Id := Etype (First_Discriminant (Typ));
3680 A : constant Node_Id :=
3681 Make_Defining_Identifier (Loc,
3682 Chars => Name_A);
3684 B : constant Node_Id :=
3685 Make_Defining_Identifier (Loc,
3686 Chars => Name_B);
3688 begin
3689 -- Add A and B to the parameter list
3691 Append_To (Pspecs,
3692 Make_Parameter_Specification (Loc,
3693 Defining_Identifier => A,
3694 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
3696 Append_To (Pspecs,
3697 Make_Parameter_Specification (Loc,
3698 Defining_Identifier => B,
3699 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
3701 -- Generate the following header code to compare the inferred
3702 -- discriminants:
3704 -- if a /= b then
3705 -- return False;
3706 -- end if;
3708 Append_To (Stmts,
3709 Make_If_Statement (Loc,
3710 Condition =>
3711 Make_Op_Ne (Loc,
3712 Left_Opnd => New_Reference_To (A, Loc),
3713 Right_Opnd => New_Reference_To (B, Loc)),
3714 Then_Statements => New_List (
3715 Make_Simple_Return_Statement (Loc,
3716 Expression => New_Occurrence_Of (Standard_False, Loc)))));
3718 -- Generate component-by-component comparison. Note that we must
3719 -- propagate one of the inferred discriminant formals to act as
3720 -- the case statement switch.
3722 Append_List_To (Stmts,
3723 Make_Eq_Case (Typ, Comps, A));
3725 end;
3727 -- Normal case (not unchecked union)
3729 else
3730 Append_To (Stmts,
3731 Make_Eq_If (Typ,
3732 Discriminant_Specifications (Def)));
3734 Append_List_To (Stmts,
3735 Make_Eq_Case (Typ, Comps));
3736 end if;
3738 Append_To (Stmts,
3739 Make_Simple_Return_Statement (Loc,
3740 Expression => New_Reference_To (Standard_True, Loc)));
3742 Set_TSS (Typ, F);
3743 Set_Is_Pure (F);
3745 if not Debug_Generated_Code then
3746 Set_Debug_Info_Off (F);
3747 end if;
3748 end Build_Variant_Record_Equality;
3750 -----------------------------
3751 -- Check_Stream_Attributes --
3752 -----------------------------
3754 procedure Check_Stream_Attributes (Typ : Entity_Id) is
3755 Comp : Entity_Id;
3756 Par_Read : constant Boolean :=
3757 Stream_Attribute_Available (Typ, TSS_Stream_Read)
3758 and then not Has_Specified_Stream_Read (Typ);
3759 Par_Write : constant Boolean :=
3760 Stream_Attribute_Available (Typ, TSS_Stream_Write)
3761 and then not Has_Specified_Stream_Write (Typ);
3763 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type);
3764 -- Check that Comp has a user-specified Nam stream attribute
3766 ----------------
3767 -- Check_Attr --
3768 ----------------
3770 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type) is
3771 begin
3772 if not Stream_Attribute_Available (Etype (Comp), TSS_Nam) then
3773 Error_Msg_Name_1 := Nam;
3774 Error_Msg_N
3775 ("|component& in limited extension must have% attribute", Comp);
3776 end if;
3777 end Check_Attr;
3779 -- Start of processing for Check_Stream_Attributes
3781 begin
3782 if Par_Read or else Par_Write then
3783 Comp := First_Component (Typ);
3784 while Present (Comp) loop
3785 if Comes_From_Source (Comp)
3786 and then Original_Record_Component (Comp) = Comp
3787 and then Is_Limited_Type (Etype (Comp))
3788 then
3789 if Par_Read then
3790 Check_Attr (Name_Read, TSS_Stream_Read);
3791 end if;
3793 if Par_Write then
3794 Check_Attr (Name_Write, TSS_Stream_Write);
3795 end if;
3796 end if;
3798 Next_Component (Comp);
3799 end loop;
3800 end if;
3801 end Check_Stream_Attributes;
3803 -----------------------------
3804 -- Expand_Record_Extension --
3805 -----------------------------
3807 -- Add a field _parent at the beginning of the record extension. This is
3808 -- used to implement inheritance. Here are some examples of expansion:
3810 -- 1. no discriminants
3811 -- type T2 is new T1 with null record;
3812 -- gives
3813 -- type T2 is new T1 with record
3814 -- _Parent : T1;
3815 -- end record;
3817 -- 2. renamed discriminants
3818 -- type T2 (B, C : Int) is new T1 (A => B) with record
3819 -- _Parent : T1 (A => B);
3820 -- D : Int;
3821 -- end;
3823 -- 3. inherited discriminants
3824 -- type T2 is new T1 with record -- discriminant A inherited
3825 -- _Parent : T1 (A);
3826 -- D : Int;
3827 -- end;
3829 procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
3830 Indic : constant Node_Id := Subtype_Indication (Def);
3831 Loc : constant Source_Ptr := Sloc (Def);
3832 Rec_Ext_Part : Node_Id := Record_Extension_Part (Def);
3833 Par_Subtype : Entity_Id;
3834 Comp_List : Node_Id;
3835 Comp_Decl : Node_Id;
3836 Parent_N : Node_Id;
3837 D : Entity_Id;
3838 List_Constr : constant List_Id := New_List;
3840 begin
3841 -- Expand_Record_Extension is called directly from the semantics, so
3842 -- we must check to see whether expansion is active before proceeding
3844 if not Expander_Active then
3845 return;
3846 end if;
3848 -- This may be a derivation of an untagged private type whose full
3849 -- view is tagged, in which case the Derived_Type_Definition has no
3850 -- extension part. Build an empty one now.
3852 if No (Rec_Ext_Part) then
3853 Rec_Ext_Part :=
3854 Make_Record_Definition (Loc,
3855 End_Label => Empty,
3856 Component_List => Empty,
3857 Null_Present => True);
3859 Set_Record_Extension_Part (Def, Rec_Ext_Part);
3860 Mark_Rewrite_Insertion (Rec_Ext_Part);
3861 end if;
3863 Comp_List := Component_List (Rec_Ext_Part);
3865 Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
3867 -- If the derived type inherits its discriminants the type of the
3868 -- _parent field must be constrained by the inherited discriminants
3870 if Has_Discriminants (T)
3871 and then Nkind (Indic) /= N_Subtype_Indication
3872 and then not Is_Constrained (Entity (Indic))
3873 then
3874 D := First_Discriminant (T);
3875 while Present (D) loop
3876 Append_To (List_Constr, New_Occurrence_Of (D, Loc));
3877 Next_Discriminant (D);
3878 end loop;
3880 Par_Subtype :=
3881 Process_Subtype (
3882 Make_Subtype_Indication (Loc,
3883 Subtype_Mark => New_Reference_To (Entity (Indic), Loc),
3884 Constraint =>
3885 Make_Index_Or_Discriminant_Constraint (Loc,
3886 Constraints => List_Constr)),
3887 Def);
3889 -- Otherwise the original subtype_indication is just what is needed
3891 else
3892 Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
3893 end if;
3895 -- If this is an extension of a type with unknown discriminants, use
3896 -- full view to provide proper discriminants to gigi.
3898 if Has_Unknown_Discriminants (Par_Subtype)
3899 and then Is_Private_Type (Par_Subtype)
3900 and then Present (Full_View (Par_Subtype))
3901 then
3902 Par_Subtype := Full_View (Par_Subtype);
3903 end if;
3905 Set_Parent_Subtype (T, Par_Subtype);
3907 Comp_Decl :=
3908 Make_Component_Declaration (Loc,
3909 Defining_Identifier => Parent_N,
3910 Component_Definition =>
3911 Make_Component_Definition (Loc,
3912 Aliased_Present => False,
3913 Subtype_Indication => New_Reference_To (Par_Subtype, Loc)));
3915 if Null_Present (Rec_Ext_Part) then
3916 Set_Component_List (Rec_Ext_Part,
3917 Make_Component_List (Loc,
3918 Component_Items => New_List (Comp_Decl),
3919 Variant_Part => Empty,
3920 Null_Present => False));
3921 Set_Null_Present (Rec_Ext_Part, False);
3923 elsif Null_Present (Comp_List)
3924 or else Is_Empty_List (Component_Items (Comp_List))
3925 then
3926 Set_Component_Items (Comp_List, New_List (Comp_Decl));
3927 Set_Null_Present (Comp_List, False);
3929 else
3930 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
3931 end if;
3933 Analyze (Comp_Decl);
3934 end Expand_Record_Extension;
3936 ------------------------------------
3937 -- Expand_N_Full_Type_Declaration --
3938 ------------------------------------
3940 procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
3941 Def_Id : constant Entity_Id := Defining_Identifier (N);
3942 B_Id : constant Entity_Id := Base_Type (Def_Id);
3943 Par_Id : Entity_Id;
3944 FN : Node_Id;
3946 procedure Build_Master (Def_Id : Entity_Id);
3947 -- Create the master associated with Def_Id
3949 ------------------
3950 -- Build_Master --
3951 ------------------
3953 procedure Build_Master (Def_Id : Entity_Id) is
3954 begin
3955 -- Anonymous access types are created for the components of the
3956 -- record parameter for an entry declaration. No master is created
3957 -- for such a type.
3959 if Has_Task (Designated_Type (Def_Id))
3960 and then Comes_From_Source (N)
3961 then
3962 Build_Master_Entity (Def_Id);
3963 Build_Master_Renaming (Parent (Def_Id), Def_Id);
3965 -- Create a class-wide master because a Master_Id must be generated
3966 -- for access-to-limited-class-wide types whose root may be extended
3967 -- with task components.
3969 -- Note: This code covers access-to-limited-interfaces because they
3970 -- can be used to reference tasks implementing them.
3972 elsif Is_Class_Wide_Type (Designated_Type (Def_Id))
3973 and then Is_Limited_Type (Designated_Type (Def_Id))
3974 and then Tasking_Allowed
3976 -- Do not create a class-wide master for types whose convention is
3977 -- Java since these types cannot embed Ada tasks anyway. Note that
3978 -- the following test cannot catch the following case:
3980 -- package java.lang.Object is
3981 -- type Typ is tagged limited private;
3982 -- type Ref is access all Typ'Class;
3983 -- private
3984 -- type Typ is tagged limited ...;
3985 -- pragma Convention (Typ, Java)
3986 -- end;
3988 -- Because the convention appears after we have done the
3989 -- processing for type Ref.
3991 and then Convention (Designated_Type (Def_Id)) /= Convention_Java
3992 and then Convention (Designated_Type (Def_Id)) /= Convention_CIL
3993 then
3994 Build_Class_Wide_Master (Def_Id);
3995 end if;
3996 end Build_Master;
3998 -- Start of processing for Expand_N_Full_Type_Declaration
4000 begin
4001 if Is_Access_Type (Def_Id) then
4002 Build_Master (Def_Id);
4004 if Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
4005 Expand_Access_Protected_Subprogram_Type (N);
4006 end if;
4008 elsif Ada_Version >= Ada_05
4009 and then Is_Array_Type (Def_Id)
4010 and then Is_Access_Type (Component_Type (Def_Id))
4011 and then Ekind (Component_Type (Def_Id)) = E_Anonymous_Access_Type
4012 then
4013 Build_Master (Component_Type (Def_Id));
4015 elsif Has_Task (Def_Id) then
4016 Expand_Previous_Access_Type (Def_Id);
4018 elsif Ada_Version >= Ada_05
4019 and then
4020 (Is_Record_Type (Def_Id)
4021 or else (Is_Array_Type (Def_Id)
4022 and then Is_Record_Type (Component_Type (Def_Id))))
4023 then
4024 declare
4025 Comp : Entity_Id;
4026 Typ : Entity_Id;
4027 M_Id : Entity_Id;
4029 begin
4030 -- Look for the first anonymous access type component
4032 if Is_Array_Type (Def_Id) then
4033 Comp := First_Entity (Component_Type (Def_Id));
4034 else
4035 Comp := First_Entity (Def_Id);
4036 end if;
4038 while Present (Comp) loop
4039 Typ := Etype (Comp);
4041 exit when Is_Access_Type (Typ)
4042 and then Ekind (Typ) = E_Anonymous_Access_Type;
4044 Next_Entity (Comp);
4045 end loop;
4047 -- If found we add a renaming declaration of master_id and we
4048 -- associate it to each anonymous access type component. Do
4049 -- nothing if the access type already has a master. This will be
4050 -- the case if the array type is the packed array created for a
4051 -- user-defined array type T, where the master_id is created when
4052 -- expanding the declaration for T.
4054 if Present (Comp)
4055 and then Ekind (Typ) = E_Anonymous_Access_Type
4056 and then not Restriction_Active (No_Task_Hierarchy)
4057 and then No (Master_Id (Typ))
4059 -- Do not consider run-times with no tasking support
4061 and then RTE_Available (RE_Current_Master)
4062 and then Has_Task (Non_Limited_Designated_Type (Typ))
4063 then
4064 Build_Master_Entity (Def_Id);
4065 M_Id := Build_Master_Renaming (N, Def_Id);
4067 if Is_Array_Type (Def_Id) then
4068 Comp := First_Entity (Component_Type (Def_Id));
4069 else
4070 Comp := First_Entity (Def_Id);
4071 end if;
4073 while Present (Comp) loop
4074 Typ := Etype (Comp);
4076 if Is_Access_Type (Typ)
4077 and then Ekind (Typ) = E_Anonymous_Access_Type
4078 then
4079 Set_Master_Id (Typ, M_Id);
4080 end if;
4082 Next_Entity (Comp);
4083 end loop;
4084 end if;
4085 end;
4086 end if;
4088 Par_Id := Etype (B_Id);
4090 -- The parent type is private then we need to inherit any TSS operations
4091 -- from the full view.
4093 if Ekind (Par_Id) in Private_Kind
4094 and then Present (Full_View (Par_Id))
4095 then
4096 Par_Id := Base_Type (Full_View (Par_Id));
4097 end if;
4099 if Nkind (Type_Definition (Original_Node (N))) =
4100 N_Derived_Type_Definition
4101 and then not Is_Tagged_Type (Def_Id)
4102 and then Present (Freeze_Node (Par_Id))
4103 and then Present (TSS_Elist (Freeze_Node (Par_Id)))
4104 then
4105 Ensure_Freeze_Node (B_Id);
4106 FN := Freeze_Node (B_Id);
4108 if No (TSS_Elist (FN)) then
4109 Set_TSS_Elist (FN, New_Elmt_List);
4110 end if;
4112 declare
4113 T_E : constant Elist_Id := TSS_Elist (FN);
4114 Elmt : Elmt_Id;
4116 begin
4117 Elmt := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
4118 while Present (Elmt) loop
4119 if Chars (Node (Elmt)) /= Name_uInit then
4120 Append_Elmt (Node (Elmt), T_E);
4121 end if;
4123 Next_Elmt (Elmt);
4124 end loop;
4126 -- If the derived type itself is private with a full view, then
4127 -- associate the full view with the inherited TSS_Elist as well.
4129 if Ekind (B_Id) in Private_Kind
4130 and then Present (Full_View (B_Id))
4131 then
4132 Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
4133 Set_TSS_Elist
4134 (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
4135 end if;
4136 end;
4137 end if;
4138 end Expand_N_Full_Type_Declaration;
4140 ---------------------------------
4141 -- Expand_N_Object_Declaration --
4142 ---------------------------------
4144 -- First we do special processing for objects of a tagged type where this
4145 -- is the point at which the type is frozen. The creation of the dispatch
4146 -- table and the initialization procedure have to be deferred to this
4147 -- point, since we reference previously declared primitive subprograms.
4149 -- For all types, we call an initialization procedure if there is one
4151 procedure Expand_N_Object_Declaration (N : Node_Id) is
4152 Def_Id : constant Entity_Id := Defining_Identifier (N);
4153 Expr : constant Node_Id := Expression (N);
4154 Loc : constant Source_Ptr := Sloc (N);
4155 Typ : constant Entity_Id := Etype (Def_Id);
4156 Base_Typ : constant Entity_Id := Base_Type (Typ);
4157 Expr_Q : Node_Id;
4158 Id_Ref : Node_Id;
4159 New_Ref : Node_Id;
4161 Init_After : Node_Id := N;
4162 -- Node after which the init proc call is to be inserted. This is
4163 -- normally N, except for the case of a shared passive variable, in
4164 -- which case the init proc call must be inserted only after the bodies
4165 -- of the shared variable procedures have been seen.
4167 begin
4168 -- Don't do anything for deferred constants. All proper actions will
4169 -- be expanded during the full declaration.
4171 if No (Expr) and Constant_Present (N) then
4172 return;
4173 end if;
4175 -- Force construction of dispatch tables of library level tagged types
4177 if VM_Target = No_VM
4178 and then Static_Dispatch_Tables
4179 and then Is_Library_Level_Entity (Def_Id)
4180 and then Is_Library_Level_Tagged_Type (Base_Typ)
4181 and then (Ekind (Base_Typ) = E_Record_Type
4182 or else Ekind (Base_Typ) = E_Protected_Type
4183 or else Ekind (Base_Typ) = E_Task_Type)
4184 and then not Has_Dispatch_Table (Base_Typ)
4185 then
4186 declare
4187 New_Nodes : List_Id := No_List;
4189 begin
4190 if Is_Concurrent_Type (Base_Typ) then
4191 New_Nodes := Make_DT (Corresponding_Record_Type (Base_Typ), N);
4192 else
4193 New_Nodes := Make_DT (Base_Typ, N);
4194 end if;
4196 if not Is_Empty_List (New_Nodes) then
4197 Insert_List_Before (N, New_Nodes);
4198 end if;
4199 end;
4200 end if;
4202 -- Make shared memory routines for shared passive variable
4204 if Is_Shared_Passive (Def_Id) then
4205 Init_After := Make_Shared_Var_Procs (N);
4206 end if;
4208 -- If tasks being declared, make sure we have an activation chain
4209 -- defined for the tasks (has no effect if we already have one), and
4210 -- also that a Master variable is established and that the appropriate
4211 -- enclosing construct is established as a task master.
4213 if Has_Task (Typ) then
4214 Build_Activation_Chain_Entity (N);
4215 Build_Master_Entity (Def_Id);
4216 end if;
4218 -- Build a list controller for declarations where the type is anonymous
4219 -- access and the designated type is controlled. Only declarations from
4220 -- source files receive such controllers in order to provide the same
4221 -- lifespan for any potential coextensions that may be associated with
4222 -- the object. Finalization lists of internal controlled anonymous
4223 -- access objects are already handled in Expand_N_Allocator.
4225 if Comes_From_Source (N)
4226 and then Ekind (Typ) = E_Anonymous_Access_Type
4227 and then Is_Controlled (Directly_Designated_Type (Typ))
4228 and then No (Associated_Final_Chain (Typ))
4229 then
4230 Build_Final_List (N, Typ);
4231 end if;
4233 -- Default initialization required, and no expression present
4235 if No (Expr) then
4237 -- Expand Initialize call for controlled objects. One may wonder why
4238 -- the Initialize Call is not done in the regular Init procedure
4239 -- attached to the record type. That's because the init procedure is
4240 -- recursively called on each component, including _Parent, thus the
4241 -- Init call for a controlled object would generate not only one
4242 -- Initialize call as it is required but one for each ancestor of
4243 -- its type. This processing is suppressed if No_Initialization set.
4245 if not Needs_Finalization (Typ)
4246 or else No_Initialization (N)
4247 then
4248 null;
4250 elsif not Abort_Allowed
4251 or else not Comes_From_Source (N)
4252 then
4253 Insert_Actions_After (Init_After,
4254 Make_Init_Call (
4255 Ref => New_Occurrence_Of (Def_Id, Loc),
4256 Typ => Base_Type (Typ),
4257 Flist_Ref => Find_Final_List (Def_Id),
4258 With_Attach => Make_Integer_Literal (Loc, 1)));
4260 -- Abort allowed
4262 else
4263 -- We need to protect the initialize call
4265 -- begin
4266 -- Defer_Abort.all;
4267 -- Initialize (...);
4268 -- at end
4269 -- Undefer_Abort.all;
4270 -- end;
4272 -- ??? this won't protect the initialize call for controlled
4273 -- components which are part of the init proc, so this block
4274 -- should probably also contain the call to _init_proc but this
4275 -- requires some code reorganization...
4277 declare
4278 L : constant List_Id :=
4279 Make_Init_Call
4280 (Ref => New_Occurrence_Of (Def_Id, Loc),
4281 Typ => Base_Type (Typ),
4282 Flist_Ref => Find_Final_List (Def_Id),
4283 With_Attach => Make_Integer_Literal (Loc, 1));
4285 Blk : constant Node_Id :=
4286 Make_Block_Statement (Loc,
4287 Handled_Statement_Sequence =>
4288 Make_Handled_Sequence_Of_Statements (Loc, L));
4290 begin
4291 Prepend_To (L, Build_Runtime_Call (Loc, RE_Abort_Defer));
4292 Set_At_End_Proc (Handled_Statement_Sequence (Blk),
4293 New_Occurrence_Of (RTE (RE_Abort_Undefer_Direct), Loc));
4294 Insert_Actions_After (Init_After, New_List (Blk));
4295 Expand_At_End_Handler
4296 (Handled_Statement_Sequence (Blk), Entity (Identifier (Blk)));
4297 end;
4298 end if;
4300 -- Call type initialization procedure if there is one. We build the
4301 -- call and put it immediately after the object declaration, so that
4302 -- it will be expanded in the usual manner. Note that this will
4303 -- result in proper handling of defaulted discriminants.
4305 -- Need call if there is a base init proc
4307 if Has_Non_Null_Base_Init_Proc (Typ)
4309 -- Suppress call if No_Initialization set on declaration
4311 and then not No_Initialization (N)
4313 -- Suppress call for special case of value type for VM
4315 and then not Is_Value_Type (Typ)
4317 -- Suppress call if Suppress_Init_Proc set on the type. This is
4318 -- needed for the derived type case, where Suppress_Initialization
4319 -- may be set for the derived type, even if there is an init proc
4320 -- defined for the root type.
4322 and then not Suppress_Init_Proc (Typ)
4323 then
4324 -- Return without initializing when No_Default_Initialization
4325 -- applies. Note that the actual restriction check occurs later,
4326 -- when the object is frozen, because we don't know yet whether
4327 -- the object is imported, which is a case where the check does
4328 -- not apply.
4330 if Restriction_Active (No_Default_Initialization) then
4331 return;
4332 end if;
4334 -- The call to the initialization procedure does NOT freeze the
4335 -- object being initialized. This is because the call is not a
4336 -- source level call. This works fine, because the only possible
4337 -- statements depending on freeze status that can appear after the
4338 -- _Init call are rep clauses which can safely appear after actual
4339 -- references to the object.
4341 Id_Ref := New_Reference_To (Def_Id, Loc);
4342 Set_Must_Not_Freeze (Id_Ref);
4343 Set_Assignment_OK (Id_Ref);
4345 declare
4346 Init_Expr : constant Node_Id :=
4347 Static_Initialization (Base_Init_Proc (Typ));
4348 begin
4349 if Present (Init_Expr) then
4350 Set_Expression
4351 (N, New_Copy_Tree (Init_Expr, New_Scope => Current_Scope));
4352 return;
4353 else
4354 Initialization_Warning (Id_Ref);
4356 Insert_Actions_After (Init_After,
4357 Build_Initialization_Call (Loc, Id_Ref, Typ));
4358 end if;
4359 end;
4361 -- If simple initialization is required, then set an appropriate
4362 -- simple initialization expression in place. This special
4363 -- initialization is required even though No_Init_Flag is present,
4364 -- but is not needed if there was an explicit initialization.
4366 -- An internally generated temporary needs no initialization because
4367 -- it will be assigned subsequently. In particular, there is no point
4368 -- in applying Initialize_Scalars to such a temporary.
4370 elsif Needs_Simple_Initialization (Typ)
4371 and then not Is_Internal (Def_Id)
4372 and then not Has_Init_Expression (N)
4373 then
4374 Set_No_Initialization (N, False);
4375 Set_Expression (N, Get_Simple_Init_Val (Typ, N, Esize (Def_Id)));
4376 Analyze_And_Resolve (Expression (N), Typ);
4377 end if;
4379 -- Generate attribute for Persistent_BSS if needed
4381 if Persistent_BSS_Mode
4382 and then Comes_From_Source (N)
4383 and then Is_Potentially_Persistent_Type (Typ)
4384 and then not Has_Init_Expression (N)
4385 and then Is_Library_Level_Entity (Def_Id)
4386 then
4387 declare
4388 Prag : Node_Id;
4389 begin
4390 Prag :=
4391 Make_Linker_Section_Pragma
4392 (Def_Id, Sloc (N), ".persistent.bss");
4393 Insert_After (N, Prag);
4394 Analyze (Prag);
4395 end;
4396 end if;
4398 -- If access type, then we know it is null if not initialized
4400 if Is_Access_Type (Typ) then
4401 Set_Is_Known_Null (Def_Id);
4402 end if;
4404 -- Explicit initialization present
4406 else
4407 -- Obtain actual expression from qualified expression
4409 if Nkind (Expr) = N_Qualified_Expression then
4410 Expr_Q := Expression (Expr);
4411 else
4412 Expr_Q := Expr;
4413 end if;
4415 -- When we have the appropriate type of aggregate in the expression
4416 -- (it has been determined during analysis of the aggregate by
4417 -- setting the delay flag), let's perform in place assignment and
4418 -- thus avoid creating a temporary.
4420 if Is_Delayed_Aggregate (Expr_Q) then
4421 Convert_Aggr_In_Object_Decl (N);
4423 -- Ada 2005 (AI-318-02): If the initialization expression is a call
4424 -- to a build-in-place function, then access to the declared object
4425 -- must be passed to the function. Currently we limit such functions
4426 -- to those with constrained limited result subtypes, but eventually
4427 -- plan to expand the allowed forms of functions that are treated as
4428 -- build-in-place.
4430 elsif Ada_Version >= Ada_05
4431 and then Is_Build_In_Place_Function_Call (Expr_Q)
4432 then
4433 Make_Build_In_Place_Call_In_Object_Declaration (N, Expr_Q);
4435 -- The previous call expands the expression initializing the
4436 -- built-in-place object into further code that will be analyzed
4437 -- later. No further expansion needed here.
4439 return;
4441 else
4442 -- In most cases, we must check that the initial value meets any
4443 -- constraint imposed by the declared type. However, there is one
4444 -- very important exception to this rule. If the entity has an
4445 -- unconstrained nominal subtype, then it acquired its constraints
4446 -- from the expression in the first place, and not only does this
4447 -- mean that the constraint check is not needed, but an attempt to
4448 -- perform the constraint check can cause order of elaboration
4449 -- problems.
4451 if not Is_Constr_Subt_For_U_Nominal (Typ) then
4453 -- If this is an allocator for an aggregate that has been
4454 -- allocated in place, delay checks until assignments are
4455 -- made, because the discriminants are not initialized.
4457 if Nkind (Expr) = N_Allocator
4458 and then No_Initialization (Expr)
4459 then
4460 null;
4461 else
4462 Apply_Constraint_Check (Expr, Typ);
4463 end if;
4464 end if;
4466 -- Ada 2005 (AI-251): Rewrite the expression that initializes a
4467 -- class-wide object to ensure that we copy the full object,
4468 -- unless we are targetting a VM where interfaces are handled by
4469 -- VM itself. Note that if the root type of Typ is an ancestor
4470 -- of Expr's type, both types share the same dispatch table and
4471 -- there is no need to displace the pointer.
4473 -- Replace
4474 -- CW : I'Class := Obj;
4475 -- by
4476 -- Temp : I'Class := I'Class (Base_Address (Obj'Address));
4477 -- CW : I'Class renames Displace (Temp, I'Tag);
4479 if Is_Interface (Typ)
4480 and then Is_Class_Wide_Type (Typ)
4481 and then
4482 (Is_Class_Wide_Type (Etype (Expr))
4483 or else
4484 not Is_Ancestor (Root_Type (Typ), Etype (Expr)))
4485 and then Comes_From_Source (Def_Id)
4486 and then VM_Target = No_VM
4487 then
4488 declare
4489 Decl_1 : Node_Id;
4490 Decl_2 : Node_Id;
4492 begin
4493 Decl_1 :=
4494 Make_Object_Declaration (Loc,
4495 Defining_Identifier =>
4496 Make_Defining_Identifier (Loc,
4497 New_Internal_Name ('D')),
4499 Object_Definition =>
4500 Make_Attribute_Reference (Loc,
4501 Prefix =>
4502 New_Occurrence_Of
4503 (Root_Type (Etype (Def_Id)), Loc),
4504 Attribute_Name => Name_Class),
4506 Expression =>
4507 Unchecked_Convert_To
4508 (Class_Wide_Type (Root_Type (Etype (Def_Id))),
4509 Make_Explicit_Dereference (Loc,
4510 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
4511 Make_Function_Call (Loc,
4512 Name =>
4513 New_Reference_To (RTE (RE_Base_Address),
4514 Loc),
4515 Parameter_Associations => New_List (
4516 Make_Attribute_Reference (Loc,
4517 Prefix => Relocate_Node (Expr),
4518 Attribute_Name => Name_Address)))))));
4520 Insert_Action (N, Decl_1);
4522 Decl_2 :=
4523 Make_Object_Renaming_Declaration (Loc,
4524 Defining_Identifier =>
4525 Make_Defining_Identifier (Loc,
4526 New_Internal_Name ('D')),
4528 Subtype_Mark =>
4529 Make_Attribute_Reference (Loc,
4530 Prefix =>
4531 New_Occurrence_Of
4532 (Root_Type (Etype (Def_Id)), Loc),
4533 Attribute_Name => Name_Class),
4535 Name =>
4536 Unchecked_Convert_To (
4537 Class_Wide_Type (Root_Type (Etype (Def_Id))),
4538 Make_Explicit_Dereference (Loc,
4539 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
4540 Make_Function_Call (Loc,
4541 Name =>
4542 New_Reference_To (RTE (RE_Displace), Loc),
4544 Parameter_Associations => New_List (
4545 Make_Attribute_Reference (Loc,
4546 Prefix =>
4547 New_Reference_To
4548 (Defining_Identifier (Decl_1), Loc),
4549 Attribute_Name => Name_Address),
4551 Unchecked_Convert_To (RTE (RE_Tag),
4552 New_Reference_To
4553 (Node
4554 (First_Elmt
4555 (Access_Disp_Table
4556 (Root_Type (Typ)))),
4557 Loc))))))));
4559 Rewrite (N, Decl_2);
4560 Analyze (N);
4562 -- Replace internal identifier of Decl_2 by the identifier
4563 -- found in the sources. We also have to exchange entities
4564 -- containing their defining identifiers to ensure the
4565 -- correct replacement of the object declaration by this
4566 -- object renaming declaration (because such definings
4567 -- identifier have been previously added by Enter_Name to
4568 -- the current scope). We must preserve the homonym chain
4569 -- of the source entity as well.
4571 Set_Chars (Defining_Identifier (N), Chars (Def_Id));
4572 Set_Homonym (Defining_Identifier (N), Homonym (Def_Id));
4573 Exchange_Entities (Defining_Identifier (N), Def_Id);
4575 return;
4576 end;
4577 end if;
4579 -- If the type is controlled and not inherently limited, then
4580 -- the target is adjusted after the copy and attached to the
4581 -- finalization list. However, no adjustment is done in the case
4582 -- where the object was initialized by a call to a function whose
4583 -- result is built in place, since no copy occurred. (Eventually
4584 -- we plan to support in-place function results for some cases
4585 -- of nonlimited types. ???)
4587 if Needs_Finalization (Typ)
4588 and then not Is_Inherently_Limited_Type (Typ)
4589 then
4590 Insert_Actions_After (Init_After,
4591 Make_Adjust_Call (
4592 Ref => New_Reference_To (Def_Id, Loc),
4593 Typ => Base_Type (Typ),
4594 Flist_Ref => Find_Final_List (Def_Id),
4595 With_Attach => Make_Integer_Literal (Loc, 1)));
4596 end if;
4598 -- For tagged types, when an init value is given, the tag has to
4599 -- be re-initialized separately in order to avoid the propagation
4600 -- of a wrong tag coming from a view conversion unless the type
4601 -- is class wide (in this case the tag comes from the init value).
4602 -- Suppress the tag assignment when VM_Target because VM tags are
4603 -- represented implicitly in objects. Ditto for types that are
4604 -- CPP_CLASS, and for initializations that are aggregates, because
4605 -- they have to have the right tag.
4607 if Is_Tagged_Type (Typ)
4608 and then not Is_Class_Wide_Type (Typ)
4609 and then not Is_CPP_Class (Typ)
4610 and then VM_Target = No_VM
4611 and then Nkind (Expr) /= N_Aggregate
4612 then
4613 -- The re-assignment of the tag has to be done even if the
4614 -- object is a constant.
4616 New_Ref :=
4617 Make_Selected_Component (Loc,
4618 Prefix => New_Reference_To (Def_Id, Loc),
4619 Selector_Name =>
4620 New_Reference_To (First_Tag_Component (Typ), Loc));
4622 Set_Assignment_OK (New_Ref);
4624 Insert_After (Init_After,
4625 Make_Assignment_Statement (Loc,
4626 Name => New_Ref,
4627 Expression =>
4628 Unchecked_Convert_To (RTE (RE_Tag),
4629 New_Reference_To
4630 (Node
4631 (First_Elmt
4632 (Access_Disp_Table (Base_Type (Typ)))),
4633 Loc))));
4635 -- For discrete types, set the Is_Known_Valid flag if the
4636 -- initializing value is known to be valid.
4638 elsif Is_Discrete_Type (Typ) and then Expr_Known_Valid (Expr) then
4639 Set_Is_Known_Valid (Def_Id);
4641 elsif Is_Access_Type (Typ) then
4643 -- For access types set the Is_Known_Non_Null flag if the
4644 -- initializing value is known to be non-null. We can also set
4645 -- Can_Never_Be_Null if this is a constant.
4647 if Known_Non_Null (Expr) then
4648 Set_Is_Known_Non_Null (Def_Id, True);
4650 if Constant_Present (N) then
4651 Set_Can_Never_Be_Null (Def_Id);
4652 end if;
4653 end if;
4654 end if;
4656 -- If validity checking on copies, validate initial expression.
4657 -- But skip this if declaration is for a generic type, since it
4658 -- makes no sense to validate generic types. Not clear if this
4659 -- can happen for legal programs, but it definitely can arise
4660 -- from previous instantiation errors.
4662 if Validity_Checks_On
4663 and then Validity_Check_Copies
4664 and then not Is_Generic_Type (Etype (Def_Id))
4665 then
4666 Ensure_Valid (Expr);
4667 Set_Is_Known_Valid (Def_Id);
4668 end if;
4669 end if;
4671 -- Cases where the back end cannot handle the initialization directly
4672 -- In such cases, we expand an assignment that will be appropriately
4673 -- handled by Expand_N_Assignment_Statement.
4675 -- The exclusion of the unconstrained case is wrong, but for now it
4676 -- is too much trouble ???
4678 if (Is_Possibly_Unaligned_Slice (Expr)
4679 or else (Is_Possibly_Unaligned_Object (Expr)
4680 and then not Represented_As_Scalar (Etype (Expr))))
4682 -- The exclusion of the unconstrained case is wrong, but for now
4683 -- it is too much trouble ???
4685 and then not (Is_Array_Type (Etype (Expr))
4686 and then not Is_Constrained (Etype (Expr)))
4687 then
4688 declare
4689 Stat : constant Node_Id :=
4690 Make_Assignment_Statement (Loc,
4691 Name => New_Reference_To (Def_Id, Loc),
4692 Expression => Relocate_Node (Expr));
4693 begin
4694 Set_Expression (N, Empty);
4695 Set_No_Initialization (N);
4696 Set_Assignment_OK (Name (Stat));
4697 Set_No_Ctrl_Actions (Stat);
4698 Insert_After_And_Analyze (Init_After, Stat);
4699 end;
4700 end if;
4701 end if;
4703 exception
4704 when RE_Not_Available =>
4705 return;
4706 end Expand_N_Object_Declaration;
4708 ---------------------------------
4709 -- Expand_N_Subtype_Indication --
4710 ---------------------------------
4712 -- Add a check on the range of the subtype. The static case is partially
4713 -- duplicated by Process_Range_Expr_In_Decl in Sem_Ch3, but we still need
4714 -- to check here for the static case in order to avoid generating
4715 -- extraneous expanded code. Also deal with validity checking.
4717 procedure Expand_N_Subtype_Indication (N : Node_Id) is
4718 Ran : constant Node_Id := Range_Expression (Constraint (N));
4719 Typ : constant Entity_Id := Entity (Subtype_Mark (N));
4721 begin
4722 if Nkind (Constraint (N)) = N_Range_Constraint then
4723 Validity_Check_Range (Range_Expression (Constraint (N)));
4724 end if;
4726 if Nkind_In (Parent (N), N_Constrained_Array_Definition, N_Slice) then
4727 Apply_Range_Check (Ran, Typ);
4728 end if;
4729 end Expand_N_Subtype_Indication;
4731 ---------------------------
4732 -- Expand_N_Variant_Part --
4733 ---------------------------
4735 -- If the last variant does not contain the Others choice, replace it with
4736 -- an N_Others_Choice node since Gigi always wants an Others. Note that we
4737 -- do not bother to call Analyze on the modified variant part, since it's
4738 -- only effect would be to compute the Others_Discrete_Choices node
4739 -- laboriously, and of course we already know the list of choices that
4740 -- corresponds to the others choice (it's the list we are replacing!)
4742 procedure Expand_N_Variant_Part (N : Node_Id) is
4743 Last_Var : constant Node_Id := Last_Non_Pragma (Variants (N));
4744 Others_Node : Node_Id;
4745 begin
4746 if Nkind (First (Discrete_Choices (Last_Var))) /= N_Others_Choice then
4747 Others_Node := Make_Others_Choice (Sloc (Last_Var));
4748 Set_Others_Discrete_Choices
4749 (Others_Node, Discrete_Choices (Last_Var));
4750 Set_Discrete_Choices (Last_Var, New_List (Others_Node));
4751 end if;
4752 end Expand_N_Variant_Part;
4754 ---------------------------------
4755 -- Expand_Previous_Access_Type --
4756 ---------------------------------
4758 procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
4759 T : Entity_Id := First_Entity (Current_Scope);
4761 begin
4762 -- Find all access types declared in the current scope, whose
4763 -- designated type is Def_Id. If it does not have a Master_Id,
4764 -- create one now.
4766 while Present (T) loop
4767 if Is_Access_Type (T)
4768 and then Designated_Type (T) = Def_Id
4769 and then No (Master_Id (T))
4770 then
4771 Build_Master_Entity (Def_Id);
4772 Build_Master_Renaming (Parent (Def_Id), T);
4773 end if;
4775 Next_Entity (T);
4776 end loop;
4777 end Expand_Previous_Access_Type;
4779 ------------------------------
4780 -- Expand_Record_Controller --
4781 ------------------------------
4783 procedure Expand_Record_Controller (T : Entity_Id) is
4784 Def : Node_Id := Type_Definition (Parent (T));
4785 Comp_List : Node_Id;
4786 Comp_Decl : Node_Id;
4787 Loc : Source_Ptr;
4788 First_Comp : Node_Id;
4789 Controller_Type : Entity_Id;
4790 Ent : Entity_Id;
4792 begin
4793 if Nkind (Def) = N_Derived_Type_Definition then
4794 Def := Record_Extension_Part (Def);
4795 end if;
4797 if Null_Present (Def) then
4798 Set_Component_List (Def,
4799 Make_Component_List (Sloc (Def),
4800 Component_Items => Empty_List,
4801 Variant_Part => Empty,
4802 Null_Present => True));
4803 end if;
4805 Comp_List := Component_List (Def);
4807 if Null_Present (Comp_List)
4808 or else Is_Empty_List (Component_Items (Comp_List))
4809 then
4810 Loc := Sloc (Comp_List);
4811 else
4812 Loc := Sloc (First (Component_Items (Comp_List)));
4813 end if;
4815 if Is_Inherently_Limited_Type (T) then
4816 Controller_Type := RTE (RE_Limited_Record_Controller);
4817 else
4818 Controller_Type := RTE (RE_Record_Controller);
4819 end if;
4821 Ent := Make_Defining_Identifier (Loc, Name_uController);
4823 Comp_Decl :=
4824 Make_Component_Declaration (Loc,
4825 Defining_Identifier => Ent,
4826 Component_Definition =>
4827 Make_Component_Definition (Loc,
4828 Aliased_Present => False,
4829 Subtype_Indication => New_Reference_To (Controller_Type, Loc)));
4831 if Null_Present (Comp_List)
4832 or else Is_Empty_List (Component_Items (Comp_List))
4833 then
4834 Set_Component_Items (Comp_List, New_List (Comp_Decl));
4835 Set_Null_Present (Comp_List, False);
4837 else
4838 -- The controller cannot be placed before the _Parent field since
4839 -- gigi lays out field in order and _parent must be first to preserve
4840 -- the polymorphism of tagged types.
4842 First_Comp := First (Component_Items (Comp_List));
4844 if not Is_Tagged_Type (T) then
4845 Insert_Before (First_Comp, Comp_Decl);
4847 -- if T is a tagged type, place controller declaration after parent
4848 -- field and after eventual tags of interface types.
4850 else
4851 while Present (First_Comp)
4852 and then
4853 (Chars (Defining_Identifier (First_Comp)) = Name_uParent
4854 or else Is_Tag (Defining_Identifier (First_Comp))
4856 -- Ada 2005 (AI-251): The following condition covers secondary
4857 -- tags but also the adjacent component containing the offset
4858 -- to the base of the object (component generated if the parent
4859 -- has discriminants --- see Add_Interface_Tag_Components).
4860 -- This is required to avoid the addition of the controller
4861 -- between the secondary tag and its adjacent component.
4863 or else Present
4864 (Related_Type
4865 (Defining_Identifier (First_Comp))))
4866 loop
4867 Next (First_Comp);
4868 end loop;
4870 -- An empty tagged extension might consist only of the parent
4871 -- component. Otherwise insert the controller before the first
4872 -- component that is neither parent nor tag.
4874 if Present (First_Comp) then
4875 Insert_Before (First_Comp, Comp_Decl);
4876 else
4877 Append (Comp_Decl, Component_Items (Comp_List));
4878 end if;
4879 end if;
4880 end if;
4882 Push_Scope (T);
4883 Analyze (Comp_Decl);
4884 Set_Ekind (Ent, E_Component);
4885 Init_Component_Location (Ent);
4887 -- Move the _controller entity ahead in the list of internal entities
4888 -- of the enclosing record so that it is selected instead of a
4889 -- potentially inherited one.
4891 declare
4892 E : constant Entity_Id := Last_Entity (T);
4893 Comp : Entity_Id;
4895 begin
4896 pragma Assert (Chars (E) = Name_uController);
4898 Set_Next_Entity (E, First_Entity (T));
4899 Set_First_Entity (T, E);
4901 Comp := Next_Entity (E);
4902 while Next_Entity (Comp) /= E loop
4903 Next_Entity (Comp);
4904 end loop;
4906 Set_Next_Entity (Comp, Empty);
4907 Set_Last_Entity (T, Comp);
4908 end;
4910 End_Scope;
4912 exception
4913 when RE_Not_Available =>
4914 return;
4915 end Expand_Record_Controller;
4917 ------------------------
4918 -- Expand_Tagged_Root --
4919 ------------------------
4921 procedure Expand_Tagged_Root (T : Entity_Id) is
4922 Def : constant Node_Id := Type_Definition (Parent (T));
4923 Comp_List : Node_Id;
4924 Comp_Decl : Node_Id;
4925 Sloc_N : Source_Ptr;
4927 begin
4928 if Null_Present (Def) then
4929 Set_Component_List (Def,
4930 Make_Component_List (Sloc (Def),
4931 Component_Items => Empty_List,
4932 Variant_Part => Empty,
4933 Null_Present => True));
4934 end if;
4936 Comp_List := Component_List (Def);
4938 if Null_Present (Comp_List)
4939 or else Is_Empty_List (Component_Items (Comp_List))
4940 then
4941 Sloc_N := Sloc (Comp_List);
4942 else
4943 Sloc_N := Sloc (First (Component_Items (Comp_List)));
4944 end if;
4946 Comp_Decl :=
4947 Make_Component_Declaration (Sloc_N,
4948 Defining_Identifier => First_Tag_Component (T),
4949 Component_Definition =>
4950 Make_Component_Definition (Sloc_N,
4951 Aliased_Present => False,
4952 Subtype_Indication => New_Reference_To (RTE (RE_Tag), Sloc_N)));
4954 if Null_Present (Comp_List)
4955 or else Is_Empty_List (Component_Items (Comp_List))
4956 then
4957 Set_Component_Items (Comp_List, New_List (Comp_Decl));
4958 Set_Null_Present (Comp_List, False);
4960 else
4961 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
4962 end if;
4964 -- We don't Analyze the whole expansion because the tag component has
4965 -- already been analyzed previously. Here we just insure that the tree
4966 -- is coherent with the semantic decoration
4968 Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
4970 exception
4971 when RE_Not_Available =>
4972 return;
4973 end Expand_Tagged_Root;
4975 ----------------------
4976 -- Clean_Task_Names --
4977 ----------------------
4979 procedure Clean_Task_Names
4980 (Typ : Entity_Id;
4981 Proc_Id : Entity_Id)
4983 begin
4984 if Has_Task (Typ)
4985 and then not Restriction_Active (No_Implicit_Heap_Allocations)
4986 and then not Global_Discard_Names
4987 and then VM_Target = No_VM
4988 then
4989 Set_Uses_Sec_Stack (Proc_Id);
4990 end if;
4991 end Clean_Task_Names;
4993 -----------------------
4994 -- Freeze_Array_Type --
4995 -----------------------
4997 procedure Freeze_Array_Type (N : Node_Id) is
4998 Typ : constant Entity_Id := Entity (N);
4999 Comp_Typ : constant Entity_Id := Component_Type (Typ);
5000 Base : constant Entity_Id := Base_Type (Typ);
5002 begin
5003 if not Is_Bit_Packed_Array (Typ) then
5005 -- If the component contains tasks, so does the array type. This may
5006 -- not be indicated in the array type because the component may have
5007 -- been a private type at the point of definition. Same if component
5008 -- type is controlled.
5010 Set_Has_Task (Base, Has_Task (Comp_Typ));
5011 Set_Has_Controlled_Component (Base,
5012 Has_Controlled_Component (Comp_Typ)
5013 or else Is_Controlled (Comp_Typ));
5015 if No (Init_Proc (Base)) then
5017 -- If this is an anonymous array created for a declaration with
5018 -- an initial value, its init_proc will never be called. The
5019 -- initial value itself may have been expanded into assignments,
5020 -- in which case the object declaration is carries the
5021 -- No_Initialization flag.
5023 if Is_Itype (Base)
5024 and then Nkind (Associated_Node_For_Itype (Base)) =
5025 N_Object_Declaration
5026 and then (Present (Expression (Associated_Node_For_Itype (Base)))
5027 or else
5028 No_Initialization (Associated_Node_For_Itype (Base)))
5029 then
5030 null;
5032 -- We do not need an init proc for string or wide [wide] string,
5033 -- since the only time these need initialization in normalize or
5034 -- initialize scalars mode, and these types are treated specially
5035 -- and do not need initialization procedures.
5037 elsif Root_Type (Base) = Standard_String
5038 or else Root_Type (Base) = Standard_Wide_String
5039 or else Root_Type (Base) = Standard_Wide_Wide_String
5040 then
5041 null;
5043 -- Otherwise we have to build an init proc for the subtype
5045 else
5046 Build_Array_Init_Proc (Base, N);
5047 end if;
5048 end if;
5050 if Typ = Base then
5051 if Has_Controlled_Component (Base) then
5052 Build_Controlling_Procs (Base);
5054 if not Is_Limited_Type (Comp_Typ)
5055 and then Number_Dimensions (Typ) = 1
5056 then
5057 Build_Slice_Assignment (Typ);
5058 end if;
5060 elsif Ekind (Comp_Typ) = E_Anonymous_Access_Type
5061 and then Needs_Finalization (Directly_Designated_Type (Comp_Typ))
5062 then
5063 Set_Associated_Final_Chain (Comp_Typ, Add_Final_Chain (Typ));
5064 end if;
5065 end if;
5067 -- For packed case, default initialization, except if the component type
5068 -- is itself a packed structure with an initialization procedure, or
5069 -- initialize/normalize scalars active, and we have a base type, or the
5070 -- type is public, because in that case a client might specify
5071 -- Normalize_Scalars and there better be a public Init_Proc for it.
5073 elsif (Present (Init_Proc (Component_Type (Base)))
5074 and then No (Base_Init_Proc (Base)))
5075 or else (Init_Or_Norm_Scalars and then Base = Typ)
5076 or else Is_Public (Typ)
5077 then
5078 Build_Array_Init_Proc (Base, N);
5079 end if;
5080 end Freeze_Array_Type;
5082 -----------------------------
5083 -- Freeze_Enumeration_Type --
5084 -----------------------------
5086 procedure Freeze_Enumeration_Type (N : Node_Id) is
5087 Typ : constant Entity_Id := Entity (N);
5088 Loc : constant Source_Ptr := Sloc (Typ);
5089 Ent : Entity_Id;
5090 Lst : List_Id;
5091 Num : Nat;
5092 Arr : Entity_Id;
5093 Fent : Entity_Id;
5094 Ityp : Entity_Id;
5095 Is_Contiguous : Boolean;
5096 Pos_Expr : Node_Id;
5097 Last_Repval : Uint;
5099 Func : Entity_Id;
5100 pragma Warnings (Off, Func);
5102 begin
5103 -- Various optimizations possible if given representation is contiguous
5105 Is_Contiguous := True;
5107 Ent := First_Literal (Typ);
5108 Last_Repval := Enumeration_Rep (Ent);
5110 Next_Literal (Ent);
5111 while Present (Ent) loop
5112 if Enumeration_Rep (Ent) - Last_Repval /= 1 then
5113 Is_Contiguous := False;
5114 exit;
5115 else
5116 Last_Repval := Enumeration_Rep (Ent);
5117 end if;
5119 Next_Literal (Ent);
5120 end loop;
5122 if Is_Contiguous then
5123 Set_Has_Contiguous_Rep (Typ);
5124 Ent := First_Literal (Typ);
5125 Num := 1;
5126 Lst := New_List (New_Reference_To (Ent, Sloc (Ent)));
5128 else
5129 -- Build list of literal references
5131 Lst := New_List;
5132 Num := 0;
5134 Ent := First_Literal (Typ);
5135 while Present (Ent) loop
5136 Append_To (Lst, New_Reference_To (Ent, Sloc (Ent)));
5137 Num := Num + 1;
5138 Next_Literal (Ent);
5139 end loop;
5140 end if;
5142 -- Now build an array declaration
5144 -- typA : array (Natural range 0 .. num - 1) of ctype :=
5145 -- (v, v, v, v, v, ....)
5147 -- where ctype is the corresponding integer type. If the representation
5148 -- is contiguous, we only keep the first literal, which provides the
5149 -- offset for Pos_To_Rep computations.
5151 Arr :=
5152 Make_Defining_Identifier (Loc,
5153 Chars => New_External_Name (Chars (Typ), 'A'));
5155 Append_Freeze_Action (Typ,
5156 Make_Object_Declaration (Loc,
5157 Defining_Identifier => Arr,
5158 Constant_Present => True,
5160 Object_Definition =>
5161 Make_Constrained_Array_Definition (Loc,
5162 Discrete_Subtype_Definitions => New_List (
5163 Make_Subtype_Indication (Loc,
5164 Subtype_Mark => New_Reference_To (Standard_Natural, Loc),
5165 Constraint =>
5166 Make_Range_Constraint (Loc,
5167 Range_Expression =>
5168 Make_Range (Loc,
5169 Low_Bound =>
5170 Make_Integer_Literal (Loc, 0),
5171 High_Bound =>
5172 Make_Integer_Literal (Loc, Num - 1))))),
5174 Component_Definition =>
5175 Make_Component_Definition (Loc,
5176 Aliased_Present => False,
5177 Subtype_Indication => New_Reference_To (Typ, Loc))),
5179 Expression =>
5180 Make_Aggregate (Loc,
5181 Expressions => Lst)));
5183 Set_Enum_Pos_To_Rep (Typ, Arr);
5185 -- Now we build the function that converts representation values to
5186 -- position values. This function has the form:
5188 -- function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
5189 -- begin
5190 -- case ityp!(A) is
5191 -- when enum-lit'Enum_Rep => return posval;
5192 -- when enum-lit'Enum_Rep => return posval;
5193 -- ...
5194 -- when others =>
5195 -- [raise Constraint_Error when F "invalid data"]
5196 -- return -1;
5197 -- end case;
5198 -- end;
5200 -- Note: the F parameter determines whether the others case (no valid
5201 -- representation) raises Constraint_Error or returns a unique value
5202 -- of minus one. The latter case is used, e.g. in 'Valid code.
5204 -- Note: the reason we use Enum_Rep values in the case here is to avoid
5205 -- the code generator making inappropriate assumptions about the range
5206 -- of the values in the case where the value is invalid. ityp is a
5207 -- signed or unsigned integer type of appropriate width.
5209 -- Note: if exceptions are not supported, then we suppress the raise
5210 -- and return -1 unconditionally (this is an erroneous program in any
5211 -- case and there is no obligation to raise Constraint_Error here!) We
5212 -- also do this if pragma Restrictions (No_Exceptions) is active.
5214 -- Is this right??? What about No_Exception_Propagation???
5216 -- Representations are signed
5218 if Enumeration_Rep (First_Literal (Typ)) < 0 then
5220 -- The underlying type is signed. Reset the Is_Unsigned_Type
5221 -- explicitly, because it might have been inherited from
5222 -- parent type.
5224 Set_Is_Unsigned_Type (Typ, False);
5226 if Esize (Typ) <= Standard_Integer_Size then
5227 Ityp := Standard_Integer;
5228 else
5229 Ityp := Universal_Integer;
5230 end if;
5232 -- Representations are unsigned
5234 else
5235 if Esize (Typ) <= Standard_Integer_Size then
5236 Ityp := RTE (RE_Unsigned);
5237 else
5238 Ityp := RTE (RE_Long_Long_Unsigned);
5239 end if;
5240 end if;
5242 -- The body of the function is a case statement. First collect case
5243 -- alternatives, or optimize the contiguous case.
5245 Lst := New_List;
5247 -- If representation is contiguous, Pos is computed by subtracting
5248 -- the representation of the first literal.
5250 if Is_Contiguous then
5251 Ent := First_Literal (Typ);
5253 if Enumeration_Rep (Ent) = Last_Repval then
5255 -- Another special case: for a single literal, Pos is zero
5257 Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
5259 else
5260 Pos_Expr :=
5261 Convert_To (Standard_Integer,
5262 Make_Op_Subtract (Loc,
5263 Left_Opnd =>
5264 Unchecked_Convert_To (Ityp,
5265 Make_Identifier (Loc, Name_uA)),
5266 Right_Opnd =>
5267 Make_Integer_Literal (Loc,
5268 Intval =>
5269 Enumeration_Rep (First_Literal (Typ)))));
5270 end if;
5272 Append_To (Lst,
5273 Make_Case_Statement_Alternative (Loc,
5274 Discrete_Choices => New_List (
5275 Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
5276 Low_Bound =>
5277 Make_Integer_Literal (Loc,
5278 Intval => Enumeration_Rep (Ent)),
5279 High_Bound =>
5280 Make_Integer_Literal (Loc, Intval => Last_Repval))),
5282 Statements => New_List (
5283 Make_Simple_Return_Statement (Loc,
5284 Expression => Pos_Expr))));
5286 else
5287 Ent := First_Literal (Typ);
5288 while Present (Ent) loop
5289 Append_To (Lst,
5290 Make_Case_Statement_Alternative (Loc,
5291 Discrete_Choices => New_List (
5292 Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
5293 Intval => Enumeration_Rep (Ent))),
5295 Statements => New_List (
5296 Make_Simple_Return_Statement (Loc,
5297 Expression =>
5298 Make_Integer_Literal (Loc,
5299 Intval => Enumeration_Pos (Ent))))));
5301 Next_Literal (Ent);
5302 end loop;
5303 end if;
5305 -- In normal mode, add the others clause with the test
5307 if not No_Exception_Handlers_Set then
5308 Append_To (Lst,
5309 Make_Case_Statement_Alternative (Loc,
5310 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
5311 Statements => New_List (
5312 Make_Raise_Constraint_Error (Loc,
5313 Condition => Make_Identifier (Loc, Name_uF),
5314 Reason => CE_Invalid_Data),
5315 Make_Simple_Return_Statement (Loc,
5316 Expression =>
5317 Make_Integer_Literal (Loc, -1)))));
5319 -- If either of the restrictions No_Exceptions_Handlers/Propagation is
5320 -- active then return -1 (we cannot usefully raise Constraint_Error in
5321 -- this case). See description above for further details.
5323 else
5324 Append_To (Lst,
5325 Make_Case_Statement_Alternative (Loc,
5326 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
5327 Statements => New_List (
5328 Make_Simple_Return_Statement (Loc,
5329 Expression =>
5330 Make_Integer_Literal (Loc, -1)))));
5331 end if;
5333 -- Now we can build the function body
5335 Fent :=
5336 Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
5338 Func :=
5339 Make_Subprogram_Body (Loc,
5340 Specification =>
5341 Make_Function_Specification (Loc,
5342 Defining_Unit_Name => Fent,
5343 Parameter_Specifications => New_List (
5344 Make_Parameter_Specification (Loc,
5345 Defining_Identifier =>
5346 Make_Defining_Identifier (Loc, Name_uA),
5347 Parameter_Type => New_Reference_To (Typ, Loc)),
5348 Make_Parameter_Specification (Loc,
5349 Defining_Identifier =>
5350 Make_Defining_Identifier (Loc, Name_uF),
5351 Parameter_Type => New_Reference_To (Standard_Boolean, Loc))),
5353 Result_Definition => New_Reference_To (Standard_Integer, Loc)),
5355 Declarations => Empty_List,
5357 Handled_Statement_Sequence =>
5358 Make_Handled_Sequence_Of_Statements (Loc,
5359 Statements => New_List (
5360 Make_Case_Statement (Loc,
5361 Expression =>
5362 Unchecked_Convert_To (Ityp,
5363 Make_Identifier (Loc, Name_uA)),
5364 Alternatives => Lst))));
5366 Set_TSS (Typ, Fent);
5367 Set_Is_Pure (Fent);
5369 if not Debug_Generated_Code then
5370 Set_Debug_Info_Off (Fent);
5371 end if;
5373 exception
5374 when RE_Not_Available =>
5375 return;
5376 end Freeze_Enumeration_Type;
5378 ------------------------
5379 -- Freeze_Record_Type --
5380 ------------------------
5382 procedure Freeze_Record_Type (N : Node_Id) is
5384 procedure Add_Internal_Interface_Entities (Tagged_Type : Entity_Id);
5385 -- Add to the list of primitives of Tagged_Types the internal entities
5386 -- associated with interface primitives that are located in secondary
5387 -- dispatch tables.
5389 -------------------------------------
5390 -- Add_Internal_Interface_Entities --
5391 -------------------------------------
5393 procedure Add_Internal_Interface_Entities (Tagged_Type : Entity_Id) is
5394 Elmt : Elmt_Id;
5395 Iface : Entity_Id;
5396 Iface_Elmt : Elmt_Id;
5397 Iface_Prim : Entity_Id;
5398 Ifaces_List : Elist_Id;
5399 New_Subp : Entity_Id := Empty;
5400 Prim : Entity_Id;
5402 begin
5403 pragma Assert (Ada_Version >= Ada_05
5404 and then Is_Record_Type (Tagged_Type)
5405 and then Is_Tagged_Type (Tagged_Type)
5406 and then Has_Interfaces (Tagged_Type)
5407 and then not Is_Interface (Tagged_Type));
5409 Collect_Interfaces (Tagged_Type, Ifaces_List);
5411 Iface_Elmt := First_Elmt (Ifaces_List);
5412 while Present (Iface_Elmt) loop
5413 Iface := Node (Iface_Elmt);
5415 -- Exclude from this processing interfaces that are parents
5416 -- of Tagged_Type because their primitives are located in the
5417 -- primary dispatch table (and hence no auxiliary internal
5418 -- entities are required to handle secondary dispatch tables
5419 -- in such case).
5421 if not Is_Ancestor (Iface, Tagged_Type) then
5422 Elmt := First_Elmt (Primitive_Operations (Iface));
5423 while Present (Elmt) loop
5424 Iface_Prim := Node (Elmt);
5426 if not Is_Predefined_Dispatching_Operation (Iface_Prim) then
5427 Prim :=
5428 Find_Primitive_Covering_Interface
5429 (Tagged_Type => Tagged_Type,
5430 Iface_Prim => Iface_Prim);
5432 pragma Assert (Present (Prim));
5434 Derive_Subprogram
5435 (New_Subp => New_Subp,
5436 Parent_Subp => Iface_Prim,
5437 Derived_Type => Tagged_Type,
5438 Parent_Type => Iface);
5440 -- Ada 2005 (AI-251): Decorate internal entity Iface_Subp
5441 -- associated with interface types. These entities are
5442 -- only registered in the list of primitives of its
5443 -- corresponding tagged type because they are only used
5444 -- to fill the contents of the secondary dispatch tables.
5445 -- Therefore they are removed from the homonym chains.
5447 Set_Is_Hidden (New_Subp);
5448 Set_Is_Internal (New_Subp);
5449 Set_Alias (New_Subp, Prim);
5450 Set_Is_Abstract_Subprogram (New_Subp,
5451 Is_Abstract_Subprogram (Prim));
5452 Set_Interface_Alias (New_Subp, Iface_Prim);
5454 -- Internal entities associated with interface types are
5455 -- only registered in the list of primitives of the
5456 -- tagged type. They are only used to fill the contents
5457 -- of the secondary dispatch tables. Therefore they are
5458 -- not needed in the homonym chains.
5460 Remove_Homonym (New_Subp);
5462 -- Hidden entities associated with interfaces must have
5463 -- set the Has_Delay_Freeze attribute to ensure that, in
5464 -- case of locally defined tagged types (or compiling
5465 -- with static dispatch tables generation disabled) the
5466 -- corresponding entry of the secondary dispatch table is
5467 -- filled when such entity is frozen.
5469 Set_Has_Delayed_Freeze (New_Subp);
5470 end if;
5472 Next_Elmt (Elmt);
5473 end loop;
5474 end if;
5476 Next_Elmt (Iface_Elmt);
5477 end loop;
5478 end Add_Internal_Interface_Entities;
5480 -- Local variables
5482 Def_Id : constant Node_Id := Entity (N);
5483 Type_Decl : constant Node_Id := Parent (Def_Id);
5484 Comp : Entity_Id;
5485 Comp_Typ : Entity_Id;
5486 Has_Static_DT : Boolean := False;
5487 Predef_List : List_Id;
5489 Flist : Entity_Id := Empty;
5490 -- Finalization list allocated for the case of a type with anonymous
5491 -- access components whose designated type is potentially controlled.
5493 Renamed_Eq : Node_Id := Empty;
5494 -- Defining unit name for the predefined equality function in the case
5495 -- where the type has a primitive operation that is a renaming of
5496 -- predefined equality (but only if there is also an overriding
5497 -- user-defined equality function). Used to pass this entity from
5498 -- Make_Predefined_Primitive_Specs to Predefined_Primitive_Bodies.
5500 Wrapper_Decl_List : List_Id := No_List;
5501 Wrapper_Body_List : List_Id := No_List;
5502 Null_Proc_Decl_List : List_Id := No_List;
5504 -- Start of processing for Freeze_Record_Type
5506 begin
5507 -- Build discriminant checking functions if not a derived type (for
5508 -- derived types that are not tagged types, always use the discriminant
5509 -- checking functions of the parent type). However, for untagged types
5510 -- the derivation may have taken place before the parent was frozen, so
5511 -- we copy explicitly the discriminant checking functions from the
5512 -- parent into the components of the derived type.
5514 if not Is_Derived_Type (Def_Id)
5515 or else Has_New_Non_Standard_Rep (Def_Id)
5516 or else Is_Tagged_Type (Def_Id)
5517 then
5518 Build_Discr_Checking_Funcs (Type_Decl);
5520 elsif Is_Derived_Type (Def_Id)
5521 and then not Is_Tagged_Type (Def_Id)
5523 -- If we have a derived Unchecked_Union, we do not inherit the
5524 -- discriminant checking functions from the parent type since the
5525 -- discriminants are non existent.
5527 and then not Is_Unchecked_Union (Def_Id)
5528 and then Has_Discriminants (Def_Id)
5529 then
5530 declare
5531 Old_Comp : Entity_Id;
5533 begin
5534 Old_Comp :=
5535 First_Component (Base_Type (Underlying_Type (Etype (Def_Id))));
5536 Comp := First_Component (Def_Id);
5537 while Present (Comp) loop
5538 if Ekind (Comp) = E_Component
5539 and then Chars (Comp) = Chars (Old_Comp)
5540 then
5541 Set_Discriminant_Checking_Func (Comp,
5542 Discriminant_Checking_Func (Old_Comp));
5543 end if;
5545 Next_Component (Old_Comp);
5546 Next_Component (Comp);
5547 end loop;
5548 end;
5549 end if;
5551 if Is_Derived_Type (Def_Id)
5552 and then Is_Limited_Type (Def_Id)
5553 and then Is_Tagged_Type (Def_Id)
5554 then
5555 Check_Stream_Attributes (Def_Id);
5556 end if;
5558 -- Update task and controlled component flags, because some of the
5559 -- component types may have been private at the point of the record
5560 -- declaration.
5562 Comp := First_Component (Def_Id);
5564 while Present (Comp) loop
5565 Comp_Typ := Etype (Comp);
5567 if Has_Task (Comp_Typ) then
5568 Set_Has_Task (Def_Id);
5570 elsif Has_Controlled_Component (Comp_Typ)
5571 or else (Chars (Comp) /= Name_uParent
5572 and then Is_Controlled (Comp_Typ))
5573 then
5574 Set_Has_Controlled_Component (Def_Id);
5576 elsif Ekind (Comp_Typ) = E_Anonymous_Access_Type
5577 and then Needs_Finalization (Directly_Designated_Type (Comp_Typ))
5578 then
5579 if No (Flist) then
5580 Flist := Add_Final_Chain (Def_Id);
5581 end if;
5583 Set_Associated_Final_Chain (Comp_Typ, Flist);
5584 end if;
5586 Next_Component (Comp);
5587 end loop;
5589 -- Creation of the Dispatch Table. Note that a Dispatch Table is built
5590 -- for regular tagged types as well as for Ada types deriving from a C++
5591 -- Class, but not for tagged types directly corresponding to C++ classes
5592 -- In the later case we assume that it is created in the C++ side and we
5593 -- just use it.
5595 if Is_Tagged_Type (Def_Id) then
5596 Has_Static_DT :=
5597 Static_Dispatch_Tables
5598 and then Is_Library_Level_Tagged_Type (Def_Id);
5600 -- Add the _Tag component
5602 if Underlying_Type (Etype (Def_Id)) = Def_Id then
5603 Expand_Tagged_Root (Def_Id);
5604 end if;
5606 if Is_CPP_Class (Def_Id) then
5607 Set_All_DT_Position (Def_Id);
5608 Set_Default_Constructor (Def_Id);
5610 -- Create the tag entities with a minimum decoration
5612 if VM_Target = No_VM then
5613 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
5614 end if;
5616 else
5617 if not Has_Static_DT then
5619 -- Usually inherited primitives are not delayed but the first
5620 -- Ada extension of a CPP_Class is an exception since the
5621 -- address of the inherited subprogram has to be inserted in
5622 -- the new Ada Dispatch Table and this is a freezing action.
5624 -- Similarly, if this is an inherited operation whose parent is
5625 -- not frozen yet, it is not in the DT of the parent, and we
5626 -- generate an explicit freeze node for the inherited operation
5627 -- so that it is properly inserted in the DT of the current
5628 -- type.
5630 declare
5631 Elmt : Elmt_Id := First_Elmt (Primitive_Operations (Def_Id));
5632 Subp : Entity_Id;
5634 begin
5635 while Present (Elmt) loop
5636 Subp := Node (Elmt);
5638 if Present (Alias (Subp)) then
5639 if Is_CPP_Class (Etype (Def_Id)) then
5640 Set_Has_Delayed_Freeze (Subp);
5642 elsif Has_Delayed_Freeze (Alias (Subp))
5643 and then not Is_Frozen (Alias (Subp))
5644 then
5645 Set_Is_Frozen (Subp, False);
5646 Set_Has_Delayed_Freeze (Subp);
5647 end if;
5648 end if;
5650 Next_Elmt (Elmt);
5651 end loop;
5652 end;
5653 end if;
5655 -- Unfreeze momentarily the type to add the predefined primitives
5656 -- operations. The reason we unfreeze is so that these predefined
5657 -- operations will indeed end up as primitive operations (which
5658 -- must be before the freeze point).
5660 Set_Is_Frozen (Def_Id, False);
5662 -- Do not add the spec of predefined primitives in case of
5663 -- CPP tagged type derivations that have convention CPP.
5665 if Is_CPP_Class (Root_Type (Def_Id))
5666 and then Convention (Def_Id) = Convention_CPP
5667 then
5668 null;
5670 -- Do not add the spec of the predefined primitives if we are
5671 -- compiling under restriction No_Dispatching_Calls
5673 elsif not Restriction_Active (No_Dispatching_Calls) then
5674 Make_Predefined_Primitive_Specs
5675 (Def_Id, Predef_List, Renamed_Eq);
5676 Insert_List_Before_And_Analyze (N, Predef_List);
5677 end if;
5679 -- Ada 2005 (AI-391): For a nonabstract null extension, create
5680 -- wrapper functions for each nonoverridden inherited function
5681 -- with a controlling result of the type. The wrapper for such
5682 -- a function returns an extension aggregate that invokes the
5683 -- the parent function.
5685 if Ada_Version >= Ada_05
5686 and then not Is_Abstract_Type (Def_Id)
5687 and then Is_Null_Extension (Def_Id)
5688 then
5689 Make_Controlling_Function_Wrappers
5690 (Def_Id, Wrapper_Decl_List, Wrapper_Body_List);
5691 Insert_List_Before_And_Analyze (N, Wrapper_Decl_List);
5692 end if;
5694 -- Ada 2005 (AI-251): For a nonabstract type extension, build
5695 -- null procedure declarations for each set of homographic null
5696 -- procedures that are inherited from interface types but not
5697 -- overridden. This is done to ensure that the dispatch table
5698 -- entry associated with such null primitives are properly filled.
5700 if Ada_Version >= Ada_05
5701 and then Etype (Def_Id) /= Def_Id
5702 and then not Is_Abstract_Type (Def_Id)
5703 then
5704 Make_Null_Procedure_Specs (Def_Id, Null_Proc_Decl_List);
5705 Insert_Actions (N, Null_Proc_Decl_List);
5706 end if;
5708 -- Ada 2005 (AI-251): Add internal entities associated with
5709 -- secondary dispatch tables to the list of primitives of tagged
5710 -- types that are not interfaces
5712 if Ada_Version >= Ada_05
5713 and then not Is_Interface (Def_Id)
5714 and then Has_Interfaces (Def_Id)
5715 then
5716 Add_Internal_Interface_Entities (Def_Id);
5717 end if;
5719 Set_Is_Frozen (Def_Id);
5720 Set_All_DT_Position (Def_Id);
5722 -- Add the controlled component before the freezing actions
5723 -- referenced in those actions.
5725 if Has_New_Controlled_Component (Def_Id) then
5726 Expand_Record_Controller (Def_Id);
5727 end if;
5729 -- Create and decorate the tags. Suppress their creation when
5730 -- VM_Target because the dispatching mechanism is handled
5731 -- internally by the VMs.
5733 if VM_Target = No_VM then
5734 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
5736 -- Generate dispatch table of locally defined tagged type.
5737 -- Dispatch tables of library level tagged types are built
5738 -- later (see Analyze_Declarations).
5740 if VM_Target = No_VM
5741 and then not Has_Static_DT
5742 then
5743 Append_Freeze_Actions (Def_Id, Make_DT (Def_Id));
5744 end if;
5745 end if;
5747 -- If the type has unknown discriminants, propagate dispatching
5748 -- information to its underlying record view, which does not get
5749 -- its own dispatch table.
5751 if Is_Derived_Type (Def_Id)
5752 and then Has_Unknown_Discriminants (Def_Id)
5753 and then Present (Underlying_Record_View (Def_Id))
5754 then
5755 declare
5756 Rep : constant Entity_Id :=
5757 Underlying_Record_View (Def_Id);
5758 begin
5759 Set_Access_Disp_Table
5760 (Rep, Access_Disp_Table (Def_Id));
5761 Set_Dispatch_Table_Wrappers
5762 (Rep, Dispatch_Table_Wrappers (Def_Id));
5763 Set_Primitive_Operations
5764 (Rep, Primitive_Operations (Def_Id));
5765 end;
5766 end if;
5768 -- Make sure that the primitives Initialize, Adjust and Finalize
5769 -- are Frozen before other TSS subprograms. We don't want them
5770 -- Frozen inside.
5772 if Is_Controlled (Def_Id) then
5773 if not Is_Limited_Type (Def_Id) then
5774 Append_Freeze_Actions (Def_Id,
5775 Freeze_Entity
5776 (Find_Prim_Op (Def_Id, Name_Adjust), Sloc (Def_Id)));
5777 end if;
5779 Append_Freeze_Actions (Def_Id,
5780 Freeze_Entity
5781 (Find_Prim_Op (Def_Id, Name_Initialize), Sloc (Def_Id)));
5783 Append_Freeze_Actions (Def_Id,
5784 Freeze_Entity
5785 (Find_Prim_Op (Def_Id, Name_Finalize), Sloc (Def_Id)));
5786 end if;
5788 -- Freeze rest of primitive operations. There is no need to handle
5789 -- the predefined primitives if we are compiling under restriction
5790 -- No_Dispatching_Calls
5792 if not Restriction_Active (No_Dispatching_Calls) then
5793 Append_Freeze_Actions
5794 (Def_Id, Predefined_Primitive_Freeze (Def_Id));
5795 end if;
5796 end if;
5798 -- In the non-tagged case, an equality function is provided only for
5799 -- variant records (that are not unchecked unions).
5801 elsif Has_Discriminants (Def_Id)
5802 and then not Is_Limited_Type (Def_Id)
5803 then
5804 declare
5805 Comps : constant Node_Id :=
5806 Component_List (Type_Definition (Type_Decl));
5808 begin
5809 if Present (Comps)
5810 and then Present (Variant_Part (Comps))
5811 then
5812 Build_Variant_Record_Equality (Def_Id);
5813 end if;
5814 end;
5815 end if;
5817 -- Before building the record initialization procedure, if we are
5818 -- dealing with a concurrent record value type, then we must go through
5819 -- the discriminants, exchanging discriminals between the concurrent
5820 -- type and the concurrent record value type. See the section "Handling
5821 -- of Discriminants" in the Einfo spec for details.
5823 if Is_Concurrent_Record_Type (Def_Id)
5824 and then Has_Discriminants (Def_Id)
5825 then
5826 declare
5827 Ctyp : constant Entity_Id :=
5828 Corresponding_Concurrent_Type (Def_Id);
5829 Conc_Discr : Entity_Id;
5830 Rec_Discr : Entity_Id;
5831 Temp : Entity_Id;
5833 begin
5834 Conc_Discr := First_Discriminant (Ctyp);
5835 Rec_Discr := First_Discriminant (Def_Id);
5837 while Present (Conc_Discr) loop
5838 Temp := Discriminal (Conc_Discr);
5839 Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
5840 Set_Discriminal (Rec_Discr, Temp);
5842 Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
5843 Set_Discriminal_Link (Discriminal (Rec_Discr), Rec_Discr);
5845 Next_Discriminant (Conc_Discr);
5846 Next_Discriminant (Rec_Discr);
5847 end loop;
5848 end;
5849 end if;
5851 if Has_Controlled_Component (Def_Id) then
5852 if No (Controller_Component (Def_Id)) then
5853 Expand_Record_Controller (Def_Id);
5854 end if;
5856 Build_Controlling_Procs (Def_Id);
5857 end if;
5859 Adjust_Discriminants (Def_Id);
5861 if VM_Target = No_VM or else not Is_Interface (Def_Id) then
5863 -- Do not need init for interfaces on e.g. CIL since they're
5864 -- abstract. Helps operation of peverify (the PE Verify tool).
5866 Build_Record_Init_Proc (Type_Decl, Def_Id);
5867 end if;
5869 -- For tagged type that are not interfaces, build bodies of primitive
5870 -- operations. Note that we do this after building the record
5871 -- initialization procedure, since the primitive operations may need
5872 -- the initialization routine. There is no need to add predefined
5873 -- primitives of interfaces because all their predefined primitives
5874 -- are abstract.
5876 if Is_Tagged_Type (Def_Id)
5877 and then not Is_Interface (Def_Id)
5878 then
5879 -- Do not add the body of predefined primitives in case of
5880 -- CPP tagged type derivations that have convention CPP.
5882 if Is_CPP_Class (Root_Type (Def_Id))
5883 and then Convention (Def_Id) = Convention_CPP
5884 then
5885 null;
5887 -- Do not add the body of the predefined primitives if we are
5888 -- compiling under restriction No_Dispatching_Calls or if we are
5889 -- compiling a CPP tagged type.
5891 elsif not Restriction_Active (No_Dispatching_Calls) then
5892 Predef_List := Predefined_Primitive_Bodies (Def_Id, Renamed_Eq);
5893 Append_Freeze_Actions (Def_Id, Predef_List);
5894 end if;
5896 -- Ada 2005 (AI-391): If any wrappers were created for nonoverridden
5897 -- inherited functions, then add their bodies to the freeze actions.
5899 if Present (Wrapper_Body_List) then
5900 Append_Freeze_Actions (Def_Id, Wrapper_Body_List);
5901 end if;
5902 end if;
5903 end Freeze_Record_Type;
5905 ------------------------------
5906 -- Freeze_Stream_Operations --
5907 ------------------------------
5909 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
5910 Names : constant array (1 .. 4) of TSS_Name_Type :=
5911 (TSS_Stream_Input,
5912 TSS_Stream_Output,
5913 TSS_Stream_Read,
5914 TSS_Stream_Write);
5915 Stream_Op : Entity_Id;
5917 begin
5918 -- Primitive operations of tagged types are frozen when the dispatch
5919 -- table is constructed.
5921 if not Comes_From_Source (Typ)
5922 or else Is_Tagged_Type (Typ)
5923 then
5924 return;
5925 end if;
5927 for J in Names'Range loop
5928 Stream_Op := TSS (Typ, Names (J));
5930 if Present (Stream_Op)
5931 and then Is_Subprogram (Stream_Op)
5932 and then Nkind (Unit_Declaration_Node (Stream_Op)) =
5933 N_Subprogram_Declaration
5934 and then not Is_Frozen (Stream_Op)
5935 then
5936 Append_Freeze_Actions
5937 (Typ, Freeze_Entity (Stream_Op, Sloc (N)));
5938 end if;
5939 end loop;
5940 end Freeze_Stream_Operations;
5942 -----------------
5943 -- Freeze_Type --
5944 -----------------
5946 -- Full type declarations are expanded at the point at which the type is
5947 -- frozen. The formal N is the Freeze_Node for the type. Any statements or
5948 -- declarations generated by the freezing (e.g. the procedure generated
5949 -- for initialization) are chained in the Actions field list of the freeze
5950 -- node using Append_Freeze_Actions.
5952 function Freeze_Type (N : Node_Id) return Boolean is
5953 Def_Id : constant Entity_Id := Entity (N);
5954 RACW_Seen : Boolean := False;
5955 Result : Boolean := False;
5957 begin
5958 -- Process associated access types needing special processing
5960 if Present (Access_Types_To_Process (N)) then
5961 declare
5962 E : Elmt_Id := First_Elmt (Access_Types_To_Process (N));
5963 begin
5964 while Present (E) loop
5966 if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
5967 Validate_RACW_Primitives (Node (E));
5968 RACW_Seen := True;
5969 end if;
5971 E := Next_Elmt (E);
5972 end loop;
5973 end;
5975 if RACW_Seen then
5977 -- If there are RACWs designating this type, make stubs now
5979 Remote_Types_Tagged_Full_View_Encountered (Def_Id);
5980 end if;
5981 end if;
5983 -- Freeze processing for record types
5985 if Is_Record_Type (Def_Id) then
5986 if Ekind (Def_Id) = E_Record_Type then
5987 Freeze_Record_Type (N);
5989 -- The subtype may have been declared before the type was frozen. If
5990 -- the type has controlled components it is necessary to create the
5991 -- entity for the controller explicitly because it did not exist at
5992 -- the point of the subtype declaration. Only the entity is needed,
5993 -- the back-end will obtain the layout from the type. This is only
5994 -- necessary if this is constrained subtype whose component list is
5995 -- not shared with the base type.
5997 elsif Ekind (Def_Id) = E_Record_Subtype
5998 and then Has_Discriminants (Def_Id)
5999 and then Last_Entity (Def_Id) /= Last_Entity (Base_Type (Def_Id))
6000 and then Present (Controller_Component (Def_Id))
6001 then
6002 declare
6003 Old_C : constant Entity_Id := Controller_Component (Def_Id);
6004 New_C : Entity_Id;
6006 begin
6007 if Scope (Old_C) = Base_Type (Def_Id) then
6009 -- The entity is the one in the parent. Create new one
6011 New_C := New_Copy (Old_C);
6012 Set_Parent (New_C, Parent (Old_C));
6013 Push_Scope (Def_Id);
6014 Enter_Name (New_C);
6015 End_Scope;
6016 end if;
6017 end;
6019 if Is_Itype (Def_Id)
6020 and then Is_Record_Type (Underlying_Type (Scope (Def_Id)))
6021 then
6022 -- The freeze node is only used to introduce the controller,
6023 -- the back-end has no use for it for a discriminated
6024 -- component.
6026 Set_Freeze_Node (Def_Id, Empty);
6027 Set_Has_Delayed_Freeze (Def_Id, False);
6028 Result := True;
6029 end if;
6031 -- Similar process if the controller of the subtype is not present
6032 -- but the parent has it. This can happen with constrained
6033 -- record components where the subtype is an itype.
6035 elsif Ekind (Def_Id) = E_Record_Subtype
6036 and then Is_Itype (Def_Id)
6037 and then No (Controller_Component (Def_Id))
6038 and then Present (Controller_Component (Etype (Def_Id)))
6039 then
6040 declare
6041 Old_C : constant Entity_Id :=
6042 Controller_Component (Etype (Def_Id));
6043 New_C : constant Entity_Id := New_Copy (Old_C);
6045 begin
6046 Set_Next_Entity (New_C, First_Entity (Def_Id));
6047 Set_First_Entity (Def_Id, New_C);
6049 -- The freeze node is only used to introduce the controller,
6050 -- the back-end has no use for it for a discriminated
6051 -- component.
6053 Set_Freeze_Node (Def_Id, Empty);
6054 Set_Has_Delayed_Freeze (Def_Id, False);
6055 Result := True;
6056 end;
6057 end if;
6059 -- Freeze processing for array types
6061 elsif Is_Array_Type (Def_Id) then
6062 Freeze_Array_Type (N);
6064 -- Freeze processing for access types
6066 -- For pool-specific access types, find out the pool object used for
6067 -- this type, needs actual expansion of it in some cases. Here are the
6068 -- different cases :
6070 -- 1. Rep Clause "for Def_Id'Storage_Size use 0;"
6071 -- ---> don't use any storage pool
6073 -- 2. Rep Clause : for Def_Id'Storage_Size use Expr.
6074 -- Expand:
6075 -- Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
6077 -- 3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
6078 -- ---> Storage Pool is the specified one
6080 -- See GNAT Pool packages in the Run-Time for more details
6082 elsif Ekind (Def_Id) = E_Access_Type
6083 or else Ekind (Def_Id) = E_General_Access_Type
6084 then
6085 declare
6086 Loc : constant Source_Ptr := Sloc (N);
6087 Desig_Type : constant Entity_Id := Designated_Type (Def_Id);
6088 Pool_Object : Entity_Id;
6090 Freeze_Action_Typ : Entity_Id;
6092 begin
6093 -- Case 1
6095 -- Rep Clause "for Def_Id'Storage_Size use 0;"
6096 -- ---> don't use any storage pool
6098 if No_Pool_Assigned (Def_Id) then
6099 null;
6101 -- Case 2
6103 -- Rep Clause : for Def_Id'Storage_Size use Expr.
6104 -- ---> Expand:
6105 -- Def_Id__Pool : Stack_Bounded_Pool
6106 -- (Expr, DT'Size, DT'Alignment);
6108 elsif Has_Storage_Size_Clause (Def_Id) then
6109 declare
6110 DT_Size : Node_Id;
6111 DT_Align : Node_Id;
6113 begin
6114 -- For unconstrained composite types we give a size of zero
6115 -- so that the pool knows that it needs a special algorithm
6116 -- for variable size object allocation.
6118 if Is_Composite_Type (Desig_Type)
6119 and then not Is_Constrained (Desig_Type)
6120 then
6121 DT_Size :=
6122 Make_Integer_Literal (Loc, 0);
6124 DT_Align :=
6125 Make_Integer_Literal (Loc, Maximum_Alignment);
6127 else
6128 DT_Size :=
6129 Make_Attribute_Reference (Loc,
6130 Prefix => New_Reference_To (Desig_Type, Loc),
6131 Attribute_Name => Name_Max_Size_In_Storage_Elements);
6133 DT_Align :=
6134 Make_Attribute_Reference (Loc,
6135 Prefix => New_Reference_To (Desig_Type, Loc),
6136 Attribute_Name => Name_Alignment);
6137 end if;
6139 Pool_Object :=
6140 Make_Defining_Identifier (Loc,
6141 Chars => New_External_Name (Chars (Def_Id), 'P'));
6143 -- We put the code associated with the pools in the entity
6144 -- that has the later freeze node, usually the access type
6145 -- but it can also be the designated_type; because the pool
6146 -- code requires both those types to be frozen
6148 if Is_Frozen (Desig_Type)
6149 and then (No (Freeze_Node (Desig_Type))
6150 or else Analyzed (Freeze_Node (Desig_Type)))
6151 then
6152 Freeze_Action_Typ := Def_Id;
6154 -- A Taft amendment type cannot get the freeze actions
6155 -- since the full view is not there.
6157 elsif Is_Incomplete_Or_Private_Type (Desig_Type)
6158 and then No (Full_View (Desig_Type))
6159 then
6160 Freeze_Action_Typ := Def_Id;
6162 else
6163 Freeze_Action_Typ := Desig_Type;
6164 end if;
6166 Append_Freeze_Action (Freeze_Action_Typ,
6167 Make_Object_Declaration (Loc,
6168 Defining_Identifier => Pool_Object,
6169 Object_Definition =>
6170 Make_Subtype_Indication (Loc,
6171 Subtype_Mark =>
6172 New_Reference_To
6173 (RTE (RE_Stack_Bounded_Pool), Loc),
6175 Constraint =>
6176 Make_Index_Or_Discriminant_Constraint (Loc,
6177 Constraints => New_List (
6179 -- First discriminant is the Pool Size
6181 New_Reference_To (
6182 Storage_Size_Variable (Def_Id), Loc),
6184 -- Second discriminant is the element size
6186 DT_Size,
6188 -- Third discriminant is the alignment
6190 DT_Align)))));
6191 end;
6193 Set_Associated_Storage_Pool (Def_Id, Pool_Object);
6195 -- Case 3
6197 -- Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
6198 -- ---> Storage Pool is the specified one
6200 elsif Present (Associated_Storage_Pool (Def_Id)) then
6202 -- Nothing to do the associated storage pool has been attached
6203 -- when analyzing the rep. clause
6205 null;
6206 end if;
6208 -- For access-to-controlled types (including class-wide types and
6209 -- Taft-amendment types which potentially have controlled
6210 -- components), expand the list controller object that will store
6211 -- the dynamically allocated objects. Do not do this
6212 -- transformation for expander-generated access types, but do it
6213 -- for types that are the full view of types derived from other
6214 -- private types. Also suppress the list controller in the case
6215 -- of a designated type with convention Java, since this is used
6216 -- when binding to Java API specs, where there's no equivalent of
6217 -- a finalization list and we don't want to pull in the
6218 -- finalization support if not needed.
6220 if not Comes_From_Source (Def_Id)
6221 and then not Has_Private_Declaration (Def_Id)
6222 then
6223 null;
6225 elsif (Needs_Finalization (Desig_Type)
6226 and then Convention (Desig_Type) /= Convention_Java
6227 and then Convention (Desig_Type) /= Convention_CIL)
6228 or else
6229 (Is_Incomplete_Or_Private_Type (Desig_Type)
6230 and then No (Full_View (Desig_Type))
6232 -- An exception is made for types defined in the run-time
6233 -- because Ada.Tags.Tag itself is such a type and cannot
6234 -- afford this unnecessary overhead that would generates a
6235 -- loop in the expansion scheme...
6237 and then not In_Runtime (Def_Id)
6239 -- Another exception is if Restrictions (No_Finalization)
6240 -- is active, since then we know nothing is controlled.
6242 and then not Restriction_Active (No_Finalization))
6244 -- If the designated type is not frozen yet, its controlled
6245 -- status must be retrieved explicitly.
6247 or else (Is_Array_Type (Desig_Type)
6248 and then not Is_Frozen (Desig_Type)
6249 and then Needs_Finalization (Component_Type (Desig_Type)))
6251 -- The designated type has controlled anonymous access
6252 -- discriminants.
6254 or else Has_Controlled_Coextensions (Desig_Type)
6255 then
6256 Set_Associated_Final_Chain (Def_Id, Add_Final_Chain (Def_Id));
6257 end if;
6258 end;
6260 -- Freeze processing for enumeration types
6262 elsif Ekind (Def_Id) = E_Enumeration_Type then
6264 -- We only have something to do if we have a non-standard
6265 -- representation (i.e. at least one literal whose pos value
6266 -- is not the same as its representation)
6268 if Has_Non_Standard_Rep (Def_Id) then
6269 Freeze_Enumeration_Type (N);
6270 end if;
6272 -- Private types that are completed by a derivation from a private
6273 -- type have an internally generated full view, that needs to be
6274 -- frozen. This must be done explicitly because the two views share
6275 -- the freeze node, and the underlying full view is not visible when
6276 -- the freeze node is analyzed.
6278 elsif Is_Private_Type (Def_Id)
6279 and then Is_Derived_Type (Def_Id)
6280 and then Present (Full_View (Def_Id))
6281 and then Is_Itype (Full_View (Def_Id))
6282 and then Has_Private_Declaration (Full_View (Def_Id))
6283 and then Freeze_Node (Full_View (Def_Id)) = N
6284 then
6285 Set_Entity (N, Full_View (Def_Id));
6286 Result := Freeze_Type (N);
6287 Set_Entity (N, Def_Id);
6289 -- All other types require no expander action. There are such cases
6290 -- (e.g. task types and protected types). In such cases, the freeze
6291 -- nodes are there for use by Gigi.
6293 end if;
6295 Freeze_Stream_Operations (N, Def_Id);
6296 return Result;
6298 exception
6299 when RE_Not_Available =>
6300 return False;
6301 end Freeze_Type;
6303 -------------------------
6304 -- Get_Simple_Init_Val --
6305 -------------------------
6307 function Get_Simple_Init_Val
6308 (T : Entity_Id;
6309 N : Node_Id;
6310 Size : Uint := No_Uint) return Node_Id
6312 Loc : constant Source_Ptr := Sloc (N);
6313 Val : Node_Id;
6314 Result : Node_Id;
6315 Val_RE : RE_Id;
6317 Size_To_Use : Uint;
6318 -- This is the size to be used for computation of the appropriate
6319 -- initial value for the Normalize_Scalars and Initialize_Scalars case.
6321 IV_Attribute : constant Boolean :=
6322 Nkind (N) = N_Attribute_Reference
6323 and then Attribute_Name (N) = Name_Invalid_Value;
6325 Lo_Bound : Uint;
6326 Hi_Bound : Uint;
6327 -- These are the values computed by the procedure Check_Subtype_Bounds
6329 procedure Check_Subtype_Bounds;
6330 -- This procedure examines the subtype T, and its ancestor subtypes and
6331 -- derived types to determine the best known information about the
6332 -- bounds of the subtype. After the call Lo_Bound is set either to
6333 -- No_Uint if no information can be determined, or to a value which
6334 -- represents a known low bound, i.e. a valid value of the subtype can
6335 -- not be less than this value. Hi_Bound is similarly set to a known
6336 -- high bound (valid value cannot be greater than this).
6338 --------------------------
6339 -- Check_Subtype_Bounds --
6340 --------------------------
6342 procedure Check_Subtype_Bounds is
6343 ST1 : Entity_Id;
6344 ST2 : Entity_Id;
6345 Lo : Node_Id;
6346 Hi : Node_Id;
6347 Loval : Uint;
6348 Hival : Uint;
6350 begin
6351 Lo_Bound := No_Uint;
6352 Hi_Bound := No_Uint;
6354 -- Loop to climb ancestor subtypes and derived types
6356 ST1 := T;
6357 loop
6358 if not Is_Discrete_Type (ST1) then
6359 return;
6360 end if;
6362 Lo := Type_Low_Bound (ST1);
6363 Hi := Type_High_Bound (ST1);
6365 if Compile_Time_Known_Value (Lo) then
6366 Loval := Expr_Value (Lo);
6368 if Lo_Bound = No_Uint or else Lo_Bound < Loval then
6369 Lo_Bound := Loval;
6370 end if;
6371 end if;
6373 if Compile_Time_Known_Value (Hi) then
6374 Hival := Expr_Value (Hi);
6376 if Hi_Bound = No_Uint or else Hi_Bound > Hival then
6377 Hi_Bound := Hival;
6378 end if;
6379 end if;
6381 ST2 := Ancestor_Subtype (ST1);
6383 if No (ST2) then
6384 ST2 := Etype (ST1);
6385 end if;
6387 exit when ST1 = ST2;
6388 ST1 := ST2;
6389 end loop;
6390 end Check_Subtype_Bounds;
6392 -- Start of processing for Get_Simple_Init_Val
6394 begin
6395 -- For a private type, we should always have an underlying type
6396 -- (because this was already checked in Needs_Simple_Initialization).
6397 -- What we do is to get the value for the underlying type and then do
6398 -- an Unchecked_Convert to the private type.
6400 if Is_Private_Type (T) then
6401 Val := Get_Simple_Init_Val (Underlying_Type (T), N, Size);
6403 -- A special case, if the underlying value is null, then qualify it
6404 -- with the underlying type, so that the null is properly typed
6405 -- Similarly, if it is an aggregate it must be qualified, because an
6406 -- unchecked conversion does not provide a context for it.
6408 if Nkind_In (Val, N_Null, N_Aggregate) then
6409 Val :=
6410 Make_Qualified_Expression (Loc,
6411 Subtype_Mark =>
6412 New_Occurrence_Of (Underlying_Type (T), Loc),
6413 Expression => Val);
6414 end if;
6416 Result := Unchecked_Convert_To (T, Val);
6418 -- Don't truncate result (important for Initialize/Normalize_Scalars)
6420 if Nkind (Result) = N_Unchecked_Type_Conversion
6421 and then Is_Scalar_Type (Underlying_Type (T))
6422 then
6423 Set_No_Truncation (Result);
6424 end if;
6426 return Result;
6428 -- For scalars, we must have normalize/initialize scalars case, or
6429 -- if the node N is an 'Invalid_Value attribute node.
6431 elsif Is_Scalar_Type (T) then
6432 pragma Assert (Init_Or_Norm_Scalars or IV_Attribute);
6434 -- Compute size of object. If it is given by the caller, we can use
6435 -- it directly, otherwise we use Esize (T) as an estimate. As far as
6436 -- we know this covers all cases correctly.
6438 if Size = No_Uint or else Size <= Uint_0 then
6439 Size_To_Use := UI_Max (Uint_1, Esize (T));
6440 else
6441 Size_To_Use := Size;
6442 end if;
6444 -- Maximum size to use is 64 bits, since we will create values
6445 -- of type Unsigned_64 and the range must fit this type.
6447 if Size_To_Use /= No_Uint and then Size_To_Use > Uint_64 then
6448 Size_To_Use := Uint_64;
6449 end if;
6451 -- Check known bounds of subtype
6453 Check_Subtype_Bounds;
6455 -- Processing for Normalize_Scalars case
6457 if Normalize_Scalars and then not IV_Attribute then
6459 -- If zero is invalid, it is a convenient value to use that is
6460 -- for sure an appropriate invalid value in all situations.
6462 if Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
6463 Val := Make_Integer_Literal (Loc, 0);
6465 -- Cases where all one bits is the appropriate invalid value
6467 -- For modular types, all 1 bits is either invalid or valid. If
6468 -- it is valid, then there is nothing that can be done since there
6469 -- are no invalid values (we ruled out zero already).
6471 -- For signed integer types that have no negative values, either
6472 -- there is room for negative values, or there is not. If there
6473 -- is, then all 1 bits may be interpreted as minus one, which is
6474 -- certainly invalid. Alternatively it is treated as the largest
6475 -- positive value, in which case the observation for modular types
6476 -- still applies.
6478 -- For float types, all 1-bits is a NaN (not a number), which is
6479 -- certainly an appropriately invalid value.
6481 elsif Is_Unsigned_Type (T)
6482 or else Is_Floating_Point_Type (T)
6483 or else Is_Enumeration_Type (T)
6484 then
6485 Val := Make_Integer_Literal (Loc, 2 ** Size_To_Use - 1);
6487 -- Resolve as Unsigned_64, because the largest number we
6488 -- can generate is out of range of universal integer.
6490 Analyze_And_Resolve (Val, RTE (RE_Unsigned_64));
6492 -- Case of signed types
6494 else
6495 declare
6496 Signed_Size : constant Uint :=
6497 UI_Min (Uint_63, Size_To_Use - 1);
6499 begin
6500 -- Normally we like to use the most negative number. The
6501 -- one exception is when this number is in the known
6502 -- subtype range and the largest positive number is not in
6503 -- the known subtype range.
6505 -- For this exceptional case, use largest positive value
6507 if Lo_Bound /= No_Uint and then Hi_Bound /= No_Uint
6508 and then Lo_Bound <= (-(2 ** Signed_Size))
6509 and then Hi_Bound < 2 ** Signed_Size
6510 then
6511 Val := Make_Integer_Literal (Loc, 2 ** Signed_Size - 1);
6513 -- Normal case of largest negative value
6515 else
6516 Val := Make_Integer_Literal (Loc, -(2 ** Signed_Size));
6517 end if;
6518 end;
6519 end if;
6521 -- Here for Initialize_Scalars case (or Invalid_Value attribute used)
6523 else
6524 -- For float types, use float values from System.Scalar_Values
6526 if Is_Floating_Point_Type (T) then
6527 if Root_Type (T) = Standard_Short_Float then
6528 Val_RE := RE_IS_Isf;
6529 elsif Root_Type (T) = Standard_Float then
6530 Val_RE := RE_IS_Ifl;
6531 elsif Root_Type (T) = Standard_Long_Float then
6532 Val_RE := RE_IS_Ilf;
6533 else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
6534 Val_RE := RE_IS_Ill;
6535 end if;
6537 -- If zero is invalid, use zero values from System.Scalar_Values
6539 elsif Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
6540 if Size_To_Use <= 8 then
6541 Val_RE := RE_IS_Iz1;
6542 elsif Size_To_Use <= 16 then
6543 Val_RE := RE_IS_Iz2;
6544 elsif Size_To_Use <= 32 then
6545 Val_RE := RE_IS_Iz4;
6546 else
6547 Val_RE := RE_IS_Iz8;
6548 end if;
6550 -- For unsigned, use unsigned values from System.Scalar_Values
6552 elsif Is_Unsigned_Type (T) then
6553 if Size_To_Use <= 8 then
6554 Val_RE := RE_IS_Iu1;
6555 elsif Size_To_Use <= 16 then
6556 Val_RE := RE_IS_Iu2;
6557 elsif Size_To_Use <= 32 then
6558 Val_RE := RE_IS_Iu4;
6559 else
6560 Val_RE := RE_IS_Iu8;
6561 end if;
6563 -- For signed, use signed values from System.Scalar_Values
6565 else
6566 if Size_To_Use <= 8 then
6567 Val_RE := RE_IS_Is1;
6568 elsif Size_To_Use <= 16 then
6569 Val_RE := RE_IS_Is2;
6570 elsif Size_To_Use <= 32 then
6571 Val_RE := RE_IS_Is4;
6572 else
6573 Val_RE := RE_IS_Is8;
6574 end if;
6575 end if;
6577 Val := New_Occurrence_Of (RTE (Val_RE), Loc);
6578 end if;
6580 -- The final expression is obtained by doing an unchecked conversion
6581 -- of this result to the base type of the required subtype. We use
6582 -- the base type to avoid the unchecked conversion from chopping
6583 -- bits, and then we set Kill_Range_Check to preserve the "bad"
6584 -- value.
6586 Result := Unchecked_Convert_To (Base_Type (T), Val);
6588 -- Ensure result is not truncated, since we want the "bad" bits
6589 -- and also kill range check on result.
6591 if Nkind (Result) = N_Unchecked_Type_Conversion then
6592 Set_No_Truncation (Result);
6593 Set_Kill_Range_Check (Result, True);
6594 end if;
6596 return Result;
6598 -- String or Wide_[Wide]_String (must have Initialize_Scalars set)
6600 elsif Root_Type (T) = Standard_String
6601 or else
6602 Root_Type (T) = Standard_Wide_String
6603 or else
6604 Root_Type (T) = Standard_Wide_Wide_String
6605 then
6606 pragma Assert (Init_Or_Norm_Scalars);
6608 return
6609 Make_Aggregate (Loc,
6610 Component_Associations => New_List (
6611 Make_Component_Association (Loc,
6612 Choices => New_List (
6613 Make_Others_Choice (Loc)),
6614 Expression =>
6615 Get_Simple_Init_Val
6616 (Component_Type (T), N, Esize (Root_Type (T))))));
6618 -- Access type is initialized to null
6620 elsif Is_Access_Type (T) then
6621 return
6622 Make_Null (Loc);
6624 -- No other possibilities should arise, since we should only be
6625 -- calling Get_Simple_Init_Val if Needs_Simple_Initialization
6626 -- returned True, indicating one of the above cases held.
6628 else
6629 raise Program_Error;
6630 end if;
6632 exception
6633 when RE_Not_Available =>
6634 return Empty;
6635 end Get_Simple_Init_Val;
6637 ------------------------------
6638 -- Has_New_Non_Standard_Rep --
6639 ------------------------------
6641 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
6642 begin
6643 if not Is_Derived_Type (T) then
6644 return Has_Non_Standard_Rep (T)
6645 or else Has_Non_Standard_Rep (Root_Type (T));
6647 -- If Has_Non_Standard_Rep is not set on the derived type, the
6648 -- representation is fully inherited.
6650 elsif not Has_Non_Standard_Rep (T) then
6651 return False;
6653 else
6654 return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
6656 -- May need a more precise check here: the First_Rep_Item may
6657 -- be a stream attribute, which does not affect the representation
6658 -- of the type ???
6659 end if;
6660 end Has_New_Non_Standard_Rep;
6662 ----------------
6663 -- In_Runtime --
6664 ----------------
6666 function In_Runtime (E : Entity_Id) return Boolean is
6667 S1 : Entity_Id;
6669 begin
6670 S1 := Scope (E);
6671 while Scope (S1) /= Standard_Standard loop
6672 S1 := Scope (S1);
6673 end loop;
6675 return Chars (S1) = Name_System or else Chars (S1) = Name_Ada;
6676 end In_Runtime;
6678 ----------------------------
6679 -- Initialization_Warning --
6680 ----------------------------
6682 procedure Initialization_Warning (E : Entity_Id) is
6683 Warning_Needed : Boolean;
6685 begin
6686 Warning_Needed := False;
6688 if Ekind (Current_Scope) = E_Package
6689 and then Static_Elaboration_Desired (Current_Scope)
6690 then
6691 if Is_Type (E) then
6692 if Is_Record_Type (E) then
6693 if Has_Discriminants (E)
6694 or else Is_Limited_Type (E)
6695 or else Has_Non_Standard_Rep (E)
6696 then
6697 Warning_Needed := True;
6699 else
6700 -- Verify that at least one component has an initialization
6701 -- expression. No need for a warning on a type if all its
6702 -- components have no initialization.
6704 declare
6705 Comp : Entity_Id;
6707 begin
6708 Comp := First_Component (E);
6709 while Present (Comp) loop
6710 if Ekind (Comp) = E_Discriminant
6711 or else
6712 (Nkind (Parent (Comp)) = N_Component_Declaration
6713 and then Present (Expression (Parent (Comp))))
6714 then
6715 Warning_Needed := True;
6716 exit;
6717 end if;
6719 Next_Component (Comp);
6720 end loop;
6721 end;
6722 end if;
6724 if Warning_Needed then
6725 Error_Msg_N
6726 ("Objects of the type cannot be initialized " &
6727 "statically by default?",
6728 Parent (E));
6729 end if;
6730 end if;
6732 else
6733 Error_Msg_N ("Object cannot be initialized statically?", E);
6734 end if;
6735 end if;
6736 end Initialization_Warning;
6738 ------------------
6739 -- Init_Formals --
6740 ------------------
6742 function Init_Formals (Typ : Entity_Id) return List_Id is
6743 Loc : constant Source_Ptr := Sloc (Typ);
6744 Formals : List_Id;
6746 begin
6747 -- First parameter is always _Init : in out typ. Note that we need
6748 -- this to be in/out because in the case of the task record value,
6749 -- there are default record fields (_Priority, _Size, -Task_Info)
6750 -- that may be referenced in the generated initialization routine.
6752 Formals := New_List (
6753 Make_Parameter_Specification (Loc,
6754 Defining_Identifier =>
6755 Make_Defining_Identifier (Loc, Name_uInit),
6756 In_Present => True,
6757 Out_Present => True,
6758 Parameter_Type => New_Reference_To (Typ, Loc)));
6760 -- For task record value, or type that contains tasks, add two more
6761 -- formals, _Master : Master_Id and _Chain : in out Activation_Chain
6762 -- We also add these parameters for the task record type case.
6764 if Has_Task (Typ)
6765 or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
6766 then
6767 Append_To (Formals,
6768 Make_Parameter_Specification (Loc,
6769 Defining_Identifier =>
6770 Make_Defining_Identifier (Loc, Name_uMaster),
6771 Parameter_Type => New_Reference_To (RTE (RE_Master_Id), Loc)));
6773 Append_To (Formals,
6774 Make_Parameter_Specification (Loc,
6775 Defining_Identifier =>
6776 Make_Defining_Identifier (Loc, Name_uChain),
6777 In_Present => True,
6778 Out_Present => True,
6779 Parameter_Type =>
6780 New_Reference_To (RTE (RE_Activation_Chain), Loc)));
6782 Append_To (Formals,
6783 Make_Parameter_Specification (Loc,
6784 Defining_Identifier =>
6785 Make_Defining_Identifier (Loc, Name_uTask_Name),
6786 In_Present => True,
6787 Parameter_Type =>
6788 New_Reference_To (Standard_String, Loc)));
6789 end if;
6791 return Formals;
6793 exception
6794 when RE_Not_Available =>
6795 return Empty_List;
6796 end Init_Formals;
6798 -------------------------
6799 -- Init_Secondary_Tags --
6800 -------------------------
6802 procedure Init_Secondary_Tags
6803 (Typ : Entity_Id;
6804 Target : Node_Id;
6805 Stmts_List : List_Id;
6806 Fixed_Comps : Boolean := True;
6807 Variable_Comps : Boolean := True)
6809 Loc : constant Source_Ptr := Sloc (Target);
6811 procedure Inherit_CPP_Tag
6812 (Typ : Entity_Id;
6813 Iface : Entity_Id;
6814 Tag_Comp : Entity_Id;
6815 Iface_Tag : Node_Id);
6816 -- Inherit the C++ tag of the secondary dispatch table of Typ associated
6817 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
6819 procedure Initialize_Tag
6820 (Typ : Entity_Id;
6821 Iface : Entity_Id;
6822 Tag_Comp : Entity_Id;
6823 Iface_Tag : Node_Id);
6824 -- Initialize the tag of the secondary dispatch table of Typ associated
6825 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
6826 -- Compiling under the CPP full ABI compatibility mode, if the ancestor
6827 -- of Typ CPP tagged type we generate code to inherit the contents of
6828 -- the dispatch table directly from the ancestor.
6830 ---------------------
6831 -- Inherit_CPP_Tag --
6832 ---------------------
6834 procedure Inherit_CPP_Tag
6835 (Typ : Entity_Id;
6836 Iface : Entity_Id;
6837 Tag_Comp : Entity_Id;
6838 Iface_Tag : Node_Id)
6840 begin
6841 pragma Assert (Is_CPP_Class (Etype (Typ)));
6843 Append_To (Stmts_List,
6844 Build_Inherit_Prims (Loc,
6845 Typ => Iface,
6846 Old_Tag_Node =>
6847 Make_Selected_Component (Loc,
6848 Prefix => New_Copy_Tree (Target),
6849 Selector_Name => New_Reference_To (Tag_Comp, Loc)),
6850 New_Tag_Node =>
6851 New_Reference_To (Iface_Tag, Loc),
6852 Num_Prims =>
6853 UI_To_Int (DT_Entry_Count (First_Tag_Component (Iface)))));
6854 end Inherit_CPP_Tag;
6856 --------------------
6857 -- Initialize_Tag --
6858 --------------------
6860 procedure Initialize_Tag
6861 (Typ : Entity_Id;
6862 Iface : Entity_Id;
6863 Tag_Comp : Entity_Id;
6864 Iface_Tag : Node_Id)
6866 Comp_Typ : Entity_Id;
6867 Offset_To_Top_Comp : Entity_Id := Empty;
6869 begin
6870 -- Initialize the pointer to the secondary DT associated with the
6871 -- interface.
6873 if not Is_Ancestor (Iface, Typ) then
6874 Append_To (Stmts_List,
6875 Make_Assignment_Statement (Loc,
6876 Name =>
6877 Make_Selected_Component (Loc,
6878 Prefix => New_Copy_Tree (Target),
6879 Selector_Name => New_Reference_To (Tag_Comp, Loc)),
6880 Expression =>
6881 New_Reference_To (Iface_Tag, Loc)));
6882 end if;
6884 Comp_Typ := Scope (Tag_Comp);
6886 -- Initialize the entries of the table of interfaces. We generate a
6887 -- different call when the parent of the type has variable size
6888 -- components.
6890 if Comp_Typ /= Etype (Comp_Typ)
6891 and then Is_Variable_Size_Record (Etype (Comp_Typ))
6892 and then Chars (Tag_Comp) /= Name_uTag
6893 then
6894 pragma Assert (Present (DT_Offset_To_Top_Func (Tag_Comp)));
6896 -- Issue error if Set_Dynamic_Offset_To_Top is not available in a
6897 -- configurable run-time environment.
6899 if not RTE_Available (RE_Set_Dynamic_Offset_To_Top) then
6900 Error_Msg_CRT
6901 ("variable size record with interface types", Typ);
6902 return;
6903 end if;
6905 -- Generate:
6906 -- Set_Dynamic_Offset_To_Top
6907 -- (This => Init,
6908 -- Interface_T => Iface'Tag,
6909 -- Offset_Value => n,
6910 -- Offset_Func => Fn'Address)
6912 Append_To (Stmts_List,
6913 Make_Procedure_Call_Statement (Loc,
6914 Name => New_Reference_To
6915 (RTE (RE_Set_Dynamic_Offset_To_Top), Loc),
6916 Parameter_Associations => New_List (
6917 Make_Attribute_Reference (Loc,
6918 Prefix => New_Copy_Tree (Target),
6919 Attribute_Name => Name_Address),
6921 Unchecked_Convert_To (RTE (RE_Tag),
6922 New_Reference_To
6923 (Node (First_Elmt (Access_Disp_Table (Iface))),
6924 Loc)),
6926 Unchecked_Convert_To
6927 (RTE (RE_Storage_Offset),
6928 Make_Attribute_Reference (Loc,
6929 Prefix =>
6930 Make_Selected_Component (Loc,
6931 Prefix => New_Copy_Tree (Target),
6932 Selector_Name =>
6933 New_Reference_To (Tag_Comp, Loc)),
6934 Attribute_Name => Name_Position)),
6936 Unchecked_Convert_To (RTE (RE_Offset_To_Top_Function_Ptr),
6937 Make_Attribute_Reference (Loc,
6938 Prefix => New_Reference_To
6939 (DT_Offset_To_Top_Func (Tag_Comp), Loc),
6940 Attribute_Name => Name_Address)))));
6942 -- In this case the next component stores the value of the
6943 -- offset to the top.
6945 Offset_To_Top_Comp := Next_Entity (Tag_Comp);
6946 pragma Assert (Present (Offset_To_Top_Comp));
6948 Append_To (Stmts_List,
6949 Make_Assignment_Statement (Loc,
6950 Name =>
6951 Make_Selected_Component (Loc,
6952 Prefix => New_Copy_Tree (Target),
6953 Selector_Name => New_Reference_To
6954 (Offset_To_Top_Comp, Loc)),
6955 Expression =>
6956 Make_Attribute_Reference (Loc,
6957 Prefix =>
6958 Make_Selected_Component (Loc,
6959 Prefix => New_Copy_Tree (Target),
6960 Selector_Name =>
6961 New_Reference_To (Tag_Comp, Loc)),
6962 Attribute_Name => Name_Position)));
6964 -- Normal case: No discriminants in the parent type
6966 else
6967 -- Don't need to set any value if this interface shares
6968 -- the primary dispatch table.
6970 if not Is_Ancestor (Iface, Typ) then
6971 Append_To (Stmts_List,
6972 Build_Set_Static_Offset_To_Top (Loc,
6973 Iface_Tag => New_Reference_To (Iface_Tag, Loc),
6974 Offset_Value =>
6975 Unchecked_Convert_To (RTE (RE_Storage_Offset),
6976 Make_Attribute_Reference (Loc,
6977 Prefix =>
6978 Make_Selected_Component (Loc,
6979 Prefix => New_Copy_Tree (Target),
6980 Selector_Name =>
6981 New_Reference_To (Tag_Comp, Loc)),
6982 Attribute_Name => Name_Position))));
6983 end if;
6985 -- Generate:
6986 -- Register_Interface_Offset
6987 -- (This => Init,
6988 -- Interface_T => Iface'Tag,
6989 -- Is_Constant => True,
6990 -- Offset_Value => n,
6991 -- Offset_Func => null);
6993 if RTE_Available (RE_Register_Interface_Offset) then
6994 Append_To (Stmts_List,
6995 Make_Procedure_Call_Statement (Loc,
6996 Name => New_Reference_To
6997 (RTE (RE_Register_Interface_Offset), Loc),
6998 Parameter_Associations => New_List (
6999 Make_Attribute_Reference (Loc,
7000 Prefix => New_Copy_Tree (Target),
7001 Attribute_Name => Name_Address),
7003 Unchecked_Convert_To (RTE (RE_Tag),
7004 New_Reference_To
7005 (Node (First_Elmt (Access_Disp_Table (Iface))), Loc)),
7007 New_Occurrence_Of (Standard_True, Loc),
7009 Unchecked_Convert_To
7010 (RTE (RE_Storage_Offset),
7011 Make_Attribute_Reference (Loc,
7012 Prefix =>
7013 Make_Selected_Component (Loc,
7014 Prefix => New_Copy_Tree (Target),
7015 Selector_Name =>
7016 New_Reference_To (Tag_Comp, Loc)),
7017 Attribute_Name => Name_Position)),
7019 Make_Null (Loc))));
7020 end if;
7021 end if;
7022 end Initialize_Tag;
7024 -- Local variables
7026 Full_Typ : Entity_Id;
7027 Ifaces_List : Elist_Id;
7028 Ifaces_Comp_List : Elist_Id;
7029 Ifaces_Tag_List : Elist_Id;
7030 Iface_Elmt : Elmt_Id;
7031 Iface_Comp_Elmt : Elmt_Id;
7032 Iface_Tag_Elmt : Elmt_Id;
7033 Tag_Comp : Node_Id;
7034 In_Variable_Pos : Boolean;
7036 -- Start of processing for Init_Secondary_Tags
7038 begin
7039 -- Handle private types
7041 if Present (Full_View (Typ)) then
7042 Full_Typ := Full_View (Typ);
7043 else
7044 Full_Typ := Typ;
7045 end if;
7047 Collect_Interfaces_Info
7048 (Full_Typ, Ifaces_List, Ifaces_Comp_List, Ifaces_Tag_List);
7050 Iface_Elmt := First_Elmt (Ifaces_List);
7051 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
7052 Iface_Tag_Elmt := First_Elmt (Ifaces_Tag_List);
7053 while Present (Iface_Elmt) loop
7054 Tag_Comp := Node (Iface_Comp_Elmt);
7056 -- If we are compiling under the CPP full ABI compatibility mode and
7057 -- the ancestor is a CPP_Pragma tagged type then we generate code to
7058 -- inherit the contents of the dispatch table directly from the
7059 -- ancestor.
7061 if Is_CPP_Class (Etype (Full_Typ)) then
7062 Inherit_CPP_Tag (Full_Typ,
7063 Iface => Node (Iface_Elmt),
7064 Tag_Comp => Tag_Comp,
7065 Iface_Tag => Node (Iface_Tag_Elmt));
7067 -- Otherwise generate code to initialize the tag
7069 else
7070 -- Check if the parent of the record type has variable size
7071 -- components.
7073 In_Variable_Pos := Scope (Tag_Comp) /= Etype (Scope (Tag_Comp))
7074 and then Is_Variable_Size_Record (Etype (Scope (Tag_Comp)));
7076 if (In_Variable_Pos and then Variable_Comps)
7077 or else (not In_Variable_Pos and then Fixed_Comps)
7078 then
7079 Initialize_Tag (Full_Typ,
7080 Iface => Node (Iface_Elmt),
7081 Tag_Comp => Tag_Comp,
7082 Iface_Tag => Node (Iface_Tag_Elmt));
7083 end if;
7084 end if;
7086 Next_Elmt (Iface_Elmt);
7087 Next_Elmt (Iface_Comp_Elmt);
7088 Next_Elmt (Iface_Tag_Elmt);
7089 end loop;
7090 end Init_Secondary_Tags;
7092 -----------------------------
7093 -- Is_Variable_Size_Record --
7094 -----------------------------
7096 function Is_Variable_Size_Record (E : Entity_Id) return Boolean is
7097 Comp : Entity_Id;
7098 Comp_Typ : Entity_Id;
7099 Idx : Node_Id;
7101 function Is_Constant_Bound (Exp : Node_Id) return Boolean;
7102 -- To simplify handling of array components. Determines whether the
7103 -- given bound is constant (a constant or enumeration literal, or an
7104 -- integer literal) as opposed to per-object, through an expression
7105 -- or a discriminant.
7107 -----------------------
7108 -- Is_Constant_Bound --
7109 -----------------------
7111 function Is_Constant_Bound (Exp : Node_Id) return Boolean is
7112 begin
7113 if Nkind (Exp) = N_Integer_Literal then
7114 return True;
7115 else
7116 return
7117 Is_Entity_Name (Exp)
7118 and then Present (Entity (Exp))
7119 and then
7120 (Ekind (Entity (Exp)) = E_Constant
7121 or else Ekind (Entity (Exp)) = E_Enumeration_Literal);
7122 end if;
7123 end Is_Constant_Bound;
7125 -- Start of processing for Is_Variable_Sized_Record
7127 begin
7128 pragma Assert (Is_Record_Type (E));
7130 Comp := First_Entity (E);
7131 while Present (Comp) loop
7132 Comp_Typ := Etype (Comp);
7134 if Is_Record_Type (Comp_Typ) then
7136 -- Recursive call if the record type has discriminants
7138 if Has_Discriminants (Comp_Typ)
7139 and then Is_Variable_Size_Record (Comp_Typ)
7140 then
7141 return True;
7142 end if;
7144 elsif Is_Array_Type (Comp_Typ) then
7146 -- Check if some index is initialized with a non-constant value
7148 Idx := First_Index (Comp_Typ);
7149 while Present (Idx) loop
7150 if Nkind (Idx) = N_Range then
7151 if not Is_Constant_Bound (Low_Bound (Idx))
7152 or else
7153 not Is_Constant_Bound (High_Bound (Idx))
7154 then
7155 return True;
7156 end if;
7157 end if;
7159 Idx := Next_Index (Idx);
7160 end loop;
7161 end if;
7163 Next_Entity (Comp);
7164 end loop;
7166 return False;
7167 end Is_Variable_Size_Record;
7169 ----------------------------------------
7170 -- Make_Controlling_Function_Wrappers --
7171 ----------------------------------------
7173 procedure Make_Controlling_Function_Wrappers
7174 (Tag_Typ : Entity_Id;
7175 Decl_List : out List_Id;
7176 Body_List : out List_Id)
7178 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7179 Prim_Elmt : Elmt_Id;
7180 Subp : Entity_Id;
7181 Actual_List : List_Id;
7182 Formal_List : List_Id;
7183 Formal : Entity_Id;
7184 Par_Formal : Entity_Id;
7185 Formal_Node : Node_Id;
7186 Func_Body : Node_Id;
7187 Func_Decl : Node_Id;
7188 Func_Spec : Node_Id;
7189 Return_Stmt : Node_Id;
7191 begin
7192 Decl_List := New_List;
7193 Body_List := New_List;
7195 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7197 while Present (Prim_Elmt) loop
7198 Subp := Node (Prim_Elmt);
7200 -- If a primitive function with a controlling result of the type has
7201 -- not been overridden by the user, then we must create a wrapper
7202 -- function here that effectively overrides it and invokes the
7203 -- (non-abstract) parent function. This can only occur for a null
7204 -- extension. Note that functions with anonymous controlling access
7205 -- results don't qualify and must be overridden. We also exclude
7206 -- Input attributes, since each type will have its own version of
7207 -- Input constructed by the expander. The test for Comes_From_Source
7208 -- is needed to distinguish inherited operations from renamings
7209 -- (which also have Alias set).
7211 -- The function may be abstract, or require_Overriding may be set
7212 -- for it, because tests for null extensions may already have reset
7213 -- the Is_Abstract_Subprogram_Flag. If Requires_Overriding is not
7214 -- set, functions that need wrappers are recognized by having an
7215 -- alias that returns the parent type.
7217 if Comes_From_Source (Subp)
7218 or else No (Alias (Subp))
7219 or else Ekind (Subp) /= E_Function
7220 or else not Has_Controlling_Result (Subp)
7221 or else Is_Access_Type (Etype (Subp))
7222 or else Is_Abstract_Subprogram (Alias (Subp))
7223 or else Is_TSS (Subp, TSS_Stream_Input)
7224 then
7225 goto Next_Prim;
7227 elsif Is_Abstract_Subprogram (Subp)
7228 or else Requires_Overriding (Subp)
7229 or else
7230 (Is_Null_Extension (Etype (Subp))
7231 and then Etype (Alias (Subp)) /= Etype (Subp))
7232 then
7233 Formal_List := No_List;
7234 Formal := First_Formal (Subp);
7236 if Present (Formal) then
7237 Formal_List := New_List;
7239 while Present (Formal) loop
7240 Append
7241 (Make_Parameter_Specification
7242 (Loc,
7243 Defining_Identifier =>
7244 Make_Defining_Identifier (Sloc (Formal),
7245 Chars => Chars (Formal)),
7246 In_Present => In_Present (Parent (Formal)),
7247 Out_Present => Out_Present (Parent (Formal)),
7248 Null_Exclusion_Present =>
7249 Null_Exclusion_Present (Parent (Formal)),
7250 Parameter_Type =>
7251 New_Reference_To (Etype (Formal), Loc),
7252 Expression =>
7253 New_Copy_Tree (Expression (Parent (Formal)))),
7254 Formal_List);
7256 Next_Formal (Formal);
7257 end loop;
7258 end if;
7260 Func_Spec :=
7261 Make_Function_Specification (Loc,
7262 Defining_Unit_Name =>
7263 Make_Defining_Identifier (Loc,
7264 Chars => Chars (Subp)),
7265 Parameter_Specifications => Formal_List,
7266 Result_Definition =>
7267 New_Reference_To (Etype (Subp), Loc));
7269 Func_Decl := Make_Subprogram_Declaration (Loc, Func_Spec);
7270 Append_To (Decl_List, Func_Decl);
7272 -- Build a wrapper body that calls the parent function. The body
7273 -- contains a single return statement that returns an extension
7274 -- aggregate whose ancestor part is a call to the parent function,
7275 -- passing the formals as actuals (with any controlling arguments
7276 -- converted to the types of the corresponding formals of the
7277 -- parent function, which might be anonymous access types), and
7278 -- having a null extension.
7280 Formal := First_Formal (Subp);
7281 Par_Formal := First_Formal (Alias (Subp));
7282 Formal_Node := First (Formal_List);
7284 if Present (Formal) then
7285 Actual_List := New_List;
7286 else
7287 Actual_List := No_List;
7288 end if;
7290 while Present (Formal) loop
7291 if Is_Controlling_Formal (Formal) then
7292 Append_To (Actual_List,
7293 Make_Type_Conversion (Loc,
7294 Subtype_Mark =>
7295 New_Occurrence_Of (Etype (Par_Formal), Loc),
7296 Expression =>
7297 New_Reference_To
7298 (Defining_Identifier (Formal_Node), Loc)));
7299 else
7300 Append_To
7301 (Actual_List,
7302 New_Reference_To
7303 (Defining_Identifier (Formal_Node), Loc));
7304 end if;
7306 Next_Formal (Formal);
7307 Next_Formal (Par_Formal);
7308 Next (Formal_Node);
7309 end loop;
7311 Return_Stmt :=
7312 Make_Simple_Return_Statement (Loc,
7313 Expression =>
7314 Make_Extension_Aggregate (Loc,
7315 Ancestor_Part =>
7316 Make_Function_Call (Loc,
7317 Name => New_Reference_To (Alias (Subp), Loc),
7318 Parameter_Associations => Actual_List),
7319 Null_Record_Present => True));
7321 Func_Body :=
7322 Make_Subprogram_Body (Loc,
7323 Specification => New_Copy_Tree (Func_Spec),
7324 Declarations => Empty_List,
7325 Handled_Statement_Sequence =>
7326 Make_Handled_Sequence_Of_Statements (Loc,
7327 Statements => New_List (Return_Stmt)));
7329 Set_Defining_Unit_Name
7330 (Specification (Func_Body),
7331 Make_Defining_Identifier (Loc, Chars (Subp)));
7333 Append_To (Body_List, Func_Body);
7335 -- Replace the inherited function with the wrapper function
7336 -- in the primitive operations list.
7338 Override_Dispatching_Operation
7339 (Tag_Typ, Subp, New_Op => Defining_Unit_Name (Func_Spec));
7340 end if;
7342 <<Next_Prim>>
7343 Next_Elmt (Prim_Elmt);
7344 end loop;
7345 end Make_Controlling_Function_Wrappers;
7347 ------------------
7348 -- Make_Eq_Case --
7349 ------------------
7351 -- <Make_Eq_If shared components>
7352 -- case X.D1 is
7353 -- when V1 => <Make_Eq_Case> on subcomponents
7354 -- ...
7355 -- when Vn => <Make_Eq_Case> on subcomponents
7356 -- end case;
7358 function Make_Eq_Case
7359 (E : Entity_Id;
7360 CL : Node_Id;
7361 Discr : Entity_Id := Empty) return List_Id
7363 Loc : constant Source_Ptr := Sloc (E);
7364 Result : constant List_Id := New_List;
7365 Variant : Node_Id;
7366 Alt_List : List_Id;
7368 begin
7369 Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
7371 if No (Variant_Part (CL)) then
7372 return Result;
7373 end if;
7375 Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
7377 if No (Variant) then
7378 return Result;
7379 end if;
7381 Alt_List := New_List;
7383 while Present (Variant) loop
7384 Append_To (Alt_List,
7385 Make_Case_Statement_Alternative (Loc,
7386 Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
7387 Statements => Make_Eq_Case (E, Component_List (Variant))));
7389 Next_Non_Pragma (Variant);
7390 end loop;
7392 -- If we have an Unchecked_Union, use one of the parameters that
7393 -- captures the discriminants.
7395 if Is_Unchecked_Union (E) then
7396 Append_To (Result,
7397 Make_Case_Statement (Loc,
7398 Expression => New_Reference_To (Discr, Loc),
7399 Alternatives => Alt_List));
7401 else
7402 Append_To (Result,
7403 Make_Case_Statement (Loc,
7404 Expression =>
7405 Make_Selected_Component (Loc,
7406 Prefix => Make_Identifier (Loc, Name_X),
7407 Selector_Name => New_Copy (Name (Variant_Part (CL)))),
7408 Alternatives => Alt_List));
7409 end if;
7411 return Result;
7412 end Make_Eq_Case;
7414 ----------------
7415 -- Make_Eq_If --
7416 ----------------
7418 -- Generates:
7420 -- if
7421 -- X.C1 /= Y.C1
7422 -- or else
7423 -- X.C2 /= Y.C2
7424 -- ...
7425 -- then
7426 -- return False;
7427 -- end if;
7429 -- or a null statement if the list L is empty
7431 function Make_Eq_If
7432 (E : Entity_Id;
7433 L : List_Id) return Node_Id
7435 Loc : constant Source_Ptr := Sloc (E);
7436 C : Node_Id;
7437 Field_Name : Name_Id;
7438 Cond : Node_Id;
7440 begin
7441 if No (L) then
7442 return Make_Null_Statement (Loc);
7444 else
7445 Cond := Empty;
7447 C := First_Non_Pragma (L);
7448 while Present (C) loop
7449 Field_Name := Chars (Defining_Identifier (C));
7451 -- The tags must not be compared: they are not part of the value.
7452 -- Ditto for the controller component, if present.
7454 -- Note also that in the following, we use Make_Identifier for
7455 -- the component names. Use of New_Reference_To to identify the
7456 -- components would be incorrect because the wrong entities for
7457 -- discriminants could be picked up in the private type case.
7459 if Field_Name /= Name_uTag
7460 and then
7461 Field_Name /= Name_uController
7462 then
7463 Evolve_Or_Else (Cond,
7464 Make_Op_Ne (Loc,
7465 Left_Opnd =>
7466 Make_Selected_Component (Loc,
7467 Prefix => Make_Identifier (Loc, Name_X),
7468 Selector_Name =>
7469 Make_Identifier (Loc, Field_Name)),
7471 Right_Opnd =>
7472 Make_Selected_Component (Loc,
7473 Prefix => Make_Identifier (Loc, Name_Y),
7474 Selector_Name =>
7475 Make_Identifier (Loc, Field_Name))));
7476 end if;
7478 Next_Non_Pragma (C);
7479 end loop;
7481 if No (Cond) then
7482 return Make_Null_Statement (Loc);
7484 else
7485 return
7486 Make_Implicit_If_Statement (E,
7487 Condition => Cond,
7488 Then_Statements => New_List (
7489 Make_Simple_Return_Statement (Loc,
7490 Expression => New_Occurrence_Of (Standard_False, Loc))));
7491 end if;
7492 end if;
7493 end Make_Eq_If;
7495 -------------------------------
7496 -- Make_Null_Procedure_Specs --
7497 -------------------------------
7499 procedure Make_Null_Procedure_Specs
7500 (Tag_Typ : Entity_Id;
7501 Decl_List : out List_Id)
7503 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7504 Formal : Entity_Id;
7505 Formal_List : List_Id;
7506 Parent_Subp : Entity_Id;
7507 Prim_Elmt : Elmt_Id;
7508 Proc_Spec : Node_Id;
7509 Proc_Decl : Node_Id;
7510 Subp : Entity_Id;
7512 function Is_Null_Interface_Primitive (E : Entity_Id) return Boolean;
7513 -- Returns True if E is a null procedure that is an interface primitive
7515 ---------------------------------
7516 -- Is_Null_Interface_Primitive --
7517 ---------------------------------
7519 function Is_Null_Interface_Primitive (E : Entity_Id) return Boolean is
7520 begin
7521 return Comes_From_Source (E)
7522 and then Is_Dispatching_Operation (E)
7523 and then Ekind (E) = E_Procedure
7524 and then Null_Present (Parent (E))
7525 and then Is_Interface (Find_Dispatching_Type (E));
7526 end Is_Null_Interface_Primitive;
7528 -- Start of processing for Make_Null_Procedure_Specs
7530 begin
7531 Decl_List := New_List;
7532 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7533 while Present (Prim_Elmt) loop
7534 Subp := Node (Prim_Elmt);
7536 -- If a null procedure inherited from an interface has not been
7537 -- overridden, then we build a null procedure declaration to
7538 -- override the inherited procedure.
7540 Parent_Subp := Alias (Subp);
7542 if Present (Parent_Subp)
7543 and then Is_Null_Interface_Primitive (Parent_Subp)
7544 then
7545 Formal_List := No_List;
7546 Formal := First_Formal (Subp);
7548 if Present (Formal) then
7549 Formal_List := New_List;
7551 while Present (Formal) loop
7552 Append
7553 (Make_Parameter_Specification (Loc,
7554 Defining_Identifier =>
7555 Make_Defining_Identifier (Sloc (Formal),
7556 Chars => Chars (Formal)),
7557 In_Present => In_Present (Parent (Formal)),
7558 Out_Present => Out_Present (Parent (Formal)),
7559 Null_Exclusion_Present =>
7560 Null_Exclusion_Present (Parent (Formal)),
7561 Parameter_Type =>
7562 New_Occurrence_Of (Etype (Formal), Loc),
7563 Expression =>
7564 New_Copy_Tree (Expression (Parent (Formal)))),
7565 Formal_List);
7567 Next_Formal (Formal);
7568 end loop;
7569 end if;
7571 Proc_Spec :=
7572 Make_Procedure_Specification (Loc,
7573 Defining_Unit_Name =>
7574 Make_Defining_Identifier (Loc, Chars (Subp)),
7575 Parameter_Specifications => Formal_List);
7576 Set_Null_Present (Proc_Spec);
7578 Proc_Decl := Make_Subprogram_Declaration (Loc, Proc_Spec);
7579 Append_To (Decl_List, Proc_Decl);
7580 Analyze (Proc_Decl);
7581 end if;
7583 Next_Elmt (Prim_Elmt);
7584 end loop;
7585 end Make_Null_Procedure_Specs;
7587 -------------------------------------
7588 -- Make_Predefined_Primitive_Specs --
7589 -------------------------------------
7591 procedure Make_Predefined_Primitive_Specs
7592 (Tag_Typ : Entity_Id;
7593 Predef_List : out List_Id;
7594 Renamed_Eq : out Entity_Id)
7596 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7597 Res : constant List_Id := New_List;
7598 Prim : Elmt_Id;
7599 Eq_Needed : Boolean;
7600 Eq_Spec : Node_Id;
7601 Eq_Name : Name_Id := Name_Op_Eq;
7603 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
7604 -- Returns true if Prim is a renaming of an unresolved predefined
7605 -- equality operation.
7607 -------------------------------
7608 -- Is_Predefined_Eq_Renaming --
7609 -------------------------------
7611 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
7612 begin
7613 return Chars (Prim) /= Name_Op_Eq
7614 and then Present (Alias (Prim))
7615 and then Comes_From_Source (Prim)
7616 and then Is_Intrinsic_Subprogram (Alias (Prim))
7617 and then Chars (Alias (Prim)) = Name_Op_Eq;
7618 end Is_Predefined_Eq_Renaming;
7620 -- Start of processing for Make_Predefined_Primitive_Specs
7622 begin
7623 Renamed_Eq := Empty;
7625 -- Spec of _Size
7627 Append_To (Res, Predef_Spec_Or_Body (Loc,
7628 Tag_Typ => Tag_Typ,
7629 Name => Name_uSize,
7630 Profile => New_List (
7631 Make_Parameter_Specification (Loc,
7632 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7633 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7635 Ret_Type => Standard_Long_Long_Integer));
7637 -- Spec of _Alignment
7639 Append_To (Res, Predef_Spec_Or_Body (Loc,
7640 Tag_Typ => Tag_Typ,
7641 Name => Name_uAlignment,
7642 Profile => New_List (
7643 Make_Parameter_Specification (Loc,
7644 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7645 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7647 Ret_Type => Standard_Integer));
7649 -- Specs for dispatching stream attributes
7651 declare
7652 Stream_Op_TSS_Names :
7653 constant array (Integer range <>) of TSS_Name_Type :=
7654 (TSS_Stream_Read,
7655 TSS_Stream_Write,
7656 TSS_Stream_Input,
7657 TSS_Stream_Output);
7659 begin
7660 for Op in Stream_Op_TSS_Names'Range loop
7661 if Stream_Operation_OK (Tag_Typ, Stream_Op_TSS_Names (Op)) then
7662 Append_To (Res,
7663 Predef_Stream_Attr_Spec (Loc, Tag_Typ,
7664 Stream_Op_TSS_Names (Op)));
7665 end if;
7666 end loop;
7667 end;
7669 -- Spec of "=" is expanded if the type is not limited and if a
7670 -- user defined "=" was not already declared for the non-full
7671 -- view of a private extension
7673 if not Is_Limited_Type (Tag_Typ) then
7674 Eq_Needed := True;
7675 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
7676 while Present (Prim) loop
7678 -- If a primitive is encountered that renames the predefined
7679 -- equality operator before reaching any explicit equality
7680 -- primitive, then we still need to create a predefined
7681 -- equality function, because calls to it can occur via
7682 -- the renaming. A new name is created for the equality
7683 -- to avoid conflicting with any user-defined equality.
7684 -- (Note that this doesn't account for renamings of
7685 -- equality nested within subpackages???)
7687 if Is_Predefined_Eq_Renaming (Node (Prim)) then
7688 Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
7690 -- User-defined equality
7692 elsif Chars (Node (Prim)) = Name_Op_Eq
7693 and then Etype (First_Formal (Node (Prim))) =
7694 Etype (Next_Formal (First_Formal (Node (Prim))))
7695 and then Base_Type (Etype (Node (Prim))) = Standard_Boolean
7696 then
7697 if No (Alias (Node (Prim)))
7698 or else Nkind (Unit_Declaration_Node (Node (Prim))) =
7699 N_Subprogram_Renaming_Declaration
7700 then
7701 Eq_Needed := False;
7702 exit;
7704 -- If the parent is not an interface type and has an abstract
7705 -- equality function, the inherited equality is abstract as
7706 -- well, and no body can be created for it.
7708 elsif not Is_Interface (Etype (Tag_Typ))
7709 and then Present (Alias (Node (Prim)))
7710 and then Is_Abstract_Subprogram (Alias (Node (Prim)))
7711 then
7712 Eq_Needed := False;
7713 exit;
7715 -- If the type has an equality function corresponding with
7716 -- a primitive defined in an interface type, the inherited
7717 -- equality is abstract as well, and no body can be created
7718 -- for it.
7720 elsif Present (Alias (Node (Prim)))
7721 and then Comes_From_Source (Ultimate_Alias (Node (Prim)))
7722 and then
7723 Is_Interface
7724 (Find_Dispatching_Type (Ultimate_Alias (Node (Prim))))
7725 then
7726 Eq_Needed := False;
7727 exit;
7728 end if;
7729 end if;
7731 Next_Elmt (Prim);
7732 end loop;
7734 -- If a renaming of predefined equality was found but there was no
7735 -- user-defined equality (so Eq_Needed is still true), then set the
7736 -- name back to Name_Op_Eq. But in the case where a user-defined
7737 -- equality was located after such a renaming, then the predefined
7738 -- equality function is still needed, so Eq_Needed must be set back
7739 -- to True.
7741 if Eq_Name /= Name_Op_Eq then
7742 if Eq_Needed then
7743 Eq_Name := Name_Op_Eq;
7744 else
7745 Eq_Needed := True;
7746 end if;
7747 end if;
7749 if Eq_Needed then
7750 Eq_Spec := Predef_Spec_Or_Body (Loc,
7751 Tag_Typ => Tag_Typ,
7752 Name => Eq_Name,
7753 Profile => New_List (
7754 Make_Parameter_Specification (Loc,
7755 Defining_Identifier =>
7756 Make_Defining_Identifier (Loc, Name_X),
7757 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
7758 Make_Parameter_Specification (Loc,
7759 Defining_Identifier =>
7760 Make_Defining_Identifier (Loc, Name_Y),
7761 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7762 Ret_Type => Standard_Boolean);
7763 Append_To (Res, Eq_Spec);
7765 if Eq_Name /= Name_Op_Eq then
7766 Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
7768 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
7769 while Present (Prim) loop
7771 -- Any renamings of equality that appeared before an
7772 -- overriding equality must be updated to refer to the
7773 -- entity for the predefined equality, otherwise calls via
7774 -- the renaming would get incorrectly resolved to call the
7775 -- user-defined equality function.
7777 if Is_Predefined_Eq_Renaming (Node (Prim)) then
7778 Set_Alias (Node (Prim), Renamed_Eq);
7780 -- Exit upon encountering a user-defined equality
7782 elsif Chars (Node (Prim)) = Name_Op_Eq
7783 and then No (Alias (Node (Prim)))
7784 then
7785 exit;
7786 end if;
7788 Next_Elmt (Prim);
7789 end loop;
7790 end if;
7791 end if;
7793 -- Spec for dispatching assignment
7795 Append_To (Res, Predef_Spec_Or_Body (Loc,
7796 Tag_Typ => Tag_Typ,
7797 Name => Name_uAssign,
7798 Profile => New_List (
7799 Make_Parameter_Specification (Loc,
7800 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7801 Out_Present => True,
7802 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
7804 Make_Parameter_Specification (Loc,
7805 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
7806 Parameter_Type => New_Reference_To (Tag_Typ, Loc)))));
7807 end if;
7809 -- Ada 2005: Generate declarations for the following primitive
7810 -- operations for limited interfaces and synchronized types that
7811 -- implement a limited interface.
7813 -- Disp_Asynchronous_Select
7814 -- Disp_Conditional_Select
7815 -- Disp_Get_Prim_Op_Kind
7816 -- Disp_Get_Task_Id
7817 -- Disp_Requeue
7818 -- Disp_Timed_Select
7820 -- These operations cannot be implemented on VM targets, so we simply
7821 -- disable their generation in this case. We also disable generation
7822 -- of these bodies if No_Dispatching_Calls is active.
7824 if Ada_Version >= Ada_05
7825 and then VM_Target = No_VM
7826 and then RTE_Available (RE_Select_Specific_Data)
7827 then
7828 -- These primitives are defined abstract in interface types
7830 if Is_Interface (Tag_Typ)
7831 and then Is_Limited_Record (Tag_Typ)
7832 then
7833 Append_To (Res,
7834 Make_Abstract_Subprogram_Declaration (Loc,
7835 Specification =>
7836 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
7838 Append_To (Res,
7839 Make_Abstract_Subprogram_Declaration (Loc,
7840 Specification =>
7841 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
7843 Append_To (Res,
7844 Make_Abstract_Subprogram_Declaration (Loc,
7845 Specification =>
7846 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
7848 Append_To (Res,
7849 Make_Abstract_Subprogram_Declaration (Loc,
7850 Specification =>
7851 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
7853 Append_To (Res,
7854 Make_Abstract_Subprogram_Declaration (Loc,
7855 Specification =>
7856 Make_Disp_Requeue_Spec (Tag_Typ)));
7858 Append_To (Res,
7859 Make_Abstract_Subprogram_Declaration (Loc,
7860 Specification =>
7861 Make_Disp_Timed_Select_Spec (Tag_Typ)));
7863 -- If the ancestor is an interface type we declare non-abstract
7864 -- primitives to override the abstract primitives of the interface
7865 -- type.
7867 elsif (not Is_Interface (Tag_Typ)
7868 and then Is_Interface (Etype (Tag_Typ))
7869 and then Is_Limited_Record (Etype (Tag_Typ)))
7870 or else
7871 (Is_Concurrent_Record_Type (Tag_Typ)
7872 and then Has_Interfaces (Tag_Typ))
7873 then
7874 Append_To (Res,
7875 Make_Subprogram_Declaration (Loc,
7876 Specification =>
7877 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
7879 Append_To (Res,
7880 Make_Subprogram_Declaration (Loc,
7881 Specification =>
7882 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
7884 Append_To (Res,
7885 Make_Subprogram_Declaration (Loc,
7886 Specification =>
7887 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
7889 Append_To (Res,
7890 Make_Subprogram_Declaration (Loc,
7891 Specification =>
7892 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
7894 Append_To (Res,
7895 Make_Subprogram_Declaration (Loc,
7896 Specification =>
7897 Make_Disp_Requeue_Spec (Tag_Typ)));
7899 Append_To (Res,
7900 Make_Subprogram_Declaration (Loc,
7901 Specification =>
7902 Make_Disp_Timed_Select_Spec (Tag_Typ)));
7903 end if;
7904 end if;
7906 -- Specs for finalization actions that may be required in case a future
7907 -- extension contain a controlled element. We generate those only for
7908 -- root tagged types where they will get dummy bodies or when the type
7909 -- has controlled components and their body must be generated. It is
7910 -- also impossible to provide those for tagged types defined within
7911 -- s-finimp since it would involve circularity problems
7913 if In_Finalization_Root (Tag_Typ) then
7914 null;
7916 -- We also skip these if finalization is not available
7918 elsif Restriction_Active (No_Finalization) then
7919 null;
7921 elsif Etype (Tag_Typ) = Tag_Typ
7922 or else Needs_Finalization (Tag_Typ)
7924 -- Ada 2005 (AI-251): We must also generate these subprograms if
7925 -- the immediate ancestor is an interface to ensure the correct
7926 -- initialization of its dispatch table.
7928 or else (not Is_Interface (Tag_Typ)
7929 and then Is_Interface (Etype (Tag_Typ)))
7931 -- Ada 205 (AI-251): We must also generate these subprograms if
7932 -- the parent of an nonlimited interface is a limited interface
7934 or else (Is_Interface (Tag_Typ)
7935 and then not Is_Limited_Interface (Tag_Typ)
7936 and then Is_Limited_Interface (Etype (Tag_Typ)))
7937 then
7938 if not Is_Limited_Type (Tag_Typ) then
7939 Append_To (Res,
7940 Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
7941 end if;
7943 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
7944 end if;
7946 Predef_List := Res;
7947 end Make_Predefined_Primitive_Specs;
7949 ---------------------------------
7950 -- Needs_Simple_Initialization --
7951 ---------------------------------
7953 function Needs_Simple_Initialization (T : Entity_Id) return Boolean is
7954 begin
7955 -- Check for private type, in which case test applies to the underlying
7956 -- type of the private type.
7958 if Is_Private_Type (T) then
7959 declare
7960 RT : constant Entity_Id := Underlying_Type (T);
7962 begin
7963 if Present (RT) then
7964 return Needs_Simple_Initialization (RT);
7965 else
7966 return False;
7967 end if;
7968 end;
7970 -- Cases needing simple initialization are access types, and, if pragma
7971 -- Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
7972 -- types.
7974 elsif Is_Access_Type (T)
7975 or else (Init_Or_Norm_Scalars and then (Is_Scalar_Type (T)))
7976 then
7977 return True;
7979 -- If Initialize/Normalize_Scalars is in effect, string objects also
7980 -- need initialization, unless they are created in the course of
7981 -- expanding an aggregate (since in the latter case they will be
7982 -- filled with appropriate initializing values before they are used).
7984 elsif Init_Or_Norm_Scalars
7985 and then
7986 (Root_Type (T) = Standard_String
7987 or else Root_Type (T) = Standard_Wide_String
7988 or else Root_Type (T) = Standard_Wide_Wide_String)
7989 and then
7990 (not Is_Itype (T)
7991 or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
7992 then
7993 return True;
7995 else
7996 return False;
7997 end if;
7998 end Needs_Simple_Initialization;
8000 ----------------------
8001 -- Predef_Deep_Spec --
8002 ----------------------
8004 function Predef_Deep_Spec
8005 (Loc : Source_Ptr;
8006 Tag_Typ : Entity_Id;
8007 Name : TSS_Name_Type;
8008 For_Body : Boolean := False) return Node_Id
8010 Prof : List_Id;
8011 Type_B : Entity_Id;
8013 begin
8014 if Name = TSS_Deep_Finalize then
8015 Prof := New_List;
8016 Type_B := Standard_Boolean;
8018 else
8019 Prof := New_List (
8020 Make_Parameter_Specification (Loc,
8021 Defining_Identifier => Make_Defining_Identifier (Loc, Name_L),
8022 In_Present => True,
8023 Out_Present => True,
8024 Parameter_Type =>
8025 New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
8026 Type_B := Standard_Short_Short_Integer;
8027 end if;
8029 Append_To (Prof,
8030 Make_Parameter_Specification (Loc,
8031 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
8032 In_Present => True,
8033 Out_Present => True,
8034 Parameter_Type => New_Reference_To (Tag_Typ, Loc)));
8036 Append_To (Prof,
8037 Make_Parameter_Specification (Loc,
8038 Defining_Identifier => Make_Defining_Identifier (Loc, Name_B),
8039 Parameter_Type => New_Reference_To (Type_B, Loc)));
8041 return Predef_Spec_Or_Body (Loc,
8042 Name => Make_TSS_Name (Tag_Typ, Name),
8043 Tag_Typ => Tag_Typ,
8044 Profile => Prof,
8045 For_Body => For_Body);
8047 exception
8048 when RE_Not_Available =>
8049 return Empty;
8050 end Predef_Deep_Spec;
8052 -------------------------
8053 -- Predef_Spec_Or_Body --
8054 -------------------------
8056 function Predef_Spec_Or_Body
8057 (Loc : Source_Ptr;
8058 Tag_Typ : Entity_Id;
8059 Name : Name_Id;
8060 Profile : List_Id;
8061 Ret_Type : Entity_Id := Empty;
8062 For_Body : Boolean := False) return Node_Id
8064 Id : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
8065 Spec : Node_Id;
8067 begin
8068 Set_Is_Public (Id, Is_Public (Tag_Typ));
8070 -- The internal flag is set to mark these declarations because they have
8071 -- specific properties. First, they are primitives even if they are not
8072 -- defined in the type scope (the freezing point is not necessarily in
8073 -- the same scope). Second, the predefined equality can be overridden by
8074 -- a user-defined equality, no body will be generated in this case.
8076 Set_Is_Internal (Id);
8078 if not Debug_Generated_Code then
8079 Set_Debug_Info_Off (Id);
8080 end if;
8082 if No (Ret_Type) then
8083 Spec :=
8084 Make_Procedure_Specification (Loc,
8085 Defining_Unit_Name => Id,
8086 Parameter_Specifications => Profile);
8087 else
8088 Spec :=
8089 Make_Function_Specification (Loc,
8090 Defining_Unit_Name => Id,
8091 Parameter_Specifications => Profile,
8092 Result_Definition =>
8093 New_Reference_To (Ret_Type, Loc));
8094 end if;
8096 if Is_Interface (Tag_Typ) then
8097 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
8099 -- If body case, return empty subprogram body. Note that this is ill-
8100 -- formed, because there is not even a null statement, and certainly not
8101 -- a return in the function case. The caller is expected to do surgery
8102 -- on the body to add the appropriate stuff.
8104 elsif For_Body then
8105 return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
8107 -- For the case of an Input attribute predefined for an abstract type,
8108 -- generate an abstract specification. This will never be called, but we
8109 -- need the slot allocated in the dispatching table so that attributes
8110 -- typ'Class'Input and typ'Class'Output will work properly.
8112 elsif Is_TSS (Name, TSS_Stream_Input)
8113 and then Is_Abstract_Type (Tag_Typ)
8114 then
8115 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
8117 -- Normal spec case, where we return a subprogram declaration
8119 else
8120 return Make_Subprogram_Declaration (Loc, Spec);
8121 end if;
8122 end Predef_Spec_Or_Body;
8124 -----------------------------
8125 -- Predef_Stream_Attr_Spec --
8126 -----------------------------
8128 function Predef_Stream_Attr_Spec
8129 (Loc : Source_Ptr;
8130 Tag_Typ : Entity_Id;
8131 Name : TSS_Name_Type;
8132 For_Body : Boolean := False) return Node_Id
8134 Ret_Type : Entity_Id;
8136 begin
8137 if Name = TSS_Stream_Input then
8138 Ret_Type := Tag_Typ;
8139 else
8140 Ret_Type := Empty;
8141 end if;
8143 return Predef_Spec_Or_Body (Loc,
8144 Name => Make_TSS_Name (Tag_Typ, Name),
8145 Tag_Typ => Tag_Typ,
8146 Profile => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
8147 Ret_Type => Ret_Type,
8148 For_Body => For_Body);
8149 end Predef_Stream_Attr_Spec;
8151 ---------------------------------
8152 -- Predefined_Primitive_Bodies --
8153 ---------------------------------
8155 function Predefined_Primitive_Bodies
8156 (Tag_Typ : Entity_Id;
8157 Renamed_Eq : Entity_Id) return List_Id
8159 Loc : constant Source_Ptr := Sloc (Tag_Typ);
8160 Res : constant List_Id := New_List;
8161 Decl : Node_Id;
8162 Prim : Elmt_Id;
8163 Eq_Needed : Boolean;
8164 Eq_Name : Name_Id;
8165 Ent : Entity_Id;
8167 pragma Warnings (Off, Ent);
8169 begin
8170 pragma Assert (not Is_Interface (Tag_Typ));
8172 -- See if we have a predefined "=" operator
8174 if Present (Renamed_Eq) then
8175 Eq_Needed := True;
8176 Eq_Name := Chars (Renamed_Eq);
8178 -- If the parent is an interface type then it has defined all the
8179 -- predefined primitives abstract and we need to check if the type
8180 -- has some user defined "=" function to avoid generating it.
8182 elsif Is_Interface (Etype (Tag_Typ)) then
8183 Eq_Needed := True;
8184 Eq_Name := Name_Op_Eq;
8186 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
8187 while Present (Prim) loop
8188 if Chars (Node (Prim)) = Name_Op_Eq
8189 and then not Is_Internal (Node (Prim))
8190 then
8191 Eq_Needed := False;
8192 Eq_Name := No_Name;
8193 exit;
8194 end if;
8196 Next_Elmt (Prim);
8197 end loop;
8199 else
8200 Eq_Needed := False;
8201 Eq_Name := No_Name;
8203 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
8204 while Present (Prim) loop
8205 if Chars (Node (Prim)) = Name_Op_Eq
8206 and then Is_Internal (Node (Prim))
8207 then
8208 Eq_Needed := True;
8209 Eq_Name := Name_Op_Eq;
8210 exit;
8211 end if;
8213 Next_Elmt (Prim);
8214 end loop;
8215 end if;
8217 -- Body of _Alignment
8219 Decl := Predef_Spec_Or_Body (Loc,
8220 Tag_Typ => Tag_Typ,
8221 Name => Name_uAlignment,
8222 Profile => New_List (
8223 Make_Parameter_Specification (Loc,
8224 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
8225 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8227 Ret_Type => Standard_Integer,
8228 For_Body => True);
8230 Set_Handled_Statement_Sequence (Decl,
8231 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8232 Make_Simple_Return_Statement (Loc,
8233 Expression =>
8234 Make_Attribute_Reference (Loc,
8235 Prefix => Make_Identifier (Loc, Name_X),
8236 Attribute_Name => Name_Alignment)))));
8238 Append_To (Res, Decl);
8240 -- Body of _Size
8242 Decl := Predef_Spec_Or_Body (Loc,
8243 Tag_Typ => Tag_Typ,
8244 Name => Name_uSize,
8245 Profile => New_List (
8246 Make_Parameter_Specification (Loc,
8247 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
8248 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8250 Ret_Type => Standard_Long_Long_Integer,
8251 For_Body => True);
8253 Set_Handled_Statement_Sequence (Decl,
8254 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8255 Make_Simple_Return_Statement (Loc,
8256 Expression =>
8257 Make_Attribute_Reference (Loc,
8258 Prefix => Make_Identifier (Loc, Name_X),
8259 Attribute_Name => Name_Size)))));
8261 Append_To (Res, Decl);
8263 -- Bodies for Dispatching stream IO routines. We need these only for
8264 -- non-limited types (in the limited case there is no dispatching).
8265 -- We also skip them if dispatching or finalization are not available.
8267 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Read)
8268 and then No (TSS (Tag_Typ, TSS_Stream_Read))
8269 then
8270 Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
8271 Append_To (Res, Decl);
8272 end if;
8274 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Write)
8275 and then No (TSS (Tag_Typ, TSS_Stream_Write))
8276 then
8277 Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
8278 Append_To (Res, Decl);
8279 end if;
8281 -- Skip body of _Input for the abstract case, since the corresponding
8282 -- spec is abstract (see Predef_Spec_Or_Body).
8284 if not Is_Abstract_Type (Tag_Typ)
8285 and then Stream_Operation_OK (Tag_Typ, TSS_Stream_Input)
8286 and then No (TSS (Tag_Typ, TSS_Stream_Input))
8287 then
8288 Build_Record_Or_Elementary_Input_Function
8289 (Loc, Tag_Typ, Decl, Ent);
8290 Append_To (Res, Decl);
8291 end if;
8293 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Output)
8294 and then No (TSS (Tag_Typ, TSS_Stream_Output))
8295 then
8296 Build_Record_Or_Elementary_Output_Procedure
8297 (Loc, Tag_Typ, Decl, Ent);
8298 Append_To (Res, Decl);
8299 end if;
8301 -- Ada 2005: Generate bodies for the following primitive operations for
8302 -- limited interfaces and synchronized types that implement a limited
8303 -- interface.
8305 -- disp_asynchronous_select
8306 -- disp_conditional_select
8307 -- disp_get_prim_op_kind
8308 -- disp_get_task_id
8309 -- disp_timed_select
8311 -- The interface versions will have null bodies
8313 -- These operations cannot be implemented on VM targets, so we simply
8314 -- disable their generation in this case. We also disable generation
8315 -- of these bodies if No_Dispatching_Calls is active.
8317 if Ada_Version >= Ada_05
8318 and then VM_Target = No_VM
8319 and then not Restriction_Active (No_Dispatching_Calls)
8320 and then not Is_Interface (Tag_Typ)
8321 and then
8322 ((Is_Interface (Etype (Tag_Typ))
8323 and then Is_Limited_Record (Etype (Tag_Typ)))
8324 or else (Is_Concurrent_Record_Type (Tag_Typ)
8325 and then Has_Interfaces (Tag_Typ)))
8326 and then RTE_Available (RE_Select_Specific_Data)
8327 then
8328 Append_To (Res, Make_Disp_Asynchronous_Select_Body (Tag_Typ));
8329 Append_To (Res, Make_Disp_Conditional_Select_Body (Tag_Typ));
8330 Append_To (Res, Make_Disp_Get_Prim_Op_Kind_Body (Tag_Typ));
8331 Append_To (Res, Make_Disp_Get_Task_Id_Body (Tag_Typ));
8332 Append_To (Res, Make_Disp_Requeue_Body (Tag_Typ));
8333 Append_To (Res, Make_Disp_Timed_Select_Body (Tag_Typ));
8334 end if;
8336 if not Is_Limited_Type (Tag_Typ)
8337 and then not Is_Interface (Tag_Typ)
8338 then
8339 -- Body for equality
8341 if Eq_Needed then
8342 Decl :=
8343 Predef_Spec_Or_Body (Loc,
8344 Tag_Typ => Tag_Typ,
8345 Name => Eq_Name,
8346 Profile => New_List (
8347 Make_Parameter_Specification (Loc,
8348 Defining_Identifier =>
8349 Make_Defining_Identifier (Loc, Name_X),
8350 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
8352 Make_Parameter_Specification (Loc,
8353 Defining_Identifier =>
8354 Make_Defining_Identifier (Loc, Name_Y),
8355 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8357 Ret_Type => Standard_Boolean,
8358 For_Body => True);
8360 declare
8361 Def : constant Node_Id := Parent (Tag_Typ);
8362 Stmts : constant List_Id := New_List;
8363 Variant_Case : Boolean := Has_Discriminants (Tag_Typ);
8364 Comps : Node_Id := Empty;
8365 Typ_Def : Node_Id := Type_Definition (Def);
8367 begin
8368 if Variant_Case then
8369 if Nkind (Typ_Def) = N_Derived_Type_Definition then
8370 Typ_Def := Record_Extension_Part (Typ_Def);
8371 end if;
8373 if Present (Typ_Def) then
8374 Comps := Component_List (Typ_Def);
8375 end if;
8377 Variant_Case := Present (Comps)
8378 and then Present (Variant_Part (Comps));
8379 end if;
8381 if Variant_Case then
8382 Append_To (Stmts,
8383 Make_Eq_If (Tag_Typ, Discriminant_Specifications (Def)));
8384 Append_List_To (Stmts, Make_Eq_Case (Tag_Typ, Comps));
8385 Append_To (Stmts,
8386 Make_Simple_Return_Statement (Loc,
8387 Expression => New_Reference_To (Standard_True, Loc)));
8389 else
8390 Append_To (Stmts,
8391 Make_Simple_Return_Statement (Loc,
8392 Expression =>
8393 Expand_Record_Equality (Tag_Typ,
8394 Typ => Tag_Typ,
8395 Lhs => Make_Identifier (Loc, Name_X),
8396 Rhs => Make_Identifier (Loc, Name_Y),
8397 Bodies => Declarations (Decl))));
8398 end if;
8400 Set_Handled_Statement_Sequence (Decl,
8401 Make_Handled_Sequence_Of_Statements (Loc, Stmts));
8402 end;
8403 Append_To (Res, Decl);
8404 end if;
8406 -- Body for dispatching assignment
8408 Decl :=
8409 Predef_Spec_Or_Body (Loc,
8410 Tag_Typ => Tag_Typ,
8411 Name => Name_uAssign,
8412 Profile => New_List (
8413 Make_Parameter_Specification (Loc,
8414 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
8415 Out_Present => True,
8416 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
8418 Make_Parameter_Specification (Loc,
8419 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
8420 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8421 For_Body => True);
8423 Set_Handled_Statement_Sequence (Decl,
8424 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8425 Make_Assignment_Statement (Loc,
8426 Name => Make_Identifier (Loc, Name_X),
8427 Expression => Make_Identifier (Loc, Name_Y)))));
8429 Append_To (Res, Decl);
8430 end if;
8432 -- Generate dummy bodies for finalization actions of types that have
8433 -- no controlled components.
8435 -- Skip this processing if we are in the finalization routine in the
8436 -- runtime itself, otherwise we get hopelessly circularly confused!
8438 if In_Finalization_Root (Tag_Typ) then
8439 null;
8441 -- Skip this if finalization is not available
8443 elsif Restriction_Active (No_Finalization) then
8444 null;
8446 elsif (Etype (Tag_Typ) = Tag_Typ
8447 or else Is_Controlled (Tag_Typ)
8449 -- Ada 2005 (AI-251): We must also generate these subprograms
8450 -- if the immediate ancestor of Tag_Typ is an interface to
8451 -- ensure the correct initialization of its dispatch table.
8453 or else (not Is_Interface (Tag_Typ)
8454 and then
8455 Is_Interface (Etype (Tag_Typ))))
8456 and then not Has_Controlled_Component (Tag_Typ)
8457 then
8458 if not Is_Limited_Type (Tag_Typ) then
8459 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
8461 if Is_Controlled (Tag_Typ) then
8462 Set_Handled_Statement_Sequence (Decl,
8463 Make_Handled_Sequence_Of_Statements (Loc,
8464 Make_Adjust_Call (
8465 Ref => Make_Identifier (Loc, Name_V),
8466 Typ => Tag_Typ,
8467 Flist_Ref => Make_Identifier (Loc, Name_L),
8468 With_Attach => Make_Identifier (Loc, Name_B))));
8470 else
8471 Set_Handled_Statement_Sequence (Decl,
8472 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8473 Make_Null_Statement (Loc))));
8474 end if;
8476 Append_To (Res, Decl);
8477 end if;
8479 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
8481 if Is_Controlled (Tag_Typ) then
8482 Set_Handled_Statement_Sequence (Decl,
8483 Make_Handled_Sequence_Of_Statements (Loc,
8484 Make_Final_Call (
8485 Ref => Make_Identifier (Loc, Name_V),
8486 Typ => Tag_Typ,
8487 With_Detach => Make_Identifier (Loc, Name_B))));
8489 else
8490 Set_Handled_Statement_Sequence (Decl,
8491 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8492 Make_Null_Statement (Loc))));
8493 end if;
8495 Append_To (Res, Decl);
8496 end if;
8498 return Res;
8499 end Predefined_Primitive_Bodies;
8501 ---------------------------------
8502 -- Predefined_Primitive_Freeze --
8503 ---------------------------------
8505 function Predefined_Primitive_Freeze
8506 (Tag_Typ : Entity_Id) return List_Id
8508 Loc : constant Source_Ptr := Sloc (Tag_Typ);
8509 Res : constant List_Id := New_List;
8510 Prim : Elmt_Id;
8511 Frnodes : List_Id;
8513 begin
8514 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
8515 while Present (Prim) loop
8516 if Is_Predefined_Dispatching_Operation (Node (Prim)) then
8517 Frnodes := Freeze_Entity (Node (Prim), Loc);
8519 if Present (Frnodes) then
8520 Append_List_To (Res, Frnodes);
8521 end if;
8522 end if;
8524 Next_Elmt (Prim);
8525 end loop;
8527 return Res;
8528 end Predefined_Primitive_Freeze;
8530 -------------------------
8531 -- Stream_Operation_OK --
8532 -------------------------
8534 function Stream_Operation_OK
8535 (Typ : Entity_Id;
8536 Operation : TSS_Name_Type) return Boolean
8538 Has_Predefined_Or_Specified_Stream_Attribute : Boolean := False;
8540 begin
8541 -- Special case of a limited type extension: a default implementation
8542 -- of the stream attributes Read or Write exists if that attribute
8543 -- has been specified or is available for an ancestor type; a default
8544 -- implementation of the attribute Output (resp. Input) exists if the
8545 -- attribute has been specified or Write (resp. Read) is available for
8546 -- an ancestor type. The last condition only applies under Ada 2005.
8548 if Is_Limited_Type (Typ)
8549 and then Is_Tagged_Type (Typ)
8550 then
8551 if Operation = TSS_Stream_Read then
8552 Has_Predefined_Or_Specified_Stream_Attribute :=
8553 Has_Specified_Stream_Read (Typ);
8555 elsif Operation = TSS_Stream_Write then
8556 Has_Predefined_Or_Specified_Stream_Attribute :=
8557 Has_Specified_Stream_Write (Typ);
8559 elsif Operation = TSS_Stream_Input then
8560 Has_Predefined_Or_Specified_Stream_Attribute :=
8561 Has_Specified_Stream_Input (Typ)
8562 or else
8563 (Ada_Version >= Ada_05
8564 and then Stream_Operation_OK (Typ, TSS_Stream_Read));
8566 elsif Operation = TSS_Stream_Output then
8567 Has_Predefined_Or_Specified_Stream_Attribute :=
8568 Has_Specified_Stream_Output (Typ)
8569 or else
8570 (Ada_Version >= Ada_05
8571 and then Stream_Operation_OK (Typ, TSS_Stream_Write));
8572 end if;
8574 -- Case of inherited TSS_Stream_Read or TSS_Stream_Write
8576 if not Has_Predefined_Or_Specified_Stream_Attribute
8577 and then Is_Derived_Type (Typ)
8578 and then (Operation = TSS_Stream_Read
8579 or else Operation = TSS_Stream_Write)
8580 then
8581 Has_Predefined_Or_Specified_Stream_Attribute :=
8582 Present
8583 (Find_Inherited_TSS (Base_Type (Etype (Typ)), Operation));
8584 end if;
8585 end if;
8587 -- If the type is not limited, or else is limited but the attribute is
8588 -- explicitly specified or is predefined for the type, then return True,
8589 -- unless other conditions prevail, such as restrictions prohibiting
8590 -- streams or dispatching operations.
8592 -- We exclude the Input operation from being a predefined subprogram in
8593 -- the case where the associated type is an abstract extension, because
8594 -- the attribute is not callable in that case, per 13.13.2(49/2). Also,
8595 -- we don't want an abstract version created because types derived from
8596 -- the abstract type may not even have Input available (for example if
8597 -- derived from a private view of the abstract type that doesn't have
8598 -- a visible Input), but a VM such as .NET or the Java VM can treat the
8599 -- operation as inherited anyway, and we don't want an abstract function
8600 -- to be (implicitly) inherited in that case because it can lead to a VM
8601 -- exception.
8603 return (not Is_Limited_Type (Typ)
8604 or else Has_Predefined_Or_Specified_Stream_Attribute)
8605 and then (Operation /= TSS_Stream_Input
8606 or else not Is_Abstract_Type (Typ)
8607 or else not Is_Derived_Type (Typ))
8608 and then not Has_Unknown_Discriminants (Typ)
8609 and then not (Is_Interface (Typ)
8610 and then (Is_Task_Interface (Typ)
8611 or else Is_Protected_Interface (Typ)
8612 or else Is_Synchronized_Interface (Typ)))
8613 and then not Restriction_Active (No_Streams)
8614 and then not Restriction_Active (No_Dispatch)
8615 and then not No_Run_Time_Mode
8616 and then RTE_Available (RE_Tag)
8617 and then RTE_Available (RE_Root_Stream_Type);
8618 end Stream_Operation_OK;
8620 end Exp_Ch3;