mips.h (set_volatile): Delete.
[official-gcc.git] / gcc / ada / exp_ch3.adb
blob6be11a7f640c0376a65182c585b0dbcfe1183dfd
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-2007, 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_Attr; use Sem_Attr;
53 with Sem_Cat; use Sem_Cat;
54 with Sem_Ch3; use Sem_Ch3;
55 with Sem_Ch8; use Sem_Ch8;
56 with Sem_Disp; use Sem_Disp;
57 with Sem_Eval; use Sem_Eval;
58 with Sem_Mech; use Sem_Mech;
59 with Sem_Res; use Sem_Res;
60 with Sem_Util; use Sem_Util;
61 with Sinfo; use Sinfo;
62 with Stand; use Stand;
63 with Snames; use Snames;
64 with Targparm; use Targparm;
65 with Tbuild; use Tbuild;
66 with Ttypes; use Ttypes;
67 with Validsw; use Validsw;
69 package body Exp_Ch3 is
71 -----------------------
72 -- Local Subprograms --
73 -----------------------
75 function Add_Final_Chain (Def_Id : Entity_Id) return Entity_Id;
76 -- Add the declaration of a finalization list to the freeze actions for
77 -- Def_Id, and return its defining identifier.
79 procedure Adjust_Discriminants (Rtype : Entity_Id);
80 -- This is used when freezing a record type. It attempts to construct
81 -- more restrictive subtypes for discriminants so that the max size of
82 -- the record can be calculated more accurately. See the body of this
83 -- procedure for details.
85 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id);
86 -- Build initialization procedure for given array type. Nod is a node
87 -- used for attachment of any actions required in its construction.
88 -- It also supplies the source location used for the procedure.
90 function Build_Discriminant_Formals
91 (Rec_Id : Entity_Id;
92 Use_Dl : Boolean) return List_Id;
93 -- This function uses the discriminants of a type to build a list of
94 -- formal parameters, used in the following function. If the flag Use_Dl
95 -- is set, the list is built using the already defined discriminals
96 -- of the type. Otherwise new identifiers are created, with the source
97 -- names of the discriminants.
99 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id;
100 -- This function builds a static aggregate that can serve as the initial
101 -- value for an array type whose bounds are static, and whose component
102 -- type is a composite type that has a static equivalent aggregate.
103 -- The equivalent array aggregate is used both for object initialization
104 -- and for component initialization, when used in the following function.
106 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id;
107 -- This function builds a static aggregate that can serve as the initial
108 -- value for a record type whose components are scalar and initialized
109 -- with compile-time values, or arrays with similar initialization or
110 -- defaults. When possible, initialization of an object of the type can
111 -- be achieved by using a copy of the aggregate as an initial value, thus
112 -- removing the implicit call that would otherwise constitute elaboration
113 -- code.
115 function Build_Master_Renaming
116 (N : Node_Id;
117 T : Entity_Id) return Entity_Id;
118 -- If the designated type of an access type is a task type or contains
119 -- tasks, we make sure that a _Master variable is declared in the current
120 -- scope, and then declare a renaming for it:
122 -- atypeM : Master_Id renames _Master;
124 -- where atyp is the name of the access type. This declaration is used when
125 -- an allocator for the access type is expanded. The node is the full
126 -- declaration of the designated type that contains tasks. The renaming
127 -- declaration is inserted before N, and after the Master declaration.
129 procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id);
130 -- Build record initialization procedure. N is the type declaration
131 -- node, and Pe is the corresponding entity for the record type.
133 procedure Build_Slice_Assignment (Typ : Entity_Id);
134 -- Build assignment procedure for one-dimensional arrays of controlled
135 -- types. Other array and slice assignments are expanded in-line, but
136 -- the code expansion for controlled components (when control actions
137 -- are active) can lead to very large blocks that GCC3 handles poorly.
139 procedure Build_Variant_Record_Equality (Typ : Entity_Id);
140 -- Create An Equality function for the non-tagged variant record 'Typ'
141 -- and attach it to the TSS list
143 procedure Check_Stream_Attributes (Typ : Entity_Id);
144 -- Check that if a limited extension has a parent with user-defined stream
145 -- attributes, and does not itself have user-defined stream-attributes,
146 -- then any limited component of the extension also has the corresponding
147 -- user-defined stream attributes.
149 procedure Clean_Task_Names
150 (Typ : Entity_Id;
151 Proc_Id : Entity_Id);
152 -- If an initialization procedure includes calls to generate names
153 -- for task subcomponents, indicate that secondary stack cleanup is
154 -- needed after an initialization. Typ is the component type, and Proc_Id
155 -- the initialization procedure for the enclosing composite type.
157 procedure Expand_Tagged_Root (T : Entity_Id);
158 -- Add a field _Tag at the beginning of the record. This field carries
159 -- the value of the access to the Dispatch table. This procedure is only
160 -- called on root type, the _Tag field being inherited by the descendants.
162 procedure Expand_Record_Controller (T : Entity_Id);
163 -- T must be a record type that Has_Controlled_Component. Add a field
164 -- _controller of type Record_Controller or Limited_Record_Controller
165 -- in the record T.
167 procedure Freeze_Array_Type (N : Node_Id);
168 -- Freeze an array type. Deals with building the initialization procedure,
169 -- creating the packed array type for a packed array and also with the
170 -- creation of the controlling procedures for the controlled case. The
171 -- argument N is the N_Freeze_Entity node for the type.
173 procedure Freeze_Enumeration_Type (N : Node_Id);
174 -- Freeze enumeration type with non-standard representation. Builds the
175 -- array and function needed to convert between enumeration pos and
176 -- enumeration representation values. N is the N_Freeze_Entity node
177 -- for the type.
179 procedure Freeze_Record_Type (N : Node_Id);
180 -- Freeze record type. Builds all necessary discriminant checking
181 -- and other ancillary functions, and builds dispatch tables where
182 -- needed. The argument N is the N_Freeze_Entity node. This processing
183 -- applies only to E_Record_Type entities, not to class wide types,
184 -- record subtypes, or private types.
186 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id);
187 -- Treat user-defined stream operations as renaming_as_body if the
188 -- subprogram they rename is not frozen when the type is frozen.
190 procedure Initialization_Warning (E : Entity_Id);
191 -- If static elaboration of the package is requested, indicate
192 -- when a type does meet the conditions for static initialization. If
193 -- E is a type, it has components that have no static initialization.
194 -- if E is an entity, its initial expression is not compile-time known.
196 function Init_Formals (Typ : Entity_Id) return List_Id;
197 -- This function builds the list of formals for an initialization routine.
198 -- The first formal is always _Init with the given type. For task value
199 -- record types and types containing tasks, three additional formals are
200 -- added:
202 -- _Master : Master_Id
203 -- _Chain : in out Activation_Chain
204 -- _Task_Name : String
206 -- The caller must append additional entries for discriminants if required.
208 function In_Runtime (E : Entity_Id) return Boolean;
209 -- Check if E is defined in the RTL (in a child of Ada or System). Used
210 -- to avoid to bring in the overhead of _Input, _Output for tagged types.
212 function Is_Variable_Size_Record (E : Entity_Id) return Boolean;
213 -- Returns true if E has variable size components
215 function Make_Eq_Case
216 (E : Entity_Id;
217 CL : Node_Id;
218 Discr : Entity_Id := Empty) return List_Id;
219 -- Building block for variant record equality. Defined to share the code
220 -- between the tagged and non-tagged case. Given a Component_List node CL,
221 -- it generates an 'if' followed by a 'case' statement that compares all
222 -- components of local temporaries named X and Y (that are declared as
223 -- formals at some upper level). E provides the Sloc to be used for the
224 -- generated code. Discr is used as the case statement switch in the case
225 -- of Unchecked_Union equality.
227 function Make_Eq_If
228 (E : Entity_Id;
229 L : List_Id) return Node_Id;
230 -- Building block for variant record equality. Defined to share the code
231 -- between the tagged and non-tagged case. Given the list of components
232 -- (or discriminants) L, it generates a return statement that compares all
233 -- components of local temporaries named X and Y (that are declared as
234 -- formals at some upper level). E provides the Sloc to be used for the
235 -- generated code.
237 procedure Make_Predefined_Primitive_Specs
238 (Tag_Typ : Entity_Id;
239 Predef_List : out List_Id;
240 Renamed_Eq : out Node_Id);
241 -- Create a list with the specs of the predefined primitive operations.
242 -- The following entries are present for all tagged types, and provide
243 -- the results of the corresponding attribute applied to the object.
244 -- Dispatching is required in general, since the result of the attribute
245 -- will vary with the actual object subtype.
247 -- _alignment provides result of 'Alignment attribute
248 -- _size provides result of 'Size attribute
249 -- typSR provides result of 'Read attribute
250 -- typSW provides result of 'Write attribute
251 -- typSI provides result of 'Input attribute
252 -- typSO provides result of 'Output attribute
254 -- The following entries are additionally present for non-limited tagged
255 -- types, and implement additional dispatching operations for predefined
256 -- operations:
258 -- _equality implements "=" operator
259 -- _assign implements assignment operation
260 -- typDF implements deep finalization
261 -- typDA implements deep adjust
263 -- The latter two are empty procedures unless the type contains some
264 -- controlled components that require finalization actions (the deep
265 -- in the name refers to the fact that the action applies to components).
267 -- The list is returned in Predef_List. The Parameter Renamed_Eq either
268 -- returns the value Empty, or else the defining unit name for the
269 -- predefined equality function in the case where the type has a primitive
270 -- operation that is a renaming of predefined equality (but only if there
271 -- is also an overriding user-defined equality function). The returned
272 -- Renamed_Eq will be passed to the corresponding parameter of
273 -- Predefined_Primitive_Bodies.
275 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean;
276 -- returns True if there are representation clauses for type T that are not
277 -- inherited. If the result is false, the init_proc and the discriminant
278 -- checking functions of the parent can be reused by a derived type.
280 procedure Make_Controlling_Function_Wrappers
281 (Tag_Typ : Entity_Id;
282 Decl_List : out List_Id;
283 Body_List : out List_Id);
284 -- Ada 2005 (AI-391): Makes specs and bodies for the wrapper functions
285 -- associated with inherited functions with controlling results which
286 -- are not overridden. The body of each wrapper function consists solely
287 -- of a return statement whose expression is an extension aggregate
288 -- invoking the inherited subprogram's parent subprogram and extended
289 -- with a null association list.
291 procedure Make_Null_Procedure_Specs
292 (Tag_Typ : Entity_Id;
293 Decl_List : out List_Id);
294 -- Ada 2005 (AI-251): Makes specs for null procedures associated with any
295 -- null procedures inherited from an interface type that have not been
296 -- overridden. Only one null procedure will be created for a given set of
297 -- inherited null procedures with homographic profiles.
299 function Predef_Spec_Or_Body
300 (Loc : Source_Ptr;
301 Tag_Typ : Entity_Id;
302 Name : Name_Id;
303 Profile : List_Id;
304 Ret_Type : Entity_Id := Empty;
305 For_Body : Boolean := False) return Node_Id;
306 -- This function generates the appropriate expansion for a predefined
307 -- primitive operation specified by its name, parameter profile and
308 -- return type (Empty means this is a procedure). If For_Body is false,
309 -- then the returned node is a subprogram declaration. If For_Body is
310 -- true, then the returned node is a empty subprogram body containing
311 -- no declarations and no statements.
313 function Predef_Stream_Attr_Spec
314 (Loc : Source_Ptr;
315 Tag_Typ : Entity_Id;
316 Name : TSS_Name_Type;
317 For_Body : Boolean := False) return Node_Id;
318 -- Specialized version of Predef_Spec_Or_Body that apply to read, write,
319 -- input and output attribute whose specs are constructed in Exp_Strm.
321 function Predef_Deep_Spec
322 (Loc : Source_Ptr;
323 Tag_Typ : Entity_Id;
324 Name : TSS_Name_Type;
325 For_Body : Boolean := False) return Node_Id;
326 -- Specialized version of Predef_Spec_Or_Body that apply to _deep_adjust
327 -- and _deep_finalize
329 function Predefined_Primitive_Bodies
330 (Tag_Typ : Entity_Id;
331 Renamed_Eq : Node_Id) return List_Id;
332 -- Create the bodies of the predefined primitives that are described in
333 -- Predefined_Primitive_Specs. When not empty, Renamed_Eq must denote
334 -- the defining unit name of the type's predefined equality as returned
335 -- by Make_Predefined_Primitive_Specs.
337 function Predefined_Primitive_Freeze (Tag_Typ : Entity_Id) return List_Id;
338 -- Freeze entities of all predefined primitive operations. This is needed
339 -- because the bodies of these operations do not normally do any freezing.
341 function Stream_Operation_OK
342 (Typ : Entity_Id;
343 Operation : TSS_Name_Type) return Boolean;
344 -- Check whether the named stream operation must be emitted for a given
345 -- type. The rules for inheritance of stream attributes by type extensions
346 -- are enforced by this function. Furthermore, various restrictions prevent
347 -- the generation of these operations, as a useful optimization or for
348 -- certification purposes.
350 ---------------------
351 -- Add_Final_Chain --
352 ---------------------
354 function Add_Final_Chain (Def_Id : Entity_Id) return Entity_Id is
355 Loc : constant Source_Ptr := Sloc (Def_Id);
356 Flist : Entity_Id;
358 begin
359 Flist :=
360 Make_Defining_Identifier (Loc,
361 New_External_Name (Chars (Def_Id), 'L'));
363 Append_Freeze_Action (Def_Id,
364 Make_Object_Declaration (Loc,
365 Defining_Identifier => Flist,
366 Object_Definition =>
367 New_Reference_To (RTE (RE_List_Controller), Loc)));
369 return Flist;
370 end Add_Final_Chain;
372 --------------------------
373 -- Adjust_Discriminants --
374 --------------------------
376 -- This procedure attempts to define subtypes for discriminants that are
377 -- more restrictive than those declared. Such a replacement is possible if
378 -- we can demonstrate that values outside the restricted range would cause
379 -- constraint errors in any case. The advantage of restricting the
380 -- discriminant types in this way is that the maximum size of the variant
381 -- record can be calculated more conservatively.
383 -- An example of a situation in which we can perform this type of
384 -- restriction is the following:
386 -- subtype B is range 1 .. 10;
387 -- type Q is array (B range <>) of Integer;
389 -- type V (N : Natural) is record
390 -- C : Q (1 .. N);
391 -- end record;
393 -- In this situation, we can restrict the upper bound of N to 10, since
394 -- any larger value would cause a constraint error in any case.
396 -- There are many situations in which such restriction is possible, but
397 -- for now, we just look for cases like the above, where the component
398 -- in question is a one dimensional array whose upper bound is one of
399 -- the record discriminants. Also the component must not be part of
400 -- any variant part, since then the component does not always exist.
402 procedure Adjust_Discriminants (Rtype : Entity_Id) is
403 Loc : constant Source_Ptr := Sloc (Rtype);
404 Comp : Entity_Id;
405 Ctyp : Entity_Id;
406 Ityp : Entity_Id;
407 Lo : Node_Id;
408 Hi : Node_Id;
409 P : Node_Id;
410 Loval : Uint;
411 Discr : Entity_Id;
412 Dtyp : Entity_Id;
413 Dhi : Node_Id;
414 Dhiv : Uint;
415 Ahi : Node_Id;
416 Ahiv : Uint;
417 Tnn : Entity_Id;
419 begin
420 Comp := First_Component (Rtype);
421 while Present (Comp) loop
423 -- If our parent is a variant, quit, we do not look at components
424 -- that are in variant parts, because they may not always exist.
426 P := Parent (Comp); -- component declaration
427 P := Parent (P); -- component list
429 exit when Nkind (Parent (P)) = N_Variant;
431 -- We are looking for a one dimensional array type
433 Ctyp := Etype (Comp);
435 if not Is_Array_Type (Ctyp)
436 or else Number_Dimensions (Ctyp) > 1
437 then
438 goto Continue;
439 end if;
441 -- The lower bound must be constant, and the upper bound is a
442 -- discriminant (which is a discriminant of the current record).
444 Ityp := Etype (First_Index (Ctyp));
445 Lo := Type_Low_Bound (Ityp);
446 Hi := Type_High_Bound (Ityp);
448 if not Compile_Time_Known_Value (Lo)
449 or else Nkind (Hi) /= N_Identifier
450 or else No (Entity (Hi))
451 or else Ekind (Entity (Hi)) /= E_Discriminant
452 then
453 goto Continue;
454 end if;
456 -- We have an array with appropriate bounds
458 Loval := Expr_Value (Lo);
459 Discr := Entity (Hi);
460 Dtyp := Etype (Discr);
462 -- See if the discriminant has a known upper bound
464 Dhi := Type_High_Bound (Dtyp);
466 if not Compile_Time_Known_Value (Dhi) then
467 goto Continue;
468 end if;
470 Dhiv := Expr_Value (Dhi);
472 -- See if base type of component array has known upper bound
474 Ahi := Type_High_Bound (Etype (First_Index (Base_Type (Ctyp))));
476 if not Compile_Time_Known_Value (Ahi) then
477 goto Continue;
478 end if;
480 Ahiv := Expr_Value (Ahi);
482 -- The condition for doing the restriction is that the high bound
483 -- of the discriminant is greater than the low bound of the array,
484 -- and is also greater than the high bound of the base type index.
486 if Dhiv > Loval and then Dhiv > Ahiv then
488 -- We can reset the upper bound of the discriminant type to
489 -- whichever is larger, the low bound of the component, or
490 -- the high bound of the base type array index.
492 -- We build a subtype that is declared as
494 -- subtype Tnn is discr_type range discr_type'First .. max;
496 -- And insert this declaration into the tree. The type of the
497 -- discriminant is then reset to this more restricted subtype.
499 Tnn := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
501 Insert_Action (Declaration_Node (Rtype),
502 Make_Subtype_Declaration (Loc,
503 Defining_Identifier => Tnn,
504 Subtype_Indication =>
505 Make_Subtype_Indication (Loc,
506 Subtype_Mark => New_Occurrence_Of (Dtyp, Loc),
507 Constraint =>
508 Make_Range_Constraint (Loc,
509 Range_Expression =>
510 Make_Range (Loc,
511 Low_Bound =>
512 Make_Attribute_Reference (Loc,
513 Attribute_Name => Name_First,
514 Prefix => New_Occurrence_Of (Dtyp, Loc)),
515 High_Bound =>
516 Make_Integer_Literal (Loc,
517 Intval => UI_Max (Loval, Ahiv)))))));
519 Set_Etype (Discr, Tnn);
520 end if;
522 <<Continue>>
523 Next_Component (Comp);
524 end loop;
525 end Adjust_Discriminants;
527 ---------------------------
528 -- Build_Array_Init_Proc --
529 ---------------------------
531 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id) is
532 Loc : constant Source_Ptr := Sloc (Nod);
533 Comp_Type : constant Entity_Id := Component_Type (A_Type);
534 Index_List : List_Id;
535 Proc_Id : Entity_Id;
536 Body_Stmts : List_Id;
538 function Init_Component return List_Id;
539 -- Create one statement to initialize one array component, designated
540 -- by a full set of indices.
542 function Init_One_Dimension (N : Int) return List_Id;
543 -- Create loop to initialize one dimension of the array. The single
544 -- statement in the loop body initializes the inner dimensions if any,
545 -- or else the single component. Note that this procedure is called
546 -- recursively, with N being the dimension to be initialized. A call
547 -- with N greater than the number of dimensions simply generates the
548 -- component initialization, terminating the recursion.
550 --------------------
551 -- Init_Component --
552 --------------------
554 function Init_Component return List_Id is
555 Comp : Node_Id;
557 begin
558 Comp :=
559 Make_Indexed_Component (Loc,
560 Prefix => Make_Identifier (Loc, Name_uInit),
561 Expressions => Index_List);
563 if Needs_Simple_Initialization (Comp_Type) then
564 Set_Assignment_OK (Comp);
565 return New_List (
566 Make_Assignment_Statement (Loc,
567 Name => Comp,
568 Expression =>
569 Get_Simple_Init_Val
570 (Comp_Type, Loc, Component_Size (A_Type))));
572 else
573 Clean_Task_Names (Comp_Type, Proc_Id);
574 return
575 Build_Initialization_Call
576 (Loc, Comp, Comp_Type,
577 In_Init_Proc => True,
578 Enclos_Type => A_Type);
579 end if;
580 end Init_Component;
582 ------------------------
583 -- Init_One_Dimension --
584 ------------------------
586 function Init_One_Dimension (N : Int) return List_Id is
587 Index : Entity_Id;
589 begin
590 -- If the component does not need initializing, then there is nothing
591 -- to do here, so we return a null body. This occurs when generating
592 -- the dummy Init_Proc needed for Initialize_Scalars processing.
594 if not Has_Non_Null_Base_Init_Proc (Comp_Type)
595 and then not Needs_Simple_Initialization (Comp_Type)
596 and then not Has_Task (Comp_Type)
597 then
598 return New_List (Make_Null_Statement (Loc));
600 -- If all dimensions dealt with, we simply initialize the component
602 elsif N > Number_Dimensions (A_Type) then
603 return Init_Component;
605 -- Here we generate the required loop
607 else
608 Index :=
609 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
611 Append (New_Reference_To (Index, Loc), Index_List);
613 return New_List (
614 Make_Implicit_Loop_Statement (Nod,
615 Identifier => Empty,
616 Iteration_Scheme =>
617 Make_Iteration_Scheme (Loc,
618 Loop_Parameter_Specification =>
619 Make_Loop_Parameter_Specification (Loc,
620 Defining_Identifier => Index,
621 Discrete_Subtype_Definition =>
622 Make_Attribute_Reference (Loc,
623 Prefix => Make_Identifier (Loc, Name_uInit),
624 Attribute_Name => Name_Range,
625 Expressions => New_List (
626 Make_Integer_Literal (Loc, N))))),
627 Statements => Init_One_Dimension (N + 1)));
628 end if;
629 end Init_One_Dimension;
631 -- Start of processing for Build_Array_Init_Proc
633 begin
634 -- Nothing to generate in the following cases:
636 -- 1. Initialization is suppressed for the type
637 -- 2. The type is a value type, in the CIL sense.
638 -- 3. An initialization already exists for the base type
640 if Suppress_Init_Proc (A_Type)
641 or else Is_Value_Type (Comp_Type)
642 or else Present (Base_Init_Proc (A_Type))
643 then
644 return;
645 end if;
647 Index_List := New_List;
649 -- We need an initialization procedure if any of the following is true:
651 -- 1. The component type has an initialization procedure
652 -- 2. The component type needs simple initialization
653 -- 3. Tasks are present
654 -- 4. The type is marked as a public entity
656 -- The reason for the public entity test is to deal properly with the
657 -- Initialize_Scalars pragma. This pragma can be set in the client and
658 -- not in the declaring package, this means the client will make a call
659 -- to the initialization procedure (because one of conditions 1-3 must
660 -- apply in this case), and we must generate a procedure (even if it is
661 -- null) to satisfy the call in this case.
663 -- Exception: do not build an array init_proc for a type whose root
664 -- type is Standard.String or Standard.Wide_[Wide_]String, since there
665 -- is no place to put the code, and in any case we handle initialization
666 -- of such types (in the Initialize_Scalars case, that's the only time
667 -- the issue arises) in a special manner anyway which does not need an
668 -- init_proc.
670 if Has_Non_Null_Base_Init_Proc (Comp_Type)
671 or else Needs_Simple_Initialization (Comp_Type)
672 or else Has_Task (Comp_Type)
673 or else (not Restriction_Active (No_Initialize_Scalars)
674 and then Is_Public (A_Type)
675 and then Root_Type (A_Type) /= Standard_String
676 and then Root_Type (A_Type) /= Standard_Wide_String
677 and then Root_Type (A_Type) /= Standard_Wide_Wide_String)
678 then
679 Proc_Id :=
680 Make_Defining_Identifier (Loc, Make_Init_Proc_Name (A_Type));
682 Body_Stmts := Init_One_Dimension (1);
684 Discard_Node (
685 Make_Subprogram_Body (Loc,
686 Specification =>
687 Make_Procedure_Specification (Loc,
688 Defining_Unit_Name => Proc_Id,
689 Parameter_Specifications => Init_Formals (A_Type)),
690 Declarations => New_List,
691 Handled_Statement_Sequence =>
692 Make_Handled_Sequence_Of_Statements (Loc,
693 Statements => Body_Stmts)));
695 Set_Ekind (Proc_Id, E_Procedure);
696 Set_Is_Public (Proc_Id, Is_Public (A_Type));
697 Set_Is_Internal (Proc_Id);
698 Set_Has_Completion (Proc_Id);
700 if not Debug_Generated_Code then
701 Set_Debug_Info_Off (Proc_Id);
702 end if;
704 -- Set inlined unless controlled stuff or tasks around, in which
705 -- case we do not want to inline, because nested stuff may cause
706 -- difficulties in inter-unit inlining, and furthermore there is
707 -- in any case no point in inlining such complex init procs.
709 if not Has_Task (Proc_Id)
710 and then not Controlled_Type (Proc_Id)
711 then
712 Set_Is_Inlined (Proc_Id);
713 end if;
715 -- Associate Init_Proc with type, and determine if the procedure
716 -- is null (happens because of the Initialize_Scalars pragma case,
717 -- where we have to generate a null procedure in case it is called
718 -- by a client with Initialize_Scalars set). Such procedures have
719 -- to be generated, but do not have to be called, so we mark them
720 -- as null to suppress the call.
722 Set_Init_Proc (A_Type, Proc_Id);
724 if List_Length (Body_Stmts) = 1
725 and then Nkind (First (Body_Stmts)) = N_Null_Statement
726 then
727 Set_Is_Null_Init_Proc (Proc_Id);
729 else
730 -- Try to build a static aggregate to initialize statically
731 -- objects of the type. This can only be done for constrained
732 -- one-dimensional arrays with static bounds.
734 Set_Static_Initialization
735 (Proc_Id,
736 Build_Equivalent_Array_Aggregate (First_Subtype (A_Type)));
737 end if;
738 end if;
739 end Build_Array_Init_Proc;
741 -----------------------------
742 -- Build_Class_Wide_Master --
743 -----------------------------
745 procedure Build_Class_Wide_Master (T : Entity_Id) is
746 Loc : constant Source_Ptr := Sloc (T);
747 M_Id : Entity_Id;
748 Decl : Node_Id;
749 P : Node_Id;
750 Par : Node_Id;
752 begin
753 -- Nothing to do if there is no task hierarchy
755 if Restriction_Active (No_Task_Hierarchy) then
756 return;
757 end if;
759 -- Find declaration that created the access type: either a type
760 -- declaration, or an object declaration with an access definition,
761 -- in which case the type is anonymous.
763 if Is_Itype (T) then
764 P := Associated_Node_For_Itype (T);
765 else
766 P := Parent (T);
767 end if;
769 -- Nothing to do if we already built a master entity for this scope
771 if not Has_Master_Entity (Scope (T)) then
773 -- First build the master entity
774 -- _Master : constant Master_Id := Current_Master.all;
775 -- and insert it just before the current declaration.
777 Decl :=
778 Make_Object_Declaration (Loc,
779 Defining_Identifier =>
780 Make_Defining_Identifier (Loc, Name_uMaster),
781 Constant_Present => True,
782 Object_Definition => New_Reference_To (Standard_Integer, Loc),
783 Expression =>
784 Make_Explicit_Dereference (Loc,
785 New_Reference_To (RTE (RE_Current_Master), Loc)));
787 Insert_Action (P, Decl);
788 Analyze (Decl);
789 Set_Has_Master_Entity (Scope (T));
791 -- Now mark the containing scope as a task master
793 Par := P;
794 while Nkind (Par) /= N_Compilation_Unit loop
795 Par := Parent (Par);
797 -- If we fall off the top, we are at the outer level, and the
798 -- environment task is our effective master, so nothing to mark.
800 if Nkind (Par) = N_Task_Body
801 or else Nkind (Par) = N_Block_Statement
802 or else Nkind (Par) = N_Subprogram_Body
803 then
804 Set_Is_Task_Master (Par, True);
805 exit;
806 end if;
807 end loop;
808 end if;
810 -- Now define the renaming of the master_id
812 M_Id :=
813 Make_Defining_Identifier (Loc,
814 New_External_Name (Chars (T), 'M'));
816 Decl :=
817 Make_Object_Renaming_Declaration (Loc,
818 Defining_Identifier => M_Id,
819 Subtype_Mark => New_Reference_To (Standard_Integer, Loc),
820 Name => Make_Identifier (Loc, Name_uMaster));
821 Insert_Before (P, Decl);
822 Analyze (Decl);
824 Set_Master_Id (T, M_Id);
826 exception
827 when RE_Not_Available =>
828 return;
829 end Build_Class_Wide_Master;
831 --------------------------------
832 -- Build_Discr_Checking_Funcs --
833 --------------------------------
835 procedure Build_Discr_Checking_Funcs (N : Node_Id) is
836 Rec_Id : Entity_Id;
837 Loc : Source_Ptr;
838 Enclosing_Func_Id : Entity_Id;
839 Sequence : Nat := 1;
840 Type_Def : Node_Id;
841 V : Node_Id;
843 function Build_Case_Statement
844 (Case_Id : Entity_Id;
845 Variant : Node_Id) return Node_Id;
846 -- Build a case statement containing only two alternatives. The first
847 -- alternative corresponds exactly to the discrete choices given on the
848 -- variant with contains the components that we are generating the
849 -- checks for. If the discriminant is one of these return False. The
850 -- second alternative is an OTHERS choice that will return True
851 -- indicating the discriminant did not match.
853 function Build_Dcheck_Function
854 (Case_Id : Entity_Id;
855 Variant : Node_Id) return Entity_Id;
856 -- Build the discriminant checking function for a given variant
858 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id);
859 -- Builds the discriminant checking function for each variant of the
860 -- given variant part of the record type.
862 --------------------------
863 -- Build_Case_Statement --
864 --------------------------
866 function Build_Case_Statement
867 (Case_Id : Entity_Id;
868 Variant : Node_Id) return Node_Id
870 Alt_List : constant List_Id := New_List;
871 Actuals_List : List_Id;
872 Case_Node : Node_Id;
873 Case_Alt_Node : Node_Id;
874 Choice : Node_Id;
875 Choice_List : List_Id;
876 D : Entity_Id;
877 Return_Node : Node_Id;
879 begin
880 Case_Node := New_Node (N_Case_Statement, Loc);
882 -- Replace the discriminant which controls the variant, with the name
883 -- of the formal of the checking function.
885 Set_Expression (Case_Node,
886 Make_Identifier (Loc, Chars (Case_Id)));
888 Choice := First (Discrete_Choices (Variant));
890 if Nkind (Choice) = N_Others_Choice then
891 Choice_List := New_Copy_List (Others_Discrete_Choices (Choice));
892 else
893 Choice_List := New_Copy_List (Discrete_Choices (Variant));
894 end if;
896 if not Is_Empty_List (Choice_List) then
897 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
898 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
900 -- In case this is a nested variant, we need to return the result
901 -- of the discriminant checking function for the immediately
902 -- enclosing variant.
904 if Present (Enclosing_Func_Id) then
905 Actuals_List := New_List;
907 D := First_Discriminant (Rec_Id);
908 while Present (D) loop
909 Append (Make_Identifier (Loc, Chars (D)), Actuals_List);
910 Next_Discriminant (D);
911 end loop;
913 Return_Node :=
914 Make_Simple_Return_Statement (Loc,
915 Expression =>
916 Make_Function_Call (Loc,
917 Name =>
918 New_Reference_To (Enclosing_Func_Id, Loc),
919 Parameter_Associations =>
920 Actuals_List));
922 else
923 Return_Node :=
924 Make_Simple_Return_Statement (Loc,
925 Expression =>
926 New_Reference_To (Standard_False, Loc));
927 end if;
929 Set_Statements (Case_Alt_Node, New_List (Return_Node));
930 Append (Case_Alt_Node, Alt_List);
931 end if;
933 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
934 Choice_List := New_List (New_Node (N_Others_Choice, Loc));
935 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
937 Return_Node :=
938 Make_Simple_Return_Statement (Loc,
939 Expression =>
940 New_Reference_To (Standard_True, Loc));
942 Set_Statements (Case_Alt_Node, New_List (Return_Node));
943 Append (Case_Alt_Node, Alt_List);
945 Set_Alternatives (Case_Node, Alt_List);
946 return Case_Node;
947 end Build_Case_Statement;
949 ---------------------------
950 -- Build_Dcheck_Function --
951 ---------------------------
953 function Build_Dcheck_Function
954 (Case_Id : Entity_Id;
955 Variant : Node_Id) return Entity_Id
957 Body_Node : Node_Id;
958 Func_Id : Entity_Id;
959 Parameter_List : List_Id;
960 Spec_Node : Node_Id;
962 begin
963 Body_Node := New_Node (N_Subprogram_Body, Loc);
964 Sequence := Sequence + 1;
966 Func_Id :=
967 Make_Defining_Identifier (Loc,
968 Chars => New_External_Name (Chars (Rec_Id), 'D', Sequence));
970 Spec_Node := New_Node (N_Function_Specification, Loc);
971 Set_Defining_Unit_Name (Spec_Node, Func_Id);
973 Parameter_List := Build_Discriminant_Formals (Rec_Id, False);
975 Set_Parameter_Specifications (Spec_Node, Parameter_List);
976 Set_Result_Definition (Spec_Node,
977 New_Reference_To (Standard_Boolean, Loc));
978 Set_Specification (Body_Node, Spec_Node);
979 Set_Declarations (Body_Node, New_List);
981 Set_Handled_Statement_Sequence (Body_Node,
982 Make_Handled_Sequence_Of_Statements (Loc,
983 Statements => New_List (
984 Build_Case_Statement (Case_Id, Variant))));
986 Set_Ekind (Func_Id, E_Function);
987 Set_Mechanism (Func_Id, Default_Mechanism);
988 Set_Is_Inlined (Func_Id, True);
989 Set_Is_Pure (Func_Id, True);
990 Set_Is_Public (Func_Id, Is_Public (Rec_Id));
991 Set_Is_Internal (Func_Id, True);
993 if not Debug_Generated_Code then
994 Set_Debug_Info_Off (Func_Id);
995 end if;
997 Analyze (Body_Node);
999 Append_Freeze_Action (Rec_Id, Body_Node);
1000 Set_Dcheck_Function (Variant, Func_Id);
1001 return Func_Id;
1002 end Build_Dcheck_Function;
1004 ----------------------------
1005 -- Build_Dcheck_Functions --
1006 ----------------------------
1008 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id) is
1009 Component_List_Node : Node_Id;
1010 Decl : Entity_Id;
1011 Discr_Name : Entity_Id;
1012 Func_Id : Entity_Id;
1013 Variant : Node_Id;
1014 Saved_Enclosing_Func_Id : Entity_Id;
1016 begin
1017 -- Build the discriminant checking function for each variant, label
1018 -- all components of that variant with the function's name.
1020 Discr_Name := Entity (Name (Variant_Part_Node));
1021 Variant := First_Non_Pragma (Variants (Variant_Part_Node));
1023 while Present (Variant) loop
1024 Func_Id := Build_Dcheck_Function (Discr_Name, Variant);
1025 Component_List_Node := Component_List (Variant);
1027 if not Null_Present (Component_List_Node) then
1028 Decl :=
1029 First_Non_Pragma (Component_Items (Component_List_Node));
1031 while Present (Decl) loop
1032 Set_Discriminant_Checking_Func
1033 (Defining_Identifier (Decl), Func_Id);
1035 Next_Non_Pragma (Decl);
1036 end loop;
1038 if Present (Variant_Part (Component_List_Node)) then
1039 Saved_Enclosing_Func_Id := Enclosing_Func_Id;
1040 Enclosing_Func_Id := Func_Id;
1041 Build_Dcheck_Functions (Variant_Part (Component_List_Node));
1042 Enclosing_Func_Id := Saved_Enclosing_Func_Id;
1043 end if;
1044 end if;
1046 Next_Non_Pragma (Variant);
1047 end loop;
1048 end Build_Dcheck_Functions;
1050 -- Start of processing for Build_Discr_Checking_Funcs
1052 begin
1053 -- Only build if not done already
1055 if not Discr_Check_Funcs_Built (N) then
1056 Type_Def := Type_Definition (N);
1058 if Nkind (Type_Def) = N_Record_Definition then
1059 if No (Component_List (Type_Def)) then -- null record.
1060 return;
1061 else
1062 V := Variant_Part (Component_List (Type_Def));
1063 end if;
1065 else pragma Assert (Nkind (Type_Def) = N_Derived_Type_Definition);
1066 if No (Component_List (Record_Extension_Part (Type_Def))) then
1067 return;
1068 else
1069 V := Variant_Part
1070 (Component_List (Record_Extension_Part (Type_Def)));
1071 end if;
1072 end if;
1074 Rec_Id := Defining_Identifier (N);
1076 if Present (V) and then not Is_Unchecked_Union (Rec_Id) then
1077 Loc := Sloc (N);
1078 Enclosing_Func_Id := Empty;
1079 Build_Dcheck_Functions (V);
1080 end if;
1082 Set_Discr_Check_Funcs_Built (N);
1083 end if;
1084 end Build_Discr_Checking_Funcs;
1086 --------------------------------
1087 -- Build_Discriminant_Formals --
1088 --------------------------------
1090 function Build_Discriminant_Formals
1091 (Rec_Id : Entity_Id;
1092 Use_Dl : Boolean) return List_Id
1094 Loc : Source_Ptr := Sloc (Rec_Id);
1095 Parameter_List : constant List_Id := New_List;
1096 D : Entity_Id;
1097 Formal : Entity_Id;
1098 Param_Spec_Node : Node_Id;
1100 begin
1101 if Has_Discriminants (Rec_Id) then
1102 D := First_Discriminant (Rec_Id);
1103 while Present (D) loop
1104 Loc := Sloc (D);
1106 if Use_Dl then
1107 Formal := Discriminal (D);
1108 else
1109 Formal := Make_Defining_Identifier (Loc, Chars (D));
1110 end if;
1112 Param_Spec_Node :=
1113 Make_Parameter_Specification (Loc,
1114 Defining_Identifier => Formal,
1115 Parameter_Type =>
1116 New_Reference_To (Etype (D), Loc));
1117 Append (Param_Spec_Node, Parameter_List);
1118 Next_Discriminant (D);
1119 end loop;
1120 end if;
1122 return Parameter_List;
1123 end Build_Discriminant_Formals;
1125 --------------------------------------
1126 -- Build_Equivalent_Array_Aggregate --
1127 --------------------------------------
1129 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id is
1130 Loc : constant Source_Ptr := Sloc (T);
1131 Comp_Type : constant Entity_Id := Component_Type (T);
1132 Index_Type : constant Entity_Id := Etype (First_Index (T));
1133 Proc : constant Entity_Id := Base_Init_Proc (T);
1134 Lo, Hi : Node_Id;
1135 Aggr : Node_Id;
1136 Expr : Node_Id;
1138 begin
1139 if not Is_Constrained (T)
1140 or else Number_Dimensions (T) > 1
1141 or else No (Proc)
1142 then
1143 Initialization_Warning (T);
1144 return Empty;
1145 end if;
1147 Lo := Type_Low_Bound (Index_Type);
1148 Hi := Type_High_Bound (Index_Type);
1150 if not Compile_Time_Known_Value (Lo)
1151 or else not Compile_Time_Known_Value (Hi)
1152 then
1153 Initialization_Warning (T);
1154 return Empty;
1155 end if;
1157 if Is_Record_Type (Comp_Type)
1158 and then Present (Base_Init_Proc (Comp_Type))
1159 then
1160 Expr := Static_Initialization (Base_Init_Proc (Comp_Type));
1162 if No (Expr) then
1163 Initialization_Warning (T);
1164 return Empty;
1165 end if;
1167 else
1168 Initialization_Warning (T);
1169 return Empty;
1170 end if;
1172 Aggr := Make_Aggregate (Loc, No_List, New_List);
1173 Set_Etype (Aggr, T);
1174 Set_Aggregate_Bounds (Aggr,
1175 Make_Range (Loc,
1176 Low_Bound => New_Copy (Lo),
1177 High_Bound => New_Copy (Hi)));
1178 Set_Parent (Aggr, Parent (Proc));
1180 Append_To (Component_Associations (Aggr),
1181 Make_Component_Association (Loc,
1182 Choices =>
1183 New_List (
1184 Make_Range (Loc,
1185 Low_Bound => New_Copy (Lo),
1186 High_Bound => New_Copy (Hi))),
1187 Expression => Expr));
1189 if Static_Array_Aggregate (Aggr) then
1190 return Aggr;
1191 else
1192 Initialization_Warning (T);
1193 return Empty;
1194 end if;
1195 end Build_Equivalent_Array_Aggregate;
1197 ---------------------------------------
1198 -- Build_Equivalent_Record_Aggregate --
1199 ---------------------------------------
1201 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id is
1202 Agg : Node_Id;
1203 Comp : Entity_Id;
1205 -- Start of processing for Build_Equivalent_Record_Aggregate
1207 begin
1208 if not Is_Record_Type (T)
1209 or else Has_Discriminants (T)
1210 or else Is_Limited_Type (T)
1211 or else Has_Non_Standard_Rep (T)
1212 then
1213 Initialization_Warning (T);
1214 return Empty;
1215 end if;
1217 Comp := First_Component (T);
1219 -- A null record needs no warning
1221 if No (Comp) then
1222 return Empty;
1223 end if;
1225 while Present (Comp) loop
1227 -- Array components are acceptable if initialized by a positional
1228 -- aggregate with static components.
1230 if Is_Array_Type (Etype (Comp)) then
1231 declare
1232 Comp_Type : constant Entity_Id := Component_Type (Etype (Comp));
1234 begin
1235 if Nkind (Parent (Comp)) /= N_Component_Declaration
1236 or else No (Expression (Parent (Comp)))
1237 or else Nkind (Expression (Parent (Comp))) /= N_Aggregate
1238 then
1239 Initialization_Warning (T);
1240 return Empty;
1242 elsif Is_Scalar_Type (Component_Type (Etype (Comp)))
1243 and then
1244 (not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1245 or else not Compile_Time_Known_Value
1246 (Type_High_Bound (Comp_Type)))
1247 then
1248 Initialization_Warning (T);
1249 return Empty;
1251 elsif
1252 not Static_Array_Aggregate (Expression (Parent (Comp)))
1253 then
1254 Initialization_Warning (T);
1255 return Empty;
1256 end if;
1257 end;
1259 elsif Is_Scalar_Type (Etype (Comp)) then
1260 if Nkind (Parent (Comp)) /= N_Component_Declaration
1261 or else No (Expression (Parent (Comp)))
1262 or else not Compile_Time_Known_Value (Expression (Parent (Comp)))
1263 then
1264 Initialization_Warning (T);
1265 return Empty;
1266 end if;
1268 -- For now, other types are excluded
1270 else
1271 Initialization_Warning (T);
1272 return Empty;
1273 end if;
1275 Next_Component (Comp);
1276 end loop;
1278 -- All components have static initialization. Build positional
1279 -- aggregate from the given expressions or defaults.
1281 Agg := Make_Aggregate (Sloc (T), New_List, New_List);
1282 Set_Parent (Agg, Parent (T));
1284 Comp := First_Component (T);
1285 while Present (Comp) loop
1286 Append
1287 (New_Copy_Tree (Expression (Parent (Comp))), Expressions (Agg));
1288 Next_Component (Comp);
1289 end loop;
1291 Analyze_And_Resolve (Agg, T);
1292 return Agg;
1293 end Build_Equivalent_Record_Aggregate;
1295 -------------------------------
1296 -- Build_Initialization_Call --
1297 -------------------------------
1299 -- References to a discriminant inside the record type declaration can
1300 -- appear either in the subtype_indication to constrain a record or an
1301 -- array, or as part of a larger expression given for the initial value
1302 -- of a component. In both of these cases N appears in the record
1303 -- initialization procedure and needs to be replaced by the formal
1304 -- parameter of the initialization procedure which corresponds to that
1305 -- discriminant.
1307 -- In the example below, references to discriminants D1 and D2 in proc_1
1308 -- are replaced by references to formals with the same name
1309 -- (discriminals)
1311 -- A similar replacement is done for calls to any record initialization
1312 -- procedure for any components that are themselves of a record type.
1314 -- type R (D1, D2 : Integer) is record
1315 -- X : Integer := F * D1;
1316 -- Y : Integer := F * D2;
1317 -- end record;
1319 -- procedure proc_1 (Out_2 : out R; D1 : Integer; D2 : Integer) is
1320 -- begin
1321 -- Out_2.D1 := D1;
1322 -- Out_2.D2 := D2;
1323 -- Out_2.X := F * D1;
1324 -- Out_2.Y := F * D2;
1325 -- end;
1327 function Build_Initialization_Call
1328 (Loc : Source_Ptr;
1329 Id_Ref : Node_Id;
1330 Typ : Entity_Id;
1331 In_Init_Proc : Boolean := False;
1332 Enclos_Type : Entity_Id := Empty;
1333 Discr_Map : Elist_Id := New_Elmt_List;
1334 With_Default_Init : Boolean := False) return List_Id
1336 First_Arg : Node_Id;
1337 Args : List_Id;
1338 Decls : List_Id;
1339 Decl : Node_Id;
1340 Discr : Entity_Id;
1341 Arg : Node_Id;
1342 Proc : constant Entity_Id := Base_Init_Proc (Typ);
1343 Init_Type : constant Entity_Id := Etype (First_Formal (Proc));
1344 Full_Init_Type : constant Entity_Id := Underlying_Type (Init_Type);
1345 Res : constant List_Id := New_List;
1346 Full_Type : Entity_Id := Typ;
1347 Controller_Typ : Entity_Id;
1349 begin
1350 -- Nothing to do if the Init_Proc is null, unless Initialize_Scalars
1351 -- is active (in which case we make the call anyway, since in the
1352 -- actual compiled client it may be non null).
1353 -- Also nothing to do for value types.
1355 if (Is_Null_Init_Proc (Proc) and then not Init_Or_Norm_Scalars)
1356 or else Is_Value_Type (Typ)
1357 or else Is_Value_Type (Component_Type (Typ))
1358 then
1359 return Empty_List;
1360 end if;
1362 -- Go to full view if private type. In the case of successive
1363 -- private derivations, this can require more than one step.
1365 while Is_Private_Type (Full_Type)
1366 and then Present (Full_View (Full_Type))
1367 loop
1368 Full_Type := Full_View (Full_Type);
1369 end loop;
1371 -- If Typ is derived, the procedure is the initialization procedure for
1372 -- the root type. Wrap the argument in an conversion to make it type
1373 -- honest. Actually it isn't quite type honest, because there can be
1374 -- conflicts of views in the private type case. That is why we set
1375 -- Conversion_OK in the conversion node.
1377 if (Is_Record_Type (Typ)
1378 or else Is_Array_Type (Typ)
1379 or else Is_Private_Type (Typ))
1380 and then Init_Type /= Base_Type (Typ)
1381 then
1382 First_Arg := OK_Convert_To (Etype (Init_Type), Id_Ref);
1383 Set_Etype (First_Arg, Init_Type);
1385 else
1386 First_Arg := Id_Ref;
1387 end if;
1389 Args := New_List (Convert_Concurrent (First_Arg, Typ));
1391 -- In the tasks case, add _Master as the value of the _Master parameter
1392 -- and _Chain as the value of the _Chain parameter. At the outer level,
1393 -- these will be variables holding the corresponding values obtained
1394 -- from GNARL. At inner levels, they will be the parameters passed down
1395 -- through the outer routines.
1397 if Has_Task (Full_Type) then
1398 if Restriction_Active (No_Task_Hierarchy) then
1400 -- See comments in System.Tasking.Initialization.Init_RTS
1401 -- for the value 3 (should be rtsfindable constant ???)
1403 Append_To (Args, Make_Integer_Literal (Loc, 3));
1405 else
1406 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1407 end if;
1409 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1411 -- Ada 2005 (AI-287): In case of default initialized components
1412 -- with tasks, we generate a null string actual parameter.
1413 -- This is just a workaround that must be improved later???
1415 if With_Default_Init then
1416 Append_To (Args,
1417 Make_String_Literal (Loc,
1418 Strval => ""));
1420 else
1421 Decls :=
1422 Build_Task_Image_Decls (Loc, Id_Ref, Enclos_Type, In_Init_Proc);
1423 Decl := Last (Decls);
1425 Append_To (Args,
1426 New_Occurrence_Of (Defining_Identifier (Decl), Loc));
1427 Append_List (Decls, Res);
1428 end if;
1430 else
1431 Decls := No_List;
1432 Decl := Empty;
1433 end if;
1435 -- Add discriminant values if discriminants are present
1437 if Has_Discriminants (Full_Init_Type) then
1438 Discr := First_Discriminant (Full_Init_Type);
1440 while Present (Discr) loop
1442 -- If this is a discriminated concurrent type, the init_proc
1443 -- for the corresponding record is being called. Use that type
1444 -- directly to find the discriminant value, to handle properly
1445 -- intervening renamed discriminants.
1447 declare
1448 T : Entity_Id := Full_Type;
1450 begin
1451 if Is_Protected_Type (T) then
1452 T := Corresponding_Record_Type (T);
1454 elsif Is_Private_Type (T)
1455 and then Present (Underlying_Full_View (T))
1456 and then Is_Protected_Type (Underlying_Full_View (T))
1457 then
1458 T := Corresponding_Record_Type (Underlying_Full_View (T));
1459 end if;
1461 Arg :=
1462 Get_Discriminant_Value (
1463 Discr,
1465 Discriminant_Constraint (Full_Type));
1466 end;
1468 if In_Init_Proc then
1470 -- Replace any possible references to the discriminant in the
1471 -- call to the record initialization procedure with references
1472 -- to the appropriate formal parameter.
1474 if Nkind (Arg) = N_Identifier
1475 and then Ekind (Entity (Arg)) = E_Discriminant
1476 then
1477 Arg := New_Reference_To (Discriminal (Entity (Arg)), Loc);
1479 -- Case of access discriminants. We replace the reference
1480 -- to the type by a reference to the actual object
1482 elsif Nkind (Arg) = N_Attribute_Reference
1483 and then Is_Access_Type (Etype (Arg))
1484 and then Is_Entity_Name (Prefix (Arg))
1485 and then Is_Type (Entity (Prefix (Arg)))
1486 then
1487 Arg :=
1488 Make_Attribute_Reference (Loc,
1489 Prefix => New_Copy (Prefix (Id_Ref)),
1490 Attribute_Name => Name_Unrestricted_Access);
1492 -- Otherwise make a copy of the default expression. Note that
1493 -- we use the current Sloc for this, because we do not want the
1494 -- call to appear to be at the declaration point. Within the
1495 -- expression, replace discriminants with their discriminals.
1497 else
1498 Arg :=
1499 New_Copy_Tree (Arg, Map => Discr_Map, New_Sloc => Loc);
1500 end if;
1502 else
1503 if Is_Constrained (Full_Type) then
1504 Arg := Duplicate_Subexpr_No_Checks (Arg);
1505 else
1506 -- The constraints come from the discriminant default exps,
1507 -- they must be reevaluated, so we use New_Copy_Tree but we
1508 -- ensure the proper Sloc (for any embedded calls).
1510 Arg := New_Copy_Tree (Arg, New_Sloc => Loc);
1511 end if;
1512 end if;
1514 -- Ada 2005 (AI-287) In case of default initialized components,
1515 -- we need to generate the corresponding selected component node
1516 -- to access the discriminant value. In other cases this is not
1517 -- required because we are inside the init proc and we use the
1518 -- corresponding formal.
1520 if With_Default_Init
1521 and then Nkind (Id_Ref) = N_Selected_Component
1522 and then Nkind (Arg) = N_Identifier
1523 then
1524 Append_To (Args,
1525 Make_Selected_Component (Loc,
1526 Prefix => New_Copy_Tree (Prefix (Id_Ref)),
1527 Selector_Name => Arg));
1528 else
1529 Append_To (Args, Arg);
1530 end if;
1532 Next_Discriminant (Discr);
1533 end loop;
1534 end if;
1536 -- If this is a call to initialize the parent component of a derived
1537 -- tagged type, indicate that the tag should not be set in the parent.
1539 if Is_Tagged_Type (Full_Init_Type)
1540 and then not Is_CPP_Class (Full_Init_Type)
1541 and then Nkind (Id_Ref) = N_Selected_Component
1542 and then Chars (Selector_Name (Id_Ref)) = Name_uParent
1543 then
1544 Append_To (Args, New_Occurrence_Of (Standard_False, Loc));
1545 end if;
1547 Append_To (Res,
1548 Make_Procedure_Call_Statement (Loc,
1549 Name => New_Occurrence_Of (Proc, Loc),
1550 Parameter_Associations => Args));
1552 if Controlled_Type (Typ)
1553 and then Nkind (Id_Ref) = N_Selected_Component
1554 then
1555 if Chars (Selector_Name (Id_Ref)) /= Name_uParent then
1556 Append_List_To (Res,
1557 Make_Init_Call (
1558 Ref => New_Copy_Tree (First_Arg),
1559 Typ => Typ,
1560 Flist_Ref =>
1561 Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1562 With_Attach => Make_Integer_Literal (Loc, 1)));
1564 -- If the enclosing type is an extension with new controlled
1565 -- components, it has his own record controller. If the parent
1566 -- also had a record controller, attach it to the new one.
1568 -- Build_Init_Statements relies on the fact that in this specific
1569 -- case the last statement of the result is the attach call to
1570 -- the controller. If this is changed, it must be synchronized.
1572 elsif Present (Enclos_Type)
1573 and then Has_New_Controlled_Component (Enclos_Type)
1574 and then Has_Controlled_Component (Typ)
1575 then
1576 if Is_Inherently_Limited_Type (Typ) then
1577 Controller_Typ := RTE (RE_Limited_Record_Controller);
1578 else
1579 Controller_Typ := RTE (RE_Record_Controller);
1580 end if;
1582 Append_List_To (Res,
1583 Make_Init_Call (
1584 Ref =>
1585 Make_Selected_Component (Loc,
1586 Prefix => New_Copy_Tree (First_Arg),
1587 Selector_Name => Make_Identifier (Loc, Name_uController)),
1588 Typ => Controller_Typ,
1589 Flist_Ref => Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1590 With_Attach => Make_Integer_Literal (Loc, 1)));
1591 end if;
1592 end if;
1594 return Res;
1596 exception
1597 when RE_Not_Available =>
1598 return Empty_List;
1599 end Build_Initialization_Call;
1601 ---------------------------
1602 -- Build_Master_Renaming --
1603 ---------------------------
1605 function Build_Master_Renaming
1606 (N : Node_Id;
1607 T : Entity_Id) return Entity_Id
1609 Loc : constant Source_Ptr := Sloc (N);
1610 M_Id : Entity_Id;
1611 Decl : Node_Id;
1613 begin
1614 -- Nothing to do if there is no task hierarchy
1616 if Restriction_Active (No_Task_Hierarchy) then
1617 return Empty;
1618 end if;
1620 M_Id :=
1621 Make_Defining_Identifier (Loc,
1622 New_External_Name (Chars (T), 'M'));
1624 Decl :=
1625 Make_Object_Renaming_Declaration (Loc,
1626 Defining_Identifier => M_Id,
1627 Subtype_Mark => New_Reference_To (RTE (RE_Master_Id), Loc),
1628 Name => Make_Identifier (Loc, Name_uMaster));
1629 Insert_Before (N, Decl);
1630 Analyze (Decl);
1631 return M_Id;
1633 exception
1634 when RE_Not_Available =>
1635 return Empty;
1636 end Build_Master_Renaming;
1638 ---------------------------
1639 -- Build_Master_Renaming --
1640 ---------------------------
1642 procedure Build_Master_Renaming (N : Node_Id; T : Entity_Id) is
1643 M_Id : Entity_Id;
1645 begin
1646 -- Nothing to do if there is no task hierarchy
1648 if Restriction_Active (No_Task_Hierarchy) then
1649 return;
1650 end if;
1652 M_Id := Build_Master_Renaming (N, T);
1653 Set_Master_Id (T, M_Id);
1655 exception
1656 when RE_Not_Available =>
1657 return;
1658 end Build_Master_Renaming;
1660 ----------------------------
1661 -- Build_Record_Init_Proc --
1662 ----------------------------
1664 procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id) is
1665 Loc : Source_Ptr := Sloc (N);
1666 Discr_Map : constant Elist_Id := New_Elmt_List;
1667 Proc_Id : Entity_Id;
1668 Rec_Type : Entity_Id;
1669 Set_Tag : Entity_Id := Empty;
1671 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id;
1672 -- Build a assignment statement node which assigns to record component
1673 -- its default expression if defined. The assignment left hand side is
1674 -- marked Assignment_OK so that initialization of limited private
1675 -- records works correctly, Return also the adjustment call for
1676 -- controlled objects
1678 procedure Build_Discriminant_Assignments (Statement_List : List_Id);
1679 -- If the record has discriminants, adds assignment statements to
1680 -- statement list to initialize the discriminant values from the
1681 -- arguments of the initialization procedure.
1683 function Build_Init_Statements (Comp_List : Node_Id) return List_Id;
1684 -- Build a list representing a sequence of statements which initialize
1685 -- components of the given component list. This may involve building
1686 -- case statements for the variant parts.
1688 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id;
1689 -- Given a non-tagged type-derivation that declares discriminants,
1690 -- such as
1692 -- type R (R1, R2 : Integer) is record ... end record;
1694 -- type D (D1 : Integer) is new R (1, D1);
1696 -- we make the _init_proc of D be
1698 -- procedure _init_proc(X : D; D1 : Integer) is
1699 -- begin
1700 -- _init_proc( R(X), 1, D1);
1701 -- end _init_proc;
1703 -- This function builds the call statement in this _init_proc.
1705 procedure Build_Init_Procedure;
1706 -- Build the tree corresponding to the procedure specification and body
1707 -- of the initialization procedure (by calling all the preceding
1708 -- auxiliary routines), and install it as the _init TSS.
1710 procedure Build_Offset_To_Top_Functions;
1711 -- Ada 2005 (AI-251): Build the tree corresponding to the procedure spec
1712 -- and body of the Offset_To_Top function that is generated when the
1713 -- parent of a type with discriminants has secondary dispatch tables.
1715 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id);
1716 -- Add range checks to components of discriminated records. S is a
1717 -- subtype indication of a record component. Check_List is a list
1718 -- to which the check actions are appended.
1720 function Component_Needs_Simple_Initialization
1721 (T : Entity_Id) return Boolean;
1722 -- Determines if a component needs simple initialization, given its type
1723 -- T. This is the same as Needs_Simple_Initialization except for the
1724 -- following difference: the types Tag and Interface_Tag, that are
1725 -- access types which would normally require simple initialization to
1726 -- null, do not require initialization as components, since they are
1727 -- explicitly initialized by other means.
1729 procedure Constrain_Array
1730 (SI : Node_Id;
1731 Check_List : List_Id);
1732 -- Called from Build_Record_Checks.
1733 -- Apply a list of index constraints to an unconstrained array type.
1734 -- The first parameter is the entity for the resulting subtype.
1735 -- Check_List is a list to which the check actions are appended.
1737 procedure Constrain_Index
1738 (Index : Node_Id;
1739 S : Node_Id;
1740 Check_List : List_Id);
1741 -- Process an index constraint in a constrained array declaration.
1742 -- The constraint can be a subtype name, or a range with or without
1743 -- an explicit subtype mark. The index is the corresponding index of the
1744 -- unconstrained array. S is the range expression. Check_List is a list
1745 -- to which the check actions are appended (called from
1746 -- Build_Record_Checks).
1748 function Parent_Subtype_Renaming_Discrims return Boolean;
1749 -- Returns True for base types N that rename discriminants, else False
1751 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean;
1752 -- Determines whether a record initialization procedure needs to be
1753 -- generated for the given record type.
1755 ----------------------
1756 -- Build_Assignment --
1757 ----------------------
1759 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id is
1760 Exp : Node_Id := N;
1761 Lhs : Node_Id;
1762 Typ : constant Entity_Id := Underlying_Type (Etype (Id));
1763 Kind : Node_Kind := Nkind (N);
1764 Res : List_Id;
1766 begin
1767 Loc := Sloc (N);
1768 Lhs :=
1769 Make_Selected_Component (Loc,
1770 Prefix => Make_Identifier (Loc, Name_uInit),
1771 Selector_Name => New_Occurrence_Of (Id, Loc));
1772 Set_Assignment_OK (Lhs);
1774 -- Case of an access attribute applied to the current instance.
1775 -- Replace the reference to the type by a reference to the actual
1776 -- object. (Note that this handles the case of the top level of
1777 -- the expression being given by such an attribute, but does not
1778 -- cover uses nested within an initial value expression. Nested
1779 -- uses are unlikely to occur in practice, but are theoretically
1780 -- possible. It is not clear how to handle them without fully
1781 -- traversing the expression. ???
1783 if Kind = N_Attribute_Reference
1784 and then (Attribute_Name (N) = Name_Unchecked_Access
1785 or else
1786 Attribute_Name (N) = Name_Unrestricted_Access)
1787 and then Is_Entity_Name (Prefix (N))
1788 and then Is_Type (Entity (Prefix (N)))
1789 and then Entity (Prefix (N)) = Rec_Type
1790 then
1791 Exp :=
1792 Make_Attribute_Reference (Loc,
1793 Prefix => Make_Identifier (Loc, Name_uInit),
1794 Attribute_Name => Name_Unrestricted_Access);
1795 end if;
1797 -- Ada 2005 (AI-231): Add the run-time check if required
1799 if Ada_Version >= Ada_05
1800 and then Can_Never_Be_Null (Etype (Id)) -- Lhs
1801 then
1802 if Known_Null (Exp) then
1803 return New_List (
1804 Make_Raise_Constraint_Error (Sloc (Exp),
1805 Reason => CE_Null_Not_Allowed));
1807 elsif Present (Etype (Exp))
1808 and then not Can_Never_Be_Null (Etype (Exp))
1809 then
1810 Install_Null_Excluding_Check (Exp);
1811 end if;
1812 end if;
1814 -- Take a copy of Exp to ensure that later copies of this component
1815 -- declaration in derived types see the original tree, not a node
1816 -- rewritten during expansion of the init_proc.
1818 Exp := New_Copy_Tree (Exp);
1820 Res := New_List (
1821 Make_Assignment_Statement (Loc,
1822 Name => Lhs,
1823 Expression => Exp));
1825 Set_No_Ctrl_Actions (First (Res));
1827 -- Adjust the tag if tagged (because of possible view conversions).
1828 -- Suppress the tag adjustment when VM_Target because VM tags are
1829 -- represented implicitly in objects.
1831 if Is_Tagged_Type (Typ) and then VM_Target = No_VM then
1832 Append_To (Res,
1833 Make_Assignment_Statement (Loc,
1834 Name =>
1835 Make_Selected_Component (Loc,
1836 Prefix => New_Copy_Tree (Lhs),
1837 Selector_Name =>
1838 New_Reference_To (First_Tag_Component (Typ), Loc)),
1840 Expression =>
1841 Unchecked_Convert_To (RTE (RE_Tag),
1842 New_Reference_To
1843 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc))));
1844 end if;
1846 -- Adjust the component if controlled except if it is an aggregate
1847 -- that will be expanded inline
1849 if Kind = N_Qualified_Expression then
1850 Kind := Nkind (Expression (N));
1851 end if;
1853 if Controlled_Type (Typ)
1854 and then not (Kind = N_Aggregate or else Kind = N_Extension_Aggregate)
1855 and then not Is_Inherently_Limited_Type (Typ)
1856 then
1857 Append_List_To (Res,
1858 Make_Adjust_Call (
1859 Ref => New_Copy_Tree (Lhs),
1860 Typ => Etype (Id),
1861 Flist_Ref =>
1862 Find_Final_List (Etype (Id), New_Copy_Tree (Lhs)),
1863 With_Attach => Make_Integer_Literal (Loc, 1)));
1864 end if;
1866 return Res;
1868 exception
1869 when RE_Not_Available =>
1870 return Empty_List;
1871 end Build_Assignment;
1873 ------------------------------------
1874 -- Build_Discriminant_Assignments --
1875 ------------------------------------
1877 procedure Build_Discriminant_Assignments (Statement_List : List_Id) is
1878 D : Entity_Id;
1879 Is_Tagged : constant Boolean := Is_Tagged_Type (Rec_Type);
1881 begin
1882 if Has_Discriminants (Rec_Type)
1883 and then not Is_Unchecked_Union (Rec_Type)
1884 then
1885 D := First_Discriminant (Rec_Type);
1887 while Present (D) loop
1888 -- Don't generate the assignment for discriminants in derived
1889 -- tagged types if the discriminant is a renaming of some
1890 -- ancestor discriminant. This initialization will be done
1891 -- when initializing the _parent field of the derived record.
1893 if Is_Tagged and then
1894 Present (Corresponding_Discriminant (D))
1895 then
1896 null;
1898 else
1899 Loc := Sloc (D);
1900 Append_List_To (Statement_List,
1901 Build_Assignment (D,
1902 New_Reference_To (Discriminal (D), Loc)));
1903 end if;
1905 Next_Discriminant (D);
1906 end loop;
1907 end if;
1908 end Build_Discriminant_Assignments;
1910 --------------------------
1911 -- Build_Init_Call_Thru --
1912 --------------------------
1914 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id is
1915 Parent_Proc : constant Entity_Id :=
1916 Base_Init_Proc (Etype (Rec_Type));
1918 Parent_Type : constant Entity_Id :=
1919 Etype (First_Formal (Parent_Proc));
1921 Uparent_Type : constant Entity_Id :=
1922 Underlying_Type (Parent_Type);
1924 First_Discr_Param : Node_Id;
1926 Parent_Discr : Entity_Id;
1927 First_Arg : Node_Id;
1928 Args : List_Id;
1929 Arg : Node_Id;
1930 Res : List_Id;
1932 begin
1933 -- First argument (_Init) is the object to be initialized.
1934 -- ??? not sure where to get a reasonable Loc for First_Arg
1936 First_Arg :=
1937 OK_Convert_To (Parent_Type,
1938 New_Reference_To (Defining_Identifier (First (Parameters)), Loc));
1940 Set_Etype (First_Arg, Parent_Type);
1942 Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
1944 -- In the tasks case,
1945 -- add _Master as the value of the _Master parameter
1946 -- add _Chain as the value of the _Chain parameter.
1947 -- add _Task_Name as the value of the _Task_Name parameter.
1948 -- At the outer level, these will be variables holding the
1949 -- corresponding values obtained from GNARL or the expander.
1951 -- At inner levels, they will be the parameters passed down through
1952 -- the outer routines.
1954 First_Discr_Param := Next (First (Parameters));
1956 if Has_Task (Rec_Type) then
1957 if Restriction_Active (No_Task_Hierarchy) then
1959 -- See comments in System.Tasking.Initialization.Init_RTS
1960 -- for the value 3.
1962 Append_To (Args, Make_Integer_Literal (Loc, 3));
1963 else
1964 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1965 end if;
1967 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1968 Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
1969 First_Discr_Param := Next (Next (Next (First_Discr_Param)));
1970 end if;
1972 -- Append discriminant values
1974 if Has_Discriminants (Uparent_Type) then
1975 pragma Assert (not Is_Tagged_Type (Uparent_Type));
1977 Parent_Discr := First_Discriminant (Uparent_Type);
1978 while Present (Parent_Discr) loop
1980 -- Get the initial value for this discriminant
1981 -- ??? needs to be cleaned up to use parent_Discr_Constr
1982 -- directly.
1984 declare
1985 Discr_Value : Elmt_Id :=
1986 First_Elmt
1987 (Stored_Constraint (Rec_Type));
1989 Discr : Entity_Id :=
1990 First_Stored_Discriminant (Uparent_Type);
1991 begin
1992 while Original_Record_Component (Parent_Discr) /= Discr loop
1993 Next_Stored_Discriminant (Discr);
1994 Next_Elmt (Discr_Value);
1995 end loop;
1997 Arg := Node (Discr_Value);
1998 end;
2000 -- Append it to the list
2002 if Nkind (Arg) = N_Identifier
2003 and then Ekind (Entity (Arg)) = E_Discriminant
2004 then
2005 Append_To (Args,
2006 New_Reference_To (Discriminal (Entity (Arg)), Loc));
2008 -- Case of access discriminants. We replace the reference
2009 -- to the type by a reference to the actual object.
2011 -- Is above comment right??? Use of New_Copy below seems mighty
2012 -- suspicious ???
2014 else
2015 Append_To (Args, New_Copy (Arg));
2016 end if;
2018 Next_Discriminant (Parent_Discr);
2019 end loop;
2020 end if;
2022 Res :=
2023 New_List (
2024 Make_Procedure_Call_Statement (Loc,
2025 Name => New_Occurrence_Of (Parent_Proc, Loc),
2026 Parameter_Associations => Args));
2028 return Res;
2029 end Build_Init_Call_Thru;
2031 -----------------------------------
2032 -- Build_Offset_To_Top_Functions --
2033 -----------------------------------
2035 procedure Build_Offset_To_Top_Functions is
2037 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id);
2038 -- Generate:
2039 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2040 -- begin
2041 -- return O.Iface_Comp'Position;
2042 -- end Fxx;
2044 ------------------------------
2045 -- Build_Offset_To_Top_Body --
2046 ------------------------------
2048 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id) is
2049 Body_Node : Node_Id;
2050 Func_Id : Entity_Id;
2051 Spec_Node : Node_Id;
2053 begin
2054 Func_Id :=
2055 Make_Defining_Identifier (Loc,
2056 Chars => New_Internal_Name ('F'));
2058 Set_DT_Offset_To_Top_Func (Iface_Comp, Func_Id);
2060 -- Generate
2061 -- function Fxx (O : in Rec_Typ) return Storage_Offset;
2063 Spec_Node := New_Node (N_Function_Specification, Loc);
2064 Set_Defining_Unit_Name (Spec_Node, Func_Id);
2065 Set_Parameter_Specifications (Spec_Node, New_List (
2066 Make_Parameter_Specification (Loc,
2067 Defining_Identifier => Make_Defining_Identifier (Loc, Name_uO),
2068 In_Present => True,
2069 Parameter_Type => New_Reference_To (Rec_Type, Loc))));
2070 Set_Result_Definition (Spec_Node,
2071 New_Reference_To (RTE (RE_Storage_Offset), Loc));
2073 -- Generate
2074 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2075 -- begin
2076 -- return O.Iface_Comp'Position;
2077 -- end Fxx;
2079 Body_Node := New_Node (N_Subprogram_Body, Loc);
2080 Set_Specification (Body_Node, Spec_Node);
2081 Set_Declarations (Body_Node, New_List);
2082 Set_Handled_Statement_Sequence (Body_Node,
2083 Make_Handled_Sequence_Of_Statements (Loc,
2084 Statements => New_List (
2085 Make_Simple_Return_Statement (Loc,
2086 Expression =>
2087 Make_Attribute_Reference (Loc,
2088 Prefix =>
2089 Make_Selected_Component (Loc,
2090 Prefix => Make_Identifier (Loc, Name_uO),
2091 Selector_Name => New_Reference_To
2092 (Iface_Comp, Loc)),
2093 Attribute_Name => Name_Position)))));
2095 Set_Ekind (Func_Id, E_Function);
2096 Set_Mechanism (Func_Id, Default_Mechanism);
2097 Set_Is_Internal (Func_Id, True);
2099 if not Debug_Generated_Code then
2100 Set_Debug_Info_Off (Func_Id);
2101 end if;
2103 Analyze (Body_Node);
2105 Append_Freeze_Action (Rec_Type, Body_Node);
2106 end Build_Offset_To_Top_Function;
2108 -- Local variables
2110 Ifaces_List : Elist_Id;
2111 Ifaces_Comp_List : Elist_Id;
2112 Ifaces_Tag_List : Elist_Id;
2113 Iface_Elmt : Elmt_Id;
2114 Comp_Elmt : Elmt_Id;
2116 pragma Warnings (Off, Ifaces_Tag_List);
2118 -- Start of processing for Build_Offset_To_Top_Functions
2120 begin
2121 -- Offset_To_Top_Functions are built only for derivations of types
2122 -- with discriminants that cover interface types.
2124 if not Is_Tagged_Type (Rec_Type)
2125 or else Etype (Rec_Type) = Rec_Type
2126 or else not Has_Discriminants (Etype (Rec_Type))
2127 then
2128 return;
2129 end if;
2131 Collect_Interfaces_Info
2132 (Rec_Type, Ifaces_List, Ifaces_Comp_List, Ifaces_Tag_List);
2134 -- For each interface type with secondary dispatch table we generate
2135 -- the Offset_To_Top_Functions (required to displace the pointer in
2136 -- interface conversions)
2138 Iface_Elmt := First_Elmt (Ifaces_List);
2139 Comp_Elmt := First_Elmt (Ifaces_Comp_List);
2140 while Present (Iface_Elmt) loop
2142 -- If the interface is a parent of Rec_Type it shares the primary
2143 -- dispatch table and hence there is no need to build the function
2145 if not Is_Parent (Node (Iface_Elmt), Rec_Type) then
2146 Build_Offset_To_Top_Function (Iface_Comp => Node (Comp_Elmt));
2147 end if;
2149 Next_Elmt (Iface_Elmt);
2150 Next_Elmt (Comp_Elmt);
2151 end loop;
2152 end Build_Offset_To_Top_Functions;
2154 --------------------------
2155 -- Build_Init_Procedure --
2156 --------------------------
2158 procedure Build_Init_Procedure is
2159 Body_Node : Node_Id;
2160 Handled_Stmt_Node : Node_Id;
2161 Parameters : List_Id;
2162 Proc_Spec_Node : Node_Id;
2163 Body_Stmts : List_Id;
2164 Record_Extension_Node : Node_Id;
2165 Init_Tags_List : List_Id;
2167 begin
2168 Body_Stmts := New_List;
2169 Body_Node := New_Node (N_Subprogram_Body, Loc);
2171 Proc_Id :=
2172 Make_Defining_Identifier (Loc,
2173 Chars => Make_Init_Proc_Name (Rec_Type));
2174 Set_Ekind (Proc_Id, E_Procedure);
2176 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2177 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2179 Parameters := Init_Formals (Rec_Type);
2180 Append_List_To (Parameters,
2181 Build_Discriminant_Formals (Rec_Type, True));
2183 -- For tagged types, we add a flag to indicate whether the routine
2184 -- is called to initialize a parent component in the init_proc of
2185 -- a type extension. If the flag is false, we do not set the tag
2186 -- because it has been set already in the extension.
2188 if Is_Tagged_Type (Rec_Type)
2189 and then not Is_CPP_Class (Rec_Type)
2190 then
2191 Set_Tag :=
2192 Make_Defining_Identifier (Loc,
2193 Chars => New_Internal_Name ('P'));
2195 Append_To (Parameters,
2196 Make_Parameter_Specification (Loc,
2197 Defining_Identifier => Set_Tag,
2198 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
2199 Expression => New_Occurrence_Of (Standard_True, Loc)));
2200 end if;
2202 Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
2203 Set_Specification (Body_Node, Proc_Spec_Node);
2204 Set_Declarations (Body_Node, New_List);
2206 if Parent_Subtype_Renaming_Discrims then
2208 -- N is a Derived_Type_Definition that renames the parameters
2209 -- of the ancestor type. We initialize it by expanding our
2210 -- discriminants and call the ancestor _init_proc with a
2211 -- type-converted object
2213 Append_List_To (Body_Stmts,
2214 Build_Init_Call_Thru (Parameters));
2216 elsif Nkind (Type_Definition (N)) = N_Record_Definition then
2217 Build_Discriminant_Assignments (Body_Stmts);
2219 if not Null_Present (Type_Definition (N)) then
2220 Append_List_To (Body_Stmts,
2221 Build_Init_Statements (
2222 Component_List (Type_Definition (N))));
2223 end if;
2225 else
2226 -- N is a Derived_Type_Definition with a possible non-empty
2227 -- extension. The initialization of a type extension consists
2228 -- in the initialization of the components in the extension.
2230 Build_Discriminant_Assignments (Body_Stmts);
2232 Record_Extension_Node :=
2233 Record_Extension_Part (Type_Definition (N));
2235 if not Null_Present (Record_Extension_Node) then
2236 declare
2237 Stmts : constant List_Id :=
2238 Build_Init_Statements (
2239 Component_List (Record_Extension_Node));
2241 begin
2242 -- The parent field must be initialized first because
2243 -- the offset of the new discriminants may depend on it
2245 Prepend_To (Body_Stmts, Remove_Head (Stmts));
2246 Append_List_To (Body_Stmts, Stmts);
2247 end;
2248 end if;
2249 end if;
2251 -- Add here the assignment to instantiate the Tag
2253 -- The assignment corresponds to the code:
2255 -- _Init._Tag := Typ'Tag;
2257 -- Suppress the tag assignment when VM_Target because VM tags are
2258 -- represented implicitly in objects. It is also suppressed in case
2259 -- of CPP_Class types because in this case the tag is initialized in
2260 -- the C++ side.
2262 if Is_Tagged_Type (Rec_Type)
2263 and then not Is_CPP_Class (Rec_Type)
2264 and then VM_Target = No_VM
2265 and then not No_Run_Time_Mode
2266 then
2267 -- Initialize the primary tag
2269 Init_Tags_List := New_List (
2270 Make_Assignment_Statement (Loc,
2271 Name =>
2272 Make_Selected_Component (Loc,
2273 Prefix => Make_Identifier (Loc, Name_uInit),
2274 Selector_Name =>
2275 New_Reference_To (First_Tag_Component (Rec_Type), Loc)),
2277 Expression =>
2278 New_Reference_To
2279 (Node (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2281 -- Ada 2005 (AI-251): Initialize the secondary tags components
2282 -- located at fixed positions (tags whose position depends on
2283 -- variable size components are initialized later ---see below).
2285 if Ada_Version >= Ada_05
2286 and then not Is_Interface (Rec_Type)
2287 and then Has_Abstract_Interfaces (Rec_Type)
2288 then
2289 Init_Secondary_Tags
2290 (Typ => Rec_Type,
2291 Target => Make_Identifier (Loc, Name_uInit),
2292 Stmts_List => Init_Tags_List,
2293 Fixed_Comps => True,
2294 Variable_Comps => False);
2295 end if;
2297 -- The tag must be inserted before the assignments to other
2298 -- components, because the initial value of the component may
2299 -- depend on the tag (eg. through a dispatching operation on
2300 -- an access to the current type). The tag assignment is not done
2301 -- when initializing the parent component of a type extension,
2302 -- because in that case the tag is set in the extension.
2304 -- Extensions of imported C++ classes add a final complication,
2305 -- because we cannot inhibit tag setting in the constructor for
2306 -- the parent. In that case we insert the tag initialization
2307 -- after the calls to initialize the parent.
2309 if not Is_CPP_Class (Root_Type (Rec_Type)) then
2310 Prepend_To (Body_Stmts,
2311 Make_If_Statement (Loc,
2312 Condition => New_Occurrence_Of (Set_Tag, Loc),
2313 Then_Statements => Init_Tags_List));
2315 -- CPP_Class derivation: In this case the dispatch table of the
2316 -- parent was built in the C++ side and we copy the table of the
2317 -- parent to initialize the new dispatch table.
2319 else
2320 declare
2321 Nod : Node_Id;
2323 begin
2324 -- We assume the first init_proc call is for the parent
2326 Nod := First (Body_Stmts);
2327 while Present (Next (Nod))
2328 and then (Nkind (Nod) /= N_Procedure_Call_Statement
2329 or else not Is_Init_Proc (Name (Nod)))
2330 loop
2331 Nod := Next (Nod);
2332 end loop;
2334 -- Generate:
2335 -- ancestor_constructor (_init.parent);
2336 -- if Arg2 then
2337 -- inherit_prim_ops (_init._tag, new_dt, num_prims);
2338 -- _init._tag := new_dt;
2339 -- end if;
2341 Prepend_To (Init_Tags_List,
2342 Build_Inherit_Prims (Loc,
2343 Typ => Rec_Type,
2344 Old_Tag_Node =>
2345 Make_Selected_Component (Loc,
2346 Prefix =>
2347 Make_Identifier (Loc,
2348 Chars => Name_uInit),
2349 Selector_Name =>
2350 New_Reference_To
2351 (First_Tag_Component (Rec_Type), Loc)),
2352 New_Tag_Node =>
2353 New_Reference_To
2354 (Node (First_Elmt (Access_Disp_Table (Rec_Type))),
2355 Loc),
2356 Num_Prims =>
2357 UI_To_Int
2358 (DT_Entry_Count (First_Tag_Component (Rec_Type)))));
2360 Insert_After (Nod,
2361 Make_If_Statement (Loc,
2362 Condition => New_Occurrence_Of (Set_Tag, Loc),
2363 Then_Statements => Init_Tags_List));
2365 -- We have inherited table of the parent from the CPP side.
2366 -- Now we fill the slots associated with Ada primitives.
2367 -- This needs more work to avoid its execution each time
2368 -- an object is initialized???
2370 declare
2371 E : Elmt_Id;
2372 Prim : Node_Id;
2374 begin
2375 E := First_Elmt (Primitive_Operations (Rec_Type));
2376 while Present (E) loop
2377 Prim := Node (E);
2379 if not Is_Imported (Prim)
2380 and then Convention (Prim) = Convention_CPP
2381 and then not Present (Abstract_Interface_Alias
2382 (Prim))
2383 then
2384 Register_Primitive (Loc,
2385 Prim => Prim,
2386 Ins_Nod => Last (Init_Tags_List));
2387 end if;
2389 Next_Elmt (E);
2390 end loop;
2391 end;
2392 end;
2393 end if;
2395 -- Ada 2005 (AI-251): Initialize the secondary tag components
2396 -- located at variable positions. We delay the generation of this
2397 -- code until here because the value of the attribute 'Position
2398 -- applied to variable size components of the parent type that
2399 -- depend on discriminants is only safely read at runtime after
2400 -- the parent components have been initialized.
2402 if Ada_Version >= Ada_05
2403 and then not Is_Interface (Rec_Type)
2404 and then Has_Abstract_Interfaces (Rec_Type)
2405 and then Has_Discriminants (Etype (Rec_Type))
2406 and then Is_Variable_Size_Record (Etype (Rec_Type))
2407 then
2408 Init_Tags_List := New_List;
2410 Init_Secondary_Tags
2411 (Typ => Rec_Type,
2412 Target => Make_Identifier (Loc, Name_uInit),
2413 Stmts_List => Init_Tags_List,
2414 Fixed_Comps => False,
2415 Variable_Comps => True);
2417 if Is_Non_Empty_List (Init_Tags_List) then
2418 Append_List_To (Body_Stmts, Init_Tags_List);
2419 end if;
2420 end if;
2421 end if;
2423 Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
2424 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2425 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2426 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2428 if not Debug_Generated_Code then
2429 Set_Debug_Info_Off (Proc_Id);
2430 end if;
2432 -- Associate Init_Proc with type, and determine if the procedure
2433 -- is null (happens because of the Initialize_Scalars pragma case,
2434 -- where we have to generate a null procedure in case it is called
2435 -- by a client with Initialize_Scalars set). Such procedures have
2436 -- to be generated, but do not have to be called, so we mark them
2437 -- as null to suppress the call.
2439 Set_Init_Proc (Rec_Type, Proc_Id);
2441 if List_Length (Body_Stmts) = 1
2442 and then Nkind (First (Body_Stmts)) = N_Null_Statement
2443 and then VM_Target /= CLI_Target
2444 then
2445 -- Even though the init proc may be null at this time it might get
2446 -- some stuff added to it later by the CIL backend, so always keep
2447 -- it when VM_Target = CLI_Target.
2449 Set_Is_Null_Init_Proc (Proc_Id);
2450 end if;
2451 end Build_Init_Procedure;
2453 ---------------------------
2454 -- Build_Init_Statements --
2455 ---------------------------
2457 function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
2458 Check_List : constant List_Id := New_List;
2459 Alt_List : List_Id;
2460 Statement_List : List_Id;
2461 Stmts : List_Id;
2463 Per_Object_Constraint_Components : Boolean;
2465 Decl : Node_Id;
2466 Variant : Node_Id;
2468 Id : Entity_Id;
2469 Typ : Entity_Id;
2471 function Has_Access_Constraint (E : Entity_Id) return Boolean;
2472 -- Components with access discriminants that depend on the current
2473 -- instance must be initialized after all other components.
2475 ---------------------------
2476 -- Has_Access_Constraint --
2477 ---------------------------
2479 function Has_Access_Constraint (E : Entity_Id) return Boolean is
2480 Disc : Entity_Id;
2481 T : constant Entity_Id := Etype (E);
2483 begin
2484 if Has_Per_Object_Constraint (E)
2485 and then Has_Discriminants (T)
2486 then
2487 Disc := First_Discriminant (T);
2488 while Present (Disc) loop
2489 if Is_Access_Type (Etype (Disc)) then
2490 return True;
2491 end if;
2493 Next_Discriminant (Disc);
2494 end loop;
2496 return False;
2497 else
2498 return False;
2499 end if;
2500 end Has_Access_Constraint;
2502 -- Start of processing for Build_Init_Statements
2504 begin
2505 if Null_Present (Comp_List) then
2506 return New_List (Make_Null_Statement (Loc));
2507 end if;
2509 Statement_List := New_List;
2511 -- Loop through components, skipping pragmas, in 2 steps. The first
2512 -- step deals with regular components. The second step deals with
2513 -- components have per object constraints, and no explicit initia-
2514 -- lization.
2516 Per_Object_Constraint_Components := False;
2518 -- First step : regular components
2520 Decl := First_Non_Pragma (Component_Items (Comp_List));
2521 while Present (Decl) loop
2522 Loc := Sloc (Decl);
2523 Build_Record_Checks
2524 (Subtype_Indication (Component_Definition (Decl)), Check_List);
2526 Id := Defining_Identifier (Decl);
2527 Typ := Etype (Id);
2529 if Has_Access_Constraint (Id)
2530 and then No (Expression (Decl))
2531 then
2532 -- Skip processing for now and ask for a second pass
2534 Per_Object_Constraint_Components := True;
2536 else
2537 -- Case of explicit initialization
2539 if Present (Expression (Decl)) then
2540 Stmts := Build_Assignment (Id, Expression (Decl));
2542 -- Case of composite component with its own Init_Proc
2544 elsif not Is_Interface (Typ)
2545 and then Has_Non_Null_Base_Init_Proc (Typ)
2546 then
2547 Stmts :=
2548 Build_Initialization_Call
2549 (Loc,
2550 Make_Selected_Component (Loc,
2551 Prefix => Make_Identifier (Loc, Name_uInit),
2552 Selector_Name => New_Occurrence_Of (Id, Loc)),
2553 Typ,
2554 In_Init_Proc => True,
2555 Enclos_Type => Rec_Type,
2556 Discr_Map => Discr_Map);
2558 Clean_Task_Names (Typ, Proc_Id);
2560 -- Case of component needing simple initialization
2562 elsif Component_Needs_Simple_Initialization (Typ) then
2563 Stmts :=
2564 Build_Assignment
2565 (Id, Get_Simple_Init_Val (Typ, Loc, Esize (Id)));
2567 -- Nothing needed for this case
2569 else
2570 Stmts := No_List;
2571 end if;
2573 if Present (Check_List) then
2574 Append_List_To (Statement_List, Check_List);
2575 end if;
2577 if Present (Stmts) then
2579 -- Add the initialization of the record controller before
2580 -- the _Parent field is attached to it when the attachment
2581 -- can occur. It does not work to simply initialize the
2582 -- controller first: it must be initialized after the parent
2583 -- if the parent holds discriminants that can be used to
2584 -- compute the offset of the controller. We assume here that
2585 -- the last statement of the initialization call is the
2586 -- attachment of the parent (see Build_Initialization_Call)
2588 if Chars (Id) = Name_uController
2589 and then Rec_Type /= Etype (Rec_Type)
2590 and then Has_Controlled_Component (Etype (Rec_Type))
2591 and then Has_New_Controlled_Component (Rec_Type)
2592 and then Present (Last (Statement_List))
2593 then
2594 Insert_List_Before (Last (Statement_List), Stmts);
2595 else
2596 Append_List_To (Statement_List, Stmts);
2597 end if;
2598 end if;
2599 end if;
2601 Next_Non_Pragma (Decl);
2602 end loop;
2604 if Per_Object_Constraint_Components then
2606 -- Second pass: components with per-object constraints
2608 Decl := First_Non_Pragma (Component_Items (Comp_List));
2609 while Present (Decl) loop
2610 Loc := Sloc (Decl);
2611 Id := Defining_Identifier (Decl);
2612 Typ := Etype (Id);
2614 if Has_Access_Constraint (Id)
2615 and then No (Expression (Decl))
2616 then
2617 if Has_Non_Null_Base_Init_Proc (Typ) then
2618 Append_List_To (Statement_List,
2619 Build_Initialization_Call (Loc,
2620 Make_Selected_Component (Loc,
2621 Prefix => Make_Identifier (Loc, Name_uInit),
2622 Selector_Name => New_Occurrence_Of (Id, Loc)),
2623 Typ,
2624 In_Init_Proc => True,
2625 Enclos_Type => Rec_Type,
2626 Discr_Map => Discr_Map));
2628 Clean_Task_Names (Typ, Proc_Id);
2630 elsif Component_Needs_Simple_Initialization (Typ) then
2631 Append_List_To (Statement_List,
2632 Build_Assignment
2633 (Id, Get_Simple_Init_Val (Typ, Loc, Esize (Id))));
2634 end if;
2635 end if;
2637 Next_Non_Pragma (Decl);
2638 end loop;
2639 end if;
2641 -- Process the variant part
2643 if Present (Variant_Part (Comp_List)) then
2644 Alt_List := New_List;
2645 Variant := First_Non_Pragma (Variants (Variant_Part (Comp_List)));
2646 while Present (Variant) loop
2647 Loc := Sloc (Variant);
2648 Append_To (Alt_List,
2649 Make_Case_Statement_Alternative (Loc,
2650 Discrete_Choices =>
2651 New_Copy_List (Discrete_Choices (Variant)),
2652 Statements =>
2653 Build_Init_Statements (Component_List (Variant))));
2654 Next_Non_Pragma (Variant);
2655 end loop;
2657 -- The expression of the case statement which is a reference
2658 -- to one of the discriminants is replaced by the appropriate
2659 -- formal parameter of the initialization procedure.
2661 Append_To (Statement_List,
2662 Make_Case_Statement (Loc,
2663 Expression =>
2664 New_Reference_To (Discriminal (
2665 Entity (Name (Variant_Part (Comp_List)))), Loc),
2666 Alternatives => Alt_List));
2667 end if;
2669 -- For a task record type, add the task create call and calls
2670 -- to bind any interrupt (signal) entries.
2672 if Is_Task_Record_Type (Rec_Type) then
2674 -- In the case of the restricted run time the ATCB has already
2675 -- been preallocated.
2677 if Restricted_Profile then
2678 Append_To (Statement_List,
2679 Make_Assignment_Statement (Loc,
2680 Name => Make_Selected_Component (Loc,
2681 Prefix => Make_Identifier (Loc, Name_uInit),
2682 Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
2683 Expression => Make_Attribute_Reference (Loc,
2684 Prefix =>
2685 Make_Selected_Component (Loc,
2686 Prefix => Make_Identifier (Loc, Name_uInit),
2687 Selector_Name =>
2688 Make_Identifier (Loc, Name_uATCB)),
2689 Attribute_Name => Name_Unchecked_Access)));
2690 end if;
2692 Append_To (Statement_List, Make_Task_Create_Call (Rec_Type));
2694 declare
2695 Task_Type : constant Entity_Id :=
2696 Corresponding_Concurrent_Type (Rec_Type);
2697 Task_Decl : constant Node_Id := Parent (Task_Type);
2698 Task_Def : constant Node_Id := Task_Definition (Task_Decl);
2699 Vis_Decl : Node_Id;
2700 Ent : Entity_Id;
2702 begin
2703 if Present (Task_Def) then
2704 Vis_Decl := First (Visible_Declarations (Task_Def));
2705 while Present (Vis_Decl) loop
2706 Loc := Sloc (Vis_Decl);
2708 if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
2709 if Get_Attribute_Id (Chars (Vis_Decl)) =
2710 Attribute_Address
2711 then
2712 Ent := Entity (Name (Vis_Decl));
2714 if Ekind (Ent) = E_Entry then
2715 Append_To (Statement_List,
2716 Make_Procedure_Call_Statement (Loc,
2717 Name => New_Reference_To (
2718 RTE (RE_Bind_Interrupt_To_Entry), Loc),
2719 Parameter_Associations => New_List (
2720 Make_Selected_Component (Loc,
2721 Prefix =>
2722 Make_Identifier (Loc, Name_uInit),
2723 Selector_Name =>
2724 Make_Identifier (Loc, Name_uTask_Id)),
2725 Entry_Index_Expression (
2726 Loc, Ent, Empty, Task_Type),
2727 Expression (Vis_Decl))));
2728 end if;
2729 end if;
2730 end if;
2732 Next (Vis_Decl);
2733 end loop;
2734 end if;
2735 end;
2736 end if;
2738 -- For a protected type, add statements generated by
2739 -- Make_Initialize_Protection.
2741 if Is_Protected_Record_Type (Rec_Type) then
2742 Append_List_To (Statement_List,
2743 Make_Initialize_Protection (Rec_Type));
2744 end if;
2746 -- If no initializations when generated for component declarations
2747 -- corresponding to this Statement_List, append a null statement
2748 -- to the Statement_List to make it a valid Ada tree.
2750 if Is_Empty_List (Statement_List) then
2751 Append (New_Node (N_Null_Statement, Loc), Statement_List);
2752 end if;
2754 return Statement_List;
2756 exception
2757 when RE_Not_Available =>
2758 return Empty_List;
2759 end Build_Init_Statements;
2761 -------------------------
2762 -- Build_Record_Checks --
2763 -------------------------
2765 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
2766 Subtype_Mark_Id : Entity_Id;
2768 begin
2769 if Nkind (S) = N_Subtype_Indication then
2770 Find_Type (Subtype_Mark (S));
2771 Subtype_Mark_Id := Entity (Subtype_Mark (S));
2773 -- Remaining processing depends on type
2775 case Ekind (Subtype_Mark_Id) is
2777 when Array_Kind =>
2778 Constrain_Array (S, Check_List);
2780 when others =>
2781 null;
2782 end case;
2783 end if;
2784 end Build_Record_Checks;
2786 -------------------------------------------
2787 -- Component_Needs_Simple_Initialization --
2788 -------------------------------------------
2790 function Component_Needs_Simple_Initialization
2791 (T : Entity_Id) return Boolean
2793 begin
2794 return
2795 Needs_Simple_Initialization (T)
2796 and then not Is_RTE (T, RE_Tag)
2798 -- Ada 2005 (AI-251): Check also the tag of abstract interfaces
2800 and then not Is_RTE (T, RE_Interface_Tag);
2801 end Component_Needs_Simple_Initialization;
2803 ---------------------
2804 -- Constrain_Array --
2805 ---------------------
2807 procedure Constrain_Array
2808 (SI : Node_Id;
2809 Check_List : List_Id)
2811 C : constant Node_Id := Constraint (SI);
2812 Number_Of_Constraints : Nat := 0;
2813 Index : Node_Id;
2814 S, T : Entity_Id;
2816 begin
2817 T := Entity (Subtype_Mark (SI));
2819 if Ekind (T) in Access_Kind then
2820 T := Designated_Type (T);
2821 end if;
2823 S := First (Constraints (C));
2825 while Present (S) loop
2826 Number_Of_Constraints := Number_Of_Constraints + 1;
2827 Next (S);
2828 end loop;
2830 -- In either case, the index constraint must provide a discrete
2831 -- range for each index of the array type and the type of each
2832 -- discrete range must be the same as that of the corresponding
2833 -- index. (RM 3.6.1)
2835 S := First (Constraints (C));
2836 Index := First_Index (T);
2837 Analyze (Index);
2839 -- Apply constraints to each index type
2841 for J in 1 .. Number_Of_Constraints loop
2842 Constrain_Index (Index, S, Check_List);
2843 Next (Index);
2844 Next (S);
2845 end loop;
2847 end Constrain_Array;
2849 ---------------------
2850 -- Constrain_Index --
2851 ---------------------
2853 procedure Constrain_Index
2854 (Index : Node_Id;
2855 S : Node_Id;
2856 Check_List : List_Id)
2858 T : constant Entity_Id := Etype (Index);
2860 begin
2861 if Nkind (S) = N_Range then
2862 Process_Range_Expr_In_Decl (S, T, Check_List);
2863 end if;
2864 end Constrain_Index;
2866 --------------------------------------
2867 -- Parent_Subtype_Renaming_Discrims --
2868 --------------------------------------
2870 function Parent_Subtype_Renaming_Discrims return Boolean is
2871 De : Entity_Id;
2872 Dp : Entity_Id;
2874 begin
2875 if Base_Type (Pe) /= Pe then
2876 return False;
2877 end if;
2879 if Etype (Pe) = Pe
2880 or else not Has_Discriminants (Pe)
2881 or else Is_Constrained (Pe)
2882 or else Is_Tagged_Type (Pe)
2883 then
2884 return False;
2885 end if;
2887 -- If there are no explicit stored discriminants we have inherited
2888 -- the root type discriminants so far, so no renamings occurred.
2890 if First_Discriminant (Pe) = First_Stored_Discriminant (Pe) then
2891 return False;
2892 end if;
2894 -- Check if we have done some trivial renaming of the parent
2895 -- discriminants, i.e. something like
2897 -- type DT (X1,X2: int) is new PT (X1,X2);
2899 De := First_Discriminant (Pe);
2900 Dp := First_Discriminant (Etype (Pe));
2902 while Present (De) loop
2903 pragma Assert (Present (Dp));
2905 if Corresponding_Discriminant (De) /= Dp then
2906 return True;
2907 end if;
2909 Next_Discriminant (De);
2910 Next_Discriminant (Dp);
2911 end loop;
2913 return Present (Dp);
2914 end Parent_Subtype_Renaming_Discrims;
2916 ------------------------
2917 -- Requires_Init_Proc --
2918 ------------------------
2920 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
2921 Comp_Decl : Node_Id;
2922 Id : Entity_Id;
2923 Typ : Entity_Id;
2925 begin
2926 -- Definitely do not need one if specifically suppressed
2928 if Suppress_Init_Proc (Rec_Id) then
2929 return False;
2930 end if;
2932 -- If it is a type derived from a type with unknown discriminants,
2933 -- we cannot build an initialization procedure for it.
2935 if Has_Unknown_Discriminants (Rec_Id) then
2936 return False;
2937 end if;
2939 -- Otherwise we need to generate an initialization procedure if
2940 -- Is_CPP_Class is False and at least one of the following applies:
2942 -- 1. Discriminants are present, since they need to be initialized
2943 -- with the appropriate discriminant constraint expressions.
2944 -- However, the discriminant of an unchecked union does not
2945 -- count, since the discriminant is not present.
2947 -- 2. The type is a tagged type, since the implicit Tag component
2948 -- needs to be initialized with a pointer to the dispatch table.
2950 -- 3. The type contains tasks
2952 -- 4. One or more components has an initial value
2954 -- 5. One or more components is for a type which itself requires
2955 -- an initialization procedure.
2957 -- 6. One or more components is a type that requires simple
2958 -- initialization (see Needs_Simple_Initialization), except
2959 -- that types Tag and Interface_Tag are excluded, since fields
2960 -- of these types are initialized by other means.
2962 -- 7. The type is the record type built for a task type (since at
2963 -- the very least, Create_Task must be called)
2965 -- 8. The type is the record type built for a protected type (since
2966 -- at least Initialize_Protection must be called)
2968 -- 9. The type is marked as a public entity. The reason we add this
2969 -- case (even if none of the above apply) is to properly handle
2970 -- Initialize_Scalars. If a package is compiled without an IS
2971 -- pragma, and the client is compiled with an IS pragma, then
2972 -- the client will think an initialization procedure is present
2973 -- and call it, when in fact no such procedure is required, but
2974 -- since the call is generated, there had better be a routine
2975 -- at the other end of the call, even if it does nothing!)
2977 -- Note: the reason we exclude the CPP_Class case is because in this
2978 -- case the initialization is performed in the C++ side.
2980 if Is_CPP_Class (Rec_Id) then
2981 return False;
2983 elsif Is_Interface (Rec_Id) then
2984 return False;
2986 elsif not Restriction_Active (No_Initialize_Scalars)
2987 and then Is_Public (Rec_Id)
2988 then
2989 return True;
2991 elsif (Has_Discriminants (Rec_Id)
2992 and then not Is_Unchecked_Union (Rec_Id))
2993 or else Is_Tagged_Type (Rec_Id)
2994 or else Is_Concurrent_Record_Type (Rec_Id)
2995 or else Has_Task (Rec_Id)
2996 then
2997 return True;
2998 end if;
3000 Id := First_Component (Rec_Id);
3002 while Present (Id) loop
3003 Comp_Decl := Parent (Id);
3004 Typ := Etype (Id);
3006 if Present (Expression (Comp_Decl))
3007 or else Has_Non_Null_Base_Init_Proc (Typ)
3008 or else Component_Needs_Simple_Initialization (Typ)
3009 then
3010 return True;
3011 end if;
3013 Next_Component (Id);
3014 end loop;
3016 return False;
3017 end Requires_Init_Proc;
3019 -- Start of processing for Build_Record_Init_Proc
3021 begin
3022 Rec_Type := Defining_Identifier (N);
3024 if Is_Value_Type (Rec_Type) then
3025 return;
3026 end if;
3028 -- This may be full declaration of a private type, in which case
3029 -- the visible entity is a record, and the private entity has been
3030 -- exchanged with it in the private part of the current package.
3031 -- The initialization procedure is built for the record type, which
3032 -- is retrievable from the private entity.
3034 if Is_Incomplete_Or_Private_Type (Rec_Type) then
3035 Rec_Type := Underlying_Type (Rec_Type);
3036 end if;
3038 -- If there are discriminants, build the discriminant map to replace
3039 -- discriminants by their discriminals in complex bound expressions.
3040 -- These only arise for the corresponding records of protected types.
3042 if Is_Concurrent_Record_Type (Rec_Type)
3043 and then Has_Discriminants (Rec_Type)
3044 then
3045 declare
3046 Disc : Entity_Id;
3047 begin
3048 Disc := First_Discriminant (Rec_Type);
3049 while Present (Disc) loop
3050 Append_Elmt (Disc, Discr_Map);
3051 Append_Elmt (Discriminal (Disc), Discr_Map);
3052 Next_Discriminant (Disc);
3053 end loop;
3054 end;
3055 end if;
3057 -- Derived types that have no type extension can use the initialization
3058 -- procedure of their parent and do not need a procedure of their own.
3059 -- This is only correct if there are no representation clauses for the
3060 -- type or its parent, and if the parent has in fact been frozen so
3061 -- that its initialization procedure exists.
3063 if Is_Derived_Type (Rec_Type)
3064 and then not Is_Tagged_Type (Rec_Type)
3065 and then not Is_Unchecked_Union (Rec_Type)
3066 and then not Has_New_Non_Standard_Rep (Rec_Type)
3067 and then not Parent_Subtype_Renaming_Discrims
3068 and then Has_Non_Null_Base_Init_Proc (Etype (Rec_Type))
3069 then
3070 Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
3072 -- Otherwise if we need an initialization procedure, then build one,
3073 -- mark it as public and inlinable and as having a completion.
3075 elsif Requires_Init_Proc (Rec_Type)
3076 or else Is_Unchecked_Union (Rec_Type)
3077 then
3078 Build_Offset_To_Top_Functions;
3079 Build_Init_Procedure;
3080 Set_Is_Public (Proc_Id, Is_Public (Pe));
3082 -- The initialization of protected records is not worth inlining.
3083 -- In addition, when compiled for another unit for inlining purposes,
3084 -- it may make reference to entities that have not been elaborated
3085 -- yet. The initialization of controlled records contains a nested
3086 -- clean-up procedure that makes it impractical to inline as well,
3087 -- and leads to undefined symbols if inlined in a different unit.
3088 -- Similar considerations apply to task types.
3090 if not Is_Concurrent_Type (Rec_Type)
3091 and then not Has_Task (Rec_Type)
3092 and then not Controlled_Type (Rec_Type)
3093 then
3094 Set_Is_Inlined (Proc_Id);
3095 end if;
3097 Set_Is_Internal (Proc_Id);
3098 Set_Has_Completion (Proc_Id);
3100 if not Debug_Generated_Code then
3101 Set_Debug_Info_Off (Proc_Id);
3102 end if;
3104 declare
3105 Agg : constant Node_Id :=
3106 Build_Equivalent_Record_Aggregate (Rec_Type);
3108 procedure Collect_Itypes (Comp : Node_Id);
3109 -- Generate references to itypes in the aggregate, because
3110 -- the first use of the aggregate may be in a nested scope.
3112 --------------------
3113 -- Collect_Itypes --
3114 --------------------
3116 procedure Collect_Itypes (Comp : Node_Id) is
3117 Ref : Node_Id;
3118 Sub_Aggr : Node_Id;
3119 Typ : Entity_Id;
3121 begin
3122 if Is_Array_Type (Etype (Comp))
3123 and then Is_Itype (Etype (Comp))
3124 then
3125 Typ := Etype (Comp);
3126 Ref := Make_Itype_Reference (Loc);
3127 Set_Itype (Ref, Typ);
3128 Append_Freeze_Action (Rec_Type, Ref);
3130 Ref := Make_Itype_Reference (Loc);
3131 Set_Itype (Ref, Etype (First_Index (Typ)));
3132 Append_Freeze_Action (Rec_Type, Ref);
3134 Sub_Aggr := First (Expressions (Comp));
3136 -- Recurse on nested arrays
3138 while Present (Sub_Aggr) loop
3139 Collect_Itypes (Sub_Aggr);
3140 Next (Sub_Aggr);
3141 end loop;
3142 end if;
3143 end Collect_Itypes;
3145 begin
3146 -- If there is a static initialization aggregate for the type,
3147 -- generate itype references for the types of its (sub)components,
3148 -- to prevent out-of-scope errors in the resulting tree.
3149 -- The aggregate may have been rewritten as a Raise node, in which
3150 -- case there are no relevant itypes.
3152 if Present (Agg)
3153 and then Nkind (Agg) = N_Aggregate
3154 then
3155 Set_Static_Initialization (Proc_Id, Agg);
3157 declare
3158 Comp : Node_Id;
3159 begin
3160 Comp := First (Component_Associations (Agg));
3161 while Present (Comp) loop
3162 Collect_Itypes (Expression (Comp));
3163 Next (Comp);
3164 end loop;
3165 end;
3166 end if;
3167 end;
3168 end if;
3169 end Build_Record_Init_Proc;
3171 ----------------------------
3172 -- Build_Slice_Assignment --
3173 ----------------------------
3175 -- Generates the following subprogram:
3177 -- procedure Assign
3178 -- (Source, Target : Array_Type,
3179 -- Left_Lo, Left_Hi : Index;
3180 -- Right_Lo, Right_Hi : Index;
3181 -- Rev : Boolean)
3182 -- is
3183 -- Li1 : Index;
3184 -- Ri1 : Index;
3186 -- begin
3187 -- if Rev then
3188 -- Li1 := Left_Hi;
3189 -- Ri1 := Right_Hi;
3190 -- else
3191 -- Li1 := Left_Lo;
3192 -- Ri1 := Right_Lo;
3193 -- end if;
3195 -- loop
3196 -- if Rev then
3197 -- exit when Li1 < Left_Lo;
3198 -- else
3199 -- exit when Li1 > Left_Hi;
3200 -- end if;
3202 -- Target (Li1) := Source (Ri1);
3204 -- if Rev then
3205 -- Li1 := Index'pred (Li1);
3206 -- Ri1 := Index'pred (Ri1);
3207 -- else
3208 -- Li1 := Index'succ (Li1);
3209 -- Ri1 := Index'succ (Ri1);
3210 -- end if;
3211 -- end loop;
3212 -- end Assign;
3214 procedure Build_Slice_Assignment (Typ : Entity_Id) is
3215 Loc : constant Source_Ptr := Sloc (Typ);
3216 Index : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
3218 -- Build formal parameters of procedure
3220 Larray : constant Entity_Id :=
3221 Make_Defining_Identifier
3222 (Loc, Chars => New_Internal_Name ('A'));
3223 Rarray : constant Entity_Id :=
3224 Make_Defining_Identifier
3225 (Loc, Chars => New_Internal_Name ('R'));
3226 Left_Lo : constant Entity_Id :=
3227 Make_Defining_Identifier
3228 (Loc, Chars => New_Internal_Name ('L'));
3229 Left_Hi : constant Entity_Id :=
3230 Make_Defining_Identifier
3231 (Loc, Chars => New_Internal_Name ('L'));
3232 Right_Lo : constant Entity_Id :=
3233 Make_Defining_Identifier
3234 (Loc, Chars => New_Internal_Name ('R'));
3235 Right_Hi : constant Entity_Id :=
3236 Make_Defining_Identifier
3237 (Loc, Chars => New_Internal_Name ('R'));
3238 Rev : constant Entity_Id :=
3239 Make_Defining_Identifier
3240 (Loc, Chars => New_Internal_Name ('D'));
3241 Proc_Name : constant Entity_Id :=
3242 Make_Defining_Identifier (Loc,
3243 Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
3245 Lnn : constant Entity_Id :=
3246 Make_Defining_Identifier (Loc, New_Internal_Name ('L'));
3247 Rnn : constant Entity_Id :=
3248 Make_Defining_Identifier (Loc, New_Internal_Name ('R'));
3249 -- Subscripts for left and right sides
3251 Decls : List_Id;
3252 Loops : Node_Id;
3253 Stats : List_Id;
3255 begin
3256 -- Build declarations for indices
3258 Decls := New_List;
3260 Append_To (Decls,
3261 Make_Object_Declaration (Loc,
3262 Defining_Identifier => Lnn,
3263 Object_Definition =>
3264 New_Occurrence_Of (Index, Loc)));
3266 Append_To (Decls,
3267 Make_Object_Declaration (Loc,
3268 Defining_Identifier => Rnn,
3269 Object_Definition =>
3270 New_Occurrence_Of (Index, Loc)));
3272 Stats := New_List;
3274 -- Build initializations for indices
3276 declare
3277 F_Init : constant List_Id := New_List;
3278 B_Init : constant List_Id := New_List;
3280 begin
3281 Append_To (F_Init,
3282 Make_Assignment_Statement (Loc,
3283 Name => New_Occurrence_Of (Lnn, Loc),
3284 Expression => New_Occurrence_Of (Left_Lo, Loc)));
3286 Append_To (F_Init,
3287 Make_Assignment_Statement (Loc,
3288 Name => New_Occurrence_Of (Rnn, Loc),
3289 Expression => New_Occurrence_Of (Right_Lo, Loc)));
3291 Append_To (B_Init,
3292 Make_Assignment_Statement (Loc,
3293 Name => New_Occurrence_Of (Lnn, Loc),
3294 Expression => New_Occurrence_Of (Left_Hi, Loc)));
3296 Append_To (B_Init,
3297 Make_Assignment_Statement (Loc,
3298 Name => New_Occurrence_Of (Rnn, Loc),
3299 Expression => New_Occurrence_Of (Right_Hi, Loc)));
3301 Append_To (Stats,
3302 Make_If_Statement (Loc,
3303 Condition => New_Occurrence_Of (Rev, Loc),
3304 Then_Statements => B_Init,
3305 Else_Statements => F_Init));
3306 end;
3308 -- Now construct the assignment statement
3310 Loops :=
3311 Make_Loop_Statement (Loc,
3312 Statements => New_List (
3313 Make_Assignment_Statement (Loc,
3314 Name =>
3315 Make_Indexed_Component (Loc,
3316 Prefix => New_Occurrence_Of (Larray, Loc),
3317 Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
3318 Expression =>
3319 Make_Indexed_Component (Loc,
3320 Prefix => New_Occurrence_Of (Rarray, Loc),
3321 Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
3322 End_Label => Empty);
3324 -- Build exit condition
3326 declare
3327 F_Ass : constant List_Id := New_List;
3328 B_Ass : constant List_Id := New_List;
3330 begin
3331 Append_To (F_Ass,
3332 Make_Exit_Statement (Loc,
3333 Condition =>
3334 Make_Op_Gt (Loc,
3335 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3336 Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
3338 Append_To (B_Ass,
3339 Make_Exit_Statement (Loc,
3340 Condition =>
3341 Make_Op_Lt (Loc,
3342 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3343 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
3345 Prepend_To (Statements (Loops),
3346 Make_If_Statement (Loc,
3347 Condition => New_Occurrence_Of (Rev, Loc),
3348 Then_Statements => B_Ass,
3349 Else_Statements => F_Ass));
3350 end;
3352 -- Build the increment/decrement statements
3354 declare
3355 F_Ass : constant List_Id := New_List;
3356 B_Ass : constant List_Id := New_List;
3358 begin
3359 Append_To (F_Ass,
3360 Make_Assignment_Statement (Loc,
3361 Name => New_Occurrence_Of (Lnn, Loc),
3362 Expression =>
3363 Make_Attribute_Reference (Loc,
3364 Prefix =>
3365 New_Occurrence_Of (Index, Loc),
3366 Attribute_Name => Name_Succ,
3367 Expressions => New_List (
3368 New_Occurrence_Of (Lnn, Loc)))));
3370 Append_To (F_Ass,
3371 Make_Assignment_Statement (Loc,
3372 Name => New_Occurrence_Of (Rnn, Loc),
3373 Expression =>
3374 Make_Attribute_Reference (Loc,
3375 Prefix =>
3376 New_Occurrence_Of (Index, Loc),
3377 Attribute_Name => Name_Succ,
3378 Expressions => New_List (
3379 New_Occurrence_Of (Rnn, Loc)))));
3381 Append_To (B_Ass,
3382 Make_Assignment_Statement (Loc,
3383 Name => New_Occurrence_Of (Lnn, Loc),
3384 Expression =>
3385 Make_Attribute_Reference (Loc,
3386 Prefix =>
3387 New_Occurrence_Of (Index, Loc),
3388 Attribute_Name => Name_Pred,
3389 Expressions => New_List (
3390 New_Occurrence_Of (Lnn, Loc)))));
3392 Append_To (B_Ass,
3393 Make_Assignment_Statement (Loc,
3394 Name => New_Occurrence_Of (Rnn, Loc),
3395 Expression =>
3396 Make_Attribute_Reference (Loc,
3397 Prefix =>
3398 New_Occurrence_Of (Index, Loc),
3399 Attribute_Name => Name_Pred,
3400 Expressions => New_List (
3401 New_Occurrence_Of (Rnn, Loc)))));
3403 Append_To (Statements (Loops),
3404 Make_If_Statement (Loc,
3405 Condition => New_Occurrence_Of (Rev, Loc),
3406 Then_Statements => B_Ass,
3407 Else_Statements => F_Ass));
3408 end;
3410 Append_To (Stats, Loops);
3412 declare
3413 Spec : Node_Id;
3414 Formals : List_Id := New_List;
3416 begin
3417 Formals := New_List (
3418 Make_Parameter_Specification (Loc,
3419 Defining_Identifier => Larray,
3420 Out_Present => True,
3421 Parameter_Type =>
3422 New_Reference_To (Base_Type (Typ), Loc)),
3424 Make_Parameter_Specification (Loc,
3425 Defining_Identifier => Rarray,
3426 Parameter_Type =>
3427 New_Reference_To (Base_Type (Typ), Loc)),
3429 Make_Parameter_Specification (Loc,
3430 Defining_Identifier => Left_Lo,
3431 Parameter_Type =>
3432 New_Reference_To (Index, Loc)),
3434 Make_Parameter_Specification (Loc,
3435 Defining_Identifier => Left_Hi,
3436 Parameter_Type =>
3437 New_Reference_To (Index, Loc)),
3439 Make_Parameter_Specification (Loc,
3440 Defining_Identifier => Right_Lo,
3441 Parameter_Type =>
3442 New_Reference_To (Index, Loc)),
3444 Make_Parameter_Specification (Loc,
3445 Defining_Identifier => Right_Hi,
3446 Parameter_Type =>
3447 New_Reference_To (Index, Loc)));
3449 Append_To (Formals,
3450 Make_Parameter_Specification (Loc,
3451 Defining_Identifier => Rev,
3452 Parameter_Type =>
3453 New_Reference_To (Standard_Boolean, Loc)));
3455 Spec :=
3456 Make_Procedure_Specification (Loc,
3457 Defining_Unit_Name => Proc_Name,
3458 Parameter_Specifications => Formals);
3460 Discard_Node (
3461 Make_Subprogram_Body (Loc,
3462 Specification => Spec,
3463 Declarations => Decls,
3464 Handled_Statement_Sequence =>
3465 Make_Handled_Sequence_Of_Statements (Loc,
3466 Statements => Stats)));
3467 end;
3469 Set_TSS (Typ, Proc_Name);
3470 Set_Is_Pure (Proc_Name);
3471 end Build_Slice_Assignment;
3473 ------------------------------------
3474 -- Build_Variant_Record_Equality --
3475 ------------------------------------
3477 -- Generates:
3479 -- function _Equality (X, Y : T) return Boolean is
3480 -- begin
3481 -- -- Compare discriminants
3483 -- if False or else X.D1 /= Y.D1 or else X.D2 /= Y.D2 then
3484 -- return False;
3485 -- end if;
3487 -- -- Compare components
3489 -- if False or else X.C1 /= Y.C1 or else X.C2 /= Y.C2 then
3490 -- return False;
3491 -- end if;
3493 -- -- Compare variant part
3495 -- case X.D1 is
3496 -- when V1 =>
3497 -- if False or else X.C2 /= Y.C2 or else X.C3 /= Y.C3 then
3498 -- return False;
3499 -- end if;
3500 -- ...
3501 -- when Vn =>
3502 -- if False or else X.Cn /= Y.Cn then
3503 -- return False;
3504 -- end if;
3505 -- end case;
3507 -- return True;
3508 -- end _Equality;
3510 procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
3511 Loc : constant Source_Ptr := Sloc (Typ);
3513 F : constant Entity_Id :=
3514 Make_Defining_Identifier (Loc,
3515 Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
3517 X : constant Entity_Id :=
3518 Make_Defining_Identifier (Loc,
3519 Chars => Name_X);
3521 Y : constant Entity_Id :=
3522 Make_Defining_Identifier (Loc,
3523 Chars => Name_Y);
3525 Def : constant Node_Id := Parent (Typ);
3526 Comps : constant Node_Id := Component_List (Type_Definition (Def));
3527 Stmts : constant List_Id := New_List;
3528 Pspecs : constant List_Id := New_List;
3530 begin
3531 -- Derived Unchecked_Union types no longer inherit the equality function
3532 -- of their parent.
3534 if Is_Derived_Type (Typ)
3535 and then not Is_Unchecked_Union (Typ)
3536 and then not Has_New_Non_Standard_Rep (Typ)
3537 then
3538 declare
3539 Parent_Eq : constant Entity_Id :=
3540 TSS (Root_Type (Typ), TSS_Composite_Equality);
3542 begin
3543 if Present (Parent_Eq) then
3544 Copy_TSS (Parent_Eq, Typ);
3545 return;
3546 end if;
3547 end;
3548 end if;
3550 Discard_Node (
3551 Make_Subprogram_Body (Loc,
3552 Specification =>
3553 Make_Function_Specification (Loc,
3554 Defining_Unit_Name => F,
3555 Parameter_Specifications => Pspecs,
3556 Result_Definition => New_Reference_To (Standard_Boolean, Loc)),
3557 Declarations => New_List,
3558 Handled_Statement_Sequence =>
3559 Make_Handled_Sequence_Of_Statements (Loc,
3560 Statements => Stmts)));
3562 Append_To (Pspecs,
3563 Make_Parameter_Specification (Loc,
3564 Defining_Identifier => X,
3565 Parameter_Type => New_Reference_To (Typ, Loc)));
3567 Append_To (Pspecs,
3568 Make_Parameter_Specification (Loc,
3569 Defining_Identifier => Y,
3570 Parameter_Type => New_Reference_To (Typ, Loc)));
3572 -- Unchecked_Unions require additional machinery to support equality.
3573 -- Two extra parameters (A and B) are added to the equality function
3574 -- parameter list in order to capture the inferred values of the
3575 -- discriminants in later calls.
3577 if Is_Unchecked_Union (Typ) then
3578 declare
3579 Discr_Type : constant Node_Id := Etype (First_Discriminant (Typ));
3581 A : constant Node_Id :=
3582 Make_Defining_Identifier (Loc,
3583 Chars => Name_A);
3585 B : constant Node_Id :=
3586 Make_Defining_Identifier (Loc,
3587 Chars => Name_B);
3589 begin
3590 -- Add A and B to the parameter list
3592 Append_To (Pspecs,
3593 Make_Parameter_Specification (Loc,
3594 Defining_Identifier => A,
3595 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
3597 Append_To (Pspecs,
3598 Make_Parameter_Specification (Loc,
3599 Defining_Identifier => B,
3600 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
3602 -- Generate the following header code to compare the inferred
3603 -- discriminants:
3605 -- if a /= b then
3606 -- return False;
3607 -- end if;
3609 Append_To (Stmts,
3610 Make_If_Statement (Loc,
3611 Condition =>
3612 Make_Op_Ne (Loc,
3613 Left_Opnd => New_Reference_To (A, Loc),
3614 Right_Opnd => New_Reference_To (B, Loc)),
3615 Then_Statements => New_List (
3616 Make_Simple_Return_Statement (Loc,
3617 Expression => New_Occurrence_Of (Standard_False, Loc)))));
3619 -- Generate component-by-component comparison. Note that we must
3620 -- propagate one of the inferred discriminant formals to act as
3621 -- the case statement switch.
3623 Append_List_To (Stmts,
3624 Make_Eq_Case (Typ, Comps, A));
3626 end;
3628 -- Normal case (not unchecked union)
3630 else
3631 Append_To (Stmts,
3632 Make_Eq_If (Typ,
3633 Discriminant_Specifications (Def)));
3635 Append_List_To (Stmts,
3636 Make_Eq_Case (Typ, Comps));
3637 end if;
3639 Append_To (Stmts,
3640 Make_Simple_Return_Statement (Loc,
3641 Expression => New_Reference_To (Standard_True, Loc)));
3643 Set_TSS (Typ, F);
3644 Set_Is_Pure (F);
3646 if not Debug_Generated_Code then
3647 Set_Debug_Info_Off (F);
3648 end if;
3649 end Build_Variant_Record_Equality;
3651 -----------------------------
3652 -- Check_Stream_Attributes --
3653 -----------------------------
3655 procedure Check_Stream_Attributes (Typ : Entity_Id) is
3656 Comp : Entity_Id;
3657 Par_Read : constant Boolean :=
3658 Stream_Attribute_Available (Typ, TSS_Stream_Read)
3659 and then not Has_Specified_Stream_Read (Typ);
3660 Par_Write : constant Boolean :=
3661 Stream_Attribute_Available (Typ, TSS_Stream_Write)
3662 and then not Has_Specified_Stream_Write (Typ);
3664 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type);
3665 -- Check that Comp has a user-specified Nam stream attribute
3667 ----------------
3668 -- Check_Attr --
3669 ----------------
3671 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type) is
3672 begin
3673 if not Stream_Attribute_Available (Etype (Comp), TSS_Nam) then
3674 Error_Msg_Name_1 := Nam;
3675 Error_Msg_N
3676 ("|component& in limited extension must have% attribute", Comp);
3677 end if;
3678 end Check_Attr;
3680 -- Start of processing for Check_Stream_Attributes
3682 begin
3683 if Par_Read or else Par_Write then
3684 Comp := First_Component (Typ);
3685 while Present (Comp) loop
3686 if Comes_From_Source (Comp)
3687 and then Original_Record_Component (Comp) = Comp
3688 and then Is_Limited_Type (Etype (Comp))
3689 then
3690 if Par_Read then
3691 Check_Attr (Name_Read, TSS_Stream_Read);
3692 end if;
3694 if Par_Write then
3695 Check_Attr (Name_Write, TSS_Stream_Write);
3696 end if;
3697 end if;
3699 Next_Component (Comp);
3700 end loop;
3701 end if;
3702 end Check_Stream_Attributes;
3704 -----------------------------
3705 -- Expand_Record_Extension --
3706 -----------------------------
3708 -- Add a field _parent at the beginning of the record extension. This is
3709 -- used to implement inheritance. Here are some examples of expansion:
3711 -- 1. no discriminants
3712 -- type T2 is new T1 with null record;
3713 -- gives
3714 -- type T2 is new T1 with record
3715 -- _Parent : T1;
3716 -- end record;
3718 -- 2. renamed discriminants
3719 -- type T2 (B, C : Int) is new T1 (A => B) with record
3720 -- _Parent : T1 (A => B);
3721 -- D : Int;
3722 -- end;
3724 -- 3. inherited discriminants
3725 -- type T2 is new T1 with record -- discriminant A inherited
3726 -- _Parent : T1 (A);
3727 -- D : Int;
3728 -- end;
3730 procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
3731 Indic : constant Node_Id := Subtype_Indication (Def);
3732 Loc : constant Source_Ptr := Sloc (Def);
3733 Rec_Ext_Part : Node_Id := Record_Extension_Part (Def);
3734 Par_Subtype : Entity_Id;
3735 Comp_List : Node_Id;
3736 Comp_Decl : Node_Id;
3737 Parent_N : Node_Id;
3738 D : Entity_Id;
3739 List_Constr : constant List_Id := New_List;
3741 begin
3742 -- Expand_Record_Extension is called directly from the semantics, so
3743 -- we must check to see whether expansion is active before proceeding
3745 if not Expander_Active then
3746 return;
3747 end if;
3749 -- This may be a derivation of an untagged private type whose full
3750 -- view is tagged, in which case the Derived_Type_Definition has no
3751 -- extension part. Build an empty one now.
3753 if No (Rec_Ext_Part) then
3754 Rec_Ext_Part :=
3755 Make_Record_Definition (Loc,
3756 End_Label => Empty,
3757 Component_List => Empty,
3758 Null_Present => True);
3760 Set_Record_Extension_Part (Def, Rec_Ext_Part);
3761 Mark_Rewrite_Insertion (Rec_Ext_Part);
3762 end if;
3764 Comp_List := Component_List (Rec_Ext_Part);
3766 Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
3768 -- If the derived type inherits its discriminants the type of the
3769 -- _parent field must be constrained by the inherited discriminants
3771 if Has_Discriminants (T)
3772 and then Nkind (Indic) /= N_Subtype_Indication
3773 and then not Is_Constrained (Entity (Indic))
3774 then
3775 D := First_Discriminant (T);
3776 while Present (D) loop
3777 Append_To (List_Constr, New_Occurrence_Of (D, Loc));
3778 Next_Discriminant (D);
3779 end loop;
3781 Par_Subtype :=
3782 Process_Subtype (
3783 Make_Subtype_Indication (Loc,
3784 Subtype_Mark => New_Reference_To (Entity (Indic), Loc),
3785 Constraint =>
3786 Make_Index_Or_Discriminant_Constraint (Loc,
3787 Constraints => List_Constr)),
3788 Def);
3790 -- Otherwise the original subtype_indication is just what is needed
3792 else
3793 Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
3794 end if;
3796 Set_Parent_Subtype (T, Par_Subtype);
3798 Comp_Decl :=
3799 Make_Component_Declaration (Loc,
3800 Defining_Identifier => Parent_N,
3801 Component_Definition =>
3802 Make_Component_Definition (Loc,
3803 Aliased_Present => False,
3804 Subtype_Indication => New_Reference_To (Par_Subtype, Loc)));
3806 if Null_Present (Rec_Ext_Part) then
3807 Set_Component_List (Rec_Ext_Part,
3808 Make_Component_List (Loc,
3809 Component_Items => New_List (Comp_Decl),
3810 Variant_Part => Empty,
3811 Null_Present => False));
3812 Set_Null_Present (Rec_Ext_Part, False);
3814 elsif Null_Present (Comp_List)
3815 or else Is_Empty_List (Component_Items (Comp_List))
3816 then
3817 Set_Component_Items (Comp_List, New_List (Comp_Decl));
3818 Set_Null_Present (Comp_List, False);
3820 else
3821 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
3822 end if;
3824 Analyze (Comp_Decl);
3825 end Expand_Record_Extension;
3827 ------------------------------------
3828 -- Expand_N_Full_Type_Declaration --
3829 ------------------------------------
3831 procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
3832 Def_Id : constant Entity_Id := Defining_Identifier (N);
3833 B_Id : constant Entity_Id := Base_Type (Def_Id);
3834 Par_Id : Entity_Id;
3835 FN : Node_Id;
3837 procedure Build_Master (Def_Id : Entity_Id);
3838 -- Create the master associated with Def_Id
3840 ------------------
3841 -- Build_Master --
3842 ------------------
3844 procedure Build_Master (Def_Id : Entity_Id) is
3845 begin
3846 -- Anonymous access types are created for the components of the
3847 -- record parameter for an entry declaration. No master is created
3848 -- for such a type.
3850 if Has_Task (Designated_Type (Def_Id))
3851 and then Comes_From_Source (N)
3852 then
3853 Build_Master_Entity (Def_Id);
3854 Build_Master_Renaming (Parent (Def_Id), Def_Id);
3856 -- Create a class-wide master because a Master_Id must be generated
3857 -- for access-to-limited-class-wide types whose root may be extended
3858 -- with task components, and for access-to-limited-interfaces because
3859 -- they can be used to reference tasks implementing such interface.
3861 elsif Is_Class_Wide_Type (Designated_Type (Def_Id))
3862 and then (Is_Limited_Type (Designated_Type (Def_Id))
3863 or else
3864 (Is_Interface (Designated_Type (Def_Id))
3865 and then
3866 Is_Limited_Interface (Designated_Type (Def_Id))))
3867 and then Tasking_Allowed
3869 -- Do not create a class-wide master for types whose convention is
3870 -- Java since these types cannot embed Ada tasks anyway. Note that
3871 -- the following test cannot catch the following case:
3873 -- package java.lang.Object is
3874 -- type Typ is tagged limited private;
3875 -- type Ref is access all Typ'Class;
3876 -- private
3877 -- type Typ is tagged limited ...;
3878 -- pragma Convention (Typ, Java)
3879 -- end;
3881 -- Because the convention appears after we have done the
3882 -- processing for type Ref.
3884 and then Convention (Designated_Type (Def_Id)) /= Convention_Java
3885 and then Convention (Designated_Type (Def_Id)) /= Convention_CIL
3886 then
3887 Build_Class_Wide_Master (Def_Id);
3888 end if;
3889 end Build_Master;
3891 -- Start of processing for Expand_N_Full_Type_Declaration
3893 begin
3894 if Is_Access_Type (Def_Id) then
3895 Build_Master (Def_Id);
3897 if Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
3898 Expand_Access_Protected_Subprogram_Type (N);
3899 end if;
3901 elsif Ada_Version >= Ada_05
3902 and then Is_Array_Type (Def_Id)
3903 and then Is_Access_Type (Component_Type (Def_Id))
3904 and then Ekind (Component_Type (Def_Id)) = E_Anonymous_Access_Type
3905 then
3906 Build_Master (Component_Type (Def_Id));
3908 elsif Has_Task (Def_Id) then
3909 Expand_Previous_Access_Type (Def_Id);
3911 elsif Ada_Version >= Ada_05
3912 and then
3913 (Is_Record_Type (Def_Id)
3914 or else (Is_Array_Type (Def_Id)
3915 and then Is_Record_Type (Component_Type (Def_Id))))
3916 then
3917 declare
3918 Comp : Entity_Id;
3919 Typ : Entity_Id;
3920 M_Id : Entity_Id;
3922 begin
3923 -- Look for the first anonymous access type component
3925 if Is_Array_Type (Def_Id) then
3926 Comp := First_Entity (Component_Type (Def_Id));
3927 else
3928 Comp := First_Entity (Def_Id);
3929 end if;
3931 while Present (Comp) loop
3932 Typ := Etype (Comp);
3934 exit when Is_Access_Type (Typ)
3935 and then Ekind (Typ) = E_Anonymous_Access_Type;
3937 Next_Entity (Comp);
3938 end loop;
3940 -- If found we add a renaming declaration of master_id and we
3941 -- associate it to each anonymous access type component. Do
3942 -- nothing if the access type already has a master. This will be
3943 -- the case if the array type is the packed array created for a
3944 -- user-defined array type T, where the master_id is created when
3945 -- expanding the declaration for T.
3947 if Present (Comp)
3948 and then Ekind (Typ) = E_Anonymous_Access_Type
3949 and then not Restriction_Active (No_Task_Hierarchy)
3950 and then No (Master_Id (Typ))
3952 -- Do not consider run-times with no tasking support
3954 and then RTE_Available (RE_Current_Master)
3955 and then Has_Task (Non_Limited_Designated_Type (Typ))
3956 then
3957 Build_Master_Entity (Def_Id);
3958 M_Id := Build_Master_Renaming (N, Def_Id);
3960 if Is_Array_Type (Def_Id) then
3961 Comp := First_Entity (Component_Type (Def_Id));
3962 else
3963 Comp := First_Entity (Def_Id);
3964 end if;
3966 while Present (Comp) loop
3967 Typ := Etype (Comp);
3969 if Is_Access_Type (Typ)
3970 and then Ekind (Typ) = E_Anonymous_Access_Type
3971 then
3972 Set_Master_Id (Typ, M_Id);
3973 end if;
3975 Next_Entity (Comp);
3976 end loop;
3977 end if;
3978 end;
3979 end if;
3981 Par_Id := Etype (B_Id);
3983 -- The parent type is private then we need to inherit any TSS operations
3984 -- from the full view.
3986 if Ekind (Par_Id) in Private_Kind
3987 and then Present (Full_View (Par_Id))
3988 then
3989 Par_Id := Base_Type (Full_View (Par_Id));
3990 end if;
3992 if Nkind (Type_Definition (Original_Node (N))) =
3993 N_Derived_Type_Definition
3994 and then not Is_Tagged_Type (Def_Id)
3995 and then Present (Freeze_Node (Par_Id))
3996 and then Present (TSS_Elist (Freeze_Node (Par_Id)))
3997 then
3998 Ensure_Freeze_Node (B_Id);
3999 FN := Freeze_Node (B_Id);
4001 if No (TSS_Elist (FN)) then
4002 Set_TSS_Elist (FN, New_Elmt_List);
4003 end if;
4005 declare
4006 T_E : constant Elist_Id := TSS_Elist (FN);
4007 Elmt : Elmt_Id;
4009 begin
4010 Elmt := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
4011 while Present (Elmt) loop
4012 if Chars (Node (Elmt)) /= Name_uInit then
4013 Append_Elmt (Node (Elmt), T_E);
4014 end if;
4016 Next_Elmt (Elmt);
4017 end loop;
4019 -- If the derived type itself is private with a full view, then
4020 -- associate the full view with the inherited TSS_Elist as well.
4022 if Ekind (B_Id) in Private_Kind
4023 and then Present (Full_View (B_Id))
4024 then
4025 Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
4026 Set_TSS_Elist
4027 (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
4028 end if;
4029 end;
4030 end if;
4031 end Expand_N_Full_Type_Declaration;
4033 ---------------------------------
4034 -- Expand_N_Object_Declaration --
4035 ---------------------------------
4037 -- First we do special processing for objects of a tagged type where this
4038 -- is the point at which the type is frozen. The creation of the dispatch
4039 -- table and the initialization procedure have to be deferred to this
4040 -- point, since we reference previously declared primitive subprograms.
4042 -- For all types, we call an initialization procedure if there is one
4044 procedure Expand_N_Object_Declaration (N : Node_Id) is
4045 Def_Id : constant Entity_Id := Defining_Identifier (N);
4046 Expr : constant Node_Id := Expression (N);
4047 Loc : constant Source_Ptr := Sloc (N);
4048 Typ : constant Entity_Id := Etype (Def_Id);
4049 Expr_Q : Node_Id;
4050 Id_Ref : Node_Id;
4051 New_Ref : Node_Id;
4052 BIP_Call : Boolean := False;
4054 Init_After : Node_Id := N;
4055 -- Node after which the init proc call is to be inserted. This is
4056 -- normally N, except for the case of a shared passive variable, in
4057 -- which case the init proc call must be inserted only after the bodies
4058 -- of the shared variable procedures have been seen.
4060 begin
4061 -- Don't do anything for deferred constants. All proper actions will
4062 -- be expanded during the full declaration.
4064 if No (Expr) and Constant_Present (N) then
4065 return;
4066 end if;
4068 -- Force construction of dispatch tables of library level tagged types
4070 if VM_Target = No_VM
4071 and then Static_Dispatch_Tables
4072 and then Is_Library_Level_Entity (Def_Id)
4073 and then Is_Library_Level_Tagged_Type (Typ)
4074 and then (Ekind (Typ) = E_Record_Type
4075 or else Ekind (Typ) = E_Protected_Type
4076 or else Ekind (Typ) = E_Task_Type)
4077 and then not Has_Dispatch_Table (Typ)
4078 then
4079 declare
4080 New_Nodes : List_Id := No_List;
4082 begin
4083 if Is_Concurrent_Type (Typ) then
4084 New_Nodes := Make_DT (Corresponding_Record_Type (Typ), N);
4085 else
4086 New_Nodes := Make_DT (Typ, N);
4087 end if;
4089 if not Is_Empty_List (New_Nodes) then
4090 Insert_List_Before (N, New_Nodes);
4091 end if;
4092 end;
4093 end if;
4095 -- Make shared memory routines for shared passive variable
4097 if Is_Shared_Passive (Def_Id) then
4098 Init_After := Make_Shared_Var_Procs (N);
4099 end if;
4101 -- If tasks being declared, make sure we have an activation chain
4102 -- defined for the tasks (has no effect if we already have one), and
4103 -- also that a Master variable is established and that the appropriate
4104 -- enclosing construct is established as a task master.
4106 if Has_Task (Typ) then
4107 Build_Activation_Chain_Entity (N);
4108 Build_Master_Entity (Def_Id);
4109 end if;
4111 -- Build a list controller for declarations where the type is anonymous
4112 -- access and the designated type is controlled. Only declarations from
4113 -- source files receive such controllers in order to provide the same
4114 -- lifespan for any potential coextensions that may be associated with
4115 -- the object. Finalization lists of internal controlled anonymous
4116 -- access objects are already handled in Expand_N_Allocator.
4118 if Comes_From_Source (N)
4119 and then Ekind (Typ) = E_Anonymous_Access_Type
4120 and then Is_Controlled (Directly_Designated_Type (Typ))
4121 and then No (Associated_Final_Chain (Typ))
4122 then
4123 Build_Final_List (N, Typ);
4124 end if;
4126 -- Default initialization required, and no expression present
4128 if No (Expr) then
4130 -- Expand Initialize call for controlled objects. One may wonder why
4131 -- the Initialize Call is not done in the regular Init procedure
4132 -- attached to the record type. That's because the init procedure is
4133 -- recursively called on each component, including _Parent, thus the
4134 -- Init call for a controlled object would generate not only one
4135 -- Initialize call as it is required but one for each ancestor of
4136 -- its type. This processing is suppressed if No_Initialization set.
4138 if not Controlled_Type (Typ)
4139 or else No_Initialization (N)
4140 then
4141 null;
4143 elsif not Abort_Allowed
4144 or else not Comes_From_Source (N)
4145 then
4146 Insert_Actions_After (Init_After,
4147 Make_Init_Call (
4148 Ref => New_Occurrence_Of (Def_Id, Loc),
4149 Typ => Base_Type (Typ),
4150 Flist_Ref => Find_Final_List (Def_Id),
4151 With_Attach => Make_Integer_Literal (Loc, 1)));
4153 -- Abort allowed
4155 else
4156 -- We need to protect the initialize call
4158 -- begin
4159 -- Defer_Abort.all;
4160 -- Initialize (...);
4161 -- at end
4162 -- Undefer_Abort.all;
4163 -- end;
4165 -- ??? this won't protect the initialize call for controlled
4166 -- components which are part of the init proc, so this block
4167 -- should probably also contain the call to _init_proc but this
4168 -- requires some code reorganization...
4170 declare
4171 L : constant List_Id :=
4172 Make_Init_Call
4173 (Ref => New_Occurrence_Of (Def_Id, Loc),
4174 Typ => Base_Type (Typ),
4175 Flist_Ref => Find_Final_List (Def_Id),
4176 With_Attach => Make_Integer_Literal (Loc, 1));
4178 Blk : constant Node_Id :=
4179 Make_Block_Statement (Loc,
4180 Handled_Statement_Sequence =>
4181 Make_Handled_Sequence_Of_Statements (Loc, L));
4183 begin
4184 Prepend_To (L, Build_Runtime_Call (Loc, RE_Abort_Defer));
4185 Set_At_End_Proc (Handled_Statement_Sequence (Blk),
4186 New_Occurrence_Of (RTE (RE_Abort_Undefer_Direct), Loc));
4187 Insert_Actions_After (Init_After, New_List (Blk));
4188 Expand_At_End_Handler
4189 (Handled_Statement_Sequence (Blk), Entity (Identifier (Blk)));
4190 end;
4191 end if;
4193 -- Call type initialization procedure if there is one. We build the
4194 -- call and put it immediately after the object declaration, so that
4195 -- it will be expanded in the usual manner. Note that this will
4196 -- result in proper handling of defaulted discriminants.
4198 -- Need call if there is a base init proc
4200 if Has_Non_Null_Base_Init_Proc (Typ)
4202 -- Suppress call if No_Initialization set on declaration
4204 and then not No_Initialization (N)
4206 -- Suppress call for special case of value type for VM
4208 and then not Is_Value_Type (Typ)
4210 -- Suppress call if Suppress_Init_Proc set on the type. This is
4211 -- needed for the derived type case, where Suppress_Initialization
4212 -- may be set for the derived type, even if there is an init proc
4213 -- defined for the root type.
4215 and then not Suppress_Init_Proc (Typ)
4216 then
4217 -- The call to the initialization procedure does NOT freeze the
4218 -- object being initialized. This is because the call is not a
4219 -- source level call. This works fine, because the only possible
4220 -- statements depending on freeze status that can appear after the
4221 -- _Init call are rep clauses which can safely appear after actual
4222 -- references to the object.
4224 Id_Ref := New_Reference_To (Def_Id, Loc);
4225 Set_Must_Not_Freeze (Id_Ref);
4226 Set_Assignment_OK (Id_Ref);
4228 declare
4229 Init_Expr : constant Node_Id :=
4230 Static_Initialization (Base_Init_Proc (Typ));
4231 begin
4232 if Present (Init_Expr) then
4233 Set_Expression
4234 (N, New_Copy_Tree (Init_Expr, New_Scope => Current_Scope));
4235 return;
4236 else
4237 Initialization_Warning (Id_Ref);
4239 Insert_Actions_After (Init_After,
4240 Build_Initialization_Call (Loc, Id_Ref, Typ));
4241 end if;
4242 end;
4244 -- If simple initialization is required, then set an appropriate
4245 -- simple initialization expression in place. This special
4246 -- initialization is required even though No_Init_Flag is present,
4247 -- but is not needed if there was an explicit initialization.
4249 -- An internally generated temporary needs no initialization because
4250 -- it will be assigned subsequently. In particular, there is no point
4251 -- in applying Initialize_Scalars to such a temporary.
4253 elsif Needs_Simple_Initialization (Typ)
4254 and then not Is_Internal (Def_Id)
4255 and then not Has_Init_Expression (N)
4256 then
4257 Set_No_Initialization (N, False);
4258 Set_Expression (N, Get_Simple_Init_Val (Typ, Loc, Esize (Def_Id)));
4259 Analyze_And_Resolve (Expression (N), Typ);
4260 end if;
4262 -- Generate attribute for Persistent_BSS if needed
4264 if Persistent_BSS_Mode
4265 and then Comes_From_Source (N)
4266 and then Is_Potentially_Persistent_Type (Typ)
4267 and then not Has_Init_Expression (N)
4268 and then Is_Library_Level_Entity (Def_Id)
4269 then
4270 declare
4271 Prag : Node_Id;
4272 begin
4273 Prag :=
4274 Make_Linker_Section_Pragma
4275 (Def_Id, Sloc (N), ".persistent.bss");
4276 Insert_After (N, Prag);
4277 Analyze (Prag);
4278 end;
4279 end if;
4281 -- If access type, then we know it is null if not initialized
4283 if Is_Access_Type (Typ) then
4284 Set_Is_Known_Null (Def_Id);
4285 end if;
4287 -- Explicit initialization present
4289 else
4290 -- Obtain actual expression from qualified expression
4292 if Nkind (Expr) = N_Qualified_Expression then
4293 Expr_Q := Expression (Expr);
4294 else
4295 Expr_Q := Expr;
4296 end if;
4298 -- When we have the appropriate type of aggregate in the expression
4299 -- (it has been determined during analysis of the aggregate by
4300 -- setting the delay flag), let's perform in place assignment and
4301 -- thus avoid creating a temporary.
4303 if Is_Delayed_Aggregate (Expr_Q) then
4304 Convert_Aggr_In_Object_Decl (N);
4306 else
4307 -- Ada 2005 (AI-318-02): If the initialization expression is a
4308 -- call to a build-in-place function, then access to the declared
4309 -- object must be passed to the function. Currently we limit such
4310 -- functions to those with constrained limited result subtypes,
4311 -- but eventually we plan to expand the allowed forms of functions
4312 -- that are treated as build-in-place.
4314 if Ada_Version >= Ada_05
4315 and then Is_Build_In_Place_Function_Call (Expr_Q)
4316 then
4317 Make_Build_In_Place_Call_In_Object_Declaration (N, Expr_Q);
4318 BIP_Call := True;
4319 end if;
4321 -- In most cases, we must check that the initial value meets any
4322 -- constraint imposed by the declared type. However, there is one
4323 -- very important exception to this rule. If the entity has an
4324 -- unconstrained nominal subtype, then it acquired its constraints
4325 -- from the expression in the first place, and not only does this
4326 -- mean that the constraint check is not needed, but an attempt to
4327 -- perform the constraint check can cause order order of
4328 -- elaboration problems.
4330 if not Is_Constr_Subt_For_U_Nominal (Typ) then
4332 -- If this is an allocator for an aggregate that has been
4333 -- allocated in place, delay checks until assignments are
4334 -- made, because the discriminants are not initialized.
4336 if Nkind (Expr) = N_Allocator
4337 and then No_Initialization (Expr)
4338 then
4339 null;
4340 else
4341 Apply_Constraint_Check (Expr, Typ);
4342 end if;
4343 end if;
4345 -- Ada 2005 (AI-251): Rewrite the expression that initializes a
4346 -- class-wide object to ensure that we copy the full object.
4348 -- Replace
4349 -- CW : I'Class := Obj;
4350 -- by
4351 -- CW__1 : I'Class := I'Class (Base_Address (Obj'Address));
4352 -- CW : I'Class renames Displace (CW__1, I'Tag);
4354 if Is_Interface (Typ)
4355 and then Is_Class_Wide_Type (Etype (Expr))
4356 and then Comes_From_Source (Def_Id)
4357 then
4358 declare
4359 Decl_1 : Node_Id;
4360 Decl_2 : Node_Id;
4362 begin
4363 Decl_1 :=
4364 Make_Object_Declaration (Loc,
4365 Defining_Identifier =>
4366 Make_Defining_Identifier (Loc,
4367 New_Internal_Name ('D')),
4369 Object_Definition =>
4370 Make_Attribute_Reference (Loc,
4371 Prefix =>
4372 New_Occurrence_Of
4373 (Root_Type (Etype (Def_Id)), Loc),
4374 Attribute_Name => Name_Class),
4376 Expression =>
4377 Unchecked_Convert_To
4378 (Class_Wide_Type (Root_Type (Etype (Def_Id))),
4379 Make_Explicit_Dereference (Loc,
4380 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
4381 Make_Function_Call (Loc,
4382 Name =>
4383 New_Reference_To (RTE (RE_Base_Address),
4384 Loc),
4385 Parameter_Associations => New_List (
4386 Make_Attribute_Reference (Loc,
4387 Prefix => Relocate_Node (Expr),
4388 Attribute_Name => Name_Address)))))));
4390 Insert_Action (N, Decl_1);
4392 Decl_2 :=
4393 Make_Object_Renaming_Declaration (Loc,
4394 Defining_Identifier =>
4395 Make_Defining_Identifier (Loc,
4396 New_Internal_Name ('D')),
4398 Subtype_Mark =>
4399 Make_Attribute_Reference (Loc,
4400 Prefix =>
4401 New_Occurrence_Of
4402 (Root_Type (Etype (Def_Id)), Loc),
4403 Attribute_Name => Name_Class),
4405 Name =>
4406 Unchecked_Convert_To (
4407 Class_Wide_Type (Root_Type (Etype (Def_Id))),
4408 Make_Explicit_Dereference (Loc,
4409 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
4410 Make_Function_Call (Loc,
4411 Name =>
4412 New_Reference_To (RTE (RE_Displace), Loc),
4414 Parameter_Associations => New_List (
4415 Make_Attribute_Reference (Loc,
4416 Prefix =>
4417 New_Reference_To
4418 (Defining_Identifier (Decl_1), Loc),
4419 Attribute_Name => Name_Address),
4421 Unchecked_Convert_To (RTE (RE_Tag),
4422 New_Reference_To
4423 (Node
4424 (First_Elmt
4425 (Access_Disp_Table
4426 (Root_Type (Typ)))),
4427 Loc))))))));
4429 Rewrite (N, Decl_2);
4430 Analyze (N);
4432 -- Replace internal identifier of Decl_2 by the identifier
4433 -- found in the sources. We also have to exchange entities
4434 -- containing their defining identifiers to ensure the
4435 -- correct replacement of the object declaration by this
4436 -- object renaming declaration (because such definings
4437 -- identifier have been previously added by Enter_Name to
4438 -- the current scope). We must preserve the homonym chain
4439 -- of the source entity as well.
4441 Set_Chars (Defining_Identifier (N), Chars (Def_Id));
4442 Set_Homonym (Defining_Identifier (N), Homonym (Def_Id));
4443 Exchange_Entities (Defining_Identifier (N), Def_Id);
4445 return;
4446 end;
4447 end if;
4449 -- If the type is controlled and not limited then the target is
4450 -- adjusted after the copy and attached to the finalization list.
4451 -- However, no adjustment is done in the case where the object was
4452 -- initialized by a call to a function whose result is built in
4453 -- place, since no copy occurred. (We eventually plan to support
4454 -- in-place function results for some nonlimited types. ???)
4456 if Controlled_Type (Typ)
4457 and then not Is_Limited_Type (Typ)
4458 and then not BIP_Call
4459 then
4460 Insert_Actions_After (Init_After,
4461 Make_Adjust_Call (
4462 Ref => New_Reference_To (Def_Id, Loc),
4463 Typ => Base_Type (Typ),
4464 Flist_Ref => Find_Final_List (Def_Id),
4465 With_Attach => Make_Integer_Literal (Loc, 1)));
4466 end if;
4468 -- For tagged types, when an init value is given, the tag has to
4469 -- be re-initialized separately in order to avoid the propagation
4470 -- of a wrong tag coming from a view conversion unless the type
4471 -- is class wide (in this case the tag comes from the init value).
4472 -- Suppress the tag assignment when VM_Target because VM tags are
4473 -- represented implicitly in objects. Ditto for types that are
4474 -- CPP_CLASS, and for initializations that are aggregates, because
4475 -- they have to have the right tag.
4477 if Is_Tagged_Type (Typ)
4478 and then not Is_Class_Wide_Type (Typ)
4479 and then not Is_CPP_Class (Typ)
4480 and then VM_Target = No_VM
4481 and then Nkind (Expr) /= N_Aggregate
4482 then
4483 -- The re-assignment of the tag has to be done even if the
4484 -- object is a constant.
4486 New_Ref :=
4487 Make_Selected_Component (Loc,
4488 Prefix => New_Reference_To (Def_Id, Loc),
4489 Selector_Name =>
4490 New_Reference_To (First_Tag_Component (Typ), Loc));
4492 Set_Assignment_OK (New_Ref);
4494 Insert_After (Init_After,
4495 Make_Assignment_Statement (Loc,
4496 Name => New_Ref,
4497 Expression =>
4498 Unchecked_Convert_To (RTE (RE_Tag),
4499 New_Reference_To
4500 (Node
4501 (First_Elmt
4502 (Access_Disp_Table (Base_Type (Typ)))),
4503 Loc))));
4505 -- For discrete types, set the Is_Known_Valid flag if the
4506 -- initializing value is known to be valid.
4508 elsif Is_Discrete_Type (Typ) and then Expr_Known_Valid (Expr) then
4509 Set_Is_Known_Valid (Def_Id);
4511 elsif Is_Access_Type (Typ) then
4513 -- For access types set the Is_Known_Non_Null flag if the
4514 -- initializing value is known to be non-null. We can also set
4515 -- Can_Never_Be_Null if this is a constant.
4517 if Known_Non_Null (Expr) then
4518 Set_Is_Known_Non_Null (Def_Id, True);
4520 if Constant_Present (N) then
4521 Set_Can_Never_Be_Null (Def_Id);
4522 end if;
4523 end if;
4524 end if;
4526 -- If validity checking on copies, validate initial expression
4528 if Validity_Checks_On
4529 and then Validity_Check_Copies
4530 then
4531 Ensure_Valid (Expr);
4532 Set_Is_Known_Valid (Def_Id);
4533 end if;
4534 end if;
4536 -- Cases where the back end cannot handle the initialization directly
4537 -- In such cases, we expand an assignment that will be appropriately
4538 -- handled by Expand_N_Assignment_Statement.
4540 -- The exclusion of the unconstrained case is wrong, but for now it
4541 -- is too much trouble ???
4543 if (Is_Possibly_Unaligned_Slice (Expr)
4544 or else (Is_Possibly_Unaligned_Object (Expr)
4545 and then not Represented_As_Scalar (Etype (Expr))))
4547 -- The exclusion of the unconstrained case is wrong, but for now
4548 -- it is too much trouble ???
4550 and then not (Is_Array_Type (Etype (Expr))
4551 and then not Is_Constrained (Etype (Expr)))
4552 then
4553 declare
4554 Stat : constant Node_Id :=
4555 Make_Assignment_Statement (Loc,
4556 Name => New_Reference_To (Def_Id, Loc),
4557 Expression => Relocate_Node (Expr));
4558 begin
4559 Set_Expression (N, Empty);
4560 Set_No_Initialization (N);
4561 Set_Assignment_OK (Name (Stat));
4562 Set_No_Ctrl_Actions (Stat);
4563 Insert_After_And_Analyze (Init_After, Stat);
4564 end;
4565 end if;
4566 end if;
4568 exception
4569 when RE_Not_Available =>
4570 return;
4571 end Expand_N_Object_Declaration;
4573 ---------------------------------
4574 -- Expand_N_Subtype_Indication --
4575 ---------------------------------
4577 -- Add a check on the range of the subtype. The static case is partially
4578 -- duplicated by Process_Range_Expr_In_Decl in Sem_Ch3, but we still need
4579 -- to check here for the static case in order to avoid generating
4580 -- extraneous expanded code. Also deal with validity checking.
4582 procedure Expand_N_Subtype_Indication (N : Node_Id) is
4583 Ran : constant Node_Id := Range_Expression (Constraint (N));
4584 Typ : constant Entity_Id := Entity (Subtype_Mark (N));
4586 begin
4587 if Nkind (Constraint (N)) = N_Range_Constraint then
4588 Validity_Check_Range (Range_Expression (Constraint (N)));
4589 end if;
4591 if Nkind (Parent (N)) = N_Constrained_Array_Definition
4592 or else
4593 Nkind (Parent (N)) = N_Slice
4594 then
4595 Apply_Range_Check (Ran, Typ);
4596 end if;
4597 end Expand_N_Subtype_Indication;
4599 ---------------------------
4600 -- Expand_N_Variant_Part --
4601 ---------------------------
4603 -- If the last variant does not contain the Others choice, replace it with
4604 -- an N_Others_Choice node since Gigi always wants an Others. Note that we
4605 -- do not bother to call Analyze on the modified variant part, since it's
4606 -- only effect would be to compute the Others_Discrete_Choices node
4607 -- laboriously, and of course we already know the list of choices that
4608 -- corresponds to the others choice (it's the list we are replacing!)
4610 procedure Expand_N_Variant_Part (N : Node_Id) is
4611 Last_Var : constant Node_Id := Last_Non_Pragma (Variants (N));
4612 Others_Node : Node_Id;
4613 begin
4614 if Nkind (First (Discrete_Choices (Last_Var))) /= N_Others_Choice then
4615 Others_Node := Make_Others_Choice (Sloc (Last_Var));
4616 Set_Others_Discrete_Choices
4617 (Others_Node, Discrete_Choices (Last_Var));
4618 Set_Discrete_Choices (Last_Var, New_List (Others_Node));
4619 end if;
4620 end Expand_N_Variant_Part;
4622 ---------------------------------
4623 -- Expand_Previous_Access_Type --
4624 ---------------------------------
4626 procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
4627 T : Entity_Id := First_Entity (Current_Scope);
4629 begin
4630 -- Find all access types declared in the current scope, whose
4631 -- designated type is Def_Id.
4633 while Present (T) loop
4634 if Is_Access_Type (T)
4635 and then Designated_Type (T) = Def_Id
4636 then
4637 Build_Master_Entity (Def_Id);
4638 Build_Master_Renaming (Parent (Def_Id), T);
4639 end if;
4641 Next_Entity (T);
4642 end loop;
4643 end Expand_Previous_Access_Type;
4645 ------------------------------
4646 -- Expand_Record_Controller --
4647 ------------------------------
4649 procedure Expand_Record_Controller (T : Entity_Id) is
4650 Def : Node_Id := Type_Definition (Parent (T));
4651 Comp_List : Node_Id;
4652 Comp_Decl : Node_Id;
4653 Loc : Source_Ptr;
4654 First_Comp : Node_Id;
4655 Controller_Type : Entity_Id;
4656 Ent : Entity_Id;
4658 begin
4659 if Nkind (Def) = N_Derived_Type_Definition then
4660 Def := Record_Extension_Part (Def);
4661 end if;
4663 if Null_Present (Def) then
4664 Set_Component_List (Def,
4665 Make_Component_List (Sloc (Def),
4666 Component_Items => Empty_List,
4667 Variant_Part => Empty,
4668 Null_Present => True));
4669 end if;
4671 Comp_List := Component_List (Def);
4673 if Null_Present (Comp_List)
4674 or else Is_Empty_List (Component_Items (Comp_List))
4675 then
4676 Loc := Sloc (Comp_List);
4677 else
4678 Loc := Sloc (First (Component_Items (Comp_List)));
4679 end if;
4681 if Is_Inherently_Limited_Type (T) then
4682 Controller_Type := RTE (RE_Limited_Record_Controller);
4683 else
4684 Controller_Type := RTE (RE_Record_Controller);
4685 end if;
4687 Ent := Make_Defining_Identifier (Loc, Name_uController);
4689 Comp_Decl :=
4690 Make_Component_Declaration (Loc,
4691 Defining_Identifier => Ent,
4692 Component_Definition =>
4693 Make_Component_Definition (Loc,
4694 Aliased_Present => False,
4695 Subtype_Indication => New_Reference_To (Controller_Type, Loc)));
4697 if Null_Present (Comp_List)
4698 or else Is_Empty_List (Component_Items (Comp_List))
4699 then
4700 Set_Component_Items (Comp_List, New_List (Comp_Decl));
4701 Set_Null_Present (Comp_List, False);
4703 else
4704 -- The controller cannot be placed before the _Parent field since
4705 -- gigi lays out field in order and _parent must be first to preserve
4706 -- the polymorphism of tagged types.
4708 First_Comp := First (Component_Items (Comp_List));
4710 if not Is_Tagged_Type (T) then
4711 Insert_Before (First_Comp, Comp_Decl);
4713 -- if T is a tagged type, place controller declaration after parent
4714 -- field and after eventual tags of interface types.
4716 else
4717 while Present (First_Comp)
4718 and then
4719 (Chars (Defining_Identifier (First_Comp)) = Name_uParent
4720 or else Is_Tag (Defining_Identifier (First_Comp))
4722 -- Ada 2005 (AI-251): The following condition covers secondary
4723 -- tags but also the adjacent component contanining the offset
4724 -- to the base of the object (component generated if the parent
4725 -- has discriminants --- see Add_Interface_Tag_Components).
4726 -- This is required to avoid the addition of the controller
4727 -- between the secondary tag and its adjacent component.
4729 or else Present
4730 (Related_Interface
4731 (Defining_Identifier (First_Comp))))
4732 loop
4733 Next (First_Comp);
4734 end loop;
4736 -- An empty tagged extension might consist only of the parent
4737 -- component. Otherwise insert the controller before the first
4738 -- component that is neither parent nor tag.
4740 if Present (First_Comp) then
4741 Insert_Before (First_Comp, Comp_Decl);
4742 else
4743 Append (Comp_Decl, Component_Items (Comp_List));
4744 end if;
4745 end if;
4746 end if;
4748 Push_Scope (T);
4749 Analyze (Comp_Decl);
4750 Set_Ekind (Ent, E_Component);
4751 Init_Component_Location (Ent);
4753 -- Move the _controller entity ahead in the list of internal entities
4754 -- of the enclosing record so that it is selected instead of a
4755 -- potentially inherited one.
4757 declare
4758 E : constant Entity_Id := Last_Entity (T);
4759 Comp : Entity_Id;
4761 begin
4762 pragma Assert (Chars (E) = Name_uController);
4764 Set_Next_Entity (E, First_Entity (T));
4765 Set_First_Entity (T, E);
4767 Comp := Next_Entity (E);
4768 while Next_Entity (Comp) /= E loop
4769 Next_Entity (Comp);
4770 end loop;
4772 Set_Next_Entity (Comp, Empty);
4773 Set_Last_Entity (T, Comp);
4774 end;
4776 End_Scope;
4778 exception
4779 when RE_Not_Available =>
4780 return;
4781 end Expand_Record_Controller;
4783 ------------------------
4784 -- Expand_Tagged_Root --
4785 ------------------------
4787 procedure Expand_Tagged_Root (T : Entity_Id) is
4788 Def : constant Node_Id := Type_Definition (Parent (T));
4789 Comp_List : Node_Id;
4790 Comp_Decl : Node_Id;
4791 Sloc_N : Source_Ptr;
4793 begin
4794 if Null_Present (Def) then
4795 Set_Component_List (Def,
4796 Make_Component_List (Sloc (Def),
4797 Component_Items => Empty_List,
4798 Variant_Part => Empty,
4799 Null_Present => True));
4800 end if;
4802 Comp_List := Component_List (Def);
4804 if Null_Present (Comp_List)
4805 or else Is_Empty_List (Component_Items (Comp_List))
4806 then
4807 Sloc_N := Sloc (Comp_List);
4808 else
4809 Sloc_N := Sloc (First (Component_Items (Comp_List)));
4810 end if;
4812 Comp_Decl :=
4813 Make_Component_Declaration (Sloc_N,
4814 Defining_Identifier => First_Tag_Component (T),
4815 Component_Definition =>
4816 Make_Component_Definition (Sloc_N,
4817 Aliased_Present => False,
4818 Subtype_Indication => New_Reference_To (RTE (RE_Tag), Sloc_N)));
4820 if Null_Present (Comp_List)
4821 or else Is_Empty_List (Component_Items (Comp_List))
4822 then
4823 Set_Component_Items (Comp_List, New_List (Comp_Decl));
4824 Set_Null_Present (Comp_List, False);
4826 else
4827 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
4828 end if;
4830 -- We don't Analyze the whole expansion because the tag component has
4831 -- already been analyzed previously. Here we just insure that the tree
4832 -- is coherent with the semantic decoration
4834 Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
4836 exception
4837 when RE_Not_Available =>
4838 return;
4839 end Expand_Tagged_Root;
4841 ----------------------
4842 -- Clean_Task_Names --
4843 ----------------------
4845 procedure Clean_Task_Names
4846 (Typ : Entity_Id;
4847 Proc_Id : Entity_Id)
4849 begin
4850 if Has_Task (Typ)
4851 and then not Restriction_Active (No_Implicit_Heap_Allocations)
4852 and then not Global_Discard_Names
4853 and then VM_Target = No_VM
4854 then
4855 Set_Uses_Sec_Stack (Proc_Id);
4856 end if;
4857 end Clean_Task_Names;
4859 -----------------------
4860 -- Freeze_Array_Type --
4861 -----------------------
4863 procedure Freeze_Array_Type (N : Node_Id) is
4864 Typ : constant Entity_Id := Entity (N);
4865 Comp_Typ : constant Entity_Id := Component_Type (Typ);
4866 Base : constant Entity_Id := Base_Type (Typ);
4868 begin
4869 if not Is_Bit_Packed_Array (Typ) then
4871 -- If the component contains tasks, so does the array type. This may
4872 -- not be indicated in the array type because the component may have
4873 -- been a private type at the point of definition. Same if component
4874 -- type is controlled.
4876 Set_Has_Task (Base, Has_Task (Comp_Typ));
4877 Set_Has_Controlled_Component (Base,
4878 Has_Controlled_Component (Comp_Typ)
4879 or else Is_Controlled (Comp_Typ));
4881 if No (Init_Proc (Base)) then
4883 -- If this is an anonymous array created for a declaration with
4884 -- an initial value, its init_proc will never be called. The
4885 -- initial value itself may have been expanded into assignments,
4886 -- in which case the object declaration is carries the
4887 -- No_Initialization flag.
4889 if Is_Itype (Base)
4890 and then Nkind (Associated_Node_For_Itype (Base)) =
4891 N_Object_Declaration
4892 and then (Present (Expression (Associated_Node_For_Itype (Base)))
4893 or else
4894 No_Initialization (Associated_Node_For_Itype (Base)))
4895 then
4896 null;
4898 -- We do not need an init proc for string or wide [wide] string,
4899 -- since the only time these need initialization in normalize or
4900 -- initialize scalars mode, and these types are treated specially
4901 -- and do not need initialization procedures.
4903 elsif Root_Type (Base) = Standard_String
4904 or else Root_Type (Base) = Standard_Wide_String
4905 or else Root_Type (Base) = Standard_Wide_Wide_String
4906 then
4907 null;
4909 -- Otherwise we have to build an init proc for the subtype
4911 else
4912 Build_Array_Init_Proc (Base, N);
4913 end if;
4914 end if;
4916 if Typ = Base then
4917 if Has_Controlled_Component (Base) then
4918 Build_Controlling_Procs (Base);
4920 if not Is_Limited_Type (Comp_Typ)
4921 and then Number_Dimensions (Typ) = 1
4922 then
4923 Build_Slice_Assignment (Typ);
4924 end if;
4926 elsif Ekind (Comp_Typ) = E_Anonymous_Access_Type
4927 and then Controlled_Type (Directly_Designated_Type (Comp_Typ))
4928 then
4929 Set_Associated_Final_Chain (Comp_Typ, Add_Final_Chain (Typ));
4930 end if;
4931 end if;
4933 -- For packed case, default initialization, except if the component type
4934 -- is itself a packed structure with an initialization procedure, or
4935 -- initialize/normalize scalars active, and we have a base type, or the
4936 -- type is public, because in that case a client might specify
4937 -- Normalize_Scalars and there better be a public Init_Proc for it.
4939 elsif (Present (Init_Proc (Component_Type (Base)))
4940 and then No (Base_Init_Proc (Base)))
4941 or else (Init_Or_Norm_Scalars and then Base = Typ)
4942 or else Is_Public (Typ)
4943 then
4944 Build_Array_Init_Proc (Base, N);
4945 end if;
4946 end Freeze_Array_Type;
4948 -----------------------------
4949 -- Freeze_Enumeration_Type --
4950 -----------------------------
4952 procedure Freeze_Enumeration_Type (N : Node_Id) is
4953 Typ : constant Entity_Id := Entity (N);
4954 Loc : constant Source_Ptr := Sloc (Typ);
4955 Ent : Entity_Id;
4956 Lst : List_Id;
4957 Num : Nat;
4958 Arr : Entity_Id;
4959 Fent : Entity_Id;
4960 Ityp : Entity_Id;
4961 Is_Contiguous : Boolean;
4962 Pos_Expr : Node_Id;
4963 Last_Repval : Uint;
4965 Func : Entity_Id;
4966 pragma Warnings (Off, Func);
4968 begin
4969 -- Various optimizations possible if given representation is contiguous
4971 Is_Contiguous := True;
4973 Ent := First_Literal (Typ);
4974 Last_Repval := Enumeration_Rep (Ent);
4976 Next_Literal (Ent);
4977 while Present (Ent) loop
4978 if Enumeration_Rep (Ent) - Last_Repval /= 1 then
4979 Is_Contiguous := False;
4980 exit;
4981 else
4982 Last_Repval := Enumeration_Rep (Ent);
4983 end if;
4985 Next_Literal (Ent);
4986 end loop;
4988 if Is_Contiguous then
4989 Set_Has_Contiguous_Rep (Typ);
4990 Ent := First_Literal (Typ);
4991 Num := 1;
4992 Lst := New_List (New_Reference_To (Ent, Sloc (Ent)));
4994 else
4995 -- Build list of literal references
4997 Lst := New_List;
4998 Num := 0;
5000 Ent := First_Literal (Typ);
5001 while Present (Ent) loop
5002 Append_To (Lst, New_Reference_To (Ent, Sloc (Ent)));
5003 Num := Num + 1;
5004 Next_Literal (Ent);
5005 end loop;
5006 end if;
5008 -- Now build an array declaration
5010 -- typA : array (Natural range 0 .. num - 1) of ctype :=
5011 -- (v, v, v, v, v, ....)
5013 -- where ctype is the corresponding integer type. If the representation
5014 -- is contiguous, we only keep the first literal, which provides the
5015 -- offset for Pos_To_Rep computations.
5017 Arr :=
5018 Make_Defining_Identifier (Loc,
5019 Chars => New_External_Name (Chars (Typ), 'A'));
5021 Append_Freeze_Action (Typ,
5022 Make_Object_Declaration (Loc,
5023 Defining_Identifier => Arr,
5024 Constant_Present => True,
5026 Object_Definition =>
5027 Make_Constrained_Array_Definition (Loc,
5028 Discrete_Subtype_Definitions => New_List (
5029 Make_Subtype_Indication (Loc,
5030 Subtype_Mark => New_Reference_To (Standard_Natural, Loc),
5031 Constraint =>
5032 Make_Range_Constraint (Loc,
5033 Range_Expression =>
5034 Make_Range (Loc,
5035 Low_Bound =>
5036 Make_Integer_Literal (Loc, 0),
5037 High_Bound =>
5038 Make_Integer_Literal (Loc, Num - 1))))),
5040 Component_Definition =>
5041 Make_Component_Definition (Loc,
5042 Aliased_Present => False,
5043 Subtype_Indication => New_Reference_To (Typ, Loc))),
5045 Expression =>
5046 Make_Aggregate (Loc,
5047 Expressions => Lst)));
5049 Set_Enum_Pos_To_Rep (Typ, Arr);
5051 -- Now we build the function that converts representation values to
5052 -- position values. This function has the form:
5054 -- function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
5055 -- begin
5056 -- case ityp!(A) is
5057 -- when enum-lit'Enum_Rep => return posval;
5058 -- when enum-lit'Enum_Rep => return posval;
5059 -- ...
5060 -- when others =>
5061 -- [raise Constraint_Error when F "invalid data"]
5062 -- return -1;
5063 -- end case;
5064 -- end;
5066 -- Note: the F parameter determines whether the others case (no valid
5067 -- representation) raises Constraint_Error or returns a unique value
5068 -- of minus one. The latter case is used, e.g. in 'Valid code.
5070 -- Note: the reason we use Enum_Rep values in the case here is to avoid
5071 -- the code generator making inappropriate assumptions about the range
5072 -- of the values in the case where the value is invalid. ityp is a
5073 -- signed or unsigned integer type of appropriate width.
5075 -- Note: if exceptions are not supported, then we suppress the raise
5076 -- and return -1 unconditionally (this is an erroneous program in any
5077 -- case and there is no obligation to raise Constraint_Error here!) We
5078 -- also do this if pragma Restrictions (No_Exceptions) is active.
5080 -- Is this right??? What about No_Exception_Propagation???
5082 -- Representations are signed
5084 if Enumeration_Rep (First_Literal (Typ)) < 0 then
5086 -- The underlying type is signed. Reset the Is_Unsigned_Type
5087 -- explicitly, because it might have been inherited from
5088 -- parent type.
5090 Set_Is_Unsigned_Type (Typ, False);
5092 if Esize (Typ) <= Standard_Integer_Size then
5093 Ityp := Standard_Integer;
5094 else
5095 Ityp := Universal_Integer;
5096 end if;
5098 -- Representations are unsigned
5100 else
5101 if Esize (Typ) <= Standard_Integer_Size then
5102 Ityp := RTE (RE_Unsigned);
5103 else
5104 Ityp := RTE (RE_Long_Long_Unsigned);
5105 end if;
5106 end if;
5108 -- The body of the function is a case statement. First collect case
5109 -- alternatives, or optimize the contiguous case.
5111 Lst := New_List;
5113 -- If representation is contiguous, Pos is computed by subtracting
5114 -- the representation of the first literal.
5116 if Is_Contiguous then
5117 Ent := First_Literal (Typ);
5119 if Enumeration_Rep (Ent) = Last_Repval then
5121 -- Another special case: for a single literal, Pos is zero
5123 Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
5125 else
5126 Pos_Expr :=
5127 Convert_To (Standard_Integer,
5128 Make_Op_Subtract (Loc,
5129 Left_Opnd =>
5130 Unchecked_Convert_To (Ityp,
5131 Make_Identifier (Loc, Name_uA)),
5132 Right_Opnd =>
5133 Make_Integer_Literal (Loc,
5134 Intval =>
5135 Enumeration_Rep (First_Literal (Typ)))));
5136 end if;
5138 Append_To (Lst,
5139 Make_Case_Statement_Alternative (Loc,
5140 Discrete_Choices => New_List (
5141 Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
5142 Low_Bound =>
5143 Make_Integer_Literal (Loc,
5144 Intval => Enumeration_Rep (Ent)),
5145 High_Bound =>
5146 Make_Integer_Literal (Loc, Intval => Last_Repval))),
5148 Statements => New_List (
5149 Make_Simple_Return_Statement (Loc,
5150 Expression => Pos_Expr))));
5152 else
5153 Ent := First_Literal (Typ);
5154 while Present (Ent) loop
5155 Append_To (Lst,
5156 Make_Case_Statement_Alternative (Loc,
5157 Discrete_Choices => New_List (
5158 Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
5159 Intval => Enumeration_Rep (Ent))),
5161 Statements => New_List (
5162 Make_Simple_Return_Statement (Loc,
5163 Expression =>
5164 Make_Integer_Literal (Loc,
5165 Intval => Enumeration_Pos (Ent))))));
5167 Next_Literal (Ent);
5168 end loop;
5169 end if;
5171 -- In normal mode, add the others clause with the test
5173 if not No_Exception_Handlers_Set then
5174 Append_To (Lst,
5175 Make_Case_Statement_Alternative (Loc,
5176 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
5177 Statements => New_List (
5178 Make_Raise_Constraint_Error (Loc,
5179 Condition => Make_Identifier (Loc, Name_uF),
5180 Reason => CE_Invalid_Data),
5181 Make_Simple_Return_Statement (Loc,
5182 Expression =>
5183 Make_Integer_Literal (Loc, -1)))));
5185 -- If either of the restrictions No_Exceptions_Handlers/Propagation is
5186 -- active then return -1 (we cannot usefully raise Constraint_Error in
5187 -- this case). See description above for further details.
5189 else
5190 Append_To (Lst,
5191 Make_Case_Statement_Alternative (Loc,
5192 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
5193 Statements => New_List (
5194 Make_Simple_Return_Statement (Loc,
5195 Expression =>
5196 Make_Integer_Literal (Loc, -1)))));
5197 end if;
5199 -- Now we can build the function body
5201 Fent :=
5202 Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
5204 Func :=
5205 Make_Subprogram_Body (Loc,
5206 Specification =>
5207 Make_Function_Specification (Loc,
5208 Defining_Unit_Name => Fent,
5209 Parameter_Specifications => New_List (
5210 Make_Parameter_Specification (Loc,
5211 Defining_Identifier =>
5212 Make_Defining_Identifier (Loc, Name_uA),
5213 Parameter_Type => New_Reference_To (Typ, Loc)),
5214 Make_Parameter_Specification (Loc,
5215 Defining_Identifier =>
5216 Make_Defining_Identifier (Loc, Name_uF),
5217 Parameter_Type => New_Reference_To (Standard_Boolean, Loc))),
5219 Result_Definition => New_Reference_To (Standard_Integer, Loc)),
5221 Declarations => Empty_List,
5223 Handled_Statement_Sequence =>
5224 Make_Handled_Sequence_Of_Statements (Loc,
5225 Statements => New_List (
5226 Make_Case_Statement (Loc,
5227 Expression =>
5228 Unchecked_Convert_To (Ityp,
5229 Make_Identifier (Loc, Name_uA)),
5230 Alternatives => Lst))));
5232 Set_TSS (Typ, Fent);
5233 Set_Is_Pure (Fent);
5235 if not Debug_Generated_Code then
5236 Set_Debug_Info_Off (Fent);
5237 end if;
5239 exception
5240 when RE_Not_Available =>
5241 return;
5242 end Freeze_Enumeration_Type;
5244 ------------------------
5245 -- Freeze_Record_Type --
5246 ------------------------
5248 procedure Freeze_Record_Type (N : Node_Id) is
5249 Def_Id : constant Node_Id := Entity (N);
5250 Type_Decl : constant Node_Id := Parent (Def_Id);
5251 Comp : Entity_Id;
5252 Comp_Typ : Entity_Id;
5253 Has_Static_DT : Boolean := False;
5254 Predef_List : List_Id;
5256 Flist : Entity_Id := Empty;
5257 -- Finalization list allocated for the case of a type with anonymous
5258 -- access components whose designated type is potentially controlled.
5260 Renamed_Eq : Node_Id := Empty;
5261 -- Could use some comments ???
5263 Wrapper_Decl_List : List_Id := No_List;
5264 Wrapper_Body_List : List_Id := No_List;
5265 Null_Proc_Decl_List : List_Id := No_List;
5267 begin
5268 -- Build discriminant checking functions if not a derived type (for
5269 -- derived types that are not tagged types, always use the discriminant
5270 -- checking functions of the parent type). However, for untagged types
5271 -- the derivation may have taken place before the parent was frozen, so
5272 -- we copy explicitly the discriminant checking functions from the
5273 -- parent into the components of the derived type.
5275 if not Is_Derived_Type (Def_Id)
5276 or else Has_New_Non_Standard_Rep (Def_Id)
5277 or else Is_Tagged_Type (Def_Id)
5278 then
5279 Build_Discr_Checking_Funcs (Type_Decl);
5281 elsif Is_Derived_Type (Def_Id)
5282 and then not Is_Tagged_Type (Def_Id)
5284 -- If we have a derived Unchecked_Union, we do not inherit the
5285 -- discriminant checking functions from the parent type since the
5286 -- discriminants are non existent.
5288 and then not Is_Unchecked_Union (Def_Id)
5289 and then Has_Discriminants (Def_Id)
5290 then
5291 declare
5292 Old_Comp : Entity_Id;
5294 begin
5295 Old_Comp :=
5296 First_Component (Base_Type (Underlying_Type (Etype (Def_Id))));
5297 Comp := First_Component (Def_Id);
5298 while Present (Comp) loop
5299 if Ekind (Comp) = E_Component
5300 and then Chars (Comp) = Chars (Old_Comp)
5301 then
5302 Set_Discriminant_Checking_Func (Comp,
5303 Discriminant_Checking_Func (Old_Comp));
5304 end if;
5306 Next_Component (Old_Comp);
5307 Next_Component (Comp);
5308 end loop;
5309 end;
5310 end if;
5312 if Is_Derived_Type (Def_Id)
5313 and then Is_Limited_Type (Def_Id)
5314 and then Is_Tagged_Type (Def_Id)
5315 then
5316 Check_Stream_Attributes (Def_Id);
5317 end if;
5319 -- Update task and controlled component flags, because some of the
5320 -- component types may have been private at the point of the record
5321 -- declaration.
5323 Comp := First_Component (Def_Id);
5325 while Present (Comp) loop
5326 Comp_Typ := Etype (Comp);
5328 if Has_Task (Comp_Typ) then
5329 Set_Has_Task (Def_Id);
5331 elsif Has_Controlled_Component (Comp_Typ)
5332 or else (Chars (Comp) /= Name_uParent
5333 and then Is_Controlled (Comp_Typ))
5334 then
5335 Set_Has_Controlled_Component (Def_Id);
5337 elsif Ekind (Comp_Typ) = E_Anonymous_Access_Type
5338 and then Controlled_Type (Directly_Designated_Type (Comp_Typ))
5339 then
5340 if No (Flist) then
5341 Flist := Add_Final_Chain (Def_Id);
5342 end if;
5344 Set_Associated_Final_Chain (Comp_Typ, Flist);
5345 end if;
5347 Next_Component (Comp);
5348 end loop;
5350 -- Creation of the Dispatch Table. Note that a Dispatch Table is built
5351 -- for regular tagged types as well as for Ada types deriving from a C++
5352 -- Class, but not for tagged types directly corresponding to C++ classes
5353 -- In the later case we assume that it is created in the C++ side and we
5354 -- just use it.
5356 if Is_Tagged_Type (Def_Id) then
5357 Has_Static_DT :=
5358 Static_Dispatch_Tables
5359 and then Is_Library_Level_Tagged_Type (Def_Id);
5361 -- Add the _Tag component
5363 if Underlying_Type (Etype (Def_Id)) = Def_Id then
5364 Expand_Tagged_Root (Def_Id);
5365 end if;
5367 if Is_CPP_Class (Def_Id) then
5368 Set_All_DT_Position (Def_Id);
5369 Set_Default_Constructor (Def_Id);
5371 -- Create the tag entities with a minimum decoration
5373 if VM_Target = No_VM then
5374 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
5375 end if;
5377 else
5378 if not Has_Static_DT then
5380 -- Usually inherited primitives are not delayed but the first
5381 -- Ada extension of a CPP_Class is an exception since the
5382 -- address of the inherited subprogram has to be inserted in
5383 -- the new Ada Dispatch Table and this is a freezing action.
5385 -- Similarly, if this is an inherited operation whose parent is
5386 -- not frozen yet, it is not in the DT of the parent, and we
5387 -- generate an explicit freeze node for the inherited operation
5388 -- so that it is properly inserted in the DT of the current
5389 -- type.
5391 declare
5392 Elmt : Elmt_Id := First_Elmt (Primitive_Operations (Def_Id));
5393 Subp : Entity_Id;
5395 begin
5396 while Present (Elmt) loop
5397 Subp := Node (Elmt);
5399 if Present (Alias (Subp)) then
5400 if Is_CPP_Class (Etype (Def_Id)) then
5401 Set_Has_Delayed_Freeze (Subp);
5403 elsif Has_Delayed_Freeze (Alias (Subp))
5404 and then not Is_Frozen (Alias (Subp))
5405 then
5406 Set_Is_Frozen (Subp, False);
5407 Set_Has_Delayed_Freeze (Subp);
5408 end if;
5409 end if;
5411 Next_Elmt (Elmt);
5412 end loop;
5413 end;
5414 end if;
5416 -- Unfreeze momentarily the type to add the predefined primitives
5417 -- operations. The reason we unfreeze is so that these predefined
5418 -- operations will indeed end up as primitive operations (which
5419 -- must be before the freeze point).
5421 Set_Is_Frozen (Def_Id, False);
5423 -- Do not add the spec of the predefined primitives if we are
5424 -- compiling under restriction No_Dispatching_Calls
5426 if not Restriction_Active (No_Dispatching_Calls) then
5427 Make_Predefined_Primitive_Specs
5428 (Def_Id, Predef_List, Renamed_Eq);
5429 Insert_List_Before_And_Analyze (N, Predef_List);
5430 end if;
5432 -- Ada 2005 (AI-391): For a nonabstract null extension, create
5433 -- wrapper functions for each nonoverridden inherited function
5434 -- with a controlling result of the type. The wrapper for such
5435 -- a function returns an extension aggregate that invokes the
5436 -- the parent function.
5438 if Ada_Version >= Ada_05
5439 and then not Is_Abstract_Type (Def_Id)
5440 and then Is_Null_Extension (Def_Id)
5441 then
5442 Make_Controlling_Function_Wrappers
5443 (Def_Id, Wrapper_Decl_List, Wrapper_Body_List);
5444 Insert_List_Before_And_Analyze (N, Wrapper_Decl_List);
5445 end if;
5447 -- Ada 2005 (AI-251): For a nonabstract type extension, build
5448 -- null procedure declarations for each set of homographic null
5449 -- procedures that are inherited from interface types but not
5450 -- overridden. This is done to ensure that the dispatch table
5451 -- entry associated with such null primitives are properly filled.
5453 if Ada_Version >= Ada_05
5454 and then Etype (Def_Id) /= Def_Id
5455 and then not Is_Abstract_Type (Def_Id)
5456 then
5457 Make_Null_Procedure_Specs (Def_Id, Null_Proc_Decl_List);
5458 Insert_Actions (N, Null_Proc_Decl_List);
5459 end if;
5461 Set_Is_Frozen (Def_Id);
5462 Set_All_DT_Position (Def_Id);
5464 -- Add the controlled component before the freezing actions
5465 -- referenced in those actions.
5467 if Has_New_Controlled_Component (Def_Id) then
5468 Expand_Record_Controller (Def_Id);
5469 end if;
5471 -- Create and decorate the tags. Suppress their creation when
5472 -- VM_Target because the dispatching mechanism is handled
5473 -- internally by the VMs.
5475 if VM_Target = No_VM then
5476 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
5478 -- Generate dispatch table of locally defined tagged type.
5479 -- Dispatch tables of library level tagged types are built
5480 -- later (see Analyze_Declarations).
5482 if VM_Target = No_VM
5483 and then not Has_Static_DT
5484 then
5485 Append_Freeze_Actions (Def_Id, Make_DT (Def_Id));
5486 end if;
5487 end if;
5489 -- Make sure that the primitives Initialize, Adjust and Finalize
5490 -- are Frozen before other TSS subprograms. We don't want them
5491 -- Frozen inside.
5493 if Is_Controlled (Def_Id) then
5494 if not Is_Limited_Type (Def_Id) then
5495 Append_Freeze_Actions (Def_Id,
5496 Freeze_Entity
5497 (Find_Prim_Op (Def_Id, Name_Adjust), Sloc (Def_Id)));
5498 end if;
5500 Append_Freeze_Actions (Def_Id,
5501 Freeze_Entity
5502 (Find_Prim_Op (Def_Id, Name_Initialize), Sloc (Def_Id)));
5504 Append_Freeze_Actions (Def_Id,
5505 Freeze_Entity
5506 (Find_Prim_Op (Def_Id, Name_Finalize), Sloc (Def_Id)));
5507 end if;
5509 -- Freeze rest of primitive operations. There is no need to handle
5510 -- the predefined primitives if we are compiling under restriction
5511 -- No_Dispatching_Calls
5513 if not Restriction_Active (No_Dispatching_Calls) then
5514 Append_Freeze_Actions
5515 (Def_Id, Predefined_Primitive_Freeze (Def_Id));
5516 end if;
5517 end if;
5519 -- In the non-tagged case, an equality function is provided only for
5520 -- variant records (that are not unchecked unions).
5522 elsif Has_Discriminants (Def_Id)
5523 and then not Is_Limited_Type (Def_Id)
5524 then
5525 declare
5526 Comps : constant Node_Id :=
5527 Component_List (Type_Definition (Type_Decl));
5529 begin
5530 if Present (Comps)
5531 and then Present (Variant_Part (Comps))
5532 then
5533 Build_Variant_Record_Equality (Def_Id);
5534 end if;
5535 end;
5536 end if;
5538 -- Before building the record initialization procedure, if we are
5539 -- dealing with a concurrent record value type, then we must go through
5540 -- the discriminants, exchanging discriminals between the concurrent
5541 -- type and the concurrent record value type. See the section "Handling
5542 -- of Discriminants" in the Einfo spec for details.
5544 if Is_Concurrent_Record_Type (Def_Id)
5545 and then Has_Discriminants (Def_Id)
5546 then
5547 declare
5548 Ctyp : constant Entity_Id :=
5549 Corresponding_Concurrent_Type (Def_Id);
5550 Conc_Discr : Entity_Id;
5551 Rec_Discr : Entity_Id;
5552 Temp : Entity_Id;
5554 begin
5555 Conc_Discr := First_Discriminant (Ctyp);
5556 Rec_Discr := First_Discriminant (Def_Id);
5558 while Present (Conc_Discr) loop
5559 Temp := Discriminal (Conc_Discr);
5560 Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
5561 Set_Discriminal (Rec_Discr, Temp);
5563 Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
5564 Set_Discriminal_Link (Discriminal (Rec_Discr), Rec_Discr);
5566 Next_Discriminant (Conc_Discr);
5567 Next_Discriminant (Rec_Discr);
5568 end loop;
5569 end;
5570 end if;
5572 if Has_Controlled_Component (Def_Id) then
5573 if No (Controller_Component (Def_Id)) then
5574 Expand_Record_Controller (Def_Id);
5575 end if;
5577 Build_Controlling_Procs (Def_Id);
5578 end if;
5580 Adjust_Discriminants (Def_Id);
5582 if VM_Target = No_VM or else not Is_Interface (Def_Id) then
5584 -- Do not need init for interfaces on e.g. CIL since they're
5585 -- abstract. Helps operation of peverify (the PE Verify tool).
5587 Build_Record_Init_Proc (Type_Decl, Def_Id);
5588 end if;
5590 -- For tagged type, build bodies of primitive operations. Note that we
5591 -- do this after building the record initialization experiment, since
5592 -- the primitive operations may need the initialization routine
5594 if Is_Tagged_Type (Def_Id) then
5596 -- Do not add the body of the predefined primitives if we are
5597 -- compiling under restriction No_Dispatching_Calls
5599 if not Restriction_Active (No_Dispatching_Calls) then
5600 Predef_List := Predefined_Primitive_Bodies (Def_Id, Renamed_Eq);
5601 Append_Freeze_Actions (Def_Id, Predef_List);
5602 end if;
5604 -- Ada 2005 (AI-391): If any wrappers were created for nonoverridden
5605 -- inherited functions, then add their bodies to the freeze actions.
5607 if Present (Wrapper_Body_List) then
5608 Append_Freeze_Actions (Def_Id, Wrapper_Body_List);
5609 end if;
5610 end if;
5611 end Freeze_Record_Type;
5613 ------------------------------
5614 -- Freeze_Stream_Operations --
5615 ------------------------------
5617 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
5618 Names : constant array (1 .. 4) of TSS_Name_Type :=
5619 (TSS_Stream_Input,
5620 TSS_Stream_Output,
5621 TSS_Stream_Read,
5622 TSS_Stream_Write);
5623 Stream_Op : Entity_Id;
5625 begin
5626 -- Primitive operations of tagged types are frozen when the dispatch
5627 -- table is constructed.
5629 if not Comes_From_Source (Typ)
5630 or else Is_Tagged_Type (Typ)
5631 then
5632 return;
5633 end if;
5635 for J in Names'Range loop
5636 Stream_Op := TSS (Typ, Names (J));
5638 if Present (Stream_Op)
5639 and then Is_Subprogram (Stream_Op)
5640 and then Nkind (Unit_Declaration_Node (Stream_Op)) =
5641 N_Subprogram_Declaration
5642 and then not Is_Frozen (Stream_Op)
5643 then
5644 Append_Freeze_Actions
5645 (Typ, Freeze_Entity (Stream_Op, Sloc (N)));
5646 end if;
5647 end loop;
5648 end Freeze_Stream_Operations;
5650 -----------------
5651 -- Freeze_Type --
5652 -----------------
5654 -- Full type declarations are expanded at the point at which the type is
5655 -- frozen. The formal N is the Freeze_Node for the type. Any statements or
5656 -- declarations generated by the freezing (e.g. the procedure generated
5657 -- for initialization) are chained in the Actions field list of the freeze
5658 -- node using Append_Freeze_Actions.
5660 function Freeze_Type (N : Node_Id) return Boolean is
5661 Def_Id : constant Entity_Id := Entity (N);
5662 RACW_Seen : Boolean := False;
5663 Result : Boolean := False;
5665 begin
5666 -- Process associated access types needing special processing
5668 if Present (Access_Types_To_Process (N)) then
5669 declare
5670 E : Elmt_Id := First_Elmt (Access_Types_To_Process (N));
5671 begin
5672 while Present (E) loop
5674 if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
5675 Validate_RACW_Primitives (Node (E));
5676 RACW_Seen := True;
5677 end if;
5679 E := Next_Elmt (E);
5680 end loop;
5681 end;
5683 if RACW_Seen then
5685 -- If there are RACWs designating this type, make stubs now
5687 Remote_Types_Tagged_Full_View_Encountered (Def_Id);
5688 end if;
5689 end if;
5691 -- Freeze processing for record types
5693 if Is_Record_Type (Def_Id) then
5694 if Ekind (Def_Id) = E_Record_Type then
5695 Freeze_Record_Type (N);
5697 -- The subtype may have been declared before the type was frozen. If
5698 -- the type has controlled components it is necessary to create the
5699 -- entity for the controller explicitly because it did not exist at
5700 -- the point of the subtype declaration. Only the entity is needed,
5701 -- the back-end will obtain the layout from the type. This is only
5702 -- necessary if this is constrained subtype whose component list is
5703 -- not shared with the base type.
5705 elsif Ekind (Def_Id) = E_Record_Subtype
5706 and then Has_Discriminants (Def_Id)
5707 and then Last_Entity (Def_Id) /= Last_Entity (Base_Type (Def_Id))
5708 and then Present (Controller_Component (Def_Id))
5709 then
5710 declare
5711 Old_C : constant Entity_Id := Controller_Component (Def_Id);
5712 New_C : Entity_Id;
5714 begin
5715 if Scope (Old_C) = Base_Type (Def_Id) then
5717 -- The entity is the one in the parent. Create new one
5719 New_C := New_Copy (Old_C);
5720 Set_Parent (New_C, Parent (Old_C));
5721 Push_Scope (Def_Id);
5722 Enter_Name (New_C);
5723 End_Scope;
5724 end if;
5725 end;
5727 if Is_Itype (Def_Id)
5728 and then Is_Record_Type (Underlying_Type (Scope (Def_Id)))
5729 then
5730 -- The freeze node is only used to introduce the controller,
5731 -- the back-end has no use for it for a discriminated
5732 -- component.
5734 Set_Freeze_Node (Def_Id, Empty);
5735 Set_Has_Delayed_Freeze (Def_Id, False);
5736 Result := True;
5737 end if;
5739 -- Similar process if the controller of the subtype is not present
5740 -- but the parent has it. This can happen with constrained
5741 -- record components where the subtype is an itype.
5743 elsif Ekind (Def_Id) = E_Record_Subtype
5744 and then Is_Itype (Def_Id)
5745 and then No (Controller_Component (Def_Id))
5746 and then Present (Controller_Component (Etype (Def_Id)))
5747 then
5748 declare
5749 Old_C : constant Entity_Id :=
5750 Controller_Component (Etype (Def_Id));
5751 New_C : constant Entity_Id := New_Copy (Old_C);
5753 begin
5754 Set_Next_Entity (New_C, First_Entity (Def_Id));
5755 Set_First_Entity (Def_Id, New_C);
5757 -- The freeze node is only used to introduce the controller,
5758 -- the back-end has no use for it for a discriminated
5759 -- component.
5761 Set_Freeze_Node (Def_Id, Empty);
5762 Set_Has_Delayed_Freeze (Def_Id, False);
5763 Result := True;
5764 end;
5765 end if;
5767 -- Freeze processing for array types
5769 elsif Is_Array_Type (Def_Id) then
5770 Freeze_Array_Type (N);
5772 -- Freeze processing for access types
5774 -- For pool-specific access types, find out the pool object used for
5775 -- this type, needs actual expansion of it in some cases. Here are the
5776 -- different cases :
5778 -- 1. Rep Clause "for Def_Id'Storage_Size use 0;"
5779 -- ---> don't use any storage pool
5781 -- 2. Rep Clause : for Def_Id'Storage_Size use Expr.
5782 -- Expand:
5783 -- Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
5785 -- 3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
5786 -- ---> Storage Pool is the specified one
5788 -- See GNAT Pool packages in the Run-Time for more details
5790 elsif Ekind (Def_Id) = E_Access_Type
5791 or else Ekind (Def_Id) = E_General_Access_Type
5792 then
5793 declare
5794 Loc : constant Source_Ptr := Sloc (N);
5795 Desig_Type : constant Entity_Id := Designated_Type (Def_Id);
5796 Pool_Object : Entity_Id;
5797 Siz_Exp : Node_Id;
5799 Freeze_Action_Typ : Entity_Id;
5801 begin
5802 if Has_Storage_Size_Clause (Def_Id) then
5803 Siz_Exp := Expression (Parent (Storage_Size_Variable (Def_Id)));
5804 else
5805 Siz_Exp := Empty;
5806 end if;
5808 -- Case 1
5810 -- Rep Clause "for Def_Id'Storage_Size use 0;"
5811 -- ---> don't use any storage pool
5813 if Has_Storage_Size_Clause (Def_Id)
5814 and then Compile_Time_Known_Value (Siz_Exp)
5815 and then Expr_Value (Siz_Exp) = 0
5816 then
5817 null;
5819 -- Case 2
5821 -- Rep Clause : for Def_Id'Storage_Size use Expr.
5822 -- ---> Expand:
5823 -- Def_Id__Pool : Stack_Bounded_Pool
5824 -- (Expr, DT'Size, DT'Alignment);
5826 elsif Has_Storage_Size_Clause (Def_Id) then
5827 declare
5828 DT_Size : Node_Id;
5829 DT_Align : Node_Id;
5831 begin
5832 -- For unconstrained composite types we give a size of zero
5833 -- so that the pool knows that it needs a special algorithm
5834 -- for variable size object allocation.
5836 if Is_Composite_Type (Desig_Type)
5837 and then not Is_Constrained (Desig_Type)
5838 then
5839 DT_Size :=
5840 Make_Integer_Literal (Loc, 0);
5842 DT_Align :=
5843 Make_Integer_Literal (Loc, Maximum_Alignment);
5845 else
5846 DT_Size :=
5847 Make_Attribute_Reference (Loc,
5848 Prefix => New_Reference_To (Desig_Type, Loc),
5849 Attribute_Name => Name_Max_Size_In_Storage_Elements);
5851 DT_Align :=
5852 Make_Attribute_Reference (Loc,
5853 Prefix => New_Reference_To (Desig_Type, Loc),
5854 Attribute_Name => Name_Alignment);
5855 end if;
5857 Pool_Object :=
5858 Make_Defining_Identifier (Loc,
5859 Chars => New_External_Name (Chars (Def_Id), 'P'));
5861 -- We put the code associated with the pools in the entity
5862 -- that has the later freeze node, usually the access type
5863 -- but it can also be the designated_type; because the pool
5864 -- code requires both those types to be frozen
5866 if Is_Frozen (Desig_Type)
5867 and then (No (Freeze_Node (Desig_Type))
5868 or else Analyzed (Freeze_Node (Desig_Type)))
5869 then
5870 Freeze_Action_Typ := Def_Id;
5872 -- A Taft amendment type cannot get the freeze actions
5873 -- since the full view is not there.
5875 elsif Is_Incomplete_Or_Private_Type (Desig_Type)
5876 and then No (Full_View (Desig_Type))
5877 then
5878 Freeze_Action_Typ := Def_Id;
5880 else
5881 Freeze_Action_Typ := Desig_Type;
5882 end if;
5884 Append_Freeze_Action (Freeze_Action_Typ,
5885 Make_Object_Declaration (Loc,
5886 Defining_Identifier => Pool_Object,
5887 Object_Definition =>
5888 Make_Subtype_Indication (Loc,
5889 Subtype_Mark =>
5890 New_Reference_To
5891 (RTE (RE_Stack_Bounded_Pool), Loc),
5893 Constraint =>
5894 Make_Index_Or_Discriminant_Constraint (Loc,
5895 Constraints => New_List (
5897 -- First discriminant is the Pool Size
5899 New_Reference_To (
5900 Storage_Size_Variable (Def_Id), Loc),
5902 -- Second discriminant is the element size
5904 DT_Size,
5906 -- Third discriminant is the alignment
5908 DT_Align)))));
5909 end;
5911 Set_Associated_Storage_Pool (Def_Id, Pool_Object);
5913 -- Case 3
5915 -- Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
5916 -- ---> Storage Pool is the specified one
5918 elsif Present (Associated_Storage_Pool (Def_Id)) then
5920 -- Nothing to do the associated storage pool has been attached
5921 -- when analyzing the rep. clause
5923 null;
5924 end if;
5926 -- For access-to-controlled types (including class-wide types and
5927 -- Taft-amendment types which potentially have controlled
5928 -- components), expand the list controller object that will store
5929 -- the dynamically allocated objects. Do not do this
5930 -- transformation for expander-generated access types, but do it
5931 -- for types that are the full view of types derived from other
5932 -- private types. Also suppress the list controller in the case
5933 -- of a designated type with convention Java, since this is used
5934 -- when binding to Java API specs, where there's no equivalent of
5935 -- a finalization list and we don't want to pull in the
5936 -- finalization support if not needed.
5938 if not Comes_From_Source (Def_Id)
5939 and then not Has_Private_Declaration (Def_Id)
5940 then
5941 null;
5943 elsif (Controlled_Type (Desig_Type)
5944 and then Convention (Desig_Type) /= Convention_Java
5945 and then Convention (Desig_Type) /= Convention_CIL)
5946 or else
5947 (Is_Incomplete_Or_Private_Type (Desig_Type)
5948 and then No (Full_View (Desig_Type))
5950 -- An exception is made for types defined in the run-time
5951 -- because Ada.Tags.Tag itself is such a type and cannot
5952 -- afford this unnecessary overhead that would generates a
5953 -- loop in the expansion scheme...
5955 and then not In_Runtime (Def_Id)
5957 -- Another exception is if Restrictions (No_Finalization)
5958 -- is active, since then we know nothing is controlled.
5960 and then not Restriction_Active (No_Finalization))
5962 -- If the designated type is not frozen yet, its controlled
5963 -- status must be retrieved explicitly.
5965 or else (Is_Array_Type (Desig_Type)
5966 and then not Is_Frozen (Desig_Type)
5967 and then Controlled_Type (Component_Type (Desig_Type)))
5969 -- The designated type has controlled anonymous access
5970 -- discriminants.
5972 or else Has_Controlled_Coextensions (Desig_Type)
5973 then
5974 Set_Associated_Final_Chain (Def_Id, Add_Final_Chain (Def_Id));
5975 end if;
5976 end;
5978 -- Freeze processing for enumeration types
5980 elsif Ekind (Def_Id) = E_Enumeration_Type then
5982 -- We only have something to do if we have a non-standard
5983 -- representation (i.e. at least one literal whose pos value
5984 -- is not the same as its representation)
5986 if Has_Non_Standard_Rep (Def_Id) then
5987 Freeze_Enumeration_Type (N);
5988 end if;
5990 -- Private types that are completed by a derivation from a private
5991 -- type have an internally generated full view, that needs to be
5992 -- frozen. This must be done explicitly because the two views share
5993 -- the freeze node, and the underlying full view is not visible when
5994 -- the freeze node is analyzed.
5996 elsif Is_Private_Type (Def_Id)
5997 and then Is_Derived_Type (Def_Id)
5998 and then Present (Full_View (Def_Id))
5999 and then Is_Itype (Full_View (Def_Id))
6000 and then Has_Private_Declaration (Full_View (Def_Id))
6001 and then Freeze_Node (Full_View (Def_Id)) = N
6002 then
6003 Set_Entity (N, Full_View (Def_Id));
6004 Result := Freeze_Type (N);
6005 Set_Entity (N, Def_Id);
6007 -- All other types require no expander action. There are such cases
6008 -- (e.g. task types and protected types). In such cases, the freeze
6009 -- nodes are there for use by Gigi.
6011 end if;
6013 Freeze_Stream_Operations (N, Def_Id);
6014 return Result;
6016 exception
6017 when RE_Not_Available =>
6018 return False;
6019 end Freeze_Type;
6021 -------------------------
6022 -- Get_Simple_Init_Val --
6023 -------------------------
6025 function Get_Simple_Init_Val
6026 (T : Entity_Id;
6027 Loc : Source_Ptr;
6028 Size : Uint := No_Uint) return Node_Id
6030 Val : Node_Id;
6031 Result : Node_Id;
6032 Val_RE : RE_Id;
6034 Size_To_Use : Uint;
6035 -- This is the size to be used for computation of the appropriate
6036 -- initial value for the Normalize_Scalars and Initialize_Scalars case.
6038 Lo_Bound : Uint;
6039 Hi_Bound : Uint;
6040 -- These are the values computed by the procedure Check_Subtype_Bounds
6042 procedure Check_Subtype_Bounds;
6043 -- This procedure examines the subtype T, and its ancestor subtypes and
6044 -- derived types to determine the best known information about the
6045 -- bounds of the subtype. After the call Lo_Bound is set either to
6046 -- No_Uint if no information can be determined, or to a value which
6047 -- represents a known low bound, i.e. a valid value of the subtype can
6048 -- not be less than this value. Hi_Bound is similarly set to a known
6049 -- high bound (valid value cannot be greater than this).
6051 --------------------------
6052 -- Check_Subtype_Bounds --
6053 --------------------------
6055 procedure Check_Subtype_Bounds is
6056 ST1 : Entity_Id;
6057 ST2 : Entity_Id;
6058 Lo : Node_Id;
6059 Hi : Node_Id;
6060 Loval : Uint;
6061 Hival : Uint;
6063 begin
6064 Lo_Bound := No_Uint;
6065 Hi_Bound := No_Uint;
6067 -- Loop to climb ancestor subtypes and derived types
6069 ST1 := T;
6070 loop
6071 if not Is_Discrete_Type (ST1) then
6072 return;
6073 end if;
6075 Lo := Type_Low_Bound (ST1);
6076 Hi := Type_High_Bound (ST1);
6078 if Compile_Time_Known_Value (Lo) then
6079 Loval := Expr_Value (Lo);
6081 if Lo_Bound = No_Uint or else Lo_Bound < Loval then
6082 Lo_Bound := Loval;
6083 end if;
6084 end if;
6086 if Compile_Time_Known_Value (Hi) then
6087 Hival := Expr_Value (Hi);
6089 if Hi_Bound = No_Uint or else Hi_Bound > Hival then
6090 Hi_Bound := Hival;
6091 end if;
6092 end if;
6094 ST2 := Ancestor_Subtype (ST1);
6096 if No (ST2) then
6097 ST2 := Etype (ST1);
6098 end if;
6100 exit when ST1 = ST2;
6101 ST1 := ST2;
6102 end loop;
6103 end Check_Subtype_Bounds;
6105 -- Start of processing for Get_Simple_Init_Val
6107 begin
6108 -- For a private type, we should always have an underlying type
6109 -- (because this was already checked in Needs_Simple_Initialization).
6110 -- What we do is to get the value for the underlying type and then do
6111 -- an Unchecked_Convert to the private type.
6113 if Is_Private_Type (T) then
6114 Val := Get_Simple_Init_Val (Underlying_Type (T), Loc, Size);
6116 -- A special case, if the underlying value is null, then qualify it
6117 -- with the underlying type, so that the null is properly typed
6118 -- Similarly, if it is an aggregate it must be qualified, because an
6119 -- unchecked conversion does not provide a context for it.
6121 if Nkind (Val) = N_Null
6122 or else Nkind (Val) = N_Aggregate
6123 then
6124 Val :=
6125 Make_Qualified_Expression (Loc,
6126 Subtype_Mark =>
6127 New_Occurrence_Of (Underlying_Type (T), Loc),
6128 Expression => Val);
6129 end if;
6131 Result := Unchecked_Convert_To (T, Val);
6133 -- Don't truncate result (important for Initialize/Normalize_Scalars)
6135 if Nkind (Result) = N_Unchecked_Type_Conversion
6136 and then Is_Scalar_Type (Underlying_Type (T))
6137 then
6138 Set_No_Truncation (Result);
6139 end if;
6141 return Result;
6143 -- For scalars, we must have normalize/initialize scalars case
6145 elsif Is_Scalar_Type (T) then
6146 pragma Assert (Init_Or_Norm_Scalars);
6148 -- Compute size of object. If it is given by the caller, we can use
6149 -- it directly, otherwise we use Esize (T) as an estimate. As far as
6150 -- we know this covers all cases correctly.
6152 if Size = No_Uint or else Size <= Uint_0 then
6153 Size_To_Use := UI_Max (Uint_1, Esize (T));
6154 else
6155 Size_To_Use := Size;
6156 end if;
6158 -- Maximum size to use is 64 bits, since we will create values
6159 -- of type Unsigned_64 and the range must fit this type.
6161 if Size_To_Use /= No_Uint and then Size_To_Use > Uint_64 then
6162 Size_To_Use := Uint_64;
6163 end if;
6165 -- Check known bounds of subtype
6167 Check_Subtype_Bounds;
6169 -- Processing for Normalize_Scalars case
6171 if Normalize_Scalars then
6173 -- If zero is invalid, it is a convenient value to use that is
6174 -- for sure an appropriate invalid value in all situations.
6176 if Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
6177 Val := Make_Integer_Literal (Loc, 0);
6179 -- Cases where all one bits is the appropriate invalid value
6181 -- For modular types, all 1 bits is either invalid or valid. If
6182 -- it is valid, then there is nothing that can be done since there
6183 -- are no invalid values (we ruled out zero already).
6185 -- For signed integer types that have no negative values, either
6186 -- there is room for negative values, or there is not. If there
6187 -- is, then all 1 bits may be interpreted as minus one, which is
6188 -- certainly invalid. Alternatively it is treated as the largest
6189 -- positive value, in which case the observation for modular types
6190 -- still applies.
6192 -- For float types, all 1-bits is a NaN (not a number), which is
6193 -- certainly an appropriately invalid value.
6195 elsif Is_Unsigned_Type (T)
6196 or else Is_Floating_Point_Type (T)
6197 or else Is_Enumeration_Type (T)
6198 then
6199 Val := Make_Integer_Literal (Loc, 2 ** Size_To_Use - 1);
6201 -- Resolve as Unsigned_64, because the largest number we
6202 -- can generate is out of range of universal integer.
6204 Analyze_And_Resolve (Val, RTE (RE_Unsigned_64));
6206 -- Case of signed types
6208 else
6209 declare
6210 Signed_Size : constant Uint :=
6211 UI_Min (Uint_63, Size_To_Use - 1);
6213 begin
6214 -- Normally we like to use the most negative number. The
6215 -- one exception is when this number is in the known
6216 -- subtype range and the largest positive number is not in
6217 -- the known subtype range.
6219 -- For this exceptional case, use largest positive value
6221 if Lo_Bound /= No_Uint and then Hi_Bound /= No_Uint
6222 and then Lo_Bound <= (-(2 ** Signed_Size))
6223 and then Hi_Bound < 2 ** Signed_Size
6224 then
6225 Val := Make_Integer_Literal (Loc, 2 ** Signed_Size - 1);
6227 -- Normal case of largest negative value
6229 else
6230 Val := Make_Integer_Literal (Loc, -(2 ** Signed_Size));
6231 end if;
6232 end;
6233 end if;
6235 -- Here for Initialize_Scalars case
6237 else
6238 -- For float types, use float values from System.Scalar_Values
6240 if Is_Floating_Point_Type (T) then
6241 if Root_Type (T) = Standard_Short_Float then
6242 Val_RE := RE_IS_Isf;
6243 elsif Root_Type (T) = Standard_Float then
6244 Val_RE := RE_IS_Ifl;
6245 elsif Root_Type (T) = Standard_Long_Float then
6246 Val_RE := RE_IS_Ilf;
6247 else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
6248 Val_RE := RE_IS_Ill;
6249 end if;
6251 -- If zero is invalid, use zero values from System.Scalar_Values
6253 elsif Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
6254 if Size_To_Use <= 8 then
6255 Val_RE := RE_IS_Iz1;
6256 elsif Size_To_Use <= 16 then
6257 Val_RE := RE_IS_Iz2;
6258 elsif Size_To_Use <= 32 then
6259 Val_RE := RE_IS_Iz4;
6260 else
6261 Val_RE := RE_IS_Iz8;
6262 end if;
6264 -- For unsigned, use unsigned values from System.Scalar_Values
6266 elsif Is_Unsigned_Type (T) then
6267 if Size_To_Use <= 8 then
6268 Val_RE := RE_IS_Iu1;
6269 elsif Size_To_Use <= 16 then
6270 Val_RE := RE_IS_Iu2;
6271 elsif Size_To_Use <= 32 then
6272 Val_RE := RE_IS_Iu4;
6273 else
6274 Val_RE := RE_IS_Iu8;
6275 end if;
6277 -- For signed, use signed values from System.Scalar_Values
6279 else
6280 if Size_To_Use <= 8 then
6281 Val_RE := RE_IS_Is1;
6282 elsif Size_To_Use <= 16 then
6283 Val_RE := RE_IS_Is2;
6284 elsif Size_To_Use <= 32 then
6285 Val_RE := RE_IS_Is4;
6286 else
6287 Val_RE := RE_IS_Is8;
6288 end if;
6289 end if;
6291 Val := New_Occurrence_Of (RTE (Val_RE), Loc);
6292 end if;
6294 -- The final expression is obtained by doing an unchecked conversion
6295 -- of this result to the base type of the required subtype. We use
6296 -- the base type to avoid the unchecked conversion from chopping
6297 -- bits, and then we set Kill_Range_Check to preserve the "bad"
6298 -- value.
6300 Result := Unchecked_Convert_To (Base_Type (T), Val);
6302 -- Ensure result is not truncated, since we want the "bad" bits
6303 -- and also kill range check on result.
6305 if Nkind (Result) = N_Unchecked_Type_Conversion then
6306 Set_No_Truncation (Result);
6307 Set_Kill_Range_Check (Result, True);
6308 end if;
6310 return Result;
6312 -- String or Wide_[Wide]_String (must have Initialize_Scalars set)
6314 elsif Root_Type (T) = Standard_String
6315 or else
6316 Root_Type (T) = Standard_Wide_String
6317 or else
6318 Root_Type (T) = Standard_Wide_Wide_String
6319 then
6320 pragma Assert (Init_Or_Norm_Scalars);
6322 return
6323 Make_Aggregate (Loc,
6324 Component_Associations => New_List (
6325 Make_Component_Association (Loc,
6326 Choices => New_List (
6327 Make_Others_Choice (Loc)),
6328 Expression =>
6329 Get_Simple_Init_Val
6330 (Component_Type (T), Loc, Esize (Root_Type (T))))));
6332 -- Access type is initialized to null
6334 elsif Is_Access_Type (T) then
6335 return
6336 Make_Null (Loc);
6338 -- No other possibilities should arise, since we should only be
6339 -- calling Get_Simple_Init_Val if Needs_Simple_Initialization
6340 -- returned True, indicating one of the above cases held.
6342 else
6343 raise Program_Error;
6344 end if;
6346 exception
6347 when RE_Not_Available =>
6348 return Empty;
6349 end Get_Simple_Init_Val;
6351 ------------------------------
6352 -- Has_New_Non_Standard_Rep --
6353 ------------------------------
6355 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
6356 begin
6357 if not Is_Derived_Type (T) then
6358 return Has_Non_Standard_Rep (T)
6359 or else Has_Non_Standard_Rep (Root_Type (T));
6361 -- If Has_Non_Standard_Rep is not set on the derived type, the
6362 -- representation is fully inherited.
6364 elsif not Has_Non_Standard_Rep (T) then
6365 return False;
6367 else
6368 return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
6370 -- May need a more precise check here: the First_Rep_Item may
6371 -- be a stream attribute, which does not affect the representation
6372 -- of the type ???
6373 end if;
6374 end Has_New_Non_Standard_Rep;
6376 ----------------
6377 -- In_Runtime --
6378 ----------------
6380 function In_Runtime (E : Entity_Id) return Boolean is
6381 S1 : Entity_Id;
6383 begin
6384 S1 := Scope (E);
6385 while Scope (S1) /= Standard_Standard loop
6386 S1 := Scope (S1);
6387 end loop;
6389 return Chars (S1) = Name_System or else Chars (S1) = Name_Ada;
6390 end In_Runtime;
6392 ----------------------------
6393 -- Initialization_Warning --
6394 ----------------------------
6396 procedure Initialization_Warning (E : Entity_Id) is
6397 Warning_Needed : Boolean;
6399 begin
6400 Warning_Needed := False;
6402 if Ekind (Current_Scope) = E_Package
6403 and then Static_Elaboration_Desired (Current_Scope)
6404 then
6405 if Is_Type (E) then
6406 if Is_Record_Type (E) then
6407 if Has_Discriminants (E)
6408 or else Is_Limited_Type (E)
6409 or else Has_Non_Standard_Rep (E)
6410 then
6411 Warning_Needed := True;
6413 else
6414 -- Verify that at least one component has an initializtion
6415 -- expression. No need for a warning on a type if all its
6416 -- components have no initialization.
6418 declare
6419 Comp : Entity_Id;
6421 begin
6422 Comp := First_Component (E);
6423 while Present (Comp) loop
6424 if Ekind (Comp) = E_Discriminant
6425 or else
6426 (Nkind (Parent (Comp)) = N_Component_Declaration
6427 and then Present (Expression (Parent (Comp))))
6428 then
6429 Warning_Needed := True;
6430 exit;
6431 end if;
6433 Next_Component (Comp);
6434 end loop;
6435 end;
6436 end if;
6438 if Warning_Needed then
6439 Error_Msg_N
6440 ("Objects of the type cannot be initialized " &
6441 "statically by default?",
6442 Parent (E));
6443 end if;
6444 end if;
6446 else
6447 Error_Msg_N ("Object cannot be initialized statically?", E);
6448 end if;
6449 end if;
6450 end Initialization_Warning;
6452 ------------------
6453 -- Init_Formals --
6454 ------------------
6456 function Init_Formals (Typ : Entity_Id) return List_Id is
6457 Loc : constant Source_Ptr := Sloc (Typ);
6458 Formals : List_Id;
6460 begin
6461 -- First parameter is always _Init : in out typ. Note that we need
6462 -- this to be in/out because in the case of the task record value,
6463 -- there are default record fields (_Priority, _Size, -Task_Info)
6464 -- that may be referenced in the generated initialization routine.
6466 Formals := New_List (
6467 Make_Parameter_Specification (Loc,
6468 Defining_Identifier =>
6469 Make_Defining_Identifier (Loc, Name_uInit),
6470 In_Present => True,
6471 Out_Present => True,
6472 Parameter_Type => New_Reference_To (Typ, Loc)));
6474 -- For task record value, or type that contains tasks, add two more
6475 -- formals, _Master : Master_Id and _Chain : in out Activation_Chain
6476 -- We also add these parameters for the task record type case.
6478 if Has_Task (Typ)
6479 or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
6480 then
6481 Append_To (Formals,
6482 Make_Parameter_Specification (Loc,
6483 Defining_Identifier =>
6484 Make_Defining_Identifier (Loc, Name_uMaster),
6485 Parameter_Type => New_Reference_To (RTE (RE_Master_Id), Loc)));
6487 Append_To (Formals,
6488 Make_Parameter_Specification (Loc,
6489 Defining_Identifier =>
6490 Make_Defining_Identifier (Loc, Name_uChain),
6491 In_Present => True,
6492 Out_Present => True,
6493 Parameter_Type =>
6494 New_Reference_To (RTE (RE_Activation_Chain), Loc)));
6496 Append_To (Formals,
6497 Make_Parameter_Specification (Loc,
6498 Defining_Identifier =>
6499 Make_Defining_Identifier (Loc, Name_uTask_Name),
6500 In_Present => True,
6501 Parameter_Type =>
6502 New_Reference_To (Standard_String, Loc)));
6503 end if;
6505 return Formals;
6507 exception
6508 when RE_Not_Available =>
6509 return Empty_List;
6510 end Init_Formals;
6512 -------------------------
6513 -- Init_Secondary_Tags --
6514 -------------------------
6516 procedure Init_Secondary_Tags
6517 (Typ : Entity_Id;
6518 Target : Node_Id;
6519 Stmts_List : List_Id;
6520 Fixed_Comps : Boolean := True;
6521 Variable_Comps : Boolean := True)
6523 Loc : constant Source_Ptr := Sloc (Target);
6525 procedure Inherit_CPP_Tag
6526 (Typ : Entity_Id;
6527 Iface : Entity_Id;
6528 Tag_Comp : Entity_Id;
6529 Iface_Tag : Node_Id);
6530 -- Inherit the C++ tag of the secondary dispatch table of Typ associated
6531 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
6533 procedure Initialize_Tag
6534 (Typ : Entity_Id;
6535 Iface : Entity_Id;
6536 Tag_Comp : Entity_Id;
6537 Iface_Tag : Node_Id);
6538 -- Initialize the tag of the secondary dispatch table of Typ associated
6539 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
6540 -- Compiling under the CPP full ABI compatibility mode, if the ancestor
6541 -- of Typ CPP tagged type we generate code to inherit the contents of
6542 -- the dispatch table directly from the ancestor.
6544 ---------------------
6545 -- Inherit_CPP_Tag --
6546 ---------------------
6548 procedure Inherit_CPP_Tag
6549 (Typ : Entity_Id;
6550 Iface : Entity_Id;
6551 Tag_Comp : Entity_Id;
6552 Iface_Tag : Node_Id)
6554 begin
6555 pragma Assert (Is_CPP_Class (Etype (Typ)));
6557 Append_To (Stmts_List,
6558 Build_Inherit_Prims (Loc,
6559 Typ => Iface,
6560 Old_Tag_Node =>
6561 Make_Selected_Component (Loc,
6562 Prefix => New_Copy_Tree (Target),
6563 Selector_Name => New_Reference_To (Tag_Comp, Loc)),
6564 New_Tag_Node =>
6565 New_Reference_To (Iface_Tag, Loc),
6566 Num_Prims =>
6567 UI_To_Int (DT_Entry_Count (First_Tag_Component (Iface)))));
6568 end Inherit_CPP_Tag;
6570 --------------------
6571 -- Initialize_Tag --
6572 --------------------
6574 procedure Initialize_Tag
6575 (Typ : Entity_Id;
6576 Iface : Entity_Id;
6577 Tag_Comp : Entity_Id;
6578 Iface_Tag : Node_Id)
6580 Comp_Typ : Entity_Id;
6581 Offset_To_Top_Comp : Entity_Id := Empty;
6583 begin
6584 -- Initialize the pointer to the secondary DT associated with the
6585 -- interface.
6587 if not Is_Parent (Iface, Typ) then
6588 Append_To (Stmts_List,
6589 Make_Assignment_Statement (Loc,
6590 Name =>
6591 Make_Selected_Component (Loc,
6592 Prefix => New_Copy_Tree (Target),
6593 Selector_Name => New_Reference_To (Tag_Comp, Loc)),
6594 Expression =>
6595 New_Reference_To (Iface_Tag, Loc)));
6596 end if;
6598 -- Issue error if Set_Offset_To_Top is not available in a
6599 -- configurable run-time environment.
6601 if not RTE_Available (RE_Set_Offset_To_Top) then
6602 Error_Msg_CRT ("abstract interface types", Typ);
6603 return;
6604 end if;
6606 Comp_Typ := Scope (Tag_Comp);
6608 -- Initialize the entries of the table of interfaces. We generate a
6609 -- different call when the parent of the type has variable size
6610 -- components.
6612 if Comp_Typ /= Etype (Comp_Typ)
6613 and then Is_Variable_Size_Record (Etype (Comp_Typ))
6614 and then Chars (Tag_Comp) /= Name_uTag
6615 then
6616 pragma Assert
6617 (Present (DT_Offset_To_Top_Func (Tag_Comp)));
6619 -- Generate:
6620 -- Set_Offset_To_Top
6621 -- (This => Init,
6622 -- Interface_T => Iface'Tag,
6623 -- Is_Constant => False,
6624 -- Offset_Value => n,
6625 -- Offset_Func => Fn'Address)
6627 Append_To (Stmts_List,
6628 Make_Procedure_Call_Statement (Loc,
6629 Name => New_Reference_To (RTE (RE_Set_Offset_To_Top), Loc),
6630 Parameter_Associations => New_List (
6631 Make_Attribute_Reference (Loc,
6632 Prefix => New_Copy_Tree (Target),
6633 Attribute_Name => Name_Address),
6635 Unchecked_Convert_To (RTE (RE_Tag),
6636 New_Reference_To
6637 (Node (First_Elmt (Access_Disp_Table (Iface))),
6638 Loc)),
6640 New_Occurrence_Of (Standard_False, Loc),
6642 Unchecked_Convert_To
6643 (RTE (RE_Storage_Offset),
6644 Make_Attribute_Reference (Loc,
6645 Prefix =>
6646 Make_Selected_Component (Loc,
6647 Prefix => New_Copy_Tree (Target),
6648 Selector_Name =>
6649 New_Reference_To (Tag_Comp, Loc)),
6650 Attribute_Name => Name_Position)),
6652 Unchecked_Convert_To (RTE (RE_Offset_To_Top_Function_Ptr),
6653 Make_Attribute_Reference (Loc,
6654 Prefix => New_Reference_To
6655 (DT_Offset_To_Top_Func (Tag_Comp), Loc),
6656 Attribute_Name => Name_Address)))));
6658 -- In this case the next component stores the value of the
6659 -- offset to the top.
6661 Offset_To_Top_Comp := Next_Entity (Tag_Comp);
6662 pragma Assert (Present (Offset_To_Top_Comp));
6664 Append_To (Stmts_List,
6665 Make_Assignment_Statement (Loc,
6666 Name =>
6667 Make_Selected_Component (Loc,
6668 Prefix => New_Copy_Tree (Target),
6669 Selector_Name => New_Reference_To
6670 (Offset_To_Top_Comp, Loc)),
6671 Expression =>
6672 Make_Attribute_Reference (Loc,
6673 Prefix =>
6674 Make_Selected_Component (Loc,
6675 Prefix => New_Copy_Tree (Target),
6676 Selector_Name =>
6677 New_Reference_To (Tag_Comp, Loc)),
6678 Attribute_Name => Name_Position)));
6680 -- Normal case: No discriminants in the parent type
6682 else
6683 -- Generate:
6684 -- Set_Offset_To_Top
6685 -- (This => Init,
6686 -- Interface_T => Iface'Tag,
6687 -- Is_Constant => True,
6688 -- Offset_Value => n,
6689 -- Offset_Func => null);
6691 Append_To (Stmts_List,
6692 Make_Procedure_Call_Statement (Loc,
6693 Name => New_Reference_To
6694 (RTE (RE_Set_Offset_To_Top), Loc),
6695 Parameter_Associations => New_List (
6696 Make_Attribute_Reference (Loc,
6697 Prefix => New_Copy_Tree (Target),
6698 Attribute_Name => Name_Address),
6700 Unchecked_Convert_To (RTE (RE_Tag),
6701 New_Reference_To
6702 (Node (First_Elmt
6703 (Access_Disp_Table (Iface))),
6704 Loc)),
6706 New_Occurrence_Of (Standard_True, Loc),
6708 Unchecked_Convert_To
6709 (RTE (RE_Storage_Offset),
6710 Make_Attribute_Reference (Loc,
6711 Prefix =>
6712 Make_Selected_Component (Loc,
6713 Prefix => New_Copy_Tree (Target),
6714 Selector_Name =>
6715 New_Reference_To (Tag_Comp, Loc)),
6716 Attribute_Name => Name_Position)),
6718 Make_Null (Loc))));
6719 end if;
6720 end Initialize_Tag;
6722 -- Local variables
6724 Full_Typ : Entity_Id;
6725 Ifaces_List : Elist_Id;
6726 Ifaces_Comp_List : Elist_Id;
6727 Ifaces_Tag_List : Elist_Id;
6728 Iface_Elmt : Elmt_Id;
6729 Iface_Comp_Elmt : Elmt_Id;
6730 Iface_Tag_Elmt : Elmt_Id;
6731 Tag_Comp : Node_Id;
6732 In_Variable_Pos : Boolean;
6734 -- Start of processing for Init_Secondary_Tags
6736 begin
6737 -- Handle private types
6739 if Present (Full_View (Typ)) then
6740 Full_Typ := Full_View (Typ);
6741 else
6742 Full_Typ := Typ;
6743 end if;
6745 Collect_Interfaces_Info
6746 (Full_Typ, Ifaces_List, Ifaces_Comp_List, Ifaces_Tag_List);
6748 Iface_Elmt := First_Elmt (Ifaces_List);
6749 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
6750 Iface_Tag_Elmt := First_Elmt (Ifaces_Tag_List);
6751 while Present (Iface_Elmt) loop
6752 Tag_Comp := Node (Iface_Comp_Elmt);
6754 -- If we are compiling under the CPP full ABI compatibility mode and
6755 -- the ancestor is a CPP_Pragma tagged type then we generate code to
6756 -- inherit the contents of the dispatch table directly from the
6757 -- ancestor.
6759 if Is_CPP_Class (Etype (Full_Typ)) then
6760 Inherit_CPP_Tag (Full_Typ,
6761 Iface => Node (Iface_Elmt),
6762 Tag_Comp => Tag_Comp,
6763 Iface_Tag => Node (Iface_Tag_Elmt));
6765 -- Otherwise we generate code to initialize the tag
6767 else
6768 -- Check if the parent of the record type has variable size
6769 -- components.
6771 In_Variable_Pos := Scope (Tag_Comp) /= Etype (Scope (Tag_Comp))
6772 and then Is_Variable_Size_Record (Etype (Scope (Tag_Comp)));
6774 if (In_Variable_Pos and then Variable_Comps)
6775 or else (not In_Variable_Pos and then Fixed_Comps)
6776 then
6777 Initialize_Tag (Full_Typ,
6778 Iface => Node (Iface_Elmt),
6779 Tag_Comp => Tag_Comp,
6780 Iface_Tag => Node (Iface_Tag_Elmt));
6781 end if;
6782 end if;
6784 Next_Elmt (Iface_Elmt);
6785 Next_Elmt (Iface_Comp_Elmt);
6786 Next_Elmt (Iface_Tag_Elmt);
6787 end loop;
6788 end Init_Secondary_Tags;
6790 -----------------------------
6791 -- Is_Variable_Size_Record --
6792 -----------------------------
6794 function Is_Variable_Size_Record (E : Entity_Id) return Boolean is
6795 Comp : Entity_Id;
6796 Comp_Typ : Entity_Id;
6797 Idx : Node_Id;
6799 begin
6800 pragma Assert (Is_Record_Type (E));
6802 Comp := First_Entity (E);
6803 while Present (Comp) loop
6804 Comp_Typ := Etype (Comp);
6806 if Is_Record_Type (Comp_Typ) then
6808 -- Recursive call if the record type has discriminants
6810 if Has_Discriminants (Comp_Typ)
6811 and then Is_Variable_Size_Record (Comp_Typ)
6812 then
6813 return True;
6814 end if;
6816 elsif Is_Array_Type (Comp_Typ) then
6818 -- Check if some index is initialized with a non-constant value
6820 Idx := First_Index (Comp_Typ);
6821 while Present (Idx) loop
6822 if Nkind (Idx) = N_Range then
6823 if (Nkind (Low_Bound (Idx)) = N_Identifier
6824 and then Present (Entity (Low_Bound (Idx)))
6825 and then Ekind (Entity (Low_Bound (Idx))) /= E_Constant)
6826 or else
6827 (Nkind (High_Bound (Idx)) = N_Identifier
6828 and then Present (Entity (High_Bound (Idx)))
6829 and then Ekind (Entity (High_Bound (Idx))) /= E_Constant)
6830 then
6831 return True;
6832 end if;
6833 end if;
6835 Idx := Next_Index (Idx);
6836 end loop;
6837 end if;
6839 Next_Entity (Comp);
6840 end loop;
6842 return False;
6843 end Is_Variable_Size_Record;
6845 ----------------------------------------
6846 -- Make_Controlling_Function_Wrappers --
6847 ----------------------------------------
6849 procedure Make_Controlling_Function_Wrappers
6850 (Tag_Typ : Entity_Id;
6851 Decl_List : out List_Id;
6852 Body_List : out List_Id)
6854 Loc : constant Source_Ptr := Sloc (Tag_Typ);
6855 Prim_Elmt : Elmt_Id;
6856 Subp : Entity_Id;
6857 Actual_List : List_Id;
6858 Formal_List : List_Id;
6859 Formal : Entity_Id;
6860 Par_Formal : Entity_Id;
6861 Formal_Node : Node_Id;
6862 Func_Body : Node_Id;
6863 Func_Decl : Node_Id;
6864 Func_Spec : Node_Id;
6865 Return_Stmt : Node_Id;
6867 begin
6868 Decl_List := New_List;
6869 Body_List := New_List;
6871 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
6873 while Present (Prim_Elmt) loop
6874 Subp := Node (Prim_Elmt);
6876 -- If a primitive function with a controlling result of the type has
6877 -- not been overridden by the user, then we must create a wrapper
6878 -- function here that effectively overrides it and invokes the
6879 -- (non-abstract) parent function. This can only occur for a null
6880 -- extension. Note that functions with anonymous controlling access
6881 -- results don't qualify and must be overridden. We also exclude
6882 -- Input attributes, since each type will have its own version of
6883 -- Input constructed by the expander. The test for Comes_From_Source
6884 -- is needed to distinguish inherited operations from renamings
6885 -- (which also have Alias set).
6887 -- The function may be abstract, or require_Overriding may be set
6888 -- for it, because tests for null extensions may already have reset
6889 -- the Is_Abstract_Subprogram_Flag. If Requires_Overriding is not
6890 -- set, functions that need wrappers are recognized by having an
6891 -- alias that returns the parent type.
6893 if Comes_From_Source (Subp)
6894 or else No (Alias (Subp))
6895 or else Ekind (Subp) /= E_Function
6896 or else not Has_Controlling_Result (Subp)
6897 or else Is_Access_Type (Etype (Subp))
6898 or else Is_Abstract_Subprogram (Alias (Subp))
6899 or else Is_TSS (Subp, TSS_Stream_Input)
6900 then
6901 goto Next_Prim;
6903 elsif Is_Abstract_Subprogram (Subp)
6904 or else Requires_Overriding (Subp)
6905 or else
6906 (Is_Null_Extension (Etype (Subp))
6907 and then Etype (Alias (Subp)) /= Etype (Subp))
6908 then
6909 Formal_List := No_List;
6910 Formal := First_Formal (Subp);
6912 if Present (Formal) then
6913 Formal_List := New_List;
6915 while Present (Formal) loop
6916 Append
6917 (Make_Parameter_Specification
6918 (Loc,
6919 Defining_Identifier =>
6920 Make_Defining_Identifier (Sloc (Formal),
6921 Chars => Chars (Formal)),
6922 In_Present => In_Present (Parent (Formal)),
6923 Out_Present => Out_Present (Parent (Formal)),
6924 Null_Exclusion_Present =>
6925 Null_Exclusion_Present (Parent (Formal)),
6926 Parameter_Type =>
6927 New_Reference_To (Etype (Formal), Loc),
6928 Expression =>
6929 New_Copy_Tree (Expression (Parent (Formal)))),
6930 Formal_List);
6932 Next_Formal (Formal);
6933 end loop;
6934 end if;
6936 Func_Spec :=
6937 Make_Function_Specification (Loc,
6938 Defining_Unit_Name =>
6939 Make_Defining_Identifier (Loc,
6940 Chars => Chars (Subp)),
6941 Parameter_Specifications => Formal_List,
6942 Result_Definition =>
6943 New_Reference_To (Etype (Subp), Loc));
6945 Func_Decl := Make_Subprogram_Declaration (Loc, Func_Spec);
6946 Append_To (Decl_List, Func_Decl);
6948 -- Build a wrapper body that calls the parent function. The body
6949 -- contains a single return statement that returns an extension
6950 -- aggregate whose ancestor part is a call to the parent function,
6951 -- passing the formals as actuals (with any controlling arguments
6952 -- converted to the types of the corresponding formals of the
6953 -- parent function, which might be anonymous access types), and
6954 -- having a null extension.
6956 Formal := First_Formal (Subp);
6957 Par_Formal := First_Formal (Alias (Subp));
6958 Formal_Node := First (Formal_List);
6960 if Present (Formal) then
6961 Actual_List := New_List;
6962 else
6963 Actual_List := No_List;
6964 end if;
6966 while Present (Formal) loop
6967 if Is_Controlling_Formal (Formal) then
6968 Append_To (Actual_List,
6969 Make_Type_Conversion (Loc,
6970 Subtype_Mark =>
6971 New_Occurrence_Of (Etype (Par_Formal), Loc),
6972 Expression =>
6973 New_Reference_To
6974 (Defining_Identifier (Formal_Node), Loc)));
6975 else
6976 Append_To
6977 (Actual_List,
6978 New_Reference_To
6979 (Defining_Identifier (Formal_Node), Loc));
6980 end if;
6982 Next_Formal (Formal);
6983 Next_Formal (Par_Formal);
6984 Next (Formal_Node);
6985 end loop;
6987 Return_Stmt :=
6988 Make_Simple_Return_Statement (Loc,
6989 Expression =>
6990 Make_Extension_Aggregate (Loc,
6991 Ancestor_Part =>
6992 Make_Function_Call (Loc,
6993 Name => New_Reference_To (Alias (Subp), Loc),
6994 Parameter_Associations => Actual_List),
6995 Null_Record_Present => True));
6997 Func_Body :=
6998 Make_Subprogram_Body (Loc,
6999 Specification => New_Copy_Tree (Func_Spec),
7000 Declarations => Empty_List,
7001 Handled_Statement_Sequence =>
7002 Make_Handled_Sequence_Of_Statements (Loc,
7003 Statements => New_List (Return_Stmt)));
7005 Set_Defining_Unit_Name
7006 (Specification (Func_Body),
7007 Make_Defining_Identifier (Loc, Chars (Subp)));
7009 Append_To (Body_List, Func_Body);
7011 -- Replace the inherited function with the wrapper function
7012 -- in the primitive operations list.
7014 Override_Dispatching_Operation
7015 (Tag_Typ, Subp, New_Op => Defining_Unit_Name (Func_Spec));
7016 end if;
7018 <<Next_Prim>>
7019 Next_Elmt (Prim_Elmt);
7020 end loop;
7021 end Make_Controlling_Function_Wrappers;
7023 ------------------
7024 -- Make_Eq_Case --
7025 ------------------
7027 -- <Make_Eq_if shared components>
7028 -- case X.D1 is
7029 -- when V1 => <Make_Eq_Case> on subcomponents
7030 -- ...
7031 -- when Vn => <Make_Eq_Case> on subcomponents
7032 -- end case;
7034 function Make_Eq_Case
7035 (E : Entity_Id;
7036 CL : Node_Id;
7037 Discr : Entity_Id := Empty) return List_Id
7039 Loc : constant Source_Ptr := Sloc (E);
7040 Result : constant List_Id := New_List;
7041 Variant : Node_Id;
7042 Alt_List : List_Id;
7044 begin
7045 Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
7047 if No (Variant_Part (CL)) then
7048 return Result;
7049 end if;
7051 Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
7053 if No (Variant) then
7054 return Result;
7055 end if;
7057 Alt_List := New_List;
7059 while Present (Variant) loop
7060 Append_To (Alt_List,
7061 Make_Case_Statement_Alternative (Loc,
7062 Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
7063 Statements => Make_Eq_Case (E, Component_List (Variant))));
7065 Next_Non_Pragma (Variant);
7066 end loop;
7068 -- If we have an Unchecked_Union, use one of the parameters that
7069 -- captures the discriminants.
7071 if Is_Unchecked_Union (E) then
7072 Append_To (Result,
7073 Make_Case_Statement (Loc,
7074 Expression => New_Reference_To (Discr, Loc),
7075 Alternatives => Alt_List));
7077 else
7078 Append_To (Result,
7079 Make_Case_Statement (Loc,
7080 Expression =>
7081 Make_Selected_Component (Loc,
7082 Prefix => Make_Identifier (Loc, Name_X),
7083 Selector_Name => New_Copy (Name (Variant_Part (CL)))),
7084 Alternatives => Alt_List));
7085 end if;
7087 return Result;
7088 end Make_Eq_Case;
7090 ----------------
7091 -- Make_Eq_If --
7092 ----------------
7094 -- Generates:
7096 -- if
7097 -- X.C1 /= Y.C1
7098 -- or else
7099 -- X.C2 /= Y.C2
7100 -- ...
7101 -- then
7102 -- return False;
7103 -- end if;
7105 -- or a null statement if the list L is empty
7107 function Make_Eq_If
7108 (E : Entity_Id;
7109 L : List_Id) return Node_Id
7111 Loc : constant Source_Ptr := Sloc (E);
7112 C : Node_Id;
7113 Field_Name : Name_Id;
7114 Cond : Node_Id;
7116 begin
7117 if No (L) then
7118 return Make_Null_Statement (Loc);
7120 else
7121 Cond := Empty;
7123 C := First_Non_Pragma (L);
7124 while Present (C) loop
7125 Field_Name := Chars (Defining_Identifier (C));
7127 -- The tags must not be compared: they are not part of the value.
7128 -- Ditto for the controller component, if present.
7130 -- Note also that in the following, we use Make_Identifier for
7131 -- the component names. Use of New_Reference_To to identify the
7132 -- components would be incorrect because the wrong entities for
7133 -- discriminants could be picked up in the private type case.
7135 if Field_Name /= Name_uTag
7136 and then
7137 Field_Name /= Name_uController
7138 then
7139 Evolve_Or_Else (Cond,
7140 Make_Op_Ne (Loc,
7141 Left_Opnd =>
7142 Make_Selected_Component (Loc,
7143 Prefix => Make_Identifier (Loc, Name_X),
7144 Selector_Name =>
7145 Make_Identifier (Loc, Field_Name)),
7147 Right_Opnd =>
7148 Make_Selected_Component (Loc,
7149 Prefix => Make_Identifier (Loc, Name_Y),
7150 Selector_Name =>
7151 Make_Identifier (Loc, Field_Name))));
7152 end if;
7154 Next_Non_Pragma (C);
7155 end loop;
7157 if No (Cond) then
7158 return Make_Null_Statement (Loc);
7160 else
7161 return
7162 Make_Implicit_If_Statement (E,
7163 Condition => Cond,
7164 Then_Statements => New_List (
7165 Make_Simple_Return_Statement (Loc,
7166 Expression => New_Occurrence_Of (Standard_False, Loc))));
7167 end if;
7168 end if;
7169 end Make_Eq_If;
7171 -------------------------------
7172 -- Make_Null_Procedure_Specs --
7173 -------------------------------
7175 procedure Make_Null_Procedure_Specs
7176 (Tag_Typ : Entity_Id;
7177 Decl_List : out List_Id)
7179 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7180 Formal : Entity_Id;
7181 Formal_List : List_Id;
7182 Parent_Subp : Entity_Id;
7183 Prim_Elmt : Elmt_Id;
7184 Proc_Spec : Node_Id;
7185 Proc_Decl : Node_Id;
7186 Subp : Entity_Id;
7188 function Is_Null_Interface_Primitive (E : Entity_Id) return Boolean;
7189 -- Returns True if E is a null procedure that is an interface primitive
7191 ---------------------------------
7192 -- Is_Null_Interface_Primitive --
7193 ---------------------------------
7195 function Is_Null_Interface_Primitive (E : Entity_Id) return Boolean is
7196 begin
7197 return Comes_From_Source (E)
7198 and then Is_Dispatching_Operation (E)
7199 and then Ekind (E) = E_Procedure
7200 and then Null_Present (Parent (E))
7201 and then Is_Interface (Find_Dispatching_Type (E));
7202 end Is_Null_Interface_Primitive;
7204 -- Start of processing for Make_Null_Procedure_Specs
7206 begin
7207 Decl_List := New_List;
7208 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7209 while Present (Prim_Elmt) loop
7210 Subp := Node (Prim_Elmt);
7212 -- If a null procedure inherited from an interface has not been
7213 -- overridden, then we build a null procedure declaration to
7214 -- override the inherited procedure.
7216 Parent_Subp := Alias (Subp);
7218 if Present (Parent_Subp)
7219 and then Is_Null_Interface_Primitive (Parent_Subp)
7220 then
7221 Formal_List := No_List;
7222 Formal := First_Formal (Subp);
7224 if Present (Formal) then
7225 Formal_List := New_List;
7227 while Present (Formal) loop
7228 Append
7229 (Make_Parameter_Specification (Loc,
7230 Defining_Identifier =>
7231 Make_Defining_Identifier (Sloc (Formal),
7232 Chars => Chars (Formal)),
7233 In_Present => In_Present (Parent (Formal)),
7234 Out_Present => Out_Present (Parent (Formal)),
7235 Null_Exclusion_Present =>
7236 Null_Exclusion_Present (Parent (Formal)),
7237 Parameter_Type =>
7238 New_Reference_To (Etype (Formal), Loc),
7239 Expression =>
7240 New_Copy_Tree (Expression (Parent (Formal)))),
7241 Formal_List);
7243 Next_Formal (Formal);
7244 end loop;
7245 end if;
7247 Proc_Spec :=
7248 Make_Procedure_Specification (Loc,
7249 Defining_Unit_Name =>
7250 Make_Defining_Identifier (Loc, Chars (Subp)),
7251 Parameter_Specifications => Formal_List);
7252 Set_Null_Present (Proc_Spec);
7254 Proc_Decl := Make_Subprogram_Declaration (Loc, Proc_Spec);
7255 Append_To (Decl_List, Proc_Decl);
7256 Analyze (Proc_Decl);
7257 end if;
7259 Next_Elmt (Prim_Elmt);
7260 end loop;
7261 end Make_Null_Procedure_Specs;
7263 -------------------------------------
7264 -- Make_Predefined_Primitive_Specs --
7265 -------------------------------------
7267 procedure Make_Predefined_Primitive_Specs
7268 (Tag_Typ : Entity_Id;
7269 Predef_List : out List_Id;
7270 Renamed_Eq : out Node_Id)
7272 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7273 Res : constant List_Id := New_List;
7274 Prim : Elmt_Id;
7275 Eq_Needed : Boolean;
7276 Eq_Spec : Node_Id;
7277 Eq_Name : Name_Id := Name_Op_Eq;
7279 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
7280 -- Returns true if Prim is a renaming of an unresolved predefined
7281 -- equality operation.
7283 -------------------------------
7284 -- Is_Predefined_Eq_Renaming --
7285 -------------------------------
7287 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
7288 begin
7289 return Chars (Prim) /= Name_Op_Eq
7290 and then Present (Alias (Prim))
7291 and then Comes_From_Source (Prim)
7292 and then Is_Intrinsic_Subprogram (Alias (Prim))
7293 and then Chars (Alias (Prim)) = Name_Op_Eq;
7294 end Is_Predefined_Eq_Renaming;
7296 -- Start of processing for Make_Predefined_Primitive_Specs
7298 begin
7299 Renamed_Eq := Empty;
7301 -- Spec of _Size
7303 Append_To (Res, Predef_Spec_Or_Body (Loc,
7304 Tag_Typ => Tag_Typ,
7305 Name => Name_uSize,
7306 Profile => New_List (
7307 Make_Parameter_Specification (Loc,
7308 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7309 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7311 Ret_Type => Standard_Long_Long_Integer));
7313 -- Spec of _Alignment
7315 Append_To (Res, Predef_Spec_Or_Body (Loc,
7316 Tag_Typ => Tag_Typ,
7317 Name => Name_uAlignment,
7318 Profile => New_List (
7319 Make_Parameter_Specification (Loc,
7320 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7321 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7323 Ret_Type => Standard_Integer));
7325 -- Specs for dispatching stream attributes
7327 declare
7328 Stream_Op_TSS_Names :
7329 constant array (Integer range <>) of TSS_Name_Type :=
7330 (TSS_Stream_Read,
7331 TSS_Stream_Write,
7332 TSS_Stream_Input,
7333 TSS_Stream_Output);
7335 begin
7336 for Op in Stream_Op_TSS_Names'Range loop
7337 if Stream_Operation_OK (Tag_Typ, Stream_Op_TSS_Names (Op)) then
7338 Append_To (Res,
7339 Predef_Stream_Attr_Spec (Loc, Tag_Typ,
7340 Stream_Op_TSS_Names (Op)));
7341 end if;
7342 end loop;
7343 end;
7345 -- Spec of "=" if expanded if the type is not limited and if a
7346 -- user defined "=" was not already declared for the non-full
7347 -- view of a private extension
7349 if not Is_Limited_Type (Tag_Typ) then
7350 Eq_Needed := True;
7352 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
7353 while Present (Prim) loop
7355 -- If a primitive is encountered that renames the predefined
7356 -- equality operator before reaching any explicit equality
7357 -- primitive, then we still need to create a predefined
7358 -- equality function, because calls to it can occur via
7359 -- the renaming. A new name is created for the equality
7360 -- to avoid conflicting with any user-defined equality.
7361 -- (Note that this doesn't account for renamings of
7362 -- equality nested within subpackages???)
7364 if Is_Predefined_Eq_Renaming (Node (Prim)) then
7365 Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
7367 elsif Chars (Node (Prim)) = Name_Op_Eq
7368 and then (No (Alias (Node (Prim)))
7369 or else Nkind (Unit_Declaration_Node (Node (Prim))) =
7370 N_Subprogram_Renaming_Declaration)
7371 and then Etype (First_Formal (Node (Prim))) =
7372 Etype (Next_Formal (First_Formal (Node (Prim))))
7373 and then Base_Type (Etype (Node (Prim))) = Standard_Boolean
7375 then
7376 Eq_Needed := False;
7377 exit;
7379 -- If the parent equality is abstract, the inherited equality is
7380 -- abstract as well, and no body can be created for for it.
7382 elsif Chars (Node (Prim)) = Name_Op_Eq
7383 and then Present (Alias (Node (Prim)))
7384 and then Is_Abstract_Subprogram (Alias (Node (Prim)))
7385 then
7386 Eq_Needed := False;
7387 exit;
7388 end if;
7390 Next_Elmt (Prim);
7391 end loop;
7393 -- If a renaming of predefined equality was found but there was no
7394 -- user-defined equality (so Eq_Needed is still true), then set the
7395 -- name back to Name_Op_Eq. But in the case where a user-defined
7396 -- equality was located after such a renaming, then the predefined
7397 -- equality function is still needed, so Eq_Needed must be set back
7398 -- to True.
7400 if Eq_Name /= Name_Op_Eq then
7401 if Eq_Needed then
7402 Eq_Name := Name_Op_Eq;
7403 else
7404 Eq_Needed := True;
7405 end if;
7406 end if;
7408 if Eq_Needed then
7409 Eq_Spec := Predef_Spec_Or_Body (Loc,
7410 Tag_Typ => Tag_Typ,
7411 Name => Eq_Name,
7412 Profile => New_List (
7413 Make_Parameter_Specification (Loc,
7414 Defining_Identifier =>
7415 Make_Defining_Identifier (Loc, Name_X),
7416 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
7417 Make_Parameter_Specification (Loc,
7418 Defining_Identifier =>
7419 Make_Defining_Identifier (Loc, Name_Y),
7420 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7421 Ret_Type => Standard_Boolean);
7422 Append_To (Res, Eq_Spec);
7424 if Eq_Name /= Name_Op_Eq then
7425 Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
7427 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
7428 while Present (Prim) loop
7430 -- Any renamings of equality that appeared before an
7431 -- overriding equality must be updated to refer to the
7432 -- entity for the predefined equality, otherwise calls via
7433 -- the renaming would get incorrectly resolved to call the
7434 -- user-defined equality function.
7436 if Is_Predefined_Eq_Renaming (Node (Prim)) then
7437 Set_Alias (Node (Prim), Renamed_Eq);
7439 -- Exit upon encountering a user-defined equality
7441 elsif Chars (Node (Prim)) = Name_Op_Eq
7442 and then No (Alias (Node (Prim)))
7443 then
7444 exit;
7445 end if;
7447 Next_Elmt (Prim);
7448 end loop;
7449 end if;
7450 end if;
7452 -- Spec for dispatching assignment
7454 Append_To (Res, Predef_Spec_Or_Body (Loc,
7455 Tag_Typ => Tag_Typ,
7456 Name => Name_uAssign,
7457 Profile => New_List (
7458 Make_Parameter_Specification (Loc,
7459 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7460 Out_Present => True,
7461 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
7463 Make_Parameter_Specification (Loc,
7464 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
7465 Parameter_Type => New_Reference_To (Tag_Typ, Loc)))));
7466 end if;
7468 -- Ada 2005: Generate declarations for the following primitive
7469 -- operations for limited interfaces and synchronized types that
7470 -- implement a limited interface.
7472 -- disp_asynchronous_select
7473 -- disp_conditional_select
7474 -- disp_get_prim_op_kind
7475 -- disp_get_task_id
7476 -- disp_timed_select
7478 -- These operations cannot be implemented on VM targets, so we simply
7479 -- disable their generation in this case. We also disable generation
7480 -- of these bodies if No_Dispatching_Calls is active.
7482 if Ada_Version >= Ada_05
7483 and then VM_Target = No_VM
7484 and then
7485 ((Is_Interface (Tag_Typ) and then Is_Limited_Record (Tag_Typ))
7486 or else (Is_Concurrent_Record_Type (Tag_Typ)
7487 and then Has_Abstract_Interfaces (Tag_Typ)))
7488 then
7489 Append_To (Res,
7490 Make_Subprogram_Declaration (Loc,
7491 Specification =>
7492 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
7494 Append_To (Res,
7495 Make_Subprogram_Declaration (Loc,
7496 Specification =>
7497 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
7499 Append_To (Res,
7500 Make_Subprogram_Declaration (Loc,
7501 Specification =>
7502 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
7504 Append_To (Res,
7505 Make_Subprogram_Declaration (Loc,
7506 Specification =>
7507 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
7509 Append_To (Res,
7510 Make_Subprogram_Declaration (Loc,
7511 Specification =>
7512 Make_Disp_Timed_Select_Spec (Tag_Typ)));
7513 end if;
7515 -- Specs for finalization actions that may be required in case a future
7516 -- extension contain a controlled element. We generate those only for
7517 -- root tagged types where they will get dummy bodies or when the type
7518 -- has controlled components and their body must be generated. It is
7519 -- also impossible to provide those for tagged types defined within
7520 -- s-finimp since it would involve circularity problems
7522 if In_Finalization_Root (Tag_Typ) then
7523 null;
7525 -- We also skip these if finalization is not available
7527 elsif Restriction_Active (No_Finalization) then
7528 null;
7530 elsif Etype (Tag_Typ) = Tag_Typ
7531 or else Controlled_Type (Tag_Typ)
7533 -- Ada 2005 (AI-251): We must also generate these subprograms if
7534 -- the immediate ancestor is an interface to ensure the correct
7535 -- initialization of its dispatch table.
7537 or else (not Is_Interface (Tag_Typ)
7538 and then
7539 Is_Interface (Etype (Tag_Typ)))
7540 then
7541 if not Is_Limited_Type (Tag_Typ) then
7542 Append_To (Res,
7543 Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
7544 end if;
7546 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
7547 end if;
7549 Predef_List := Res;
7550 end Make_Predefined_Primitive_Specs;
7552 ---------------------------------
7553 -- Needs_Simple_Initialization --
7554 ---------------------------------
7556 function Needs_Simple_Initialization (T : Entity_Id) return Boolean is
7557 begin
7558 -- Check for private type, in which case test applies to the underlying
7559 -- type of the private type.
7561 if Is_Private_Type (T) then
7562 declare
7563 RT : constant Entity_Id := Underlying_Type (T);
7565 begin
7566 if Present (RT) then
7567 return Needs_Simple_Initialization (RT);
7568 else
7569 return False;
7570 end if;
7571 end;
7573 -- Cases needing simple initialization are access types, and, if pragma
7574 -- Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
7575 -- types.
7577 elsif Is_Access_Type (T)
7578 or else (Init_Or_Norm_Scalars and then (Is_Scalar_Type (T)))
7579 then
7580 return True;
7582 -- If Initialize/Normalize_Scalars is in effect, string objects also
7583 -- need initialization, unless they are created in the course of
7584 -- expanding an aggregate (since in the latter case they will be
7585 -- filled with appropriate initializing values before they are used).
7587 elsif Init_Or_Norm_Scalars
7588 and then
7589 (Root_Type (T) = Standard_String
7590 or else Root_Type (T) = Standard_Wide_String
7591 or else Root_Type (T) = Standard_Wide_Wide_String)
7592 and then
7593 (not Is_Itype (T)
7594 or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
7595 then
7596 return True;
7598 else
7599 return False;
7600 end if;
7601 end Needs_Simple_Initialization;
7603 ----------------------
7604 -- Predef_Deep_Spec --
7605 ----------------------
7607 function Predef_Deep_Spec
7608 (Loc : Source_Ptr;
7609 Tag_Typ : Entity_Id;
7610 Name : TSS_Name_Type;
7611 For_Body : Boolean := False) return Node_Id
7613 Prof : List_Id;
7614 Type_B : Entity_Id;
7616 begin
7617 if Name = TSS_Deep_Finalize then
7618 Prof := New_List;
7619 Type_B := Standard_Boolean;
7621 else
7622 Prof := New_List (
7623 Make_Parameter_Specification (Loc,
7624 Defining_Identifier => Make_Defining_Identifier (Loc, Name_L),
7625 In_Present => True,
7626 Out_Present => True,
7627 Parameter_Type =>
7628 New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
7629 Type_B := Standard_Short_Short_Integer;
7630 end if;
7632 Append_To (Prof,
7633 Make_Parameter_Specification (Loc,
7634 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
7635 In_Present => True,
7636 Out_Present => True,
7637 Parameter_Type => New_Reference_To (Tag_Typ, Loc)));
7639 Append_To (Prof,
7640 Make_Parameter_Specification (Loc,
7641 Defining_Identifier => Make_Defining_Identifier (Loc, Name_B),
7642 Parameter_Type => New_Reference_To (Type_B, Loc)));
7644 return Predef_Spec_Or_Body (Loc,
7645 Name => Make_TSS_Name (Tag_Typ, Name),
7646 Tag_Typ => Tag_Typ,
7647 Profile => Prof,
7648 For_Body => For_Body);
7650 exception
7651 when RE_Not_Available =>
7652 return Empty;
7653 end Predef_Deep_Spec;
7655 -------------------------
7656 -- Predef_Spec_Or_Body --
7657 -------------------------
7659 function Predef_Spec_Or_Body
7660 (Loc : Source_Ptr;
7661 Tag_Typ : Entity_Id;
7662 Name : Name_Id;
7663 Profile : List_Id;
7664 Ret_Type : Entity_Id := Empty;
7665 For_Body : Boolean := False) return Node_Id
7667 Id : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
7668 Spec : Node_Id;
7670 begin
7671 Set_Is_Public (Id, Is_Public (Tag_Typ));
7673 -- The internal flag is set to mark these declarations because they have
7674 -- specific properties. First, they are primitives even if they are not
7675 -- defined in the type scope (the freezing point is not necessarily in
7676 -- the same scope). Second, the predefined equality can be overridden by
7677 -- a user-defined equality, no body will be generated in this case.
7679 Set_Is_Internal (Id);
7681 if not Debug_Generated_Code then
7682 Set_Debug_Info_Off (Id);
7683 end if;
7685 if No (Ret_Type) then
7686 Spec :=
7687 Make_Procedure_Specification (Loc,
7688 Defining_Unit_Name => Id,
7689 Parameter_Specifications => Profile);
7690 else
7691 Spec :=
7692 Make_Function_Specification (Loc,
7693 Defining_Unit_Name => Id,
7694 Parameter_Specifications => Profile,
7695 Result_Definition =>
7696 New_Reference_To (Ret_Type, Loc));
7697 end if;
7699 -- If body case, return empty subprogram body. Note that this is ill-
7700 -- formed, because there is not even a null statement, and certainly not
7701 -- a return in the function case. The caller is expected to do surgery
7702 -- on the body to add the appropriate stuff.
7704 if For_Body then
7705 return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
7707 -- For the case of an Input attribute predefined for an abstract type,
7708 -- generate an abstract specification. This will never be called, but we
7709 -- need the slot allocated in the dispatching table so that attributes
7710 -- typ'Class'Input and typ'Class'Output will work properly.
7712 elsif Is_TSS (Name, TSS_Stream_Input)
7713 and then Is_Abstract_Type (Tag_Typ)
7714 then
7715 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
7717 -- Normal spec case, where we return a subprogram declaration
7719 else
7720 return Make_Subprogram_Declaration (Loc, Spec);
7721 end if;
7722 end Predef_Spec_Or_Body;
7724 -----------------------------
7725 -- Predef_Stream_Attr_Spec --
7726 -----------------------------
7728 function Predef_Stream_Attr_Spec
7729 (Loc : Source_Ptr;
7730 Tag_Typ : Entity_Id;
7731 Name : TSS_Name_Type;
7732 For_Body : Boolean := False) return Node_Id
7734 Ret_Type : Entity_Id;
7736 begin
7737 if Name = TSS_Stream_Input then
7738 Ret_Type := Tag_Typ;
7739 else
7740 Ret_Type := Empty;
7741 end if;
7743 return Predef_Spec_Or_Body (Loc,
7744 Name => Make_TSS_Name (Tag_Typ, Name),
7745 Tag_Typ => Tag_Typ,
7746 Profile => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
7747 Ret_Type => Ret_Type,
7748 For_Body => For_Body);
7749 end Predef_Stream_Attr_Spec;
7751 ---------------------------------
7752 -- Predefined_Primitive_Bodies --
7753 ---------------------------------
7755 function Predefined_Primitive_Bodies
7756 (Tag_Typ : Entity_Id;
7757 Renamed_Eq : Node_Id) return List_Id
7759 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7760 Res : constant List_Id := New_List;
7761 Decl : Node_Id;
7762 Prim : Elmt_Id;
7763 Eq_Needed : Boolean;
7764 Eq_Name : Name_Id;
7765 Ent : Entity_Id;
7767 pragma Warnings (Off, Ent);
7769 begin
7770 -- See if we have a predefined "=" operator
7772 if Present (Renamed_Eq) then
7773 Eq_Needed := True;
7774 Eq_Name := Chars (Renamed_Eq);
7776 else
7777 Eq_Needed := False;
7778 Eq_Name := No_Name;
7780 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
7781 while Present (Prim) loop
7782 if Chars (Node (Prim)) = Name_Op_Eq
7783 and then Is_Internal (Node (Prim))
7784 then
7785 Eq_Needed := True;
7786 Eq_Name := Name_Op_Eq;
7787 end if;
7789 Next_Elmt (Prim);
7790 end loop;
7791 end if;
7793 -- Body of _Alignment
7795 Decl := Predef_Spec_Or_Body (Loc,
7796 Tag_Typ => Tag_Typ,
7797 Name => Name_uAlignment,
7798 Profile => New_List (
7799 Make_Parameter_Specification (Loc,
7800 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7801 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7803 Ret_Type => Standard_Integer,
7804 For_Body => True);
7806 Set_Handled_Statement_Sequence (Decl,
7807 Make_Handled_Sequence_Of_Statements (Loc, New_List (
7808 Make_Simple_Return_Statement (Loc,
7809 Expression =>
7810 Make_Attribute_Reference (Loc,
7811 Prefix => Make_Identifier (Loc, Name_X),
7812 Attribute_Name => Name_Alignment)))));
7814 Append_To (Res, Decl);
7816 -- Body of _Size
7818 Decl := Predef_Spec_Or_Body (Loc,
7819 Tag_Typ => Tag_Typ,
7820 Name => Name_uSize,
7821 Profile => New_List (
7822 Make_Parameter_Specification (Loc,
7823 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7824 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7826 Ret_Type => Standard_Long_Long_Integer,
7827 For_Body => True);
7829 Set_Handled_Statement_Sequence (Decl,
7830 Make_Handled_Sequence_Of_Statements (Loc, New_List (
7831 Make_Simple_Return_Statement (Loc,
7832 Expression =>
7833 Make_Attribute_Reference (Loc,
7834 Prefix => Make_Identifier (Loc, Name_X),
7835 Attribute_Name => Name_Size)))));
7837 Append_To (Res, Decl);
7839 -- Bodies for Dispatching stream IO routines. We need these only for
7840 -- non-limited types (in the limited case there is no dispatching).
7841 -- We also skip them if dispatching or finalization are not available.
7843 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Read)
7844 and then No (TSS (Tag_Typ, TSS_Stream_Read))
7845 then
7846 Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
7847 Append_To (Res, Decl);
7848 end if;
7850 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Write)
7851 and then No (TSS (Tag_Typ, TSS_Stream_Write))
7852 then
7853 Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
7854 Append_To (Res, Decl);
7855 end if;
7857 -- Skip body of _Input for the abstract case, since the corresponding
7858 -- spec is abstract (see Predef_Spec_Or_Body).
7860 if not Is_Abstract_Type (Tag_Typ)
7861 and then Stream_Operation_OK (Tag_Typ, TSS_Stream_Input)
7862 and then No (TSS (Tag_Typ, TSS_Stream_Input))
7863 then
7864 Build_Record_Or_Elementary_Input_Function
7865 (Loc, Tag_Typ, Decl, Ent);
7866 Append_To (Res, Decl);
7867 end if;
7869 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Output)
7870 and then No (TSS (Tag_Typ, TSS_Stream_Output))
7871 then
7872 Build_Record_Or_Elementary_Output_Procedure
7873 (Loc, Tag_Typ, Decl, Ent);
7874 Append_To (Res, Decl);
7875 end if;
7877 -- Ada 2005: Generate bodies for the following primitive operations for
7878 -- limited interfaces and synchronized types that implement a limited
7879 -- interface.
7881 -- disp_asynchronous_select
7882 -- disp_conditional_select
7883 -- disp_get_prim_op_kind
7884 -- disp_get_task_id
7885 -- disp_timed_select
7887 -- The interface versions will have null bodies
7889 -- These operations cannot be implemented on VM targets, so we simply
7890 -- disable their generation in this case. We also disable generation
7891 -- of these bodies if No_Dispatching_Calls is active.
7893 if Ada_Version >= Ada_05
7894 and then VM_Target = No_VM
7895 and then not Restriction_Active (No_Dispatching_Calls)
7896 and then
7897 ((Is_Interface (Tag_Typ) and then Is_Limited_Record (Tag_Typ))
7898 or else (Is_Concurrent_Record_Type (Tag_Typ)
7899 and then Has_Abstract_Interfaces (Tag_Typ)))
7900 then
7901 Append_To (Res, Make_Disp_Asynchronous_Select_Body (Tag_Typ));
7902 Append_To (Res, Make_Disp_Conditional_Select_Body (Tag_Typ));
7903 Append_To (Res, Make_Disp_Get_Prim_Op_Kind_Body (Tag_Typ));
7904 Append_To (Res, Make_Disp_Get_Task_Id_Body (Tag_Typ));
7905 Append_To (Res, Make_Disp_Timed_Select_Body (Tag_Typ));
7906 end if;
7908 if not Is_Limited_Type (Tag_Typ) then
7910 -- Body for equality
7912 if Eq_Needed then
7913 Decl :=
7914 Predef_Spec_Or_Body (Loc,
7915 Tag_Typ => Tag_Typ,
7916 Name => Eq_Name,
7917 Profile => New_List (
7918 Make_Parameter_Specification (Loc,
7919 Defining_Identifier =>
7920 Make_Defining_Identifier (Loc, Name_X),
7921 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
7923 Make_Parameter_Specification (Loc,
7924 Defining_Identifier =>
7925 Make_Defining_Identifier (Loc, Name_Y),
7926 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7928 Ret_Type => Standard_Boolean,
7929 For_Body => True);
7931 declare
7932 Def : constant Node_Id := Parent (Tag_Typ);
7933 Stmts : constant List_Id := New_List;
7934 Variant_Case : Boolean := Has_Discriminants (Tag_Typ);
7935 Comps : Node_Id := Empty;
7936 Typ_Def : Node_Id := Type_Definition (Def);
7938 begin
7939 if Variant_Case then
7940 if Nkind (Typ_Def) = N_Derived_Type_Definition then
7941 Typ_Def := Record_Extension_Part (Typ_Def);
7942 end if;
7944 if Present (Typ_Def) then
7945 Comps := Component_List (Typ_Def);
7946 end if;
7948 Variant_Case := Present (Comps)
7949 and then Present (Variant_Part (Comps));
7950 end if;
7952 if Variant_Case then
7953 Append_To (Stmts,
7954 Make_Eq_If (Tag_Typ, Discriminant_Specifications (Def)));
7955 Append_List_To (Stmts, Make_Eq_Case (Tag_Typ, Comps));
7956 Append_To (Stmts,
7957 Make_Simple_Return_Statement (Loc,
7958 Expression => New_Reference_To (Standard_True, Loc)));
7960 else
7961 Append_To (Stmts,
7962 Make_Simple_Return_Statement (Loc,
7963 Expression =>
7964 Expand_Record_Equality (Tag_Typ,
7965 Typ => Tag_Typ,
7966 Lhs => Make_Identifier (Loc, Name_X),
7967 Rhs => Make_Identifier (Loc, Name_Y),
7968 Bodies => Declarations (Decl))));
7969 end if;
7971 Set_Handled_Statement_Sequence (Decl,
7972 Make_Handled_Sequence_Of_Statements (Loc, Stmts));
7973 end;
7974 Append_To (Res, Decl);
7975 end if;
7977 -- Body for dispatching assignment
7979 Decl :=
7980 Predef_Spec_Or_Body (Loc,
7981 Tag_Typ => Tag_Typ,
7982 Name => Name_uAssign,
7983 Profile => New_List (
7984 Make_Parameter_Specification (Loc,
7985 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7986 Out_Present => True,
7987 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
7989 Make_Parameter_Specification (Loc,
7990 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
7991 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7992 For_Body => True);
7994 Set_Handled_Statement_Sequence (Decl,
7995 Make_Handled_Sequence_Of_Statements (Loc, New_List (
7996 Make_Assignment_Statement (Loc,
7997 Name => Make_Identifier (Loc, Name_X),
7998 Expression => Make_Identifier (Loc, Name_Y)))));
8000 Append_To (Res, Decl);
8001 end if;
8003 -- Generate dummy bodies for finalization actions of types that have
8004 -- no controlled components.
8006 -- Skip this processing if we are in the finalization routine in the
8007 -- runtime itself, otherwise we get hopelessly circularly confused!
8009 if In_Finalization_Root (Tag_Typ) then
8010 null;
8012 -- Skip this if finalization is not available
8014 elsif Restriction_Active (No_Finalization) then
8015 null;
8017 elsif (Etype (Tag_Typ) = Tag_Typ
8018 or else Is_Controlled (Tag_Typ)
8020 -- Ada 2005 (AI-251): We must also generate these subprograms
8021 -- if the immediate ancestor of Tag_Typ is an interface to
8022 -- ensure the correct initialization of its dispatch table.
8024 or else (not Is_Interface (Tag_Typ)
8025 and then
8026 Is_Interface (Etype (Tag_Typ))))
8027 and then not Has_Controlled_Component (Tag_Typ)
8028 then
8029 if not Is_Limited_Type (Tag_Typ) then
8030 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
8032 if Is_Controlled (Tag_Typ) then
8033 Set_Handled_Statement_Sequence (Decl,
8034 Make_Handled_Sequence_Of_Statements (Loc,
8035 Make_Adjust_Call (
8036 Ref => Make_Identifier (Loc, Name_V),
8037 Typ => Tag_Typ,
8038 Flist_Ref => Make_Identifier (Loc, Name_L),
8039 With_Attach => Make_Identifier (Loc, Name_B))));
8041 else
8042 Set_Handled_Statement_Sequence (Decl,
8043 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8044 Make_Null_Statement (Loc))));
8045 end if;
8047 Append_To (Res, Decl);
8048 end if;
8050 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
8052 if Is_Controlled (Tag_Typ) then
8053 Set_Handled_Statement_Sequence (Decl,
8054 Make_Handled_Sequence_Of_Statements (Loc,
8055 Make_Final_Call (
8056 Ref => Make_Identifier (Loc, Name_V),
8057 Typ => Tag_Typ,
8058 With_Detach => Make_Identifier (Loc, Name_B))));
8060 else
8061 Set_Handled_Statement_Sequence (Decl,
8062 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8063 Make_Null_Statement (Loc))));
8064 end if;
8066 Append_To (Res, Decl);
8067 end if;
8069 return Res;
8070 end Predefined_Primitive_Bodies;
8072 ---------------------------------
8073 -- Predefined_Primitive_Freeze --
8074 ---------------------------------
8076 function Predefined_Primitive_Freeze
8077 (Tag_Typ : Entity_Id) return List_Id
8079 Loc : constant Source_Ptr := Sloc (Tag_Typ);
8080 Res : constant List_Id := New_List;
8081 Prim : Elmt_Id;
8082 Frnodes : List_Id;
8084 begin
8085 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
8086 while Present (Prim) loop
8087 if Is_Predefined_Dispatching_Operation (Node (Prim)) then
8088 Frnodes := Freeze_Entity (Node (Prim), Loc);
8090 if Present (Frnodes) then
8091 Append_List_To (Res, Frnodes);
8092 end if;
8093 end if;
8095 Next_Elmt (Prim);
8096 end loop;
8098 return Res;
8099 end Predefined_Primitive_Freeze;
8101 -------------------------
8102 -- Stream_Operation_OK --
8103 -------------------------
8105 function Stream_Operation_OK
8106 (Typ : Entity_Id;
8107 Operation : TSS_Name_Type) return Boolean
8109 Has_Predefined_Or_Specified_Stream_Attribute : Boolean := False;
8111 begin
8112 -- Special case of a limited type extension: a default implementation
8113 -- of the stream attributes Read or Write exists if that attribute
8114 -- has been specified or is available for an ancestor type; a default
8115 -- implementation of the attribute Output (resp. Input) exists if the
8116 -- attribute has been specified or Write (resp. Read) is available for
8117 -- an ancestor type. The last condition only applies under Ada 2005.
8119 if Is_Limited_Type (Typ)
8120 and then Is_Tagged_Type (Typ)
8121 then
8122 if Operation = TSS_Stream_Read then
8123 Has_Predefined_Or_Specified_Stream_Attribute :=
8124 Has_Specified_Stream_Read (Typ);
8126 elsif Operation = TSS_Stream_Write then
8127 Has_Predefined_Or_Specified_Stream_Attribute :=
8128 Has_Specified_Stream_Write (Typ);
8130 elsif Operation = TSS_Stream_Input then
8131 Has_Predefined_Or_Specified_Stream_Attribute :=
8132 Has_Specified_Stream_Input (Typ)
8133 or else
8134 (Ada_Version >= Ada_05
8135 and then Stream_Operation_OK (Typ, TSS_Stream_Read));
8137 elsif Operation = TSS_Stream_Output then
8138 Has_Predefined_Or_Specified_Stream_Attribute :=
8139 Has_Specified_Stream_Output (Typ)
8140 or else
8141 (Ada_Version >= Ada_05
8142 and then Stream_Operation_OK (Typ, TSS_Stream_Write));
8143 end if;
8145 -- Case of inherited TSS_Stream_Read or TSS_Stream_Write
8147 if not Has_Predefined_Or_Specified_Stream_Attribute
8148 and then Is_Derived_Type (Typ)
8149 and then (Operation = TSS_Stream_Read
8150 or else Operation = TSS_Stream_Write)
8151 then
8152 Has_Predefined_Or_Specified_Stream_Attribute :=
8153 Present
8154 (Find_Inherited_TSS (Base_Type (Etype (Typ)), Operation));
8155 end if;
8156 end if;
8158 -- If the type is not limited, or else is limited but the attribute is
8159 -- explicitly specified or is predefined for the type, then return True,
8160 -- unless other conditions prevail, such as restrictions prohibiting
8161 -- streams or dispatching operations.
8163 -- We exclude the Input operation from being a predefined subprogram in
8164 -- the case where the associated type is an abstract extension, because
8165 -- the attribute is not callable in that case, per 13.13.2(49/2). Also,
8166 -- we don't want an abstract version created because types derived from
8167 -- the abstract type may not even have Input available (for example if
8168 -- derived from a private view of the abstract type that doesn't have
8169 -- a visible Input), but a VM such as .NET or the Java VM can treat the
8170 -- operation as inherited anyway, and we don't want an abstract function
8171 -- to be (implicitly) inherited in that case because it can lead to a VM
8172 -- exception.
8174 return (not Is_Limited_Type (Typ)
8175 or else Has_Predefined_Or_Specified_Stream_Attribute)
8176 and then (Operation /= TSS_Stream_Input
8177 or else not Is_Abstract_Type (Typ)
8178 or else not Is_Derived_Type (Typ))
8179 and then not Has_Unknown_Discriminants (Typ)
8180 and then not (Is_Interface (Typ)
8181 and then (Is_Task_Interface (Typ)
8182 or else Is_Protected_Interface (Typ)
8183 or else Is_Synchronized_Interface (Typ)))
8184 and then not Restriction_Active (No_Streams)
8185 and then not Restriction_Active (No_Dispatch)
8186 and then not No_Run_Time_Mode
8187 and then RTE_Available (RE_Tag)
8188 and then RTE_Available (RE_Root_Stream_Type);
8189 end Stream_Operation_OK;
8191 end Exp_Ch3;