Merge -r 127928:132243 from trunk
[official-gcc.git] / gcc / ada / exp_ch3.adb
blobfcc216e21c5ec9755814a38e6a0221f9093032df
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 Entity_Id);
241 -- Create a list with the specs of the predefined primitive operations.
242 -- For tagged types that are interfaces all these primitives are defined
243 -- abstract.
245 -- The following entries are present for all tagged types, and provide
246 -- the results of the corresponding attribute applied to the object.
247 -- Dispatching is required in general, since the result of the attribute
248 -- will vary with the actual object subtype.
250 -- _alignment provides result of 'Alignment attribute
251 -- _size provides result of 'Size attribute
252 -- typSR provides result of 'Read attribute
253 -- typSW provides result of 'Write attribute
254 -- typSI provides result of 'Input attribute
255 -- typSO provides result of 'Output attribute
257 -- The following entries are additionally present for non-limited tagged
258 -- types, and implement additional dispatching operations for predefined
259 -- operations:
261 -- _equality implements "=" operator
262 -- _assign implements assignment operation
263 -- typDF implements deep finalization
264 -- typDA implements deep adjust
266 -- The latter two are empty procedures unless the type contains some
267 -- controlled components that require finalization actions (the deep
268 -- in the name refers to the fact that the action applies to components).
270 -- The list is returned in Predef_List. The Parameter Renamed_Eq either
271 -- returns the value Empty, or else the defining unit name for the
272 -- predefined equality function in the case where the type has a primitive
273 -- operation that is a renaming of predefined equality (but only if there
274 -- is also an overriding user-defined equality function). The returned
275 -- Renamed_Eq will be passed to the corresponding parameter of
276 -- Predefined_Primitive_Bodies.
278 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean;
279 -- returns True if there are representation clauses for type T that are not
280 -- inherited. If the result is false, the init_proc and the discriminant
281 -- checking functions of the parent can be reused by a derived type.
283 procedure Make_Controlling_Function_Wrappers
284 (Tag_Typ : Entity_Id;
285 Decl_List : out List_Id;
286 Body_List : out List_Id);
287 -- Ada 2005 (AI-391): Makes specs and bodies for the wrapper functions
288 -- associated with inherited functions with controlling results which
289 -- are not overridden. The body of each wrapper function consists solely
290 -- of a return statement whose expression is an extension aggregate
291 -- invoking the inherited subprogram's parent subprogram and extended
292 -- with a null association list.
294 procedure Make_Null_Procedure_Specs
295 (Tag_Typ : Entity_Id;
296 Decl_List : out List_Id);
297 -- Ada 2005 (AI-251): Makes specs for null procedures associated with any
298 -- null procedures inherited from an interface type that have not been
299 -- overridden. Only one null procedure will be created for a given set of
300 -- inherited null procedures with homographic profiles.
302 function Predef_Spec_Or_Body
303 (Loc : Source_Ptr;
304 Tag_Typ : Entity_Id;
305 Name : Name_Id;
306 Profile : List_Id;
307 Ret_Type : Entity_Id := Empty;
308 For_Body : Boolean := False) return Node_Id;
309 -- This function generates the appropriate expansion for a predefined
310 -- primitive operation specified by its name, parameter profile and
311 -- return type (Empty means this is a procedure). If For_Body is false,
312 -- then the returned node is a subprogram declaration. If For_Body is
313 -- true, then the returned node is a empty subprogram body containing
314 -- no declarations and no statements.
316 function Predef_Stream_Attr_Spec
317 (Loc : Source_Ptr;
318 Tag_Typ : Entity_Id;
319 Name : TSS_Name_Type;
320 For_Body : Boolean := False) return Node_Id;
321 -- Specialized version of Predef_Spec_Or_Body that apply to read, write,
322 -- input and output attribute whose specs are constructed in Exp_Strm.
324 function Predef_Deep_Spec
325 (Loc : Source_Ptr;
326 Tag_Typ : Entity_Id;
327 Name : TSS_Name_Type;
328 For_Body : Boolean := False) return Node_Id;
329 -- Specialized version of Predef_Spec_Or_Body that apply to _deep_adjust
330 -- and _deep_finalize
332 function Predefined_Primitive_Bodies
333 (Tag_Typ : Entity_Id;
334 Renamed_Eq : Entity_Id) return List_Id;
335 -- Create the bodies of the predefined primitives that are described in
336 -- Predefined_Primitive_Specs. When not empty, Renamed_Eq must denote
337 -- the defining unit name of the type's predefined equality as returned
338 -- by Make_Predefined_Primitive_Specs.
340 function Predefined_Primitive_Freeze (Tag_Typ : Entity_Id) return List_Id;
341 -- Freeze entities of all predefined primitive operations. This is needed
342 -- because the bodies of these operations do not normally do any freezing.
344 function Stream_Operation_OK
345 (Typ : Entity_Id;
346 Operation : TSS_Name_Type) return Boolean;
347 -- Check whether the named stream operation must be emitted for a given
348 -- type. The rules for inheritance of stream attributes by type extensions
349 -- are enforced by this function. Furthermore, various restrictions prevent
350 -- the generation of these operations, as a useful optimization or for
351 -- certification purposes.
353 ---------------------
354 -- Add_Final_Chain --
355 ---------------------
357 function Add_Final_Chain (Def_Id : Entity_Id) return Entity_Id is
358 Loc : constant Source_Ptr := Sloc (Def_Id);
359 Flist : Entity_Id;
361 begin
362 Flist :=
363 Make_Defining_Identifier (Loc,
364 New_External_Name (Chars (Def_Id), 'L'));
366 Append_Freeze_Action (Def_Id,
367 Make_Object_Declaration (Loc,
368 Defining_Identifier => Flist,
369 Object_Definition =>
370 New_Reference_To (RTE (RE_List_Controller), Loc)));
372 return Flist;
373 end Add_Final_Chain;
375 --------------------------
376 -- Adjust_Discriminants --
377 --------------------------
379 -- This procedure attempts to define subtypes for discriminants that are
380 -- more restrictive than those declared. Such a replacement is possible if
381 -- we can demonstrate that values outside the restricted range would cause
382 -- constraint errors in any case. The advantage of restricting the
383 -- discriminant types in this way is that the maximum size of the variant
384 -- record can be calculated more conservatively.
386 -- An example of a situation in which we can perform this type of
387 -- restriction is the following:
389 -- subtype B is range 1 .. 10;
390 -- type Q is array (B range <>) of Integer;
392 -- type V (N : Natural) is record
393 -- C : Q (1 .. N);
394 -- end record;
396 -- In this situation, we can restrict the upper bound of N to 10, since
397 -- any larger value would cause a constraint error in any case.
399 -- There are many situations in which such restriction is possible, but
400 -- for now, we just look for cases like the above, where the component
401 -- in question is a one dimensional array whose upper bound is one of
402 -- the record discriminants. Also the component must not be part of
403 -- any variant part, since then the component does not always exist.
405 procedure Adjust_Discriminants (Rtype : Entity_Id) is
406 Loc : constant Source_Ptr := Sloc (Rtype);
407 Comp : Entity_Id;
408 Ctyp : Entity_Id;
409 Ityp : Entity_Id;
410 Lo : Node_Id;
411 Hi : Node_Id;
412 P : Node_Id;
413 Loval : Uint;
414 Discr : Entity_Id;
415 Dtyp : Entity_Id;
416 Dhi : Node_Id;
417 Dhiv : Uint;
418 Ahi : Node_Id;
419 Ahiv : Uint;
420 Tnn : Entity_Id;
422 begin
423 Comp := First_Component (Rtype);
424 while Present (Comp) loop
426 -- If our parent is a variant, quit, we do not look at components
427 -- that are in variant parts, because they may not always exist.
429 P := Parent (Comp); -- component declaration
430 P := Parent (P); -- component list
432 exit when Nkind (Parent (P)) = N_Variant;
434 -- We are looking for a one dimensional array type
436 Ctyp := Etype (Comp);
438 if not Is_Array_Type (Ctyp)
439 or else Number_Dimensions (Ctyp) > 1
440 then
441 goto Continue;
442 end if;
444 -- The lower bound must be constant, and the upper bound is a
445 -- discriminant (which is a discriminant of the current record).
447 Ityp := Etype (First_Index (Ctyp));
448 Lo := Type_Low_Bound (Ityp);
449 Hi := Type_High_Bound (Ityp);
451 if not Compile_Time_Known_Value (Lo)
452 or else Nkind (Hi) /= N_Identifier
453 or else No (Entity (Hi))
454 or else Ekind (Entity (Hi)) /= E_Discriminant
455 then
456 goto Continue;
457 end if;
459 -- We have an array with appropriate bounds
461 Loval := Expr_Value (Lo);
462 Discr := Entity (Hi);
463 Dtyp := Etype (Discr);
465 -- See if the discriminant has a known upper bound
467 Dhi := Type_High_Bound (Dtyp);
469 if not Compile_Time_Known_Value (Dhi) then
470 goto Continue;
471 end if;
473 Dhiv := Expr_Value (Dhi);
475 -- See if base type of component array has known upper bound
477 Ahi := Type_High_Bound (Etype (First_Index (Base_Type (Ctyp))));
479 if not Compile_Time_Known_Value (Ahi) then
480 goto Continue;
481 end if;
483 Ahiv := Expr_Value (Ahi);
485 -- The condition for doing the restriction is that the high bound
486 -- of the discriminant is greater than the low bound of the array,
487 -- and is also greater than the high bound of the base type index.
489 if Dhiv > Loval and then Dhiv > Ahiv then
491 -- We can reset the upper bound of the discriminant type to
492 -- whichever is larger, the low bound of the component, or
493 -- the high bound of the base type array index.
495 -- We build a subtype that is declared as
497 -- subtype Tnn is discr_type range discr_type'First .. max;
499 -- And insert this declaration into the tree. The type of the
500 -- discriminant is then reset to this more restricted subtype.
502 Tnn := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
504 Insert_Action (Declaration_Node (Rtype),
505 Make_Subtype_Declaration (Loc,
506 Defining_Identifier => Tnn,
507 Subtype_Indication =>
508 Make_Subtype_Indication (Loc,
509 Subtype_Mark => New_Occurrence_Of (Dtyp, Loc),
510 Constraint =>
511 Make_Range_Constraint (Loc,
512 Range_Expression =>
513 Make_Range (Loc,
514 Low_Bound =>
515 Make_Attribute_Reference (Loc,
516 Attribute_Name => Name_First,
517 Prefix => New_Occurrence_Of (Dtyp, Loc)),
518 High_Bound =>
519 Make_Integer_Literal (Loc,
520 Intval => UI_Max (Loval, Ahiv)))))));
522 Set_Etype (Discr, Tnn);
523 end if;
525 <<Continue>>
526 Next_Component (Comp);
527 end loop;
528 end Adjust_Discriminants;
530 ---------------------------
531 -- Build_Array_Init_Proc --
532 ---------------------------
534 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id) is
535 Loc : constant Source_Ptr := Sloc (Nod);
536 Comp_Type : constant Entity_Id := Component_Type (A_Type);
537 Index_List : List_Id;
538 Proc_Id : Entity_Id;
539 Body_Stmts : List_Id;
541 function Init_Component return List_Id;
542 -- Create one statement to initialize one array component, designated
543 -- by a full set of indices.
545 function Init_One_Dimension (N : Int) return List_Id;
546 -- Create loop to initialize one dimension of the array. The single
547 -- statement in the loop body initializes the inner dimensions if any,
548 -- or else the single component. Note that this procedure is called
549 -- recursively, with N being the dimension to be initialized. A call
550 -- with N greater than the number of dimensions simply generates the
551 -- component initialization, terminating the recursion.
553 --------------------
554 -- Init_Component --
555 --------------------
557 function Init_Component return List_Id is
558 Comp : Node_Id;
560 begin
561 Comp :=
562 Make_Indexed_Component (Loc,
563 Prefix => Make_Identifier (Loc, Name_uInit),
564 Expressions => Index_List);
566 if Needs_Simple_Initialization (Comp_Type) then
567 Set_Assignment_OK (Comp);
568 return New_List (
569 Make_Assignment_Statement (Loc,
570 Name => Comp,
571 Expression =>
572 Get_Simple_Init_Val
573 (Comp_Type, Loc, Component_Size (A_Type))));
575 else
576 Clean_Task_Names (Comp_Type, Proc_Id);
577 return
578 Build_Initialization_Call
579 (Loc, Comp, Comp_Type,
580 In_Init_Proc => True,
581 Enclos_Type => A_Type);
582 end if;
583 end Init_Component;
585 ------------------------
586 -- Init_One_Dimension --
587 ------------------------
589 function Init_One_Dimension (N : Int) return List_Id is
590 Index : Entity_Id;
592 begin
593 -- If the component does not need initializing, then there is nothing
594 -- to do here, so we return a null body. This occurs when generating
595 -- the dummy Init_Proc needed for Initialize_Scalars processing.
597 if not Has_Non_Null_Base_Init_Proc (Comp_Type)
598 and then not Needs_Simple_Initialization (Comp_Type)
599 and then not Has_Task (Comp_Type)
600 then
601 return New_List (Make_Null_Statement (Loc));
603 -- If all dimensions dealt with, we simply initialize the component
605 elsif N > Number_Dimensions (A_Type) then
606 return Init_Component;
608 -- Here we generate the required loop
610 else
611 Index :=
612 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
614 Append (New_Reference_To (Index, Loc), Index_List);
616 return New_List (
617 Make_Implicit_Loop_Statement (Nod,
618 Identifier => Empty,
619 Iteration_Scheme =>
620 Make_Iteration_Scheme (Loc,
621 Loop_Parameter_Specification =>
622 Make_Loop_Parameter_Specification (Loc,
623 Defining_Identifier => Index,
624 Discrete_Subtype_Definition =>
625 Make_Attribute_Reference (Loc,
626 Prefix => Make_Identifier (Loc, Name_uInit),
627 Attribute_Name => Name_Range,
628 Expressions => New_List (
629 Make_Integer_Literal (Loc, N))))),
630 Statements => Init_One_Dimension (N + 1)));
631 end if;
632 end Init_One_Dimension;
634 -- Start of processing for Build_Array_Init_Proc
636 begin
637 -- Nothing to generate in the following cases:
639 -- 1. Initialization is suppressed for the type
640 -- 2. The type is a value type, in the CIL sense.
641 -- 3. An initialization already exists for the base type
643 if Suppress_Init_Proc (A_Type)
644 or else Is_Value_Type (Comp_Type)
645 or else Present (Base_Init_Proc (A_Type))
646 then
647 return;
648 end if;
650 Index_List := New_List;
652 -- We need an initialization procedure if any of the following is true:
654 -- 1. The component type has an initialization procedure
655 -- 2. The component type needs simple initialization
656 -- 3. Tasks are present
657 -- 4. The type is marked as a public entity
659 -- The reason for the public entity test is to deal properly with the
660 -- Initialize_Scalars pragma. This pragma can be set in the client and
661 -- not in the declaring package, this means the client will make a call
662 -- to the initialization procedure (because one of conditions 1-3 must
663 -- apply in this case), and we must generate a procedure (even if it is
664 -- null) to satisfy the call in this case.
666 -- Exception: do not build an array init_proc for a type whose root
667 -- type is Standard.String or Standard.Wide_[Wide_]String, since there
668 -- is no place to put the code, and in any case we handle initialization
669 -- of such types (in the Initialize_Scalars case, that's the only time
670 -- the issue arises) in a special manner anyway which does not need an
671 -- init_proc.
673 if Has_Non_Null_Base_Init_Proc (Comp_Type)
674 or else Needs_Simple_Initialization (Comp_Type)
675 or else Has_Task (Comp_Type)
676 or else (not Restriction_Active (No_Initialize_Scalars)
677 and then Is_Public (A_Type)
678 and then Root_Type (A_Type) /= Standard_String
679 and then Root_Type (A_Type) /= Standard_Wide_String
680 and then Root_Type (A_Type) /= Standard_Wide_Wide_String)
681 then
682 Proc_Id :=
683 Make_Defining_Identifier (Loc, Make_Init_Proc_Name (A_Type));
685 Body_Stmts := Init_One_Dimension (1);
687 Discard_Node (
688 Make_Subprogram_Body (Loc,
689 Specification =>
690 Make_Procedure_Specification (Loc,
691 Defining_Unit_Name => Proc_Id,
692 Parameter_Specifications => Init_Formals (A_Type)),
693 Declarations => New_List,
694 Handled_Statement_Sequence =>
695 Make_Handled_Sequence_Of_Statements (Loc,
696 Statements => Body_Stmts)));
698 Set_Ekind (Proc_Id, E_Procedure);
699 Set_Is_Public (Proc_Id, Is_Public (A_Type));
700 Set_Is_Internal (Proc_Id);
701 Set_Has_Completion (Proc_Id);
703 if not Debug_Generated_Code then
704 Set_Debug_Info_Off (Proc_Id);
705 end if;
707 -- Set inlined unless controlled stuff or tasks around, in which
708 -- case we do not want to inline, because nested stuff may cause
709 -- difficulties in inter-unit inlining, and furthermore there is
710 -- in any case no point in inlining such complex init procs.
712 if not Has_Task (Proc_Id)
713 and then not Controlled_Type (Proc_Id)
714 then
715 Set_Is_Inlined (Proc_Id);
716 end if;
718 -- Associate Init_Proc with type, and determine if the procedure
719 -- is null (happens because of the Initialize_Scalars pragma case,
720 -- where we have to generate a null procedure in case it is called
721 -- by a client with Initialize_Scalars set). Such procedures have
722 -- to be generated, but do not have to be called, so we mark them
723 -- as null to suppress the call.
725 Set_Init_Proc (A_Type, Proc_Id);
727 if List_Length (Body_Stmts) = 1
728 and then Nkind (First (Body_Stmts)) = N_Null_Statement
729 then
730 Set_Is_Null_Init_Proc (Proc_Id);
732 else
733 -- Try to build a static aggregate to initialize statically
734 -- objects of the type. This can only be done for constrained
735 -- one-dimensional arrays with static bounds.
737 Set_Static_Initialization
738 (Proc_Id,
739 Build_Equivalent_Array_Aggregate (First_Subtype (A_Type)));
740 end if;
741 end if;
742 end Build_Array_Init_Proc;
744 -----------------------------
745 -- Build_Class_Wide_Master --
746 -----------------------------
748 procedure Build_Class_Wide_Master (T : Entity_Id) is
749 Loc : constant Source_Ptr := Sloc (T);
750 M_Id : Entity_Id;
751 Decl : Node_Id;
752 P : Node_Id;
753 Par : Node_Id;
755 begin
756 -- Nothing to do if there is no task hierarchy
758 if Restriction_Active (No_Task_Hierarchy) then
759 return;
760 end if;
762 -- Find declaration that created the access type: either a type
763 -- declaration, or an object declaration with an access definition,
764 -- in which case the type is anonymous.
766 if Is_Itype (T) then
767 P := Associated_Node_For_Itype (T);
768 else
769 P := Parent (T);
770 end if;
772 -- Nothing to do if we already built a master entity for this scope
774 if not Has_Master_Entity (Scope (T)) then
776 -- First build the master entity
777 -- _Master : constant Master_Id := Current_Master.all;
778 -- and insert it just before the current declaration.
780 Decl :=
781 Make_Object_Declaration (Loc,
782 Defining_Identifier =>
783 Make_Defining_Identifier (Loc, Name_uMaster),
784 Constant_Present => True,
785 Object_Definition => New_Reference_To (Standard_Integer, Loc),
786 Expression =>
787 Make_Explicit_Dereference (Loc,
788 New_Reference_To (RTE (RE_Current_Master), Loc)));
790 Insert_Action (P, Decl);
791 Analyze (Decl);
792 Set_Has_Master_Entity (Scope (T));
794 -- Now mark the containing scope as a task master
796 Par := P;
797 while Nkind (Par) /= N_Compilation_Unit loop
798 Par := Parent (Par);
800 -- If we fall off the top, we are at the outer level, and the
801 -- environment task is our effective master, so nothing to mark.
803 if Nkind_In
804 (Par, N_Task_Body, N_Block_Statement, N_Subprogram_Body)
805 then
806 Set_Is_Task_Master (Par, True);
807 exit;
808 end if;
809 end loop;
810 end if;
812 -- Now define the renaming of the master_id
814 M_Id :=
815 Make_Defining_Identifier (Loc,
816 New_External_Name (Chars (T), 'M'));
818 Decl :=
819 Make_Object_Renaming_Declaration (Loc,
820 Defining_Identifier => M_Id,
821 Subtype_Mark => New_Reference_To (Standard_Integer, Loc),
822 Name => Make_Identifier (Loc, Name_uMaster));
823 Insert_Before (P, Decl);
824 Analyze (Decl);
826 Set_Master_Id (T, M_Id);
828 exception
829 when RE_Not_Available =>
830 return;
831 end Build_Class_Wide_Master;
833 --------------------------------
834 -- Build_Discr_Checking_Funcs --
835 --------------------------------
837 procedure Build_Discr_Checking_Funcs (N : Node_Id) is
838 Rec_Id : Entity_Id;
839 Loc : Source_Ptr;
840 Enclosing_Func_Id : Entity_Id;
841 Sequence : Nat := 1;
842 Type_Def : Node_Id;
843 V : Node_Id;
845 function Build_Case_Statement
846 (Case_Id : Entity_Id;
847 Variant : Node_Id) return Node_Id;
848 -- Build a case statement containing only two alternatives. The first
849 -- alternative corresponds exactly to the discrete choices given on the
850 -- variant with contains the components that we are generating the
851 -- checks for. If the discriminant is one of these return False. The
852 -- second alternative is an OTHERS choice that will return True
853 -- indicating the discriminant did not match.
855 function Build_Dcheck_Function
856 (Case_Id : Entity_Id;
857 Variant : Node_Id) return Entity_Id;
858 -- Build the discriminant checking function for a given variant
860 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id);
861 -- Builds the discriminant checking function for each variant of the
862 -- given variant part of the record type.
864 --------------------------
865 -- Build_Case_Statement --
866 --------------------------
868 function Build_Case_Statement
869 (Case_Id : Entity_Id;
870 Variant : Node_Id) return Node_Id
872 Alt_List : constant List_Id := New_List;
873 Actuals_List : List_Id;
874 Case_Node : Node_Id;
875 Case_Alt_Node : Node_Id;
876 Choice : Node_Id;
877 Choice_List : List_Id;
878 D : Entity_Id;
879 Return_Node : Node_Id;
881 begin
882 Case_Node := New_Node (N_Case_Statement, Loc);
884 -- Replace the discriminant which controls the variant, with the name
885 -- of the formal of the checking function.
887 Set_Expression (Case_Node,
888 Make_Identifier (Loc, Chars (Case_Id)));
890 Choice := First (Discrete_Choices (Variant));
892 if Nkind (Choice) = N_Others_Choice then
893 Choice_List := New_Copy_List (Others_Discrete_Choices (Choice));
894 else
895 Choice_List := New_Copy_List (Discrete_Choices (Variant));
896 end if;
898 if not Is_Empty_List (Choice_List) then
899 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
900 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
902 -- In case this is a nested variant, we need to return the result
903 -- of the discriminant checking function for the immediately
904 -- enclosing variant.
906 if Present (Enclosing_Func_Id) then
907 Actuals_List := New_List;
909 D := First_Discriminant (Rec_Id);
910 while Present (D) loop
911 Append (Make_Identifier (Loc, Chars (D)), Actuals_List);
912 Next_Discriminant (D);
913 end loop;
915 Return_Node :=
916 Make_Simple_Return_Statement (Loc,
917 Expression =>
918 Make_Function_Call (Loc,
919 Name =>
920 New_Reference_To (Enclosing_Func_Id, Loc),
921 Parameter_Associations =>
922 Actuals_List));
924 else
925 Return_Node :=
926 Make_Simple_Return_Statement (Loc,
927 Expression =>
928 New_Reference_To (Standard_False, Loc));
929 end if;
931 Set_Statements (Case_Alt_Node, New_List (Return_Node));
932 Append (Case_Alt_Node, Alt_List);
933 end if;
935 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
936 Choice_List := New_List (New_Node (N_Others_Choice, Loc));
937 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
939 Return_Node :=
940 Make_Simple_Return_Statement (Loc,
941 Expression =>
942 New_Reference_To (Standard_True, Loc));
944 Set_Statements (Case_Alt_Node, New_List (Return_Node));
945 Append (Case_Alt_Node, Alt_List);
947 Set_Alternatives (Case_Node, Alt_List);
948 return Case_Node;
949 end Build_Case_Statement;
951 ---------------------------
952 -- Build_Dcheck_Function --
953 ---------------------------
955 function Build_Dcheck_Function
956 (Case_Id : Entity_Id;
957 Variant : Node_Id) return Entity_Id
959 Body_Node : Node_Id;
960 Func_Id : Entity_Id;
961 Parameter_List : List_Id;
962 Spec_Node : Node_Id;
964 begin
965 Body_Node := New_Node (N_Subprogram_Body, Loc);
966 Sequence := Sequence + 1;
968 Func_Id :=
969 Make_Defining_Identifier (Loc,
970 Chars => New_External_Name (Chars (Rec_Id), 'D', Sequence));
972 Spec_Node := New_Node (N_Function_Specification, Loc);
973 Set_Defining_Unit_Name (Spec_Node, Func_Id);
975 Parameter_List := Build_Discriminant_Formals (Rec_Id, False);
977 Set_Parameter_Specifications (Spec_Node, Parameter_List);
978 Set_Result_Definition (Spec_Node,
979 New_Reference_To (Standard_Boolean, Loc));
980 Set_Specification (Body_Node, Spec_Node);
981 Set_Declarations (Body_Node, New_List);
983 Set_Handled_Statement_Sequence (Body_Node,
984 Make_Handled_Sequence_Of_Statements (Loc,
985 Statements => New_List (
986 Build_Case_Statement (Case_Id, Variant))));
988 Set_Ekind (Func_Id, E_Function);
989 Set_Mechanism (Func_Id, Default_Mechanism);
990 Set_Is_Inlined (Func_Id, True);
991 Set_Is_Pure (Func_Id, True);
992 Set_Is_Public (Func_Id, Is_Public (Rec_Id));
993 Set_Is_Internal (Func_Id, True);
995 if not Debug_Generated_Code then
996 Set_Debug_Info_Off (Func_Id);
997 end if;
999 Analyze (Body_Node);
1001 Append_Freeze_Action (Rec_Id, Body_Node);
1002 Set_Dcheck_Function (Variant, Func_Id);
1003 return Func_Id;
1004 end Build_Dcheck_Function;
1006 ----------------------------
1007 -- Build_Dcheck_Functions --
1008 ----------------------------
1010 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id) is
1011 Component_List_Node : Node_Id;
1012 Decl : Entity_Id;
1013 Discr_Name : Entity_Id;
1014 Func_Id : Entity_Id;
1015 Variant : Node_Id;
1016 Saved_Enclosing_Func_Id : Entity_Id;
1018 begin
1019 -- Build the discriminant checking function for each variant, label
1020 -- all components of that variant with the function's name.
1022 Discr_Name := Entity (Name (Variant_Part_Node));
1023 Variant := First_Non_Pragma (Variants (Variant_Part_Node));
1025 while Present (Variant) loop
1026 Func_Id := Build_Dcheck_Function (Discr_Name, Variant);
1027 Component_List_Node := Component_List (Variant);
1029 if not Null_Present (Component_List_Node) then
1030 Decl :=
1031 First_Non_Pragma (Component_Items (Component_List_Node));
1033 while Present (Decl) loop
1034 Set_Discriminant_Checking_Func
1035 (Defining_Identifier (Decl), Func_Id);
1037 Next_Non_Pragma (Decl);
1038 end loop;
1040 if Present (Variant_Part (Component_List_Node)) then
1041 Saved_Enclosing_Func_Id := Enclosing_Func_Id;
1042 Enclosing_Func_Id := Func_Id;
1043 Build_Dcheck_Functions (Variant_Part (Component_List_Node));
1044 Enclosing_Func_Id := Saved_Enclosing_Func_Id;
1045 end if;
1046 end if;
1048 Next_Non_Pragma (Variant);
1049 end loop;
1050 end Build_Dcheck_Functions;
1052 -- Start of processing for Build_Discr_Checking_Funcs
1054 begin
1055 -- Only build if not done already
1057 if not Discr_Check_Funcs_Built (N) then
1058 Type_Def := Type_Definition (N);
1060 if Nkind (Type_Def) = N_Record_Definition then
1061 if No (Component_List (Type_Def)) then -- null record.
1062 return;
1063 else
1064 V := Variant_Part (Component_List (Type_Def));
1065 end if;
1067 else pragma Assert (Nkind (Type_Def) = N_Derived_Type_Definition);
1068 if No (Component_List (Record_Extension_Part (Type_Def))) then
1069 return;
1070 else
1071 V := Variant_Part
1072 (Component_List (Record_Extension_Part (Type_Def)));
1073 end if;
1074 end if;
1076 Rec_Id := Defining_Identifier (N);
1078 if Present (V) and then not Is_Unchecked_Union (Rec_Id) then
1079 Loc := Sloc (N);
1080 Enclosing_Func_Id := Empty;
1081 Build_Dcheck_Functions (V);
1082 end if;
1084 Set_Discr_Check_Funcs_Built (N);
1085 end if;
1086 end Build_Discr_Checking_Funcs;
1088 --------------------------------
1089 -- Build_Discriminant_Formals --
1090 --------------------------------
1092 function Build_Discriminant_Formals
1093 (Rec_Id : Entity_Id;
1094 Use_Dl : Boolean) return List_Id
1096 Loc : Source_Ptr := Sloc (Rec_Id);
1097 Parameter_List : constant List_Id := New_List;
1098 D : Entity_Id;
1099 Formal : Entity_Id;
1100 Param_Spec_Node : Node_Id;
1102 begin
1103 if Has_Discriminants (Rec_Id) then
1104 D := First_Discriminant (Rec_Id);
1105 while Present (D) loop
1106 Loc := Sloc (D);
1108 if Use_Dl then
1109 Formal := Discriminal (D);
1110 else
1111 Formal := Make_Defining_Identifier (Loc, Chars (D));
1112 end if;
1114 Param_Spec_Node :=
1115 Make_Parameter_Specification (Loc,
1116 Defining_Identifier => Formal,
1117 Parameter_Type =>
1118 New_Reference_To (Etype (D), Loc));
1119 Append (Param_Spec_Node, Parameter_List);
1120 Next_Discriminant (D);
1121 end loop;
1122 end if;
1124 return Parameter_List;
1125 end Build_Discriminant_Formals;
1127 --------------------------------------
1128 -- Build_Equivalent_Array_Aggregate --
1129 --------------------------------------
1131 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id is
1132 Loc : constant Source_Ptr := Sloc (T);
1133 Comp_Type : constant Entity_Id := Component_Type (T);
1134 Index_Type : constant Entity_Id := Etype (First_Index (T));
1135 Proc : constant Entity_Id := Base_Init_Proc (T);
1136 Lo, Hi : Node_Id;
1137 Aggr : Node_Id;
1138 Expr : Node_Id;
1140 begin
1141 if not Is_Constrained (T)
1142 or else Number_Dimensions (T) > 1
1143 or else No (Proc)
1144 then
1145 Initialization_Warning (T);
1146 return Empty;
1147 end if;
1149 Lo := Type_Low_Bound (Index_Type);
1150 Hi := Type_High_Bound (Index_Type);
1152 if not Compile_Time_Known_Value (Lo)
1153 or else not Compile_Time_Known_Value (Hi)
1154 then
1155 Initialization_Warning (T);
1156 return Empty;
1157 end if;
1159 if Is_Record_Type (Comp_Type)
1160 and then Present (Base_Init_Proc (Comp_Type))
1161 then
1162 Expr := Static_Initialization (Base_Init_Proc (Comp_Type));
1164 if No (Expr) then
1165 Initialization_Warning (T);
1166 return Empty;
1167 end if;
1169 else
1170 Initialization_Warning (T);
1171 return Empty;
1172 end if;
1174 Aggr := Make_Aggregate (Loc, No_List, New_List);
1175 Set_Etype (Aggr, T);
1176 Set_Aggregate_Bounds (Aggr,
1177 Make_Range (Loc,
1178 Low_Bound => New_Copy (Lo),
1179 High_Bound => New_Copy (Hi)));
1180 Set_Parent (Aggr, Parent (Proc));
1182 Append_To (Component_Associations (Aggr),
1183 Make_Component_Association (Loc,
1184 Choices =>
1185 New_List (
1186 Make_Range (Loc,
1187 Low_Bound => New_Copy (Lo),
1188 High_Bound => New_Copy (Hi))),
1189 Expression => Expr));
1191 if Static_Array_Aggregate (Aggr) then
1192 return Aggr;
1193 else
1194 Initialization_Warning (T);
1195 return Empty;
1196 end if;
1197 end Build_Equivalent_Array_Aggregate;
1199 ---------------------------------------
1200 -- Build_Equivalent_Record_Aggregate --
1201 ---------------------------------------
1203 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id is
1204 Agg : Node_Id;
1205 Comp : Entity_Id;
1207 -- Start of processing for Build_Equivalent_Record_Aggregate
1209 begin
1210 if not Is_Record_Type (T)
1211 or else Has_Discriminants (T)
1212 or else Is_Limited_Type (T)
1213 or else Has_Non_Standard_Rep (T)
1214 then
1215 Initialization_Warning (T);
1216 return Empty;
1217 end if;
1219 Comp := First_Component (T);
1221 -- A null record needs no warning
1223 if No (Comp) then
1224 return Empty;
1225 end if;
1227 while Present (Comp) loop
1229 -- Array components are acceptable if initialized by a positional
1230 -- aggregate with static components.
1232 if Is_Array_Type (Etype (Comp)) then
1233 declare
1234 Comp_Type : constant Entity_Id := Component_Type (Etype (Comp));
1236 begin
1237 if Nkind (Parent (Comp)) /= N_Component_Declaration
1238 or else No (Expression (Parent (Comp)))
1239 or else Nkind (Expression (Parent (Comp))) /= N_Aggregate
1240 then
1241 Initialization_Warning (T);
1242 return Empty;
1244 elsif Is_Scalar_Type (Component_Type (Etype (Comp)))
1245 and then
1246 (not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1247 or else not Compile_Time_Known_Value
1248 (Type_High_Bound (Comp_Type)))
1249 then
1250 Initialization_Warning (T);
1251 return Empty;
1253 elsif
1254 not Static_Array_Aggregate (Expression (Parent (Comp)))
1255 then
1256 Initialization_Warning (T);
1257 return Empty;
1258 end if;
1259 end;
1261 elsif Is_Scalar_Type (Etype (Comp)) then
1262 if Nkind (Parent (Comp)) /= N_Component_Declaration
1263 or else No (Expression (Parent (Comp)))
1264 or else not Compile_Time_Known_Value (Expression (Parent (Comp)))
1265 then
1266 Initialization_Warning (T);
1267 return Empty;
1268 end if;
1270 -- For now, other types are excluded
1272 else
1273 Initialization_Warning (T);
1274 return Empty;
1275 end if;
1277 Next_Component (Comp);
1278 end loop;
1280 -- All components have static initialization. Build positional
1281 -- aggregate from the given expressions or defaults.
1283 Agg := Make_Aggregate (Sloc (T), New_List, New_List);
1284 Set_Parent (Agg, Parent (T));
1286 Comp := First_Component (T);
1287 while Present (Comp) loop
1288 Append
1289 (New_Copy_Tree (Expression (Parent (Comp))), Expressions (Agg));
1290 Next_Component (Comp);
1291 end loop;
1293 Analyze_And_Resolve (Agg, T);
1294 return Agg;
1295 end Build_Equivalent_Record_Aggregate;
1297 -------------------------------
1298 -- Build_Initialization_Call --
1299 -------------------------------
1301 -- References to a discriminant inside the record type declaration can
1302 -- appear either in the subtype_indication to constrain a record or an
1303 -- array, or as part of a larger expression given for the initial value
1304 -- of a component. In both of these cases N appears in the record
1305 -- initialization procedure and needs to be replaced by the formal
1306 -- parameter of the initialization procedure which corresponds to that
1307 -- discriminant.
1309 -- In the example below, references to discriminants D1 and D2 in proc_1
1310 -- are replaced by references to formals with the same name
1311 -- (discriminals)
1313 -- A similar replacement is done for calls to any record initialization
1314 -- procedure for any components that are themselves of a record type.
1316 -- type R (D1, D2 : Integer) is record
1317 -- X : Integer := F * D1;
1318 -- Y : Integer := F * D2;
1319 -- end record;
1321 -- procedure proc_1 (Out_2 : out R; D1 : Integer; D2 : Integer) is
1322 -- begin
1323 -- Out_2.D1 := D1;
1324 -- Out_2.D2 := D2;
1325 -- Out_2.X := F * D1;
1326 -- Out_2.Y := F * D2;
1327 -- end;
1329 function Build_Initialization_Call
1330 (Loc : Source_Ptr;
1331 Id_Ref : Node_Id;
1332 Typ : Entity_Id;
1333 In_Init_Proc : Boolean := False;
1334 Enclos_Type : Entity_Id := Empty;
1335 Discr_Map : Elist_Id := New_Elmt_List;
1336 With_Default_Init : Boolean := False) return List_Id
1338 First_Arg : Node_Id;
1339 Args : List_Id;
1340 Decls : List_Id;
1341 Decl : Node_Id;
1342 Discr : Entity_Id;
1343 Arg : Node_Id;
1344 Proc : constant Entity_Id := Base_Init_Proc (Typ);
1345 Init_Type : constant Entity_Id := Etype (First_Formal (Proc));
1346 Full_Init_Type : constant Entity_Id := Underlying_Type (Init_Type);
1347 Res : constant List_Id := New_List;
1348 Full_Type : Entity_Id := Typ;
1349 Controller_Typ : Entity_Id;
1351 begin
1352 -- Nothing to do if the Init_Proc is null, unless Initialize_Scalars
1353 -- is active (in which case we make the call anyway, since in the
1354 -- actual compiled client it may be non null).
1355 -- Also nothing to do for value types.
1357 if (Is_Null_Init_Proc (Proc) and then not Init_Or_Norm_Scalars)
1358 or else Is_Value_Type (Typ)
1359 or else Is_Value_Type (Component_Type (Typ))
1360 then
1361 return Empty_List;
1362 end if;
1364 -- Go to full view if private type. In the case of successive
1365 -- private derivations, this can require more than one step.
1367 while Is_Private_Type (Full_Type)
1368 and then Present (Full_View (Full_Type))
1369 loop
1370 Full_Type := Full_View (Full_Type);
1371 end loop;
1373 -- If Typ is derived, the procedure is the initialization procedure for
1374 -- the root type. Wrap the argument in an conversion to make it type
1375 -- honest. Actually it isn't quite type honest, because there can be
1376 -- conflicts of views in the private type case. That is why we set
1377 -- Conversion_OK in the conversion node.
1379 if (Is_Record_Type (Typ)
1380 or else Is_Array_Type (Typ)
1381 or else Is_Private_Type (Typ))
1382 and then Init_Type /= Base_Type (Typ)
1383 then
1384 First_Arg := OK_Convert_To (Etype (Init_Type), Id_Ref);
1385 Set_Etype (First_Arg, Init_Type);
1387 else
1388 First_Arg := Id_Ref;
1389 end if;
1391 Args := New_List (Convert_Concurrent (First_Arg, Typ));
1393 -- In the tasks case, add _Master as the value of the _Master parameter
1394 -- and _Chain as the value of the _Chain parameter. At the outer level,
1395 -- these will be variables holding the corresponding values obtained
1396 -- from GNARL. At inner levels, they will be the parameters passed down
1397 -- through the outer routines.
1399 if Has_Task (Full_Type) then
1400 if Restriction_Active (No_Task_Hierarchy) then
1402 -- See comments in System.Tasking.Initialization.Init_RTS
1403 -- for the value 3 (should be rtsfindable constant ???)
1405 Append_To (Args, Make_Integer_Literal (Loc, 3));
1407 else
1408 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1409 end if;
1411 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1413 -- Ada 2005 (AI-287): In case of default initialized components
1414 -- with tasks, we generate a null string actual parameter.
1415 -- This is just a workaround that must be improved later???
1417 if With_Default_Init then
1418 Append_To (Args,
1419 Make_String_Literal (Loc,
1420 Strval => ""));
1422 else
1423 Decls :=
1424 Build_Task_Image_Decls (Loc, Id_Ref, Enclos_Type, In_Init_Proc);
1425 Decl := Last (Decls);
1427 Append_To (Args,
1428 New_Occurrence_Of (Defining_Identifier (Decl), Loc));
1429 Append_List (Decls, Res);
1430 end if;
1432 else
1433 Decls := No_List;
1434 Decl := Empty;
1435 end if;
1437 -- Add discriminant values if discriminants are present
1439 if Has_Discriminants (Full_Init_Type) then
1440 Discr := First_Discriminant (Full_Init_Type);
1442 while Present (Discr) loop
1444 -- If this is a discriminated concurrent type, the init_proc
1445 -- for the corresponding record is being called. Use that type
1446 -- directly to find the discriminant value, to handle properly
1447 -- intervening renamed discriminants.
1449 declare
1450 T : Entity_Id := Full_Type;
1452 begin
1453 if Is_Protected_Type (T) then
1454 T := Corresponding_Record_Type (T);
1456 elsif Is_Private_Type (T)
1457 and then Present (Underlying_Full_View (T))
1458 and then Is_Protected_Type (Underlying_Full_View (T))
1459 then
1460 T := Corresponding_Record_Type (Underlying_Full_View (T));
1461 end if;
1463 Arg :=
1464 Get_Discriminant_Value (
1465 Discr,
1467 Discriminant_Constraint (Full_Type));
1468 end;
1470 if In_Init_Proc then
1472 -- Replace any possible references to the discriminant in the
1473 -- call to the record initialization procedure with references
1474 -- to the appropriate formal parameter.
1476 if Nkind (Arg) = N_Identifier
1477 and then Ekind (Entity (Arg)) = E_Discriminant
1478 then
1479 Arg := New_Reference_To (Discriminal (Entity (Arg)), Loc);
1481 -- Case of access discriminants. We replace the reference
1482 -- to the type by a reference to the actual object
1484 elsif Nkind (Arg) = N_Attribute_Reference
1485 and then Is_Access_Type (Etype (Arg))
1486 and then Is_Entity_Name (Prefix (Arg))
1487 and then Is_Type (Entity (Prefix (Arg)))
1488 then
1489 Arg :=
1490 Make_Attribute_Reference (Loc,
1491 Prefix => New_Copy (Prefix (Id_Ref)),
1492 Attribute_Name => Name_Unrestricted_Access);
1494 -- Otherwise make a copy of the default expression. Note that
1495 -- we use the current Sloc for this, because we do not want the
1496 -- call to appear to be at the declaration point. Within the
1497 -- expression, replace discriminants with their discriminals.
1499 else
1500 Arg :=
1501 New_Copy_Tree (Arg, Map => Discr_Map, New_Sloc => Loc);
1502 end if;
1504 else
1505 if Is_Constrained (Full_Type) then
1506 Arg := Duplicate_Subexpr_No_Checks (Arg);
1507 else
1508 -- The constraints come from the discriminant default exps,
1509 -- they must be reevaluated, so we use New_Copy_Tree but we
1510 -- ensure the proper Sloc (for any embedded calls).
1512 Arg := New_Copy_Tree (Arg, New_Sloc => Loc);
1513 end if;
1514 end if;
1516 -- Ada 2005 (AI-287) In case of default initialized components,
1517 -- we need to generate the corresponding selected component node
1518 -- to access the discriminant value. In other cases this is not
1519 -- required because we are inside the init proc and we use the
1520 -- corresponding formal.
1522 if With_Default_Init
1523 and then Nkind (Id_Ref) = N_Selected_Component
1524 and then Nkind (Arg) = N_Identifier
1525 then
1526 Append_To (Args,
1527 Make_Selected_Component (Loc,
1528 Prefix => New_Copy_Tree (Prefix (Id_Ref)),
1529 Selector_Name => Arg));
1530 else
1531 Append_To (Args, Arg);
1532 end if;
1534 Next_Discriminant (Discr);
1535 end loop;
1536 end if;
1538 -- If this is a call to initialize the parent component of a derived
1539 -- tagged type, indicate that the tag should not be set in the parent.
1541 if Is_Tagged_Type (Full_Init_Type)
1542 and then not Is_CPP_Class (Full_Init_Type)
1543 and then Nkind (Id_Ref) = N_Selected_Component
1544 and then Chars (Selector_Name (Id_Ref)) = Name_uParent
1545 then
1546 Append_To (Args, New_Occurrence_Of (Standard_False, Loc));
1547 end if;
1549 Append_To (Res,
1550 Make_Procedure_Call_Statement (Loc,
1551 Name => New_Occurrence_Of (Proc, Loc),
1552 Parameter_Associations => Args));
1554 if Controlled_Type (Typ)
1555 and then Nkind (Id_Ref) = N_Selected_Component
1556 then
1557 if Chars (Selector_Name (Id_Ref)) /= Name_uParent then
1558 Append_List_To (Res,
1559 Make_Init_Call (
1560 Ref => New_Copy_Tree (First_Arg),
1561 Typ => Typ,
1562 Flist_Ref =>
1563 Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1564 With_Attach => Make_Integer_Literal (Loc, 1)));
1566 -- If the enclosing type is an extension with new controlled
1567 -- components, it has his own record controller. If the parent
1568 -- also had a record controller, attach it to the new one.
1570 -- Build_Init_Statements relies on the fact that in this specific
1571 -- case the last statement of the result is the attach call to
1572 -- the controller. If this is changed, it must be synchronized.
1574 elsif Present (Enclos_Type)
1575 and then Has_New_Controlled_Component (Enclos_Type)
1576 and then Has_Controlled_Component (Typ)
1577 then
1578 if Is_Inherently_Limited_Type (Typ) then
1579 Controller_Typ := RTE (RE_Limited_Record_Controller);
1580 else
1581 Controller_Typ := RTE (RE_Record_Controller);
1582 end if;
1584 Append_List_To (Res,
1585 Make_Init_Call (
1586 Ref =>
1587 Make_Selected_Component (Loc,
1588 Prefix => New_Copy_Tree (First_Arg),
1589 Selector_Name => Make_Identifier (Loc, Name_uController)),
1590 Typ => Controller_Typ,
1591 Flist_Ref => Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1592 With_Attach => Make_Integer_Literal (Loc, 1)));
1593 end if;
1594 end if;
1596 return Res;
1598 exception
1599 when RE_Not_Available =>
1600 return Empty_List;
1601 end Build_Initialization_Call;
1603 ---------------------------
1604 -- Build_Master_Renaming --
1605 ---------------------------
1607 function Build_Master_Renaming
1608 (N : Node_Id;
1609 T : Entity_Id) return Entity_Id
1611 Loc : constant Source_Ptr := Sloc (N);
1612 M_Id : Entity_Id;
1613 Decl : Node_Id;
1615 begin
1616 -- Nothing to do if there is no task hierarchy
1618 if Restriction_Active (No_Task_Hierarchy) then
1619 return Empty;
1620 end if;
1622 M_Id :=
1623 Make_Defining_Identifier (Loc,
1624 New_External_Name (Chars (T), 'M'));
1626 Decl :=
1627 Make_Object_Renaming_Declaration (Loc,
1628 Defining_Identifier => M_Id,
1629 Subtype_Mark => New_Reference_To (RTE (RE_Master_Id), Loc),
1630 Name => Make_Identifier (Loc, Name_uMaster));
1631 Insert_Before (N, Decl);
1632 Analyze (Decl);
1633 return M_Id;
1635 exception
1636 when RE_Not_Available =>
1637 return Empty;
1638 end Build_Master_Renaming;
1640 ---------------------------
1641 -- Build_Master_Renaming --
1642 ---------------------------
1644 procedure Build_Master_Renaming (N : Node_Id; T : Entity_Id) is
1645 M_Id : Entity_Id;
1647 begin
1648 -- Nothing to do if there is no task hierarchy
1650 if Restriction_Active (No_Task_Hierarchy) then
1651 return;
1652 end if;
1654 M_Id := Build_Master_Renaming (N, T);
1655 Set_Master_Id (T, M_Id);
1657 exception
1658 when RE_Not_Available =>
1659 return;
1660 end Build_Master_Renaming;
1662 ----------------------------
1663 -- Build_Record_Init_Proc --
1664 ----------------------------
1666 procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id) is
1667 Loc : Source_Ptr := Sloc (N);
1668 Discr_Map : constant Elist_Id := New_Elmt_List;
1669 Proc_Id : Entity_Id;
1670 Rec_Type : Entity_Id;
1671 Set_Tag : Entity_Id := Empty;
1673 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id;
1674 -- Build a assignment statement node which assigns to record component
1675 -- its default expression if defined. The assignment left hand side is
1676 -- marked Assignment_OK so that initialization of limited private
1677 -- records works correctly, Return also the adjustment call for
1678 -- controlled objects
1680 procedure Build_Discriminant_Assignments (Statement_List : List_Id);
1681 -- If the record has discriminants, adds assignment statements to
1682 -- statement list to initialize the discriminant values from the
1683 -- arguments of the initialization procedure.
1685 function Build_Init_Statements (Comp_List : Node_Id) return List_Id;
1686 -- Build a list representing a sequence of statements which initialize
1687 -- components of the given component list. This may involve building
1688 -- case statements for the variant parts.
1690 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id;
1691 -- Given a non-tagged type-derivation that declares discriminants,
1692 -- such as
1694 -- type R (R1, R2 : Integer) is record ... end record;
1696 -- type D (D1 : Integer) is new R (1, D1);
1698 -- we make the _init_proc of D be
1700 -- procedure _init_proc(X : D; D1 : Integer) is
1701 -- begin
1702 -- _init_proc( R(X), 1, D1);
1703 -- end _init_proc;
1705 -- This function builds the call statement in this _init_proc.
1707 procedure Build_Init_Procedure;
1708 -- Build the tree corresponding to the procedure specification and body
1709 -- of the initialization procedure (by calling all the preceding
1710 -- auxiliary routines), and install it as the _init TSS.
1712 procedure Build_Offset_To_Top_Functions;
1713 -- Ada 2005 (AI-251): Build the tree corresponding to the procedure spec
1714 -- and body of the Offset_To_Top function that is generated when the
1715 -- parent of a type with discriminants has secondary dispatch tables.
1717 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id);
1718 -- Add range checks to components of discriminated records. S is a
1719 -- subtype indication of a record component. Check_List is a list
1720 -- to which the check actions are appended.
1722 function Component_Needs_Simple_Initialization
1723 (T : Entity_Id) return Boolean;
1724 -- Determines if a component needs simple initialization, given its type
1725 -- T. This is the same as Needs_Simple_Initialization except for the
1726 -- following difference: the types Tag and Interface_Tag, that are
1727 -- access types which would normally require simple initialization to
1728 -- null, do not require initialization as components, since they are
1729 -- explicitly initialized by other means.
1731 procedure Constrain_Array
1732 (SI : Node_Id;
1733 Check_List : List_Id);
1734 -- Called from Build_Record_Checks.
1735 -- Apply a list of index constraints to an unconstrained array type.
1736 -- The first parameter is the entity for the resulting subtype.
1737 -- Check_List is a list to which the check actions are appended.
1739 procedure Constrain_Index
1740 (Index : Node_Id;
1741 S : Node_Id;
1742 Check_List : List_Id);
1743 -- Process an index constraint in a constrained array declaration.
1744 -- The constraint can be a subtype name, or a range with or without
1745 -- an explicit subtype mark. The index is the corresponding index of the
1746 -- unconstrained array. S is the range expression. Check_List is a list
1747 -- to which the check actions are appended (called from
1748 -- Build_Record_Checks).
1750 function Parent_Subtype_Renaming_Discrims return Boolean;
1751 -- Returns True for base types N that rename discriminants, else False
1753 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean;
1754 -- Determines whether a record initialization procedure needs to be
1755 -- generated for the given record type.
1757 ----------------------
1758 -- Build_Assignment --
1759 ----------------------
1761 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id is
1762 Exp : Node_Id := N;
1763 Lhs : Node_Id;
1764 Typ : constant Entity_Id := Underlying_Type (Etype (Id));
1765 Kind : Node_Kind := Nkind (N);
1766 Res : List_Id;
1768 begin
1769 Loc := Sloc (N);
1770 Lhs :=
1771 Make_Selected_Component (Loc,
1772 Prefix => Make_Identifier (Loc, Name_uInit),
1773 Selector_Name => New_Occurrence_Of (Id, Loc));
1774 Set_Assignment_OK (Lhs);
1776 -- Case of an access attribute applied to the current instance.
1777 -- Replace the reference to the type by a reference to the actual
1778 -- object. (Note that this handles the case of the top level of
1779 -- the expression being given by such an attribute, but does not
1780 -- cover uses nested within an initial value expression. Nested
1781 -- uses are unlikely to occur in practice, but are theoretically
1782 -- possible. It is not clear how to handle them without fully
1783 -- traversing the expression. ???
1785 if Kind = N_Attribute_Reference
1786 and then (Attribute_Name (N) = Name_Unchecked_Access
1787 or else
1788 Attribute_Name (N) = Name_Unrestricted_Access)
1789 and then Is_Entity_Name (Prefix (N))
1790 and then Is_Type (Entity (Prefix (N)))
1791 and then Entity (Prefix (N)) = Rec_Type
1792 then
1793 Exp :=
1794 Make_Attribute_Reference (Loc,
1795 Prefix => Make_Identifier (Loc, Name_uInit),
1796 Attribute_Name => Name_Unrestricted_Access);
1797 end if;
1799 -- Ada 2005 (AI-231): Add the run-time check if required
1801 if Ada_Version >= Ada_05
1802 and then Can_Never_Be_Null (Etype (Id)) -- Lhs
1803 then
1804 if Known_Null (Exp) then
1805 return New_List (
1806 Make_Raise_Constraint_Error (Sloc (Exp),
1807 Reason => CE_Null_Not_Allowed));
1809 elsif Present (Etype (Exp))
1810 and then not Can_Never_Be_Null (Etype (Exp))
1811 then
1812 Install_Null_Excluding_Check (Exp);
1813 end if;
1814 end if;
1816 -- Take a copy of Exp to ensure that later copies of this component
1817 -- declaration in derived types see the original tree, not a node
1818 -- rewritten during expansion of the init_proc.
1820 Exp := New_Copy_Tree (Exp);
1822 Res := New_List (
1823 Make_Assignment_Statement (Loc,
1824 Name => Lhs,
1825 Expression => Exp));
1827 Set_No_Ctrl_Actions (First (Res));
1829 -- Adjust the tag if tagged (because of possible view conversions).
1830 -- Suppress the tag adjustment when VM_Target because VM tags are
1831 -- represented implicitly in objects.
1833 if Is_Tagged_Type (Typ) and then VM_Target = No_VM then
1834 Append_To (Res,
1835 Make_Assignment_Statement (Loc,
1836 Name =>
1837 Make_Selected_Component (Loc,
1838 Prefix => New_Copy_Tree (Lhs),
1839 Selector_Name =>
1840 New_Reference_To (First_Tag_Component (Typ), Loc)),
1842 Expression =>
1843 Unchecked_Convert_To (RTE (RE_Tag),
1844 New_Reference_To
1845 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc))));
1846 end if;
1848 -- Adjust the component if controlled except if it is an aggregate
1849 -- that will be expanded inline
1851 if Kind = N_Qualified_Expression then
1852 Kind := Nkind (Expression (N));
1853 end if;
1855 if Controlled_Type (Typ)
1856 and then not (Kind = N_Aggregate or else Kind = N_Extension_Aggregate)
1857 and then not Is_Inherently_Limited_Type (Typ)
1858 then
1859 Append_List_To (Res,
1860 Make_Adjust_Call (
1861 Ref => New_Copy_Tree (Lhs),
1862 Typ => Etype (Id),
1863 Flist_Ref =>
1864 Find_Final_List (Etype (Id), New_Copy_Tree (Lhs)),
1865 With_Attach => Make_Integer_Literal (Loc, 1)));
1866 end if;
1868 return Res;
1870 exception
1871 when RE_Not_Available =>
1872 return Empty_List;
1873 end Build_Assignment;
1875 ------------------------------------
1876 -- Build_Discriminant_Assignments --
1877 ------------------------------------
1879 procedure Build_Discriminant_Assignments (Statement_List : List_Id) is
1880 D : Entity_Id;
1881 Is_Tagged : constant Boolean := Is_Tagged_Type (Rec_Type);
1883 begin
1884 if Has_Discriminants (Rec_Type)
1885 and then not Is_Unchecked_Union (Rec_Type)
1886 then
1887 D := First_Discriminant (Rec_Type);
1889 while Present (D) loop
1890 -- Don't generate the assignment for discriminants in derived
1891 -- tagged types if the discriminant is a renaming of some
1892 -- ancestor discriminant. This initialization will be done
1893 -- when initializing the _parent field of the derived record.
1895 if Is_Tagged and then
1896 Present (Corresponding_Discriminant (D))
1897 then
1898 null;
1900 else
1901 Loc := Sloc (D);
1902 Append_List_To (Statement_List,
1903 Build_Assignment (D,
1904 New_Reference_To (Discriminal (D), Loc)));
1905 end if;
1907 Next_Discriminant (D);
1908 end loop;
1909 end if;
1910 end Build_Discriminant_Assignments;
1912 --------------------------
1913 -- Build_Init_Call_Thru --
1914 --------------------------
1916 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id is
1917 Parent_Proc : constant Entity_Id :=
1918 Base_Init_Proc (Etype (Rec_Type));
1920 Parent_Type : constant Entity_Id :=
1921 Etype (First_Formal (Parent_Proc));
1923 Uparent_Type : constant Entity_Id :=
1924 Underlying_Type (Parent_Type);
1926 First_Discr_Param : Node_Id;
1928 Parent_Discr : Entity_Id;
1929 First_Arg : Node_Id;
1930 Args : List_Id;
1931 Arg : Node_Id;
1932 Res : List_Id;
1934 begin
1935 -- First argument (_Init) is the object to be initialized.
1936 -- ??? not sure where to get a reasonable Loc for First_Arg
1938 First_Arg :=
1939 OK_Convert_To (Parent_Type,
1940 New_Reference_To (Defining_Identifier (First (Parameters)), Loc));
1942 Set_Etype (First_Arg, Parent_Type);
1944 Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
1946 -- In the tasks case,
1947 -- add _Master as the value of the _Master parameter
1948 -- add _Chain as the value of the _Chain parameter.
1949 -- add _Task_Name as the value of the _Task_Name parameter.
1950 -- At the outer level, these will be variables holding the
1951 -- corresponding values obtained from GNARL or the expander.
1953 -- At inner levels, they will be the parameters passed down through
1954 -- the outer routines.
1956 First_Discr_Param := Next (First (Parameters));
1958 if Has_Task (Rec_Type) then
1959 if Restriction_Active (No_Task_Hierarchy) then
1961 -- See comments in System.Tasking.Initialization.Init_RTS
1962 -- for the value 3.
1964 Append_To (Args, Make_Integer_Literal (Loc, 3));
1965 else
1966 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1967 end if;
1969 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1970 Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
1971 First_Discr_Param := Next (Next (Next (First_Discr_Param)));
1972 end if;
1974 -- Append discriminant values
1976 if Has_Discriminants (Uparent_Type) then
1977 pragma Assert (not Is_Tagged_Type (Uparent_Type));
1979 Parent_Discr := First_Discriminant (Uparent_Type);
1980 while Present (Parent_Discr) loop
1982 -- Get the initial value for this discriminant
1983 -- ??? needs to be cleaned up to use parent_Discr_Constr
1984 -- directly.
1986 declare
1987 Discr_Value : Elmt_Id :=
1988 First_Elmt
1989 (Stored_Constraint (Rec_Type));
1991 Discr : Entity_Id :=
1992 First_Stored_Discriminant (Uparent_Type);
1993 begin
1994 while Original_Record_Component (Parent_Discr) /= Discr loop
1995 Next_Stored_Discriminant (Discr);
1996 Next_Elmt (Discr_Value);
1997 end loop;
1999 Arg := Node (Discr_Value);
2000 end;
2002 -- Append it to the list
2004 if Nkind (Arg) = N_Identifier
2005 and then Ekind (Entity (Arg)) = E_Discriminant
2006 then
2007 Append_To (Args,
2008 New_Reference_To (Discriminal (Entity (Arg)), Loc));
2010 -- Case of access discriminants. We replace the reference
2011 -- to the type by a reference to the actual object.
2013 -- Is above comment right??? Use of New_Copy below seems mighty
2014 -- suspicious ???
2016 else
2017 Append_To (Args, New_Copy (Arg));
2018 end if;
2020 Next_Discriminant (Parent_Discr);
2021 end loop;
2022 end if;
2024 Res :=
2025 New_List (
2026 Make_Procedure_Call_Statement (Loc,
2027 Name => New_Occurrence_Of (Parent_Proc, Loc),
2028 Parameter_Associations => Args));
2030 return Res;
2031 end Build_Init_Call_Thru;
2033 -----------------------------------
2034 -- Build_Offset_To_Top_Functions --
2035 -----------------------------------
2037 procedure Build_Offset_To_Top_Functions is
2039 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id);
2040 -- Generate:
2041 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2042 -- begin
2043 -- return O.Iface_Comp'Position;
2044 -- end Fxx;
2046 ------------------------------
2047 -- Build_Offset_To_Top_Body --
2048 ------------------------------
2050 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id) is
2051 Body_Node : Node_Id;
2052 Func_Id : Entity_Id;
2053 Spec_Node : Node_Id;
2055 begin
2056 Func_Id :=
2057 Make_Defining_Identifier (Loc,
2058 Chars => New_Internal_Name ('F'));
2060 Set_DT_Offset_To_Top_Func (Iface_Comp, Func_Id);
2062 -- Generate
2063 -- function Fxx (O : in Rec_Typ) return Storage_Offset;
2065 Spec_Node := New_Node (N_Function_Specification, Loc);
2066 Set_Defining_Unit_Name (Spec_Node, Func_Id);
2067 Set_Parameter_Specifications (Spec_Node, New_List (
2068 Make_Parameter_Specification (Loc,
2069 Defining_Identifier => Make_Defining_Identifier (Loc, Name_uO),
2070 In_Present => True,
2071 Parameter_Type => New_Reference_To (Rec_Type, Loc))));
2072 Set_Result_Definition (Spec_Node,
2073 New_Reference_To (RTE (RE_Storage_Offset), Loc));
2075 -- Generate
2076 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2077 -- begin
2078 -- return O.Iface_Comp'Position;
2079 -- end Fxx;
2081 Body_Node := New_Node (N_Subprogram_Body, Loc);
2082 Set_Specification (Body_Node, Spec_Node);
2083 Set_Declarations (Body_Node, New_List);
2084 Set_Handled_Statement_Sequence (Body_Node,
2085 Make_Handled_Sequence_Of_Statements (Loc,
2086 Statements => New_List (
2087 Make_Simple_Return_Statement (Loc,
2088 Expression =>
2089 Make_Attribute_Reference (Loc,
2090 Prefix =>
2091 Make_Selected_Component (Loc,
2092 Prefix => Make_Identifier (Loc, Name_uO),
2093 Selector_Name => New_Reference_To
2094 (Iface_Comp, Loc)),
2095 Attribute_Name => Name_Position)))));
2097 Set_Ekind (Func_Id, E_Function);
2098 Set_Mechanism (Func_Id, Default_Mechanism);
2099 Set_Is_Internal (Func_Id, True);
2101 if not Debug_Generated_Code then
2102 Set_Debug_Info_Off (Func_Id);
2103 end if;
2105 Analyze (Body_Node);
2107 Append_Freeze_Action (Rec_Type, Body_Node);
2108 end Build_Offset_To_Top_Function;
2110 -- Local variables
2112 Ifaces_List : Elist_Id;
2113 Ifaces_Comp_List : Elist_Id;
2114 Ifaces_Tag_List : Elist_Id;
2115 Iface_Elmt : Elmt_Id;
2116 Comp_Elmt : Elmt_Id;
2118 pragma Warnings (Off, Ifaces_Tag_List);
2120 -- Start of processing for Build_Offset_To_Top_Functions
2122 begin
2123 -- Offset_To_Top_Functions are built only for derivations of types
2124 -- with discriminants that cover interface types.
2125 -- Nothing is needed either in case of virtual machines, since
2126 -- interfaces are handled directly by the VM.
2128 if not Is_Tagged_Type (Rec_Type)
2129 or else Etype (Rec_Type) = Rec_Type
2130 or else not Has_Discriminants (Etype (Rec_Type))
2131 or else VM_Target /= No_VM
2132 then
2133 return;
2134 end if;
2136 Collect_Interfaces_Info
2137 (Rec_Type, Ifaces_List, Ifaces_Comp_List, Ifaces_Tag_List);
2139 -- For each interface type with secondary dispatch table we generate
2140 -- the Offset_To_Top_Functions (required to displace the pointer in
2141 -- interface conversions)
2143 Iface_Elmt := First_Elmt (Ifaces_List);
2144 Comp_Elmt := First_Elmt (Ifaces_Comp_List);
2145 while Present (Iface_Elmt) loop
2147 -- If the interface is a parent of Rec_Type it shares the primary
2148 -- dispatch table and hence there is no need to build the function
2150 if not Is_Parent (Node (Iface_Elmt), Rec_Type) then
2151 Build_Offset_To_Top_Function (Iface_Comp => Node (Comp_Elmt));
2152 end if;
2154 Next_Elmt (Iface_Elmt);
2155 Next_Elmt (Comp_Elmt);
2156 end loop;
2157 end Build_Offset_To_Top_Functions;
2159 --------------------------
2160 -- Build_Init_Procedure --
2161 --------------------------
2163 procedure Build_Init_Procedure is
2164 Body_Node : Node_Id;
2165 Handled_Stmt_Node : Node_Id;
2166 Parameters : List_Id;
2167 Proc_Spec_Node : Node_Id;
2168 Body_Stmts : List_Id;
2169 Record_Extension_Node : Node_Id;
2170 Init_Tags_List : List_Id;
2172 begin
2173 Body_Stmts := New_List;
2174 Body_Node := New_Node (N_Subprogram_Body, Loc);
2176 Proc_Id :=
2177 Make_Defining_Identifier (Loc,
2178 Chars => Make_Init_Proc_Name (Rec_Type));
2179 Set_Ekind (Proc_Id, E_Procedure);
2181 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2182 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2184 Parameters := Init_Formals (Rec_Type);
2185 Append_List_To (Parameters,
2186 Build_Discriminant_Formals (Rec_Type, True));
2188 -- For tagged types, we add a flag to indicate whether the routine
2189 -- is called to initialize a parent component in the init_proc of
2190 -- a type extension. If the flag is false, we do not set the tag
2191 -- because it has been set already in the extension.
2193 if Is_Tagged_Type (Rec_Type)
2194 and then not Is_CPP_Class (Rec_Type)
2195 then
2196 Set_Tag :=
2197 Make_Defining_Identifier (Loc,
2198 Chars => New_Internal_Name ('P'));
2200 Append_To (Parameters,
2201 Make_Parameter_Specification (Loc,
2202 Defining_Identifier => Set_Tag,
2203 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
2204 Expression => New_Occurrence_Of (Standard_True, Loc)));
2205 end if;
2207 Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
2208 Set_Specification (Body_Node, Proc_Spec_Node);
2209 Set_Declarations (Body_Node, New_List);
2211 if Parent_Subtype_Renaming_Discrims then
2213 -- N is a Derived_Type_Definition that renames the parameters
2214 -- of the ancestor type. We initialize it by expanding our
2215 -- discriminants and call the ancestor _init_proc with a
2216 -- type-converted object
2218 Append_List_To (Body_Stmts,
2219 Build_Init_Call_Thru (Parameters));
2221 elsif Nkind (Type_Definition (N)) = N_Record_Definition then
2222 Build_Discriminant_Assignments (Body_Stmts);
2224 if not Null_Present (Type_Definition (N)) then
2225 Append_List_To (Body_Stmts,
2226 Build_Init_Statements (
2227 Component_List (Type_Definition (N))));
2228 end if;
2230 else
2231 -- N is a Derived_Type_Definition with a possible non-empty
2232 -- extension. The initialization of a type extension consists
2233 -- in the initialization of the components in the extension.
2235 Build_Discriminant_Assignments (Body_Stmts);
2237 Record_Extension_Node :=
2238 Record_Extension_Part (Type_Definition (N));
2240 if not Null_Present (Record_Extension_Node) then
2241 declare
2242 Stmts : constant List_Id :=
2243 Build_Init_Statements (
2244 Component_List (Record_Extension_Node));
2246 begin
2247 -- The parent field must be initialized first because
2248 -- the offset of the new discriminants may depend on it
2250 Prepend_To (Body_Stmts, Remove_Head (Stmts));
2251 Append_List_To (Body_Stmts, Stmts);
2252 end;
2253 end if;
2254 end if;
2256 -- Add here the assignment to instantiate the Tag
2258 -- The assignment corresponds to the code:
2260 -- _Init._Tag := Typ'Tag;
2262 -- Suppress the tag assignment when VM_Target because VM tags are
2263 -- represented implicitly in objects. It is also suppressed in case
2264 -- of CPP_Class types because in this case the tag is initialized in
2265 -- the C++ side.
2267 if Is_Tagged_Type (Rec_Type)
2268 and then not Is_CPP_Class (Rec_Type)
2269 and then VM_Target = No_VM
2270 and then not No_Run_Time_Mode
2271 then
2272 -- Initialize the primary tag
2274 Init_Tags_List := New_List (
2275 Make_Assignment_Statement (Loc,
2276 Name =>
2277 Make_Selected_Component (Loc,
2278 Prefix => Make_Identifier (Loc, Name_uInit),
2279 Selector_Name =>
2280 New_Reference_To (First_Tag_Component (Rec_Type), Loc)),
2282 Expression =>
2283 New_Reference_To
2284 (Node (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2286 -- Ada 2005 (AI-251): Initialize the secondary tags components
2287 -- located at fixed positions (tags whose position depends on
2288 -- variable size components are initialized later ---see below).
2290 if Ada_Version >= Ada_05
2291 and then not Is_Interface (Rec_Type)
2292 and then Has_Abstract_Interfaces (Rec_Type)
2293 then
2294 Init_Secondary_Tags
2295 (Typ => Rec_Type,
2296 Target => Make_Identifier (Loc, Name_uInit),
2297 Stmts_List => Init_Tags_List,
2298 Fixed_Comps => True,
2299 Variable_Comps => False);
2300 end if;
2302 -- The tag must be inserted before the assignments to other
2303 -- components, because the initial value of the component may
2304 -- depend on the tag (eg. through a dispatching operation on
2305 -- an access to the current type). The tag assignment is not done
2306 -- when initializing the parent component of a type extension,
2307 -- because in that case the tag is set in the extension.
2309 -- Extensions of imported C++ classes add a final complication,
2310 -- because we cannot inhibit tag setting in the constructor for
2311 -- the parent. In that case we insert the tag initialization
2312 -- after the calls to initialize the parent.
2314 if not Is_CPP_Class (Root_Type (Rec_Type)) then
2315 Prepend_To (Body_Stmts,
2316 Make_If_Statement (Loc,
2317 Condition => New_Occurrence_Of (Set_Tag, Loc),
2318 Then_Statements => Init_Tags_List));
2320 -- CPP_Class derivation: In this case the dispatch table of the
2321 -- parent was built in the C++ side and we copy the table of the
2322 -- parent to initialize the new dispatch table.
2324 else
2325 declare
2326 Nod : Node_Id;
2328 begin
2329 -- We assume the first init_proc call is for the parent
2331 Nod := First (Body_Stmts);
2332 while Present (Next (Nod))
2333 and then (Nkind (Nod) /= N_Procedure_Call_Statement
2334 or else not Is_Init_Proc (Name (Nod)))
2335 loop
2336 Nod := Next (Nod);
2337 end loop;
2339 -- Generate:
2340 -- ancestor_constructor (_init.parent);
2341 -- if Arg2 then
2342 -- inherit_prim_ops (_init._tag, new_dt, num_prims);
2343 -- _init._tag := new_dt;
2344 -- end if;
2346 Prepend_To (Init_Tags_List,
2347 Build_Inherit_Prims (Loc,
2348 Typ => Rec_Type,
2349 Old_Tag_Node =>
2350 Make_Selected_Component (Loc,
2351 Prefix =>
2352 Make_Identifier (Loc,
2353 Chars => Name_uInit),
2354 Selector_Name =>
2355 New_Reference_To
2356 (First_Tag_Component (Rec_Type), Loc)),
2357 New_Tag_Node =>
2358 New_Reference_To
2359 (Node (First_Elmt (Access_Disp_Table (Rec_Type))),
2360 Loc),
2361 Num_Prims =>
2362 UI_To_Int
2363 (DT_Entry_Count (First_Tag_Component (Rec_Type)))));
2365 Insert_After (Nod,
2366 Make_If_Statement (Loc,
2367 Condition => New_Occurrence_Of (Set_Tag, Loc),
2368 Then_Statements => Init_Tags_List));
2370 -- We have inherited table of the parent from the CPP side.
2371 -- Now we fill the slots associated with Ada primitives.
2372 -- This needs more work to avoid its execution each time
2373 -- an object is initialized???
2375 declare
2376 E : Elmt_Id;
2377 Prim : Node_Id;
2379 begin
2380 E := First_Elmt (Primitive_Operations (Rec_Type));
2381 while Present (E) loop
2382 Prim := Node (E);
2384 if not Is_Imported (Prim)
2385 and then Convention (Prim) = Convention_CPP
2386 and then not Present (Abstract_Interface_Alias
2387 (Prim))
2388 then
2389 Register_Primitive (Loc,
2390 Prim => Prim,
2391 Ins_Nod => Last (Init_Tags_List));
2392 end if;
2394 Next_Elmt (E);
2395 end loop;
2396 end;
2397 end;
2398 end if;
2400 -- Ada 2005 (AI-251): Initialize the secondary tag components
2401 -- located at variable positions. We delay the generation of this
2402 -- code until here because the value of the attribute 'Position
2403 -- applied to variable size components of the parent type that
2404 -- depend on discriminants is only safely read at runtime after
2405 -- the parent components have been initialized.
2407 if Ada_Version >= Ada_05
2408 and then not Is_Interface (Rec_Type)
2409 and then Has_Abstract_Interfaces (Rec_Type)
2410 and then Has_Discriminants (Etype (Rec_Type))
2411 and then Is_Variable_Size_Record (Etype (Rec_Type))
2412 then
2413 Init_Tags_List := New_List;
2415 Init_Secondary_Tags
2416 (Typ => Rec_Type,
2417 Target => Make_Identifier (Loc, Name_uInit),
2418 Stmts_List => Init_Tags_List,
2419 Fixed_Comps => False,
2420 Variable_Comps => True);
2422 if Is_Non_Empty_List (Init_Tags_List) then
2423 Append_List_To (Body_Stmts, Init_Tags_List);
2424 end if;
2425 end if;
2426 end if;
2428 Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
2429 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2430 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2431 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2433 if not Debug_Generated_Code then
2434 Set_Debug_Info_Off (Proc_Id);
2435 end if;
2437 -- Associate Init_Proc with type, and determine if the procedure
2438 -- is null (happens because of the Initialize_Scalars pragma case,
2439 -- where we have to generate a null procedure in case it is called
2440 -- by a client with Initialize_Scalars set). Such procedures have
2441 -- to be generated, but do not have to be called, so we mark them
2442 -- as null to suppress the call.
2444 Set_Init_Proc (Rec_Type, Proc_Id);
2446 if List_Length (Body_Stmts) = 1
2447 and then Nkind (First (Body_Stmts)) = N_Null_Statement
2448 and then VM_Target /= CLI_Target
2449 then
2450 -- Even though the init proc may be null at this time it might get
2451 -- some stuff added to it later by the CIL backend, so always keep
2452 -- it when VM_Target = CLI_Target.
2454 Set_Is_Null_Init_Proc (Proc_Id);
2455 end if;
2456 end Build_Init_Procedure;
2458 ---------------------------
2459 -- Build_Init_Statements --
2460 ---------------------------
2462 function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
2463 Check_List : constant List_Id := New_List;
2464 Alt_List : List_Id;
2465 Statement_List : List_Id;
2466 Stmts : List_Id;
2468 Per_Object_Constraint_Components : Boolean;
2470 Decl : Node_Id;
2471 Variant : Node_Id;
2473 Id : Entity_Id;
2474 Typ : Entity_Id;
2476 function Has_Access_Constraint (E : Entity_Id) return Boolean;
2477 -- Components with access discriminants that depend on the current
2478 -- instance must be initialized after all other components.
2480 ---------------------------
2481 -- Has_Access_Constraint --
2482 ---------------------------
2484 function Has_Access_Constraint (E : Entity_Id) return Boolean is
2485 Disc : Entity_Id;
2486 T : constant Entity_Id := Etype (E);
2488 begin
2489 if Has_Per_Object_Constraint (E)
2490 and then Has_Discriminants (T)
2491 then
2492 Disc := First_Discriminant (T);
2493 while Present (Disc) loop
2494 if Is_Access_Type (Etype (Disc)) then
2495 return True;
2496 end if;
2498 Next_Discriminant (Disc);
2499 end loop;
2501 return False;
2502 else
2503 return False;
2504 end if;
2505 end Has_Access_Constraint;
2507 -- Start of processing for Build_Init_Statements
2509 begin
2510 if Null_Present (Comp_List) then
2511 return New_List (Make_Null_Statement (Loc));
2512 end if;
2514 Statement_List := New_List;
2516 -- Loop through components, skipping pragmas, in 2 steps. The first
2517 -- step deals with regular components. The second step deals with
2518 -- components have per object constraints, and no explicit initia-
2519 -- lization.
2521 Per_Object_Constraint_Components := False;
2523 -- First step : regular components
2525 Decl := First_Non_Pragma (Component_Items (Comp_List));
2526 while Present (Decl) loop
2527 Loc := Sloc (Decl);
2528 Build_Record_Checks
2529 (Subtype_Indication (Component_Definition (Decl)), Check_List);
2531 Id := Defining_Identifier (Decl);
2532 Typ := Etype (Id);
2534 if Has_Access_Constraint (Id)
2535 and then No (Expression (Decl))
2536 then
2537 -- Skip processing for now and ask for a second pass
2539 Per_Object_Constraint_Components := True;
2541 else
2542 -- Case of explicit initialization
2544 if Present (Expression (Decl)) then
2545 Stmts := Build_Assignment (Id, Expression (Decl));
2547 -- Case of composite component with its own Init_Proc
2549 elsif not Is_Interface (Typ)
2550 and then Has_Non_Null_Base_Init_Proc (Typ)
2551 then
2552 Stmts :=
2553 Build_Initialization_Call
2554 (Loc,
2555 Make_Selected_Component (Loc,
2556 Prefix => Make_Identifier (Loc, Name_uInit),
2557 Selector_Name => New_Occurrence_Of (Id, Loc)),
2558 Typ,
2559 In_Init_Proc => True,
2560 Enclos_Type => Rec_Type,
2561 Discr_Map => Discr_Map);
2563 Clean_Task_Names (Typ, Proc_Id);
2565 -- Case of component needing simple initialization
2567 elsif Component_Needs_Simple_Initialization (Typ) then
2568 Stmts :=
2569 Build_Assignment
2570 (Id, Get_Simple_Init_Val (Typ, Loc, Esize (Id)));
2572 -- Nothing needed for this case
2574 else
2575 Stmts := No_List;
2576 end if;
2578 if Present (Check_List) then
2579 Append_List_To (Statement_List, Check_List);
2580 end if;
2582 if Present (Stmts) then
2584 -- Add the initialization of the record controller before
2585 -- the _Parent field is attached to it when the attachment
2586 -- can occur. It does not work to simply initialize the
2587 -- controller first: it must be initialized after the parent
2588 -- if the parent holds discriminants that can be used to
2589 -- compute the offset of the controller. We assume here that
2590 -- the last statement of the initialization call is the
2591 -- attachment of the parent (see Build_Initialization_Call)
2593 if Chars (Id) = Name_uController
2594 and then Rec_Type /= Etype (Rec_Type)
2595 and then Has_Controlled_Component (Etype (Rec_Type))
2596 and then Has_New_Controlled_Component (Rec_Type)
2597 and then Present (Last (Statement_List))
2598 then
2599 Insert_List_Before (Last (Statement_List), Stmts);
2600 else
2601 Append_List_To (Statement_List, Stmts);
2602 end if;
2603 end if;
2604 end if;
2606 Next_Non_Pragma (Decl);
2607 end loop;
2609 if Per_Object_Constraint_Components then
2611 -- Second pass: components with per-object constraints
2613 Decl := First_Non_Pragma (Component_Items (Comp_List));
2614 while Present (Decl) loop
2615 Loc := Sloc (Decl);
2616 Id := Defining_Identifier (Decl);
2617 Typ := Etype (Id);
2619 if Has_Access_Constraint (Id)
2620 and then No (Expression (Decl))
2621 then
2622 if Has_Non_Null_Base_Init_Proc (Typ) then
2623 Append_List_To (Statement_List,
2624 Build_Initialization_Call (Loc,
2625 Make_Selected_Component (Loc,
2626 Prefix => Make_Identifier (Loc, Name_uInit),
2627 Selector_Name => New_Occurrence_Of (Id, Loc)),
2628 Typ,
2629 In_Init_Proc => True,
2630 Enclos_Type => Rec_Type,
2631 Discr_Map => Discr_Map));
2633 Clean_Task_Names (Typ, Proc_Id);
2635 elsif Component_Needs_Simple_Initialization (Typ) then
2636 Append_List_To (Statement_List,
2637 Build_Assignment
2638 (Id, Get_Simple_Init_Val (Typ, Loc, Esize (Id))));
2639 end if;
2640 end if;
2642 Next_Non_Pragma (Decl);
2643 end loop;
2644 end if;
2646 -- Process the variant part
2648 if Present (Variant_Part (Comp_List)) then
2649 Alt_List := New_List;
2650 Variant := First_Non_Pragma (Variants (Variant_Part (Comp_List)));
2651 while Present (Variant) loop
2652 Loc := Sloc (Variant);
2653 Append_To (Alt_List,
2654 Make_Case_Statement_Alternative (Loc,
2655 Discrete_Choices =>
2656 New_Copy_List (Discrete_Choices (Variant)),
2657 Statements =>
2658 Build_Init_Statements (Component_List (Variant))));
2659 Next_Non_Pragma (Variant);
2660 end loop;
2662 -- The expression of the case statement which is a reference
2663 -- to one of the discriminants is replaced by the appropriate
2664 -- formal parameter of the initialization procedure.
2666 Append_To (Statement_List,
2667 Make_Case_Statement (Loc,
2668 Expression =>
2669 New_Reference_To (Discriminal (
2670 Entity (Name (Variant_Part (Comp_List)))), Loc),
2671 Alternatives => Alt_List));
2672 end if;
2674 -- For a task record type, add the task create call and calls
2675 -- to bind any interrupt (signal) entries.
2677 if Is_Task_Record_Type (Rec_Type) then
2679 -- In the case of the restricted run time the ATCB has already
2680 -- been preallocated.
2682 if Restricted_Profile then
2683 Append_To (Statement_List,
2684 Make_Assignment_Statement (Loc,
2685 Name => Make_Selected_Component (Loc,
2686 Prefix => Make_Identifier (Loc, Name_uInit),
2687 Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
2688 Expression => Make_Attribute_Reference (Loc,
2689 Prefix =>
2690 Make_Selected_Component (Loc,
2691 Prefix => Make_Identifier (Loc, Name_uInit),
2692 Selector_Name =>
2693 Make_Identifier (Loc, Name_uATCB)),
2694 Attribute_Name => Name_Unchecked_Access)));
2695 end if;
2697 Append_To (Statement_List, Make_Task_Create_Call (Rec_Type));
2699 declare
2700 Task_Type : constant Entity_Id :=
2701 Corresponding_Concurrent_Type (Rec_Type);
2702 Task_Decl : constant Node_Id := Parent (Task_Type);
2703 Task_Def : constant Node_Id := Task_Definition (Task_Decl);
2704 Vis_Decl : Node_Id;
2705 Ent : Entity_Id;
2707 begin
2708 if Present (Task_Def) then
2709 Vis_Decl := First (Visible_Declarations (Task_Def));
2710 while Present (Vis_Decl) loop
2711 Loc := Sloc (Vis_Decl);
2713 if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
2714 if Get_Attribute_Id (Chars (Vis_Decl)) =
2715 Attribute_Address
2716 then
2717 Ent := Entity (Name (Vis_Decl));
2719 if Ekind (Ent) = E_Entry then
2720 Append_To (Statement_List,
2721 Make_Procedure_Call_Statement (Loc,
2722 Name => New_Reference_To (
2723 RTE (RE_Bind_Interrupt_To_Entry), Loc),
2724 Parameter_Associations => New_List (
2725 Make_Selected_Component (Loc,
2726 Prefix =>
2727 Make_Identifier (Loc, Name_uInit),
2728 Selector_Name =>
2729 Make_Identifier (Loc, Name_uTask_Id)),
2730 Entry_Index_Expression (
2731 Loc, Ent, Empty, Task_Type),
2732 Expression (Vis_Decl))));
2733 end if;
2734 end if;
2735 end if;
2737 Next (Vis_Decl);
2738 end loop;
2739 end if;
2740 end;
2741 end if;
2743 -- For a protected type, add statements generated by
2744 -- Make_Initialize_Protection.
2746 if Is_Protected_Record_Type (Rec_Type) then
2747 Append_List_To (Statement_List,
2748 Make_Initialize_Protection (Rec_Type));
2749 end if;
2751 -- If no initializations when generated for component declarations
2752 -- corresponding to this Statement_List, append a null statement
2753 -- to the Statement_List to make it a valid Ada tree.
2755 if Is_Empty_List (Statement_List) then
2756 Append (New_Node (N_Null_Statement, Loc), Statement_List);
2757 end if;
2759 return Statement_List;
2761 exception
2762 when RE_Not_Available =>
2763 return Empty_List;
2764 end Build_Init_Statements;
2766 -------------------------
2767 -- Build_Record_Checks --
2768 -------------------------
2770 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
2771 Subtype_Mark_Id : Entity_Id;
2773 begin
2774 if Nkind (S) = N_Subtype_Indication then
2775 Find_Type (Subtype_Mark (S));
2776 Subtype_Mark_Id := Entity (Subtype_Mark (S));
2778 -- Remaining processing depends on type
2780 case Ekind (Subtype_Mark_Id) is
2782 when Array_Kind =>
2783 Constrain_Array (S, Check_List);
2785 when others =>
2786 null;
2787 end case;
2788 end if;
2789 end Build_Record_Checks;
2791 -------------------------------------------
2792 -- Component_Needs_Simple_Initialization --
2793 -------------------------------------------
2795 function Component_Needs_Simple_Initialization
2796 (T : Entity_Id) return Boolean
2798 begin
2799 return
2800 Needs_Simple_Initialization (T)
2801 and then not Is_RTE (T, RE_Tag)
2803 -- Ada 2005 (AI-251): Check also the tag of abstract interfaces
2805 and then not Is_RTE (T, RE_Interface_Tag);
2806 end Component_Needs_Simple_Initialization;
2808 ---------------------
2809 -- Constrain_Array --
2810 ---------------------
2812 procedure Constrain_Array
2813 (SI : Node_Id;
2814 Check_List : List_Id)
2816 C : constant Node_Id := Constraint (SI);
2817 Number_Of_Constraints : Nat := 0;
2818 Index : Node_Id;
2819 S, T : Entity_Id;
2821 begin
2822 T := Entity (Subtype_Mark (SI));
2824 if Ekind (T) in Access_Kind then
2825 T := Designated_Type (T);
2826 end if;
2828 S := First (Constraints (C));
2830 while Present (S) loop
2831 Number_Of_Constraints := Number_Of_Constraints + 1;
2832 Next (S);
2833 end loop;
2835 -- In either case, the index constraint must provide a discrete
2836 -- range for each index of the array type and the type of each
2837 -- discrete range must be the same as that of the corresponding
2838 -- index. (RM 3.6.1)
2840 S := First (Constraints (C));
2841 Index := First_Index (T);
2842 Analyze (Index);
2844 -- Apply constraints to each index type
2846 for J in 1 .. Number_Of_Constraints loop
2847 Constrain_Index (Index, S, Check_List);
2848 Next (Index);
2849 Next (S);
2850 end loop;
2852 end Constrain_Array;
2854 ---------------------
2855 -- Constrain_Index --
2856 ---------------------
2858 procedure Constrain_Index
2859 (Index : Node_Id;
2860 S : Node_Id;
2861 Check_List : List_Id)
2863 T : constant Entity_Id := Etype (Index);
2865 begin
2866 if Nkind (S) = N_Range then
2867 Process_Range_Expr_In_Decl (S, T, Check_List);
2868 end if;
2869 end Constrain_Index;
2871 --------------------------------------
2872 -- Parent_Subtype_Renaming_Discrims --
2873 --------------------------------------
2875 function Parent_Subtype_Renaming_Discrims return Boolean is
2876 De : Entity_Id;
2877 Dp : Entity_Id;
2879 begin
2880 if Base_Type (Pe) /= Pe then
2881 return False;
2882 end if;
2884 if Etype (Pe) = Pe
2885 or else not Has_Discriminants (Pe)
2886 or else Is_Constrained (Pe)
2887 or else Is_Tagged_Type (Pe)
2888 then
2889 return False;
2890 end if;
2892 -- If there are no explicit stored discriminants we have inherited
2893 -- the root type discriminants so far, so no renamings occurred.
2895 if First_Discriminant (Pe) = First_Stored_Discriminant (Pe) then
2896 return False;
2897 end if;
2899 -- Check if we have done some trivial renaming of the parent
2900 -- discriminants, i.e. something like
2902 -- type DT (X1,X2: int) is new PT (X1,X2);
2904 De := First_Discriminant (Pe);
2905 Dp := First_Discriminant (Etype (Pe));
2907 while Present (De) loop
2908 pragma Assert (Present (Dp));
2910 if Corresponding_Discriminant (De) /= Dp then
2911 return True;
2912 end if;
2914 Next_Discriminant (De);
2915 Next_Discriminant (Dp);
2916 end loop;
2918 return Present (Dp);
2919 end Parent_Subtype_Renaming_Discrims;
2921 ------------------------
2922 -- Requires_Init_Proc --
2923 ------------------------
2925 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
2926 Comp_Decl : Node_Id;
2927 Id : Entity_Id;
2928 Typ : Entity_Id;
2930 begin
2931 -- Definitely do not need one if specifically suppressed
2933 if Suppress_Init_Proc (Rec_Id) then
2934 return False;
2935 end if;
2937 -- If it is a type derived from a type with unknown discriminants,
2938 -- we cannot build an initialization procedure for it.
2940 if Has_Unknown_Discriminants (Rec_Id) then
2941 return False;
2942 end if;
2944 -- Otherwise we need to generate an initialization procedure if
2945 -- Is_CPP_Class is False and at least one of the following applies:
2947 -- 1. Discriminants are present, since they need to be initialized
2948 -- with the appropriate discriminant constraint expressions.
2949 -- However, the discriminant of an unchecked union does not
2950 -- count, since the discriminant is not present.
2952 -- 2. The type is a tagged type, since the implicit Tag component
2953 -- needs to be initialized with a pointer to the dispatch table.
2955 -- 3. The type contains tasks
2957 -- 4. One or more components has an initial value
2959 -- 5. One or more components is for a type which itself requires
2960 -- an initialization procedure.
2962 -- 6. One or more components is a type that requires simple
2963 -- initialization (see Needs_Simple_Initialization), except
2964 -- that types Tag and Interface_Tag are excluded, since fields
2965 -- of these types are initialized by other means.
2967 -- 7. The type is the record type built for a task type (since at
2968 -- the very least, Create_Task must be called)
2970 -- 8. The type is the record type built for a protected type (since
2971 -- at least Initialize_Protection must be called)
2973 -- 9. The type is marked as a public entity. The reason we add this
2974 -- case (even if none of the above apply) is to properly handle
2975 -- Initialize_Scalars. If a package is compiled without an IS
2976 -- pragma, and the client is compiled with an IS pragma, then
2977 -- the client will think an initialization procedure is present
2978 -- and call it, when in fact no such procedure is required, but
2979 -- since the call is generated, there had better be a routine
2980 -- at the other end of the call, even if it does nothing!)
2982 -- Note: the reason we exclude the CPP_Class case is because in this
2983 -- case the initialization is performed in the C++ side.
2985 if Is_CPP_Class (Rec_Id) then
2986 return False;
2988 elsif Is_Interface (Rec_Id) then
2989 return False;
2991 elsif not Restriction_Active (No_Initialize_Scalars)
2992 and then Is_Public (Rec_Id)
2993 then
2994 return True;
2996 elsif (Has_Discriminants (Rec_Id)
2997 and then not Is_Unchecked_Union (Rec_Id))
2998 or else Is_Tagged_Type (Rec_Id)
2999 or else Is_Concurrent_Record_Type (Rec_Id)
3000 or else Has_Task (Rec_Id)
3001 then
3002 return True;
3003 end if;
3005 Id := First_Component (Rec_Id);
3007 while Present (Id) loop
3008 Comp_Decl := Parent (Id);
3009 Typ := Etype (Id);
3011 if Present (Expression (Comp_Decl))
3012 or else Has_Non_Null_Base_Init_Proc (Typ)
3013 or else Component_Needs_Simple_Initialization (Typ)
3014 then
3015 return True;
3016 end if;
3018 Next_Component (Id);
3019 end loop;
3021 return False;
3022 end Requires_Init_Proc;
3024 -- Start of processing for Build_Record_Init_Proc
3026 begin
3027 Rec_Type := Defining_Identifier (N);
3029 if Is_Value_Type (Rec_Type) then
3030 return;
3031 end if;
3033 -- This may be full declaration of a private type, in which case
3034 -- the visible entity is a record, and the private entity has been
3035 -- exchanged with it in the private part of the current package.
3036 -- The initialization procedure is built for the record type, which
3037 -- is retrievable from the private entity.
3039 if Is_Incomplete_Or_Private_Type (Rec_Type) then
3040 Rec_Type := Underlying_Type (Rec_Type);
3041 end if;
3043 -- If there are discriminants, build the discriminant map to replace
3044 -- discriminants by their discriminals in complex bound expressions.
3045 -- These only arise for the corresponding records of protected types.
3047 if Is_Concurrent_Record_Type (Rec_Type)
3048 and then Has_Discriminants (Rec_Type)
3049 then
3050 declare
3051 Disc : Entity_Id;
3052 begin
3053 Disc := First_Discriminant (Rec_Type);
3054 while Present (Disc) loop
3055 Append_Elmt (Disc, Discr_Map);
3056 Append_Elmt (Discriminal (Disc), Discr_Map);
3057 Next_Discriminant (Disc);
3058 end loop;
3059 end;
3060 end if;
3062 -- Derived types that have no type extension can use the initialization
3063 -- procedure of their parent and do not need a procedure of their own.
3064 -- This is only correct if there are no representation clauses for the
3065 -- type or its parent, and if the parent has in fact been frozen so
3066 -- that its initialization procedure exists.
3068 if Is_Derived_Type (Rec_Type)
3069 and then not Is_Tagged_Type (Rec_Type)
3070 and then not Is_Unchecked_Union (Rec_Type)
3071 and then not Has_New_Non_Standard_Rep (Rec_Type)
3072 and then not Parent_Subtype_Renaming_Discrims
3073 and then Has_Non_Null_Base_Init_Proc (Etype (Rec_Type))
3074 then
3075 Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
3077 -- Otherwise if we need an initialization procedure, then build one,
3078 -- mark it as public and inlinable and as having a completion.
3080 elsif Requires_Init_Proc (Rec_Type)
3081 or else Is_Unchecked_Union (Rec_Type)
3082 then
3083 Build_Offset_To_Top_Functions;
3084 Build_Init_Procedure;
3085 Set_Is_Public (Proc_Id, Is_Public (Pe));
3087 -- The initialization of protected records is not worth inlining.
3088 -- In addition, when compiled for another unit for inlining purposes,
3089 -- it may make reference to entities that have not been elaborated
3090 -- yet. The initialization of controlled records contains a nested
3091 -- clean-up procedure that makes it impractical to inline as well,
3092 -- and leads to undefined symbols if inlined in a different unit.
3093 -- Similar considerations apply to task types.
3095 if not Is_Concurrent_Type (Rec_Type)
3096 and then not Has_Task (Rec_Type)
3097 and then not Controlled_Type (Rec_Type)
3098 then
3099 Set_Is_Inlined (Proc_Id);
3100 end if;
3102 Set_Is_Internal (Proc_Id);
3103 Set_Has_Completion (Proc_Id);
3105 if not Debug_Generated_Code then
3106 Set_Debug_Info_Off (Proc_Id);
3107 end if;
3109 declare
3110 Agg : constant Node_Id :=
3111 Build_Equivalent_Record_Aggregate (Rec_Type);
3113 procedure Collect_Itypes (Comp : Node_Id);
3114 -- Generate references to itypes in the aggregate, because
3115 -- the first use of the aggregate may be in a nested scope.
3117 --------------------
3118 -- Collect_Itypes --
3119 --------------------
3121 procedure Collect_Itypes (Comp : Node_Id) is
3122 Ref : Node_Id;
3123 Sub_Aggr : Node_Id;
3124 Typ : Entity_Id;
3126 begin
3127 if Is_Array_Type (Etype (Comp))
3128 and then Is_Itype (Etype (Comp))
3129 then
3130 Typ := Etype (Comp);
3131 Ref := Make_Itype_Reference (Loc);
3132 Set_Itype (Ref, Typ);
3133 Append_Freeze_Action (Rec_Type, Ref);
3135 Ref := Make_Itype_Reference (Loc);
3136 Set_Itype (Ref, Etype (First_Index (Typ)));
3137 Append_Freeze_Action (Rec_Type, Ref);
3139 Sub_Aggr := First (Expressions (Comp));
3141 -- Recurse on nested arrays
3143 while Present (Sub_Aggr) loop
3144 Collect_Itypes (Sub_Aggr);
3145 Next (Sub_Aggr);
3146 end loop;
3147 end if;
3148 end Collect_Itypes;
3150 begin
3151 -- If there is a static initialization aggregate for the type,
3152 -- generate itype references for the types of its (sub)components,
3153 -- to prevent out-of-scope errors in the resulting tree.
3154 -- The aggregate may have been rewritten as a Raise node, in which
3155 -- case there are no relevant itypes.
3157 if Present (Agg)
3158 and then Nkind (Agg) = N_Aggregate
3159 then
3160 Set_Static_Initialization (Proc_Id, Agg);
3162 declare
3163 Comp : Node_Id;
3164 begin
3165 Comp := First (Component_Associations (Agg));
3166 while Present (Comp) loop
3167 Collect_Itypes (Expression (Comp));
3168 Next (Comp);
3169 end loop;
3170 end;
3171 end if;
3172 end;
3173 end if;
3174 end Build_Record_Init_Proc;
3176 ----------------------------
3177 -- Build_Slice_Assignment --
3178 ----------------------------
3180 -- Generates the following subprogram:
3182 -- procedure Assign
3183 -- (Source, Target : Array_Type,
3184 -- Left_Lo, Left_Hi : Index;
3185 -- Right_Lo, Right_Hi : Index;
3186 -- Rev : Boolean)
3187 -- is
3188 -- Li1 : Index;
3189 -- Ri1 : Index;
3191 -- begin
3192 -- if Rev then
3193 -- Li1 := Left_Hi;
3194 -- Ri1 := Right_Hi;
3195 -- else
3196 -- Li1 := Left_Lo;
3197 -- Ri1 := Right_Lo;
3198 -- end if;
3200 -- loop
3201 -- if Rev then
3202 -- exit when Li1 < Left_Lo;
3203 -- else
3204 -- exit when Li1 > Left_Hi;
3205 -- end if;
3207 -- Target (Li1) := Source (Ri1);
3209 -- if Rev then
3210 -- Li1 := Index'pred (Li1);
3211 -- Ri1 := Index'pred (Ri1);
3212 -- else
3213 -- Li1 := Index'succ (Li1);
3214 -- Ri1 := Index'succ (Ri1);
3215 -- end if;
3216 -- end loop;
3217 -- end Assign;
3219 procedure Build_Slice_Assignment (Typ : Entity_Id) is
3220 Loc : constant Source_Ptr := Sloc (Typ);
3221 Index : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
3223 -- Build formal parameters of procedure
3225 Larray : constant Entity_Id :=
3226 Make_Defining_Identifier
3227 (Loc, Chars => New_Internal_Name ('A'));
3228 Rarray : constant Entity_Id :=
3229 Make_Defining_Identifier
3230 (Loc, Chars => New_Internal_Name ('R'));
3231 Left_Lo : constant Entity_Id :=
3232 Make_Defining_Identifier
3233 (Loc, Chars => New_Internal_Name ('L'));
3234 Left_Hi : constant Entity_Id :=
3235 Make_Defining_Identifier
3236 (Loc, Chars => New_Internal_Name ('L'));
3237 Right_Lo : constant Entity_Id :=
3238 Make_Defining_Identifier
3239 (Loc, Chars => New_Internal_Name ('R'));
3240 Right_Hi : constant Entity_Id :=
3241 Make_Defining_Identifier
3242 (Loc, Chars => New_Internal_Name ('R'));
3243 Rev : constant Entity_Id :=
3244 Make_Defining_Identifier
3245 (Loc, Chars => New_Internal_Name ('D'));
3246 Proc_Name : constant Entity_Id :=
3247 Make_Defining_Identifier (Loc,
3248 Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
3250 Lnn : constant Entity_Id :=
3251 Make_Defining_Identifier (Loc, New_Internal_Name ('L'));
3252 Rnn : constant Entity_Id :=
3253 Make_Defining_Identifier (Loc, New_Internal_Name ('R'));
3254 -- Subscripts for left and right sides
3256 Decls : List_Id;
3257 Loops : Node_Id;
3258 Stats : List_Id;
3260 begin
3261 -- Build declarations for indices
3263 Decls := New_List;
3265 Append_To (Decls,
3266 Make_Object_Declaration (Loc,
3267 Defining_Identifier => Lnn,
3268 Object_Definition =>
3269 New_Occurrence_Of (Index, Loc)));
3271 Append_To (Decls,
3272 Make_Object_Declaration (Loc,
3273 Defining_Identifier => Rnn,
3274 Object_Definition =>
3275 New_Occurrence_Of (Index, Loc)));
3277 Stats := New_List;
3279 -- Build initializations for indices
3281 declare
3282 F_Init : constant List_Id := New_List;
3283 B_Init : constant List_Id := New_List;
3285 begin
3286 Append_To (F_Init,
3287 Make_Assignment_Statement (Loc,
3288 Name => New_Occurrence_Of (Lnn, Loc),
3289 Expression => New_Occurrence_Of (Left_Lo, Loc)));
3291 Append_To (F_Init,
3292 Make_Assignment_Statement (Loc,
3293 Name => New_Occurrence_Of (Rnn, Loc),
3294 Expression => New_Occurrence_Of (Right_Lo, Loc)));
3296 Append_To (B_Init,
3297 Make_Assignment_Statement (Loc,
3298 Name => New_Occurrence_Of (Lnn, Loc),
3299 Expression => New_Occurrence_Of (Left_Hi, Loc)));
3301 Append_To (B_Init,
3302 Make_Assignment_Statement (Loc,
3303 Name => New_Occurrence_Of (Rnn, Loc),
3304 Expression => New_Occurrence_Of (Right_Hi, Loc)));
3306 Append_To (Stats,
3307 Make_If_Statement (Loc,
3308 Condition => New_Occurrence_Of (Rev, Loc),
3309 Then_Statements => B_Init,
3310 Else_Statements => F_Init));
3311 end;
3313 -- Now construct the assignment statement
3315 Loops :=
3316 Make_Loop_Statement (Loc,
3317 Statements => New_List (
3318 Make_Assignment_Statement (Loc,
3319 Name =>
3320 Make_Indexed_Component (Loc,
3321 Prefix => New_Occurrence_Of (Larray, Loc),
3322 Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
3323 Expression =>
3324 Make_Indexed_Component (Loc,
3325 Prefix => New_Occurrence_Of (Rarray, Loc),
3326 Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
3327 End_Label => Empty);
3329 -- Build exit condition
3331 declare
3332 F_Ass : constant List_Id := New_List;
3333 B_Ass : constant List_Id := New_List;
3335 begin
3336 Append_To (F_Ass,
3337 Make_Exit_Statement (Loc,
3338 Condition =>
3339 Make_Op_Gt (Loc,
3340 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3341 Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
3343 Append_To (B_Ass,
3344 Make_Exit_Statement (Loc,
3345 Condition =>
3346 Make_Op_Lt (Loc,
3347 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3348 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
3350 Prepend_To (Statements (Loops),
3351 Make_If_Statement (Loc,
3352 Condition => New_Occurrence_Of (Rev, Loc),
3353 Then_Statements => B_Ass,
3354 Else_Statements => F_Ass));
3355 end;
3357 -- Build the increment/decrement statements
3359 declare
3360 F_Ass : constant List_Id := New_List;
3361 B_Ass : constant List_Id := New_List;
3363 begin
3364 Append_To (F_Ass,
3365 Make_Assignment_Statement (Loc,
3366 Name => New_Occurrence_Of (Lnn, Loc),
3367 Expression =>
3368 Make_Attribute_Reference (Loc,
3369 Prefix =>
3370 New_Occurrence_Of (Index, Loc),
3371 Attribute_Name => Name_Succ,
3372 Expressions => New_List (
3373 New_Occurrence_Of (Lnn, Loc)))));
3375 Append_To (F_Ass,
3376 Make_Assignment_Statement (Loc,
3377 Name => New_Occurrence_Of (Rnn, Loc),
3378 Expression =>
3379 Make_Attribute_Reference (Loc,
3380 Prefix =>
3381 New_Occurrence_Of (Index, Loc),
3382 Attribute_Name => Name_Succ,
3383 Expressions => New_List (
3384 New_Occurrence_Of (Rnn, Loc)))));
3386 Append_To (B_Ass,
3387 Make_Assignment_Statement (Loc,
3388 Name => New_Occurrence_Of (Lnn, Loc),
3389 Expression =>
3390 Make_Attribute_Reference (Loc,
3391 Prefix =>
3392 New_Occurrence_Of (Index, Loc),
3393 Attribute_Name => Name_Pred,
3394 Expressions => New_List (
3395 New_Occurrence_Of (Lnn, Loc)))));
3397 Append_To (B_Ass,
3398 Make_Assignment_Statement (Loc,
3399 Name => New_Occurrence_Of (Rnn, Loc),
3400 Expression =>
3401 Make_Attribute_Reference (Loc,
3402 Prefix =>
3403 New_Occurrence_Of (Index, Loc),
3404 Attribute_Name => Name_Pred,
3405 Expressions => New_List (
3406 New_Occurrence_Of (Rnn, Loc)))));
3408 Append_To (Statements (Loops),
3409 Make_If_Statement (Loc,
3410 Condition => New_Occurrence_Of (Rev, Loc),
3411 Then_Statements => B_Ass,
3412 Else_Statements => F_Ass));
3413 end;
3415 Append_To (Stats, Loops);
3417 declare
3418 Spec : Node_Id;
3419 Formals : List_Id := New_List;
3421 begin
3422 Formals := New_List (
3423 Make_Parameter_Specification (Loc,
3424 Defining_Identifier => Larray,
3425 Out_Present => True,
3426 Parameter_Type =>
3427 New_Reference_To (Base_Type (Typ), Loc)),
3429 Make_Parameter_Specification (Loc,
3430 Defining_Identifier => Rarray,
3431 Parameter_Type =>
3432 New_Reference_To (Base_Type (Typ), Loc)),
3434 Make_Parameter_Specification (Loc,
3435 Defining_Identifier => Left_Lo,
3436 Parameter_Type =>
3437 New_Reference_To (Index, Loc)),
3439 Make_Parameter_Specification (Loc,
3440 Defining_Identifier => Left_Hi,
3441 Parameter_Type =>
3442 New_Reference_To (Index, Loc)),
3444 Make_Parameter_Specification (Loc,
3445 Defining_Identifier => Right_Lo,
3446 Parameter_Type =>
3447 New_Reference_To (Index, Loc)),
3449 Make_Parameter_Specification (Loc,
3450 Defining_Identifier => Right_Hi,
3451 Parameter_Type =>
3452 New_Reference_To (Index, Loc)));
3454 Append_To (Formals,
3455 Make_Parameter_Specification (Loc,
3456 Defining_Identifier => Rev,
3457 Parameter_Type =>
3458 New_Reference_To (Standard_Boolean, Loc)));
3460 Spec :=
3461 Make_Procedure_Specification (Loc,
3462 Defining_Unit_Name => Proc_Name,
3463 Parameter_Specifications => Formals);
3465 Discard_Node (
3466 Make_Subprogram_Body (Loc,
3467 Specification => Spec,
3468 Declarations => Decls,
3469 Handled_Statement_Sequence =>
3470 Make_Handled_Sequence_Of_Statements (Loc,
3471 Statements => Stats)));
3472 end;
3474 Set_TSS (Typ, Proc_Name);
3475 Set_Is_Pure (Proc_Name);
3476 end Build_Slice_Assignment;
3478 ------------------------------------
3479 -- Build_Variant_Record_Equality --
3480 ------------------------------------
3482 -- Generates:
3484 -- function _Equality (X, Y : T) return Boolean is
3485 -- begin
3486 -- -- Compare discriminants
3488 -- if False or else X.D1 /= Y.D1 or else X.D2 /= Y.D2 then
3489 -- return False;
3490 -- end if;
3492 -- -- Compare components
3494 -- if False or else X.C1 /= Y.C1 or else X.C2 /= Y.C2 then
3495 -- return False;
3496 -- end if;
3498 -- -- Compare variant part
3500 -- case X.D1 is
3501 -- when V1 =>
3502 -- if False or else X.C2 /= Y.C2 or else X.C3 /= Y.C3 then
3503 -- return False;
3504 -- end if;
3505 -- ...
3506 -- when Vn =>
3507 -- if False or else X.Cn /= Y.Cn then
3508 -- return False;
3509 -- end if;
3510 -- end case;
3512 -- return True;
3513 -- end _Equality;
3515 procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
3516 Loc : constant Source_Ptr := Sloc (Typ);
3518 F : constant Entity_Id :=
3519 Make_Defining_Identifier (Loc,
3520 Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
3522 X : constant Entity_Id :=
3523 Make_Defining_Identifier (Loc,
3524 Chars => Name_X);
3526 Y : constant Entity_Id :=
3527 Make_Defining_Identifier (Loc,
3528 Chars => Name_Y);
3530 Def : constant Node_Id := Parent (Typ);
3531 Comps : constant Node_Id := Component_List (Type_Definition (Def));
3532 Stmts : constant List_Id := New_List;
3533 Pspecs : constant List_Id := New_List;
3535 begin
3536 -- Derived Unchecked_Union types no longer inherit the equality function
3537 -- of their parent.
3539 if Is_Derived_Type (Typ)
3540 and then not Is_Unchecked_Union (Typ)
3541 and then not Has_New_Non_Standard_Rep (Typ)
3542 then
3543 declare
3544 Parent_Eq : constant Entity_Id :=
3545 TSS (Root_Type (Typ), TSS_Composite_Equality);
3547 begin
3548 if Present (Parent_Eq) then
3549 Copy_TSS (Parent_Eq, Typ);
3550 return;
3551 end if;
3552 end;
3553 end if;
3555 Discard_Node (
3556 Make_Subprogram_Body (Loc,
3557 Specification =>
3558 Make_Function_Specification (Loc,
3559 Defining_Unit_Name => F,
3560 Parameter_Specifications => Pspecs,
3561 Result_Definition => New_Reference_To (Standard_Boolean, Loc)),
3562 Declarations => New_List,
3563 Handled_Statement_Sequence =>
3564 Make_Handled_Sequence_Of_Statements (Loc,
3565 Statements => Stmts)));
3567 Append_To (Pspecs,
3568 Make_Parameter_Specification (Loc,
3569 Defining_Identifier => X,
3570 Parameter_Type => New_Reference_To (Typ, Loc)));
3572 Append_To (Pspecs,
3573 Make_Parameter_Specification (Loc,
3574 Defining_Identifier => Y,
3575 Parameter_Type => New_Reference_To (Typ, Loc)));
3577 -- Unchecked_Unions require additional machinery to support equality.
3578 -- Two extra parameters (A and B) are added to the equality function
3579 -- parameter list in order to capture the inferred values of the
3580 -- discriminants in later calls.
3582 if Is_Unchecked_Union (Typ) then
3583 declare
3584 Discr_Type : constant Node_Id := Etype (First_Discriminant (Typ));
3586 A : constant Node_Id :=
3587 Make_Defining_Identifier (Loc,
3588 Chars => Name_A);
3590 B : constant Node_Id :=
3591 Make_Defining_Identifier (Loc,
3592 Chars => Name_B);
3594 begin
3595 -- Add A and B to the parameter list
3597 Append_To (Pspecs,
3598 Make_Parameter_Specification (Loc,
3599 Defining_Identifier => A,
3600 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
3602 Append_To (Pspecs,
3603 Make_Parameter_Specification (Loc,
3604 Defining_Identifier => B,
3605 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
3607 -- Generate the following header code to compare the inferred
3608 -- discriminants:
3610 -- if a /= b then
3611 -- return False;
3612 -- end if;
3614 Append_To (Stmts,
3615 Make_If_Statement (Loc,
3616 Condition =>
3617 Make_Op_Ne (Loc,
3618 Left_Opnd => New_Reference_To (A, Loc),
3619 Right_Opnd => New_Reference_To (B, Loc)),
3620 Then_Statements => New_List (
3621 Make_Simple_Return_Statement (Loc,
3622 Expression => New_Occurrence_Of (Standard_False, Loc)))));
3624 -- Generate component-by-component comparison. Note that we must
3625 -- propagate one of the inferred discriminant formals to act as
3626 -- the case statement switch.
3628 Append_List_To (Stmts,
3629 Make_Eq_Case (Typ, Comps, A));
3631 end;
3633 -- Normal case (not unchecked union)
3635 else
3636 Append_To (Stmts,
3637 Make_Eq_If (Typ,
3638 Discriminant_Specifications (Def)));
3640 Append_List_To (Stmts,
3641 Make_Eq_Case (Typ, Comps));
3642 end if;
3644 Append_To (Stmts,
3645 Make_Simple_Return_Statement (Loc,
3646 Expression => New_Reference_To (Standard_True, Loc)));
3648 Set_TSS (Typ, F);
3649 Set_Is_Pure (F);
3651 if not Debug_Generated_Code then
3652 Set_Debug_Info_Off (F);
3653 end if;
3654 end Build_Variant_Record_Equality;
3656 -----------------------------
3657 -- Check_Stream_Attributes --
3658 -----------------------------
3660 procedure Check_Stream_Attributes (Typ : Entity_Id) is
3661 Comp : Entity_Id;
3662 Par_Read : constant Boolean :=
3663 Stream_Attribute_Available (Typ, TSS_Stream_Read)
3664 and then not Has_Specified_Stream_Read (Typ);
3665 Par_Write : constant Boolean :=
3666 Stream_Attribute_Available (Typ, TSS_Stream_Write)
3667 and then not Has_Specified_Stream_Write (Typ);
3669 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type);
3670 -- Check that Comp has a user-specified Nam stream attribute
3672 ----------------
3673 -- Check_Attr --
3674 ----------------
3676 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type) is
3677 begin
3678 if not Stream_Attribute_Available (Etype (Comp), TSS_Nam) then
3679 Error_Msg_Name_1 := Nam;
3680 Error_Msg_N
3681 ("|component& in limited extension must have% attribute", Comp);
3682 end if;
3683 end Check_Attr;
3685 -- Start of processing for Check_Stream_Attributes
3687 begin
3688 if Par_Read or else Par_Write then
3689 Comp := First_Component (Typ);
3690 while Present (Comp) loop
3691 if Comes_From_Source (Comp)
3692 and then Original_Record_Component (Comp) = Comp
3693 and then Is_Limited_Type (Etype (Comp))
3694 then
3695 if Par_Read then
3696 Check_Attr (Name_Read, TSS_Stream_Read);
3697 end if;
3699 if Par_Write then
3700 Check_Attr (Name_Write, TSS_Stream_Write);
3701 end if;
3702 end if;
3704 Next_Component (Comp);
3705 end loop;
3706 end if;
3707 end Check_Stream_Attributes;
3709 -----------------------------
3710 -- Expand_Record_Extension --
3711 -----------------------------
3713 -- Add a field _parent at the beginning of the record extension. This is
3714 -- used to implement inheritance. Here are some examples of expansion:
3716 -- 1. no discriminants
3717 -- type T2 is new T1 with null record;
3718 -- gives
3719 -- type T2 is new T1 with record
3720 -- _Parent : T1;
3721 -- end record;
3723 -- 2. renamed discriminants
3724 -- type T2 (B, C : Int) is new T1 (A => B) with record
3725 -- _Parent : T1 (A => B);
3726 -- D : Int;
3727 -- end;
3729 -- 3. inherited discriminants
3730 -- type T2 is new T1 with record -- discriminant A inherited
3731 -- _Parent : T1 (A);
3732 -- D : Int;
3733 -- end;
3735 procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
3736 Indic : constant Node_Id := Subtype_Indication (Def);
3737 Loc : constant Source_Ptr := Sloc (Def);
3738 Rec_Ext_Part : Node_Id := Record_Extension_Part (Def);
3739 Par_Subtype : Entity_Id;
3740 Comp_List : Node_Id;
3741 Comp_Decl : Node_Id;
3742 Parent_N : Node_Id;
3743 D : Entity_Id;
3744 List_Constr : constant List_Id := New_List;
3746 begin
3747 -- Expand_Record_Extension is called directly from the semantics, so
3748 -- we must check to see whether expansion is active before proceeding
3750 if not Expander_Active then
3751 return;
3752 end if;
3754 -- This may be a derivation of an untagged private type whose full
3755 -- view is tagged, in which case the Derived_Type_Definition has no
3756 -- extension part. Build an empty one now.
3758 if No (Rec_Ext_Part) then
3759 Rec_Ext_Part :=
3760 Make_Record_Definition (Loc,
3761 End_Label => Empty,
3762 Component_List => Empty,
3763 Null_Present => True);
3765 Set_Record_Extension_Part (Def, Rec_Ext_Part);
3766 Mark_Rewrite_Insertion (Rec_Ext_Part);
3767 end if;
3769 Comp_List := Component_List (Rec_Ext_Part);
3771 Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
3773 -- If the derived type inherits its discriminants the type of the
3774 -- _parent field must be constrained by the inherited discriminants
3776 if Has_Discriminants (T)
3777 and then Nkind (Indic) /= N_Subtype_Indication
3778 and then not Is_Constrained (Entity (Indic))
3779 then
3780 D := First_Discriminant (T);
3781 while Present (D) loop
3782 Append_To (List_Constr, New_Occurrence_Of (D, Loc));
3783 Next_Discriminant (D);
3784 end loop;
3786 Par_Subtype :=
3787 Process_Subtype (
3788 Make_Subtype_Indication (Loc,
3789 Subtype_Mark => New_Reference_To (Entity (Indic), Loc),
3790 Constraint =>
3791 Make_Index_Or_Discriminant_Constraint (Loc,
3792 Constraints => List_Constr)),
3793 Def);
3795 -- Otherwise the original subtype_indication is just what is needed
3797 else
3798 Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
3799 end if;
3801 Set_Parent_Subtype (T, Par_Subtype);
3803 Comp_Decl :=
3804 Make_Component_Declaration (Loc,
3805 Defining_Identifier => Parent_N,
3806 Component_Definition =>
3807 Make_Component_Definition (Loc,
3808 Aliased_Present => False,
3809 Subtype_Indication => New_Reference_To (Par_Subtype, Loc)));
3811 if Null_Present (Rec_Ext_Part) then
3812 Set_Component_List (Rec_Ext_Part,
3813 Make_Component_List (Loc,
3814 Component_Items => New_List (Comp_Decl),
3815 Variant_Part => Empty,
3816 Null_Present => False));
3817 Set_Null_Present (Rec_Ext_Part, False);
3819 elsif Null_Present (Comp_List)
3820 or else Is_Empty_List (Component_Items (Comp_List))
3821 then
3822 Set_Component_Items (Comp_List, New_List (Comp_Decl));
3823 Set_Null_Present (Comp_List, False);
3825 else
3826 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
3827 end if;
3829 Analyze (Comp_Decl);
3830 end Expand_Record_Extension;
3832 ------------------------------------
3833 -- Expand_N_Full_Type_Declaration --
3834 ------------------------------------
3836 procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
3837 Def_Id : constant Entity_Id := Defining_Identifier (N);
3838 B_Id : constant Entity_Id := Base_Type (Def_Id);
3839 Par_Id : Entity_Id;
3840 FN : Node_Id;
3842 procedure Build_Master (Def_Id : Entity_Id);
3843 -- Create the master associated with Def_Id
3845 ------------------
3846 -- Build_Master --
3847 ------------------
3849 procedure Build_Master (Def_Id : Entity_Id) is
3850 begin
3851 -- Anonymous access types are created for the components of the
3852 -- record parameter for an entry declaration. No master is created
3853 -- for such a type.
3855 if Has_Task (Designated_Type (Def_Id))
3856 and then Comes_From_Source (N)
3857 then
3858 Build_Master_Entity (Def_Id);
3859 Build_Master_Renaming (Parent (Def_Id), Def_Id);
3861 -- Create a class-wide master because a Master_Id must be generated
3862 -- for access-to-limited-class-wide types whose root may be extended
3863 -- with task components, and for access-to-limited-interfaces because
3864 -- they can be used to reference tasks implementing such interface.
3866 elsif Is_Class_Wide_Type (Designated_Type (Def_Id))
3867 and then (Is_Limited_Type (Designated_Type (Def_Id))
3868 or else
3869 (Is_Interface (Designated_Type (Def_Id))
3870 and then
3871 Is_Limited_Interface (Designated_Type (Def_Id))))
3872 and then Tasking_Allowed
3874 -- Do not create a class-wide master for types whose convention is
3875 -- Java since these types cannot embed Ada tasks anyway. Note that
3876 -- the following test cannot catch the following case:
3878 -- package java.lang.Object is
3879 -- type Typ is tagged limited private;
3880 -- type Ref is access all Typ'Class;
3881 -- private
3882 -- type Typ is tagged limited ...;
3883 -- pragma Convention (Typ, Java)
3884 -- end;
3886 -- Because the convention appears after we have done the
3887 -- processing for type Ref.
3889 and then Convention (Designated_Type (Def_Id)) /= Convention_Java
3890 and then Convention (Designated_Type (Def_Id)) /= Convention_CIL
3891 then
3892 Build_Class_Wide_Master (Def_Id);
3893 end if;
3894 end Build_Master;
3896 -- Start of processing for Expand_N_Full_Type_Declaration
3898 begin
3899 if Is_Access_Type (Def_Id) then
3900 Build_Master (Def_Id);
3902 if Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
3903 Expand_Access_Protected_Subprogram_Type (N);
3904 end if;
3906 elsif Ada_Version >= Ada_05
3907 and then Is_Array_Type (Def_Id)
3908 and then Is_Access_Type (Component_Type (Def_Id))
3909 and then Ekind (Component_Type (Def_Id)) = E_Anonymous_Access_Type
3910 then
3911 Build_Master (Component_Type (Def_Id));
3913 elsif Has_Task (Def_Id) then
3914 Expand_Previous_Access_Type (Def_Id);
3916 elsif Ada_Version >= Ada_05
3917 and then
3918 (Is_Record_Type (Def_Id)
3919 or else (Is_Array_Type (Def_Id)
3920 and then Is_Record_Type (Component_Type (Def_Id))))
3921 then
3922 declare
3923 Comp : Entity_Id;
3924 Typ : Entity_Id;
3925 M_Id : Entity_Id;
3927 begin
3928 -- Look for the first anonymous access type component
3930 if Is_Array_Type (Def_Id) then
3931 Comp := First_Entity (Component_Type (Def_Id));
3932 else
3933 Comp := First_Entity (Def_Id);
3934 end if;
3936 while Present (Comp) loop
3937 Typ := Etype (Comp);
3939 exit when Is_Access_Type (Typ)
3940 and then Ekind (Typ) = E_Anonymous_Access_Type;
3942 Next_Entity (Comp);
3943 end loop;
3945 -- If found we add a renaming declaration of master_id and we
3946 -- associate it to each anonymous access type component. Do
3947 -- nothing if the access type already has a master. This will be
3948 -- the case if the array type is the packed array created for a
3949 -- user-defined array type T, where the master_id is created when
3950 -- expanding the declaration for T.
3952 if Present (Comp)
3953 and then Ekind (Typ) = E_Anonymous_Access_Type
3954 and then not Restriction_Active (No_Task_Hierarchy)
3955 and then No (Master_Id (Typ))
3957 -- Do not consider run-times with no tasking support
3959 and then RTE_Available (RE_Current_Master)
3960 and then Has_Task (Non_Limited_Designated_Type (Typ))
3961 then
3962 Build_Master_Entity (Def_Id);
3963 M_Id := Build_Master_Renaming (N, Def_Id);
3965 if Is_Array_Type (Def_Id) then
3966 Comp := First_Entity (Component_Type (Def_Id));
3967 else
3968 Comp := First_Entity (Def_Id);
3969 end if;
3971 while Present (Comp) loop
3972 Typ := Etype (Comp);
3974 if Is_Access_Type (Typ)
3975 and then Ekind (Typ) = E_Anonymous_Access_Type
3976 then
3977 Set_Master_Id (Typ, M_Id);
3978 end if;
3980 Next_Entity (Comp);
3981 end loop;
3982 end if;
3983 end;
3984 end if;
3986 Par_Id := Etype (B_Id);
3988 -- The parent type is private then we need to inherit any TSS operations
3989 -- from the full view.
3991 if Ekind (Par_Id) in Private_Kind
3992 and then Present (Full_View (Par_Id))
3993 then
3994 Par_Id := Base_Type (Full_View (Par_Id));
3995 end if;
3997 if Nkind (Type_Definition (Original_Node (N))) =
3998 N_Derived_Type_Definition
3999 and then not Is_Tagged_Type (Def_Id)
4000 and then Present (Freeze_Node (Par_Id))
4001 and then Present (TSS_Elist (Freeze_Node (Par_Id)))
4002 then
4003 Ensure_Freeze_Node (B_Id);
4004 FN := Freeze_Node (B_Id);
4006 if No (TSS_Elist (FN)) then
4007 Set_TSS_Elist (FN, New_Elmt_List);
4008 end if;
4010 declare
4011 T_E : constant Elist_Id := TSS_Elist (FN);
4012 Elmt : Elmt_Id;
4014 begin
4015 Elmt := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
4016 while Present (Elmt) loop
4017 if Chars (Node (Elmt)) /= Name_uInit then
4018 Append_Elmt (Node (Elmt), T_E);
4019 end if;
4021 Next_Elmt (Elmt);
4022 end loop;
4024 -- If the derived type itself is private with a full view, then
4025 -- associate the full view with the inherited TSS_Elist as well.
4027 if Ekind (B_Id) in Private_Kind
4028 and then Present (Full_View (B_Id))
4029 then
4030 Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
4031 Set_TSS_Elist
4032 (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
4033 end if;
4034 end;
4035 end if;
4036 end Expand_N_Full_Type_Declaration;
4038 ---------------------------------
4039 -- Expand_N_Object_Declaration --
4040 ---------------------------------
4042 -- First we do special processing for objects of a tagged type where this
4043 -- is the point at which the type is frozen. The creation of the dispatch
4044 -- table and the initialization procedure have to be deferred to this
4045 -- point, since we reference previously declared primitive subprograms.
4047 -- For all types, we call an initialization procedure if there is one
4049 procedure Expand_N_Object_Declaration (N : Node_Id) is
4050 Def_Id : constant Entity_Id := Defining_Identifier (N);
4051 Expr : constant Node_Id := Expression (N);
4052 Loc : constant Source_Ptr := Sloc (N);
4053 Typ : constant Entity_Id := Etype (Def_Id);
4054 Base_Typ : constant Entity_Id := Base_Type (Typ);
4055 Expr_Q : Node_Id;
4056 Id_Ref : Node_Id;
4057 New_Ref : Node_Id;
4058 BIP_Call : Boolean := False;
4060 Init_After : Node_Id := N;
4061 -- Node after which the init proc call is to be inserted. This is
4062 -- normally N, except for the case of a shared passive variable, in
4063 -- which case the init proc call must be inserted only after the bodies
4064 -- of the shared variable procedures have been seen.
4066 begin
4067 -- Don't do anything for deferred constants. All proper actions will
4068 -- be expanded during the full declaration.
4070 if No (Expr) and Constant_Present (N) then
4071 return;
4072 end if;
4074 -- Force construction of dispatch tables of library level tagged types
4076 if VM_Target = No_VM
4077 and then Static_Dispatch_Tables
4078 and then Is_Library_Level_Entity (Def_Id)
4079 and then Is_Library_Level_Tagged_Type (Base_Typ)
4080 and then (Ekind (Base_Typ) = E_Record_Type
4081 or else Ekind (Base_Typ) = E_Protected_Type
4082 or else Ekind (Base_Typ) = E_Task_Type)
4083 and then not Has_Dispatch_Table (Base_Typ)
4084 then
4085 declare
4086 New_Nodes : List_Id := No_List;
4088 begin
4089 if Is_Concurrent_Type (Base_Typ) then
4090 New_Nodes := Make_DT (Corresponding_Record_Type (Base_Typ), N);
4091 else
4092 New_Nodes := Make_DT (Base_Typ, N);
4093 end if;
4095 if not Is_Empty_List (New_Nodes) then
4096 Insert_List_Before (N, New_Nodes);
4097 end if;
4098 end;
4099 end if;
4101 -- Make shared memory routines for shared passive variable
4103 if Is_Shared_Passive (Def_Id) then
4104 Init_After := Make_Shared_Var_Procs (N);
4105 end if;
4107 -- If tasks being declared, make sure we have an activation chain
4108 -- defined for the tasks (has no effect if we already have one), and
4109 -- also that a Master variable is established and that the appropriate
4110 -- enclosing construct is established as a task master.
4112 if Has_Task (Typ) then
4113 Build_Activation_Chain_Entity (N);
4114 Build_Master_Entity (Def_Id);
4115 end if;
4117 -- Build a list controller for declarations where the type is anonymous
4118 -- access and the designated type is controlled. Only declarations from
4119 -- source files receive such controllers in order to provide the same
4120 -- lifespan for any potential coextensions that may be associated with
4121 -- the object. Finalization lists of internal controlled anonymous
4122 -- access objects are already handled in Expand_N_Allocator.
4124 if Comes_From_Source (N)
4125 and then Ekind (Typ) = E_Anonymous_Access_Type
4126 and then Is_Controlled (Directly_Designated_Type (Typ))
4127 and then No (Associated_Final_Chain (Typ))
4128 then
4129 Build_Final_List (N, Typ);
4130 end if;
4132 -- Default initialization required, and no expression present
4134 if No (Expr) then
4136 -- Expand Initialize call for controlled objects. One may wonder why
4137 -- the Initialize Call is not done in the regular Init procedure
4138 -- attached to the record type. That's because the init procedure is
4139 -- recursively called on each component, including _Parent, thus the
4140 -- Init call for a controlled object would generate not only one
4141 -- Initialize call as it is required but one for each ancestor of
4142 -- its type. This processing is suppressed if No_Initialization set.
4144 if not Controlled_Type (Typ)
4145 or else No_Initialization (N)
4146 then
4147 null;
4149 elsif not Abort_Allowed
4150 or else not Comes_From_Source (N)
4151 then
4152 Insert_Actions_After (Init_After,
4153 Make_Init_Call (
4154 Ref => New_Occurrence_Of (Def_Id, Loc),
4155 Typ => Base_Type (Typ),
4156 Flist_Ref => Find_Final_List (Def_Id),
4157 With_Attach => Make_Integer_Literal (Loc, 1)));
4159 -- Abort allowed
4161 else
4162 -- We need to protect the initialize call
4164 -- begin
4165 -- Defer_Abort.all;
4166 -- Initialize (...);
4167 -- at end
4168 -- Undefer_Abort.all;
4169 -- end;
4171 -- ??? this won't protect the initialize call for controlled
4172 -- components which are part of the init proc, so this block
4173 -- should probably also contain the call to _init_proc but this
4174 -- requires some code reorganization...
4176 declare
4177 L : constant List_Id :=
4178 Make_Init_Call
4179 (Ref => New_Occurrence_Of (Def_Id, Loc),
4180 Typ => Base_Type (Typ),
4181 Flist_Ref => Find_Final_List (Def_Id),
4182 With_Attach => Make_Integer_Literal (Loc, 1));
4184 Blk : constant Node_Id :=
4185 Make_Block_Statement (Loc,
4186 Handled_Statement_Sequence =>
4187 Make_Handled_Sequence_Of_Statements (Loc, L));
4189 begin
4190 Prepend_To (L, Build_Runtime_Call (Loc, RE_Abort_Defer));
4191 Set_At_End_Proc (Handled_Statement_Sequence (Blk),
4192 New_Occurrence_Of (RTE (RE_Abort_Undefer_Direct), Loc));
4193 Insert_Actions_After (Init_After, New_List (Blk));
4194 Expand_At_End_Handler
4195 (Handled_Statement_Sequence (Blk), Entity (Identifier (Blk)));
4196 end;
4197 end if;
4199 -- Call type initialization procedure if there is one. We build the
4200 -- call and put it immediately after the object declaration, so that
4201 -- it will be expanded in the usual manner. Note that this will
4202 -- result in proper handling of defaulted discriminants.
4204 -- Need call if there is a base init proc
4206 if Has_Non_Null_Base_Init_Proc (Typ)
4208 -- Suppress call if No_Initialization set on declaration
4210 and then not No_Initialization (N)
4212 -- Suppress call for special case of value type for VM
4214 and then not Is_Value_Type (Typ)
4216 -- Suppress call if Suppress_Init_Proc set on the type. This is
4217 -- needed for the derived type case, where Suppress_Initialization
4218 -- may be set for the derived type, even if there is an init proc
4219 -- defined for the root type.
4221 and then not Suppress_Init_Proc (Typ)
4222 then
4223 -- The call to the initialization procedure does NOT freeze the
4224 -- object being initialized. This is because the call is not a
4225 -- source level call. This works fine, because the only possible
4226 -- statements depending on freeze status that can appear after the
4227 -- _Init call are rep clauses which can safely appear after actual
4228 -- references to the object.
4230 Id_Ref := New_Reference_To (Def_Id, Loc);
4231 Set_Must_Not_Freeze (Id_Ref);
4232 Set_Assignment_OK (Id_Ref);
4234 declare
4235 Init_Expr : constant Node_Id :=
4236 Static_Initialization (Base_Init_Proc (Typ));
4237 begin
4238 if Present (Init_Expr) then
4239 Set_Expression
4240 (N, New_Copy_Tree (Init_Expr, New_Scope => Current_Scope));
4241 return;
4242 else
4243 Initialization_Warning (Id_Ref);
4245 Insert_Actions_After (Init_After,
4246 Build_Initialization_Call (Loc, Id_Ref, Typ));
4247 end if;
4248 end;
4250 -- If simple initialization is required, then set an appropriate
4251 -- simple initialization expression in place. This special
4252 -- initialization is required even though No_Init_Flag is present,
4253 -- but is not needed if there was an explicit initialization.
4255 -- An internally generated temporary needs no initialization because
4256 -- it will be assigned subsequently. In particular, there is no point
4257 -- in applying Initialize_Scalars to such a temporary.
4259 elsif Needs_Simple_Initialization (Typ)
4260 and then not Is_Internal (Def_Id)
4261 and then not Has_Init_Expression (N)
4262 then
4263 Set_No_Initialization (N, False);
4264 Set_Expression (N, Get_Simple_Init_Val (Typ, Loc, Esize (Def_Id)));
4265 Analyze_And_Resolve (Expression (N), Typ);
4266 end if;
4268 -- Generate attribute for Persistent_BSS if needed
4270 if Persistent_BSS_Mode
4271 and then Comes_From_Source (N)
4272 and then Is_Potentially_Persistent_Type (Typ)
4273 and then not Has_Init_Expression (N)
4274 and then Is_Library_Level_Entity (Def_Id)
4275 then
4276 declare
4277 Prag : Node_Id;
4278 begin
4279 Prag :=
4280 Make_Linker_Section_Pragma
4281 (Def_Id, Sloc (N), ".persistent.bss");
4282 Insert_After (N, Prag);
4283 Analyze (Prag);
4284 end;
4285 end if;
4287 -- If access type, then we know it is null if not initialized
4289 if Is_Access_Type (Typ) then
4290 Set_Is_Known_Null (Def_Id);
4291 end if;
4293 -- Explicit initialization present
4295 else
4296 -- Obtain actual expression from qualified expression
4298 if Nkind (Expr) = N_Qualified_Expression then
4299 Expr_Q := Expression (Expr);
4300 else
4301 Expr_Q := Expr;
4302 end if;
4304 -- When we have the appropriate type of aggregate in the expression
4305 -- (it has been determined during analysis of the aggregate by
4306 -- setting the delay flag), let's perform in place assignment and
4307 -- thus avoid creating a temporary.
4309 if Is_Delayed_Aggregate (Expr_Q) then
4310 Convert_Aggr_In_Object_Decl (N);
4312 else
4313 -- Ada 2005 (AI-318-02): If the initialization expression is a
4314 -- call to a build-in-place function, then access to the declared
4315 -- object must be passed to the function. Currently we limit such
4316 -- functions to those with constrained limited result subtypes,
4317 -- but eventually we plan to expand the allowed forms of functions
4318 -- that are treated as build-in-place.
4320 if Ada_Version >= Ada_05
4321 and then Is_Build_In_Place_Function_Call (Expr_Q)
4322 then
4323 Make_Build_In_Place_Call_In_Object_Declaration (N, Expr_Q);
4324 BIP_Call := True;
4325 end if;
4327 -- In most cases, we must check that the initial value meets any
4328 -- constraint imposed by the declared type. However, there is one
4329 -- very important exception to this rule. If the entity has an
4330 -- unconstrained nominal subtype, then it acquired its constraints
4331 -- from the expression in the first place, and not only does this
4332 -- mean that the constraint check is not needed, but an attempt to
4333 -- perform the constraint check can cause order order of
4334 -- elaboration problems.
4336 if not Is_Constr_Subt_For_U_Nominal (Typ) then
4338 -- If this is an allocator for an aggregate that has been
4339 -- allocated in place, delay checks until assignments are
4340 -- made, because the discriminants are not initialized.
4342 if Nkind (Expr) = N_Allocator
4343 and then No_Initialization (Expr)
4344 then
4345 null;
4346 else
4347 Apply_Constraint_Check (Expr, Typ);
4348 end if;
4349 end if;
4351 -- Ada 2005 (AI-251): Rewrite the expression that initializes a
4352 -- class-wide object to ensure that we copy the full object,
4353 -- unless we're targetting a VM where interfaces are handled by
4354 -- VM itself.
4356 -- Replace
4357 -- CW : I'Class := Obj;
4358 -- by
4359 -- CW__1 : I'Class := I'Class (Base_Address (Obj'Address));
4360 -- CW : I'Class renames Displace (CW__1, I'Tag);
4362 if Is_Interface (Typ)
4363 and then Is_Class_Wide_Type (Etype (Expr))
4364 and then Comes_From_Source (Def_Id)
4365 and then VM_Target = No_VM
4366 then
4367 declare
4368 Decl_1 : Node_Id;
4369 Decl_2 : Node_Id;
4371 begin
4372 Decl_1 :=
4373 Make_Object_Declaration (Loc,
4374 Defining_Identifier =>
4375 Make_Defining_Identifier (Loc,
4376 New_Internal_Name ('D')),
4378 Object_Definition =>
4379 Make_Attribute_Reference (Loc,
4380 Prefix =>
4381 New_Occurrence_Of
4382 (Root_Type (Etype (Def_Id)), Loc),
4383 Attribute_Name => Name_Class),
4385 Expression =>
4386 Unchecked_Convert_To
4387 (Class_Wide_Type (Root_Type (Etype (Def_Id))),
4388 Make_Explicit_Dereference (Loc,
4389 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
4390 Make_Function_Call (Loc,
4391 Name =>
4392 New_Reference_To (RTE (RE_Base_Address),
4393 Loc),
4394 Parameter_Associations => New_List (
4395 Make_Attribute_Reference (Loc,
4396 Prefix => Relocate_Node (Expr),
4397 Attribute_Name => Name_Address)))))));
4399 Insert_Action (N, Decl_1);
4401 Decl_2 :=
4402 Make_Object_Renaming_Declaration (Loc,
4403 Defining_Identifier =>
4404 Make_Defining_Identifier (Loc,
4405 New_Internal_Name ('D')),
4407 Subtype_Mark =>
4408 Make_Attribute_Reference (Loc,
4409 Prefix =>
4410 New_Occurrence_Of
4411 (Root_Type (Etype (Def_Id)), Loc),
4412 Attribute_Name => Name_Class),
4414 Name =>
4415 Unchecked_Convert_To (
4416 Class_Wide_Type (Root_Type (Etype (Def_Id))),
4417 Make_Explicit_Dereference (Loc,
4418 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
4419 Make_Function_Call (Loc,
4420 Name =>
4421 New_Reference_To (RTE (RE_Displace), Loc),
4423 Parameter_Associations => New_List (
4424 Make_Attribute_Reference (Loc,
4425 Prefix =>
4426 New_Reference_To
4427 (Defining_Identifier (Decl_1), Loc),
4428 Attribute_Name => Name_Address),
4430 Unchecked_Convert_To (RTE (RE_Tag),
4431 New_Reference_To
4432 (Node
4433 (First_Elmt
4434 (Access_Disp_Table
4435 (Root_Type (Typ)))),
4436 Loc))))))));
4438 Rewrite (N, Decl_2);
4439 Analyze (N);
4441 -- Replace internal identifier of Decl_2 by the identifier
4442 -- found in the sources. We also have to exchange entities
4443 -- containing their defining identifiers to ensure the
4444 -- correct replacement of the object declaration by this
4445 -- object renaming declaration (because such definings
4446 -- identifier have been previously added by Enter_Name to
4447 -- the current scope). We must preserve the homonym chain
4448 -- of the source entity as well.
4450 Set_Chars (Defining_Identifier (N), Chars (Def_Id));
4451 Set_Homonym (Defining_Identifier (N), Homonym (Def_Id));
4452 Exchange_Entities (Defining_Identifier (N), Def_Id);
4454 return;
4455 end;
4456 end if;
4458 -- If the type is controlled and not limited then the target is
4459 -- adjusted after the copy and attached to the finalization list.
4460 -- However, no adjustment is done in the case where the object was
4461 -- initialized by a call to a function whose result is built in
4462 -- place, since no copy occurred. (We eventually plan to support
4463 -- in-place function results for some nonlimited types. ???)
4465 if Controlled_Type (Typ)
4466 and then not Is_Limited_Type (Typ)
4467 and then not BIP_Call
4468 then
4469 Insert_Actions_After (Init_After,
4470 Make_Adjust_Call (
4471 Ref => New_Reference_To (Def_Id, Loc),
4472 Typ => Base_Type (Typ),
4473 Flist_Ref => Find_Final_List (Def_Id),
4474 With_Attach => Make_Integer_Literal (Loc, 1)));
4475 end if;
4477 -- For tagged types, when an init value is given, the tag has to
4478 -- be re-initialized separately in order to avoid the propagation
4479 -- of a wrong tag coming from a view conversion unless the type
4480 -- is class wide (in this case the tag comes from the init value).
4481 -- Suppress the tag assignment when VM_Target because VM tags are
4482 -- represented implicitly in objects. Ditto for types that are
4483 -- CPP_CLASS, and for initializations that are aggregates, because
4484 -- they have to have the right tag.
4486 if Is_Tagged_Type (Typ)
4487 and then not Is_Class_Wide_Type (Typ)
4488 and then not Is_CPP_Class (Typ)
4489 and then VM_Target = No_VM
4490 and then Nkind (Expr) /= N_Aggregate
4491 then
4492 -- The re-assignment of the tag has to be done even if the
4493 -- object is a constant.
4495 New_Ref :=
4496 Make_Selected_Component (Loc,
4497 Prefix => New_Reference_To (Def_Id, Loc),
4498 Selector_Name =>
4499 New_Reference_To (First_Tag_Component (Typ), Loc));
4501 Set_Assignment_OK (New_Ref);
4503 Insert_After (Init_After,
4504 Make_Assignment_Statement (Loc,
4505 Name => New_Ref,
4506 Expression =>
4507 Unchecked_Convert_To (RTE (RE_Tag),
4508 New_Reference_To
4509 (Node
4510 (First_Elmt
4511 (Access_Disp_Table (Base_Type (Typ)))),
4512 Loc))));
4514 -- For discrete types, set the Is_Known_Valid flag if the
4515 -- initializing value is known to be valid.
4517 elsif Is_Discrete_Type (Typ) and then Expr_Known_Valid (Expr) then
4518 Set_Is_Known_Valid (Def_Id);
4520 elsif Is_Access_Type (Typ) then
4522 -- For access types set the Is_Known_Non_Null flag if the
4523 -- initializing value is known to be non-null. We can also set
4524 -- Can_Never_Be_Null if this is a constant.
4526 if Known_Non_Null (Expr) then
4527 Set_Is_Known_Non_Null (Def_Id, True);
4529 if Constant_Present (N) then
4530 Set_Can_Never_Be_Null (Def_Id);
4531 end if;
4532 end if;
4533 end if;
4535 -- If validity checking on copies, validate initial expression.
4536 -- But skip this if declaration is for a generic type, since it
4537 -- makes no sense to validate generic types. Not clear if this
4538 -- can happen for legal programs, but it definitely can arise
4539 -- from previous instantiation errors.
4541 if Validity_Checks_On
4542 and then Validity_Check_Copies
4543 and then not Is_Generic_Type (Etype (Def_Id))
4544 then
4545 Ensure_Valid (Expr);
4546 Set_Is_Known_Valid (Def_Id);
4547 end if;
4548 end if;
4550 -- Cases where the back end cannot handle the initialization directly
4551 -- In such cases, we expand an assignment that will be appropriately
4552 -- handled by Expand_N_Assignment_Statement.
4554 -- The exclusion of the unconstrained case is wrong, but for now it
4555 -- is too much trouble ???
4557 if (Is_Possibly_Unaligned_Slice (Expr)
4558 or else (Is_Possibly_Unaligned_Object (Expr)
4559 and then not Represented_As_Scalar (Etype (Expr))))
4561 -- The exclusion of the unconstrained case is wrong, but for now
4562 -- it is too much trouble ???
4564 and then not (Is_Array_Type (Etype (Expr))
4565 and then not Is_Constrained (Etype (Expr)))
4566 then
4567 declare
4568 Stat : constant Node_Id :=
4569 Make_Assignment_Statement (Loc,
4570 Name => New_Reference_To (Def_Id, Loc),
4571 Expression => Relocate_Node (Expr));
4572 begin
4573 Set_Expression (N, Empty);
4574 Set_No_Initialization (N);
4575 Set_Assignment_OK (Name (Stat));
4576 Set_No_Ctrl_Actions (Stat);
4577 Insert_After_And_Analyze (Init_After, Stat);
4578 end;
4579 end if;
4580 end if;
4582 exception
4583 when RE_Not_Available =>
4584 return;
4585 end Expand_N_Object_Declaration;
4587 ---------------------------------
4588 -- Expand_N_Subtype_Indication --
4589 ---------------------------------
4591 -- Add a check on the range of the subtype. The static case is partially
4592 -- duplicated by Process_Range_Expr_In_Decl in Sem_Ch3, but we still need
4593 -- to check here for the static case in order to avoid generating
4594 -- extraneous expanded code. Also deal with validity checking.
4596 procedure Expand_N_Subtype_Indication (N : Node_Id) is
4597 Ran : constant Node_Id := Range_Expression (Constraint (N));
4598 Typ : constant Entity_Id := Entity (Subtype_Mark (N));
4600 begin
4601 if Nkind (Constraint (N)) = N_Range_Constraint then
4602 Validity_Check_Range (Range_Expression (Constraint (N)));
4603 end if;
4605 if Nkind_In (Parent (N), N_Constrained_Array_Definition, N_Slice) then
4606 Apply_Range_Check (Ran, Typ);
4607 end if;
4608 end Expand_N_Subtype_Indication;
4610 ---------------------------
4611 -- Expand_N_Variant_Part --
4612 ---------------------------
4614 -- If the last variant does not contain the Others choice, replace it with
4615 -- an N_Others_Choice node since Gigi always wants an Others. Note that we
4616 -- do not bother to call Analyze on the modified variant part, since it's
4617 -- only effect would be to compute the Others_Discrete_Choices node
4618 -- laboriously, and of course we already know the list of choices that
4619 -- corresponds to the others choice (it's the list we are replacing!)
4621 procedure Expand_N_Variant_Part (N : Node_Id) is
4622 Last_Var : constant Node_Id := Last_Non_Pragma (Variants (N));
4623 Others_Node : Node_Id;
4624 begin
4625 if Nkind (First (Discrete_Choices (Last_Var))) /= N_Others_Choice then
4626 Others_Node := Make_Others_Choice (Sloc (Last_Var));
4627 Set_Others_Discrete_Choices
4628 (Others_Node, Discrete_Choices (Last_Var));
4629 Set_Discrete_Choices (Last_Var, New_List (Others_Node));
4630 end if;
4631 end Expand_N_Variant_Part;
4633 ---------------------------------
4634 -- Expand_Previous_Access_Type --
4635 ---------------------------------
4637 procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
4638 T : Entity_Id := First_Entity (Current_Scope);
4640 begin
4641 -- Find all access types declared in the current scope, whose
4642 -- designated type is Def_Id. If it does not have a Master_Id,
4643 -- create one now.
4645 while Present (T) loop
4646 if Is_Access_Type (T)
4647 and then Designated_Type (T) = Def_Id
4648 and then No (Master_Id (T))
4649 then
4650 Build_Master_Entity (Def_Id);
4651 Build_Master_Renaming (Parent (Def_Id), T);
4652 end if;
4654 Next_Entity (T);
4655 end loop;
4656 end Expand_Previous_Access_Type;
4658 ------------------------------
4659 -- Expand_Record_Controller --
4660 ------------------------------
4662 procedure Expand_Record_Controller (T : Entity_Id) is
4663 Def : Node_Id := Type_Definition (Parent (T));
4664 Comp_List : Node_Id;
4665 Comp_Decl : Node_Id;
4666 Loc : Source_Ptr;
4667 First_Comp : Node_Id;
4668 Controller_Type : Entity_Id;
4669 Ent : Entity_Id;
4671 begin
4672 if Nkind (Def) = N_Derived_Type_Definition then
4673 Def := Record_Extension_Part (Def);
4674 end if;
4676 if Null_Present (Def) then
4677 Set_Component_List (Def,
4678 Make_Component_List (Sloc (Def),
4679 Component_Items => Empty_List,
4680 Variant_Part => Empty,
4681 Null_Present => True));
4682 end if;
4684 Comp_List := Component_List (Def);
4686 if Null_Present (Comp_List)
4687 or else Is_Empty_List (Component_Items (Comp_List))
4688 then
4689 Loc := Sloc (Comp_List);
4690 else
4691 Loc := Sloc (First (Component_Items (Comp_List)));
4692 end if;
4694 if Is_Inherently_Limited_Type (T) then
4695 Controller_Type := RTE (RE_Limited_Record_Controller);
4696 else
4697 Controller_Type := RTE (RE_Record_Controller);
4698 end if;
4700 Ent := Make_Defining_Identifier (Loc, Name_uController);
4702 Comp_Decl :=
4703 Make_Component_Declaration (Loc,
4704 Defining_Identifier => Ent,
4705 Component_Definition =>
4706 Make_Component_Definition (Loc,
4707 Aliased_Present => False,
4708 Subtype_Indication => New_Reference_To (Controller_Type, Loc)));
4710 if Null_Present (Comp_List)
4711 or else Is_Empty_List (Component_Items (Comp_List))
4712 then
4713 Set_Component_Items (Comp_List, New_List (Comp_Decl));
4714 Set_Null_Present (Comp_List, False);
4716 else
4717 -- The controller cannot be placed before the _Parent field since
4718 -- gigi lays out field in order and _parent must be first to preserve
4719 -- the polymorphism of tagged types.
4721 First_Comp := First (Component_Items (Comp_List));
4723 if not Is_Tagged_Type (T) then
4724 Insert_Before (First_Comp, Comp_Decl);
4726 -- if T is a tagged type, place controller declaration after parent
4727 -- field and after eventual tags of interface types.
4729 else
4730 while Present (First_Comp)
4731 and then
4732 (Chars (Defining_Identifier (First_Comp)) = Name_uParent
4733 or else Is_Tag (Defining_Identifier (First_Comp))
4735 -- Ada 2005 (AI-251): The following condition covers secondary
4736 -- tags but also the adjacent component contanining the offset
4737 -- to the base of the object (component generated if the parent
4738 -- has discriminants --- see Add_Interface_Tag_Components).
4739 -- This is required to avoid the addition of the controller
4740 -- between the secondary tag and its adjacent component.
4742 or else Present
4743 (Related_Type
4744 (Defining_Identifier (First_Comp))))
4745 loop
4746 Next (First_Comp);
4747 end loop;
4749 -- An empty tagged extension might consist only of the parent
4750 -- component. Otherwise insert the controller before the first
4751 -- component that is neither parent nor tag.
4753 if Present (First_Comp) then
4754 Insert_Before (First_Comp, Comp_Decl);
4755 else
4756 Append (Comp_Decl, Component_Items (Comp_List));
4757 end if;
4758 end if;
4759 end if;
4761 Push_Scope (T);
4762 Analyze (Comp_Decl);
4763 Set_Ekind (Ent, E_Component);
4764 Init_Component_Location (Ent);
4766 -- Move the _controller entity ahead in the list of internal entities
4767 -- of the enclosing record so that it is selected instead of a
4768 -- potentially inherited one.
4770 declare
4771 E : constant Entity_Id := Last_Entity (T);
4772 Comp : Entity_Id;
4774 begin
4775 pragma Assert (Chars (E) = Name_uController);
4777 Set_Next_Entity (E, First_Entity (T));
4778 Set_First_Entity (T, E);
4780 Comp := Next_Entity (E);
4781 while Next_Entity (Comp) /= E loop
4782 Next_Entity (Comp);
4783 end loop;
4785 Set_Next_Entity (Comp, Empty);
4786 Set_Last_Entity (T, Comp);
4787 end;
4789 End_Scope;
4791 exception
4792 when RE_Not_Available =>
4793 return;
4794 end Expand_Record_Controller;
4796 ------------------------
4797 -- Expand_Tagged_Root --
4798 ------------------------
4800 procedure Expand_Tagged_Root (T : Entity_Id) is
4801 Def : constant Node_Id := Type_Definition (Parent (T));
4802 Comp_List : Node_Id;
4803 Comp_Decl : Node_Id;
4804 Sloc_N : Source_Ptr;
4806 begin
4807 if Null_Present (Def) then
4808 Set_Component_List (Def,
4809 Make_Component_List (Sloc (Def),
4810 Component_Items => Empty_List,
4811 Variant_Part => Empty,
4812 Null_Present => True));
4813 end if;
4815 Comp_List := Component_List (Def);
4817 if Null_Present (Comp_List)
4818 or else Is_Empty_List (Component_Items (Comp_List))
4819 then
4820 Sloc_N := Sloc (Comp_List);
4821 else
4822 Sloc_N := Sloc (First (Component_Items (Comp_List)));
4823 end if;
4825 Comp_Decl :=
4826 Make_Component_Declaration (Sloc_N,
4827 Defining_Identifier => First_Tag_Component (T),
4828 Component_Definition =>
4829 Make_Component_Definition (Sloc_N,
4830 Aliased_Present => False,
4831 Subtype_Indication => New_Reference_To (RTE (RE_Tag), Sloc_N)));
4833 if Null_Present (Comp_List)
4834 or else Is_Empty_List (Component_Items (Comp_List))
4835 then
4836 Set_Component_Items (Comp_List, New_List (Comp_Decl));
4837 Set_Null_Present (Comp_List, False);
4839 else
4840 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
4841 end if;
4843 -- We don't Analyze the whole expansion because the tag component has
4844 -- already been analyzed previously. Here we just insure that the tree
4845 -- is coherent with the semantic decoration
4847 Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
4849 exception
4850 when RE_Not_Available =>
4851 return;
4852 end Expand_Tagged_Root;
4854 ----------------------
4855 -- Clean_Task_Names --
4856 ----------------------
4858 procedure Clean_Task_Names
4859 (Typ : Entity_Id;
4860 Proc_Id : Entity_Id)
4862 begin
4863 if Has_Task (Typ)
4864 and then not Restriction_Active (No_Implicit_Heap_Allocations)
4865 and then not Global_Discard_Names
4866 and then VM_Target = No_VM
4867 then
4868 Set_Uses_Sec_Stack (Proc_Id);
4869 end if;
4870 end Clean_Task_Names;
4872 -----------------------
4873 -- Freeze_Array_Type --
4874 -----------------------
4876 procedure Freeze_Array_Type (N : Node_Id) is
4877 Typ : constant Entity_Id := Entity (N);
4878 Comp_Typ : constant Entity_Id := Component_Type (Typ);
4879 Base : constant Entity_Id := Base_Type (Typ);
4881 begin
4882 if not Is_Bit_Packed_Array (Typ) then
4884 -- If the component contains tasks, so does the array type. This may
4885 -- not be indicated in the array type because the component may have
4886 -- been a private type at the point of definition. Same if component
4887 -- type is controlled.
4889 Set_Has_Task (Base, Has_Task (Comp_Typ));
4890 Set_Has_Controlled_Component (Base,
4891 Has_Controlled_Component (Comp_Typ)
4892 or else Is_Controlled (Comp_Typ));
4894 if No (Init_Proc (Base)) then
4896 -- If this is an anonymous array created for a declaration with
4897 -- an initial value, its init_proc will never be called. The
4898 -- initial value itself may have been expanded into assignments,
4899 -- in which case the object declaration is carries the
4900 -- No_Initialization flag.
4902 if Is_Itype (Base)
4903 and then Nkind (Associated_Node_For_Itype (Base)) =
4904 N_Object_Declaration
4905 and then (Present (Expression (Associated_Node_For_Itype (Base)))
4906 or else
4907 No_Initialization (Associated_Node_For_Itype (Base)))
4908 then
4909 null;
4911 -- We do not need an init proc for string or wide [wide] string,
4912 -- since the only time these need initialization in normalize or
4913 -- initialize scalars mode, and these types are treated specially
4914 -- and do not need initialization procedures.
4916 elsif Root_Type (Base) = Standard_String
4917 or else Root_Type (Base) = Standard_Wide_String
4918 or else Root_Type (Base) = Standard_Wide_Wide_String
4919 then
4920 null;
4922 -- Otherwise we have to build an init proc for the subtype
4924 else
4925 Build_Array_Init_Proc (Base, N);
4926 end if;
4927 end if;
4929 if Typ = Base then
4930 if Has_Controlled_Component (Base) then
4931 Build_Controlling_Procs (Base);
4933 if not Is_Limited_Type (Comp_Typ)
4934 and then Number_Dimensions (Typ) = 1
4935 then
4936 Build_Slice_Assignment (Typ);
4937 end if;
4939 elsif Ekind (Comp_Typ) = E_Anonymous_Access_Type
4940 and then Controlled_Type (Directly_Designated_Type (Comp_Typ))
4941 then
4942 Set_Associated_Final_Chain (Comp_Typ, Add_Final_Chain (Typ));
4943 end if;
4944 end if;
4946 -- For packed case, default initialization, except if the component type
4947 -- is itself a packed structure with an initialization procedure, or
4948 -- initialize/normalize scalars active, and we have a base type, or the
4949 -- type is public, because in that case a client might specify
4950 -- Normalize_Scalars and there better be a public Init_Proc for it.
4952 elsif (Present (Init_Proc (Component_Type (Base)))
4953 and then No (Base_Init_Proc (Base)))
4954 or else (Init_Or_Norm_Scalars and then Base = Typ)
4955 or else Is_Public (Typ)
4956 then
4957 Build_Array_Init_Proc (Base, N);
4958 end if;
4959 end Freeze_Array_Type;
4961 -----------------------------
4962 -- Freeze_Enumeration_Type --
4963 -----------------------------
4965 procedure Freeze_Enumeration_Type (N : Node_Id) is
4966 Typ : constant Entity_Id := Entity (N);
4967 Loc : constant Source_Ptr := Sloc (Typ);
4968 Ent : Entity_Id;
4969 Lst : List_Id;
4970 Num : Nat;
4971 Arr : Entity_Id;
4972 Fent : Entity_Id;
4973 Ityp : Entity_Id;
4974 Is_Contiguous : Boolean;
4975 Pos_Expr : Node_Id;
4976 Last_Repval : Uint;
4978 Func : Entity_Id;
4979 pragma Warnings (Off, Func);
4981 begin
4982 -- Various optimizations possible if given representation is contiguous
4984 Is_Contiguous := True;
4986 Ent := First_Literal (Typ);
4987 Last_Repval := Enumeration_Rep (Ent);
4989 Next_Literal (Ent);
4990 while Present (Ent) loop
4991 if Enumeration_Rep (Ent) - Last_Repval /= 1 then
4992 Is_Contiguous := False;
4993 exit;
4994 else
4995 Last_Repval := Enumeration_Rep (Ent);
4996 end if;
4998 Next_Literal (Ent);
4999 end loop;
5001 if Is_Contiguous then
5002 Set_Has_Contiguous_Rep (Typ);
5003 Ent := First_Literal (Typ);
5004 Num := 1;
5005 Lst := New_List (New_Reference_To (Ent, Sloc (Ent)));
5007 else
5008 -- Build list of literal references
5010 Lst := New_List;
5011 Num := 0;
5013 Ent := First_Literal (Typ);
5014 while Present (Ent) loop
5015 Append_To (Lst, New_Reference_To (Ent, Sloc (Ent)));
5016 Num := Num + 1;
5017 Next_Literal (Ent);
5018 end loop;
5019 end if;
5021 -- Now build an array declaration
5023 -- typA : array (Natural range 0 .. num - 1) of ctype :=
5024 -- (v, v, v, v, v, ....)
5026 -- where ctype is the corresponding integer type. If the representation
5027 -- is contiguous, we only keep the first literal, which provides the
5028 -- offset for Pos_To_Rep computations.
5030 Arr :=
5031 Make_Defining_Identifier (Loc,
5032 Chars => New_External_Name (Chars (Typ), 'A'));
5034 Append_Freeze_Action (Typ,
5035 Make_Object_Declaration (Loc,
5036 Defining_Identifier => Arr,
5037 Constant_Present => True,
5039 Object_Definition =>
5040 Make_Constrained_Array_Definition (Loc,
5041 Discrete_Subtype_Definitions => New_List (
5042 Make_Subtype_Indication (Loc,
5043 Subtype_Mark => New_Reference_To (Standard_Natural, Loc),
5044 Constraint =>
5045 Make_Range_Constraint (Loc,
5046 Range_Expression =>
5047 Make_Range (Loc,
5048 Low_Bound =>
5049 Make_Integer_Literal (Loc, 0),
5050 High_Bound =>
5051 Make_Integer_Literal (Loc, Num - 1))))),
5053 Component_Definition =>
5054 Make_Component_Definition (Loc,
5055 Aliased_Present => False,
5056 Subtype_Indication => New_Reference_To (Typ, Loc))),
5058 Expression =>
5059 Make_Aggregate (Loc,
5060 Expressions => Lst)));
5062 Set_Enum_Pos_To_Rep (Typ, Arr);
5064 -- Now we build the function that converts representation values to
5065 -- position values. This function has the form:
5067 -- function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
5068 -- begin
5069 -- case ityp!(A) is
5070 -- when enum-lit'Enum_Rep => return posval;
5071 -- when enum-lit'Enum_Rep => return posval;
5072 -- ...
5073 -- when others =>
5074 -- [raise Constraint_Error when F "invalid data"]
5075 -- return -1;
5076 -- end case;
5077 -- end;
5079 -- Note: the F parameter determines whether the others case (no valid
5080 -- representation) raises Constraint_Error or returns a unique value
5081 -- of minus one. The latter case is used, e.g. in 'Valid code.
5083 -- Note: the reason we use Enum_Rep values in the case here is to avoid
5084 -- the code generator making inappropriate assumptions about the range
5085 -- of the values in the case where the value is invalid. ityp is a
5086 -- signed or unsigned integer type of appropriate width.
5088 -- Note: if exceptions are not supported, then we suppress the raise
5089 -- and return -1 unconditionally (this is an erroneous program in any
5090 -- case and there is no obligation to raise Constraint_Error here!) We
5091 -- also do this if pragma Restrictions (No_Exceptions) is active.
5093 -- Is this right??? What about No_Exception_Propagation???
5095 -- Representations are signed
5097 if Enumeration_Rep (First_Literal (Typ)) < 0 then
5099 -- The underlying type is signed. Reset the Is_Unsigned_Type
5100 -- explicitly, because it might have been inherited from
5101 -- parent type.
5103 Set_Is_Unsigned_Type (Typ, False);
5105 if Esize (Typ) <= Standard_Integer_Size then
5106 Ityp := Standard_Integer;
5107 else
5108 Ityp := Universal_Integer;
5109 end if;
5111 -- Representations are unsigned
5113 else
5114 if Esize (Typ) <= Standard_Integer_Size then
5115 Ityp := RTE (RE_Unsigned);
5116 else
5117 Ityp := RTE (RE_Long_Long_Unsigned);
5118 end if;
5119 end if;
5121 -- The body of the function is a case statement. First collect case
5122 -- alternatives, or optimize the contiguous case.
5124 Lst := New_List;
5126 -- If representation is contiguous, Pos is computed by subtracting
5127 -- the representation of the first literal.
5129 if Is_Contiguous then
5130 Ent := First_Literal (Typ);
5132 if Enumeration_Rep (Ent) = Last_Repval then
5134 -- Another special case: for a single literal, Pos is zero
5136 Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
5138 else
5139 Pos_Expr :=
5140 Convert_To (Standard_Integer,
5141 Make_Op_Subtract (Loc,
5142 Left_Opnd =>
5143 Unchecked_Convert_To (Ityp,
5144 Make_Identifier (Loc, Name_uA)),
5145 Right_Opnd =>
5146 Make_Integer_Literal (Loc,
5147 Intval =>
5148 Enumeration_Rep (First_Literal (Typ)))));
5149 end if;
5151 Append_To (Lst,
5152 Make_Case_Statement_Alternative (Loc,
5153 Discrete_Choices => New_List (
5154 Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
5155 Low_Bound =>
5156 Make_Integer_Literal (Loc,
5157 Intval => Enumeration_Rep (Ent)),
5158 High_Bound =>
5159 Make_Integer_Literal (Loc, Intval => Last_Repval))),
5161 Statements => New_List (
5162 Make_Simple_Return_Statement (Loc,
5163 Expression => Pos_Expr))));
5165 else
5166 Ent := First_Literal (Typ);
5167 while Present (Ent) loop
5168 Append_To (Lst,
5169 Make_Case_Statement_Alternative (Loc,
5170 Discrete_Choices => New_List (
5171 Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
5172 Intval => Enumeration_Rep (Ent))),
5174 Statements => New_List (
5175 Make_Simple_Return_Statement (Loc,
5176 Expression =>
5177 Make_Integer_Literal (Loc,
5178 Intval => Enumeration_Pos (Ent))))));
5180 Next_Literal (Ent);
5181 end loop;
5182 end if;
5184 -- In normal mode, add the others clause with the test
5186 if not No_Exception_Handlers_Set then
5187 Append_To (Lst,
5188 Make_Case_Statement_Alternative (Loc,
5189 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
5190 Statements => New_List (
5191 Make_Raise_Constraint_Error (Loc,
5192 Condition => Make_Identifier (Loc, Name_uF),
5193 Reason => CE_Invalid_Data),
5194 Make_Simple_Return_Statement (Loc,
5195 Expression =>
5196 Make_Integer_Literal (Loc, -1)))));
5198 -- If either of the restrictions No_Exceptions_Handlers/Propagation is
5199 -- active then return -1 (we cannot usefully raise Constraint_Error in
5200 -- this case). See description above for further details.
5202 else
5203 Append_To (Lst,
5204 Make_Case_Statement_Alternative (Loc,
5205 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
5206 Statements => New_List (
5207 Make_Simple_Return_Statement (Loc,
5208 Expression =>
5209 Make_Integer_Literal (Loc, -1)))));
5210 end if;
5212 -- Now we can build the function body
5214 Fent :=
5215 Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
5217 Func :=
5218 Make_Subprogram_Body (Loc,
5219 Specification =>
5220 Make_Function_Specification (Loc,
5221 Defining_Unit_Name => Fent,
5222 Parameter_Specifications => New_List (
5223 Make_Parameter_Specification (Loc,
5224 Defining_Identifier =>
5225 Make_Defining_Identifier (Loc, Name_uA),
5226 Parameter_Type => New_Reference_To (Typ, Loc)),
5227 Make_Parameter_Specification (Loc,
5228 Defining_Identifier =>
5229 Make_Defining_Identifier (Loc, Name_uF),
5230 Parameter_Type => New_Reference_To (Standard_Boolean, Loc))),
5232 Result_Definition => New_Reference_To (Standard_Integer, Loc)),
5234 Declarations => Empty_List,
5236 Handled_Statement_Sequence =>
5237 Make_Handled_Sequence_Of_Statements (Loc,
5238 Statements => New_List (
5239 Make_Case_Statement (Loc,
5240 Expression =>
5241 Unchecked_Convert_To (Ityp,
5242 Make_Identifier (Loc, Name_uA)),
5243 Alternatives => Lst))));
5245 Set_TSS (Typ, Fent);
5246 Set_Is_Pure (Fent);
5248 if not Debug_Generated_Code then
5249 Set_Debug_Info_Off (Fent);
5250 end if;
5252 exception
5253 when RE_Not_Available =>
5254 return;
5255 end Freeze_Enumeration_Type;
5257 ------------------------
5258 -- Freeze_Record_Type --
5259 ------------------------
5261 procedure Freeze_Record_Type (N : Node_Id) is
5262 Def_Id : constant Node_Id := Entity (N);
5263 Type_Decl : constant Node_Id := Parent (Def_Id);
5264 Comp : Entity_Id;
5265 Comp_Typ : Entity_Id;
5266 Has_Static_DT : Boolean := False;
5267 Predef_List : List_Id;
5269 Flist : Entity_Id := Empty;
5270 -- Finalization list allocated for the case of a type with anonymous
5271 -- access components whose designated type is potentially controlled.
5273 Renamed_Eq : Node_Id := Empty;
5274 -- Defining unit name for the predefined equality function in the case
5275 -- where the type has a primitive operation that is a renaming of
5276 -- predefined equality (but only if there is also an overriding
5277 -- user-defined equality function). Used to pass this entity from
5278 -- Make_Predefined_Primitive_Specs to Predefined_Primitive_Bodies.
5280 Wrapper_Decl_List : List_Id := No_List;
5281 Wrapper_Body_List : List_Id := No_List;
5282 Null_Proc_Decl_List : List_Id := No_List;
5284 begin
5285 -- Build discriminant checking functions if not a derived type (for
5286 -- derived types that are not tagged types, always use the discriminant
5287 -- checking functions of the parent type). However, for untagged types
5288 -- the derivation may have taken place before the parent was frozen, so
5289 -- we copy explicitly the discriminant checking functions from the
5290 -- parent into the components of the derived type.
5292 if not Is_Derived_Type (Def_Id)
5293 or else Has_New_Non_Standard_Rep (Def_Id)
5294 or else Is_Tagged_Type (Def_Id)
5295 then
5296 Build_Discr_Checking_Funcs (Type_Decl);
5298 elsif Is_Derived_Type (Def_Id)
5299 and then not Is_Tagged_Type (Def_Id)
5301 -- If we have a derived Unchecked_Union, we do not inherit the
5302 -- discriminant checking functions from the parent type since the
5303 -- discriminants are non existent.
5305 and then not Is_Unchecked_Union (Def_Id)
5306 and then Has_Discriminants (Def_Id)
5307 then
5308 declare
5309 Old_Comp : Entity_Id;
5311 begin
5312 Old_Comp :=
5313 First_Component (Base_Type (Underlying_Type (Etype (Def_Id))));
5314 Comp := First_Component (Def_Id);
5315 while Present (Comp) loop
5316 if Ekind (Comp) = E_Component
5317 and then Chars (Comp) = Chars (Old_Comp)
5318 then
5319 Set_Discriminant_Checking_Func (Comp,
5320 Discriminant_Checking_Func (Old_Comp));
5321 end if;
5323 Next_Component (Old_Comp);
5324 Next_Component (Comp);
5325 end loop;
5326 end;
5327 end if;
5329 if Is_Derived_Type (Def_Id)
5330 and then Is_Limited_Type (Def_Id)
5331 and then Is_Tagged_Type (Def_Id)
5332 then
5333 Check_Stream_Attributes (Def_Id);
5334 end if;
5336 -- Update task and controlled component flags, because some of the
5337 -- component types may have been private at the point of the record
5338 -- declaration.
5340 Comp := First_Component (Def_Id);
5342 while Present (Comp) loop
5343 Comp_Typ := Etype (Comp);
5345 if Has_Task (Comp_Typ) then
5346 Set_Has_Task (Def_Id);
5348 elsif Has_Controlled_Component (Comp_Typ)
5349 or else (Chars (Comp) /= Name_uParent
5350 and then Is_Controlled (Comp_Typ))
5351 then
5352 Set_Has_Controlled_Component (Def_Id);
5354 elsif Ekind (Comp_Typ) = E_Anonymous_Access_Type
5355 and then Controlled_Type (Directly_Designated_Type (Comp_Typ))
5356 then
5357 if No (Flist) then
5358 Flist := Add_Final_Chain (Def_Id);
5359 end if;
5361 Set_Associated_Final_Chain (Comp_Typ, Flist);
5362 end if;
5364 Next_Component (Comp);
5365 end loop;
5367 -- Creation of the Dispatch Table. Note that a Dispatch Table is built
5368 -- for regular tagged types as well as for Ada types deriving from a C++
5369 -- Class, but not for tagged types directly corresponding to C++ classes
5370 -- In the later case we assume that it is created in the C++ side and we
5371 -- just use it.
5373 if Is_Tagged_Type (Def_Id) then
5374 Has_Static_DT :=
5375 Static_Dispatch_Tables
5376 and then Is_Library_Level_Tagged_Type (Def_Id);
5378 -- Add the _Tag component
5380 if Underlying_Type (Etype (Def_Id)) = Def_Id then
5381 Expand_Tagged_Root (Def_Id);
5382 end if;
5384 if Is_CPP_Class (Def_Id) then
5385 Set_All_DT_Position (Def_Id);
5386 Set_Default_Constructor (Def_Id);
5388 -- Create the tag entities with a minimum decoration
5390 if VM_Target = No_VM then
5391 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
5392 end if;
5394 else
5395 if not Has_Static_DT then
5397 -- Usually inherited primitives are not delayed but the first
5398 -- Ada extension of a CPP_Class is an exception since the
5399 -- address of the inherited subprogram has to be inserted in
5400 -- the new Ada Dispatch Table and this is a freezing action.
5402 -- Similarly, if this is an inherited operation whose parent is
5403 -- not frozen yet, it is not in the DT of the parent, and we
5404 -- generate an explicit freeze node for the inherited operation
5405 -- so that it is properly inserted in the DT of the current
5406 -- type.
5408 declare
5409 Elmt : Elmt_Id := First_Elmt (Primitive_Operations (Def_Id));
5410 Subp : Entity_Id;
5412 begin
5413 while Present (Elmt) loop
5414 Subp := Node (Elmt);
5416 if Present (Alias (Subp)) then
5417 if Is_CPP_Class (Etype (Def_Id)) then
5418 Set_Has_Delayed_Freeze (Subp);
5420 elsif Has_Delayed_Freeze (Alias (Subp))
5421 and then not Is_Frozen (Alias (Subp))
5422 then
5423 Set_Is_Frozen (Subp, False);
5424 Set_Has_Delayed_Freeze (Subp);
5425 end if;
5426 end if;
5428 Next_Elmt (Elmt);
5429 end loop;
5430 end;
5431 end if;
5433 -- Unfreeze momentarily the type to add the predefined primitives
5434 -- operations. The reason we unfreeze is so that these predefined
5435 -- operations will indeed end up as primitive operations (which
5436 -- must be before the freeze point).
5438 Set_Is_Frozen (Def_Id, False);
5440 -- Do not add the spec of the predefined primitives if we are
5441 -- compiling under restriction No_Dispatching_Calls
5443 if not Restriction_Active (No_Dispatching_Calls) then
5444 Make_Predefined_Primitive_Specs
5445 (Def_Id, Predef_List, Renamed_Eq);
5446 Insert_List_Before_And_Analyze (N, Predef_List);
5447 end if;
5449 -- Ada 2005 (AI-391): For a nonabstract null extension, create
5450 -- wrapper functions for each nonoverridden inherited function
5451 -- with a controlling result of the type. The wrapper for such
5452 -- a function returns an extension aggregate that invokes the
5453 -- the parent function.
5455 if Ada_Version >= Ada_05
5456 and then not Is_Abstract_Type (Def_Id)
5457 and then Is_Null_Extension (Def_Id)
5458 then
5459 Make_Controlling_Function_Wrappers
5460 (Def_Id, Wrapper_Decl_List, Wrapper_Body_List);
5461 Insert_List_Before_And_Analyze (N, Wrapper_Decl_List);
5462 end if;
5464 -- Ada 2005 (AI-251): For a nonabstract type extension, build
5465 -- null procedure declarations for each set of homographic null
5466 -- procedures that are inherited from interface types but not
5467 -- overridden. This is done to ensure that the dispatch table
5468 -- entry associated with such null primitives are properly filled.
5470 if Ada_Version >= Ada_05
5471 and then Etype (Def_Id) /= Def_Id
5472 and then not Is_Abstract_Type (Def_Id)
5473 then
5474 Make_Null_Procedure_Specs (Def_Id, Null_Proc_Decl_List);
5475 Insert_Actions (N, Null_Proc_Decl_List);
5476 end if;
5478 Set_Is_Frozen (Def_Id);
5479 Set_All_DT_Position (Def_Id);
5481 -- Add the controlled component before the freezing actions
5482 -- referenced in those actions.
5484 if Has_New_Controlled_Component (Def_Id) then
5485 Expand_Record_Controller (Def_Id);
5486 end if;
5488 -- Create and decorate the tags. Suppress their creation when
5489 -- VM_Target because the dispatching mechanism is handled
5490 -- internally by the VMs.
5492 if VM_Target = No_VM then
5493 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
5495 -- Generate dispatch table of locally defined tagged type.
5496 -- Dispatch tables of library level tagged types are built
5497 -- later (see Analyze_Declarations).
5499 if VM_Target = No_VM
5500 and then not Has_Static_DT
5501 then
5502 Append_Freeze_Actions (Def_Id, Make_DT (Def_Id));
5503 end if;
5504 end if;
5506 -- Make sure that the primitives Initialize, Adjust and Finalize
5507 -- are Frozen before other TSS subprograms. We don't want them
5508 -- Frozen inside.
5510 if Is_Controlled (Def_Id) then
5511 if not Is_Limited_Type (Def_Id) then
5512 Append_Freeze_Actions (Def_Id,
5513 Freeze_Entity
5514 (Find_Prim_Op (Def_Id, Name_Adjust), Sloc (Def_Id)));
5515 end if;
5517 Append_Freeze_Actions (Def_Id,
5518 Freeze_Entity
5519 (Find_Prim_Op (Def_Id, Name_Initialize), Sloc (Def_Id)));
5521 Append_Freeze_Actions (Def_Id,
5522 Freeze_Entity
5523 (Find_Prim_Op (Def_Id, Name_Finalize), Sloc (Def_Id)));
5524 end if;
5526 -- Freeze rest of primitive operations. There is no need to handle
5527 -- the predefined primitives if we are compiling under restriction
5528 -- No_Dispatching_Calls
5530 if not Restriction_Active (No_Dispatching_Calls) then
5531 Append_Freeze_Actions
5532 (Def_Id, Predefined_Primitive_Freeze (Def_Id));
5533 end if;
5534 end if;
5536 -- In the non-tagged case, an equality function is provided only for
5537 -- variant records (that are not unchecked unions).
5539 elsif Has_Discriminants (Def_Id)
5540 and then not Is_Limited_Type (Def_Id)
5541 then
5542 declare
5543 Comps : constant Node_Id :=
5544 Component_List (Type_Definition (Type_Decl));
5546 begin
5547 if Present (Comps)
5548 and then Present (Variant_Part (Comps))
5549 then
5550 Build_Variant_Record_Equality (Def_Id);
5551 end if;
5552 end;
5553 end if;
5555 -- Before building the record initialization procedure, if we are
5556 -- dealing with a concurrent record value type, then we must go through
5557 -- the discriminants, exchanging discriminals between the concurrent
5558 -- type and the concurrent record value type. See the section "Handling
5559 -- of Discriminants" in the Einfo spec for details.
5561 if Is_Concurrent_Record_Type (Def_Id)
5562 and then Has_Discriminants (Def_Id)
5563 then
5564 declare
5565 Ctyp : constant Entity_Id :=
5566 Corresponding_Concurrent_Type (Def_Id);
5567 Conc_Discr : Entity_Id;
5568 Rec_Discr : Entity_Id;
5569 Temp : Entity_Id;
5571 begin
5572 Conc_Discr := First_Discriminant (Ctyp);
5573 Rec_Discr := First_Discriminant (Def_Id);
5575 while Present (Conc_Discr) loop
5576 Temp := Discriminal (Conc_Discr);
5577 Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
5578 Set_Discriminal (Rec_Discr, Temp);
5580 Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
5581 Set_Discriminal_Link (Discriminal (Rec_Discr), Rec_Discr);
5583 Next_Discriminant (Conc_Discr);
5584 Next_Discriminant (Rec_Discr);
5585 end loop;
5586 end;
5587 end if;
5589 if Has_Controlled_Component (Def_Id) then
5590 if No (Controller_Component (Def_Id)) then
5591 Expand_Record_Controller (Def_Id);
5592 end if;
5594 Build_Controlling_Procs (Def_Id);
5595 end if;
5597 Adjust_Discriminants (Def_Id);
5599 if VM_Target = No_VM or else not Is_Interface (Def_Id) then
5601 -- Do not need init for interfaces on e.g. CIL since they're
5602 -- abstract. Helps operation of peverify (the PE Verify tool).
5604 Build_Record_Init_Proc (Type_Decl, Def_Id);
5605 end if;
5607 -- For tagged type that are not interfaces, build bodies of primitive
5608 -- operations. Note that we do this after building the record
5609 -- initialization procedure, since the primitive operations may need
5610 -- the initialization routine. There is no need to add predefined
5611 -- primitives of interfaces because all their predefined primitives
5612 -- are abstract.
5614 if Is_Tagged_Type (Def_Id)
5615 and then not Is_Interface (Def_Id)
5616 then
5618 -- Do not add the body of the predefined primitives if we are
5619 -- compiling under restriction No_Dispatching_Calls
5621 if not Restriction_Active (No_Dispatching_Calls) then
5622 Predef_List := Predefined_Primitive_Bodies (Def_Id, Renamed_Eq);
5623 Append_Freeze_Actions (Def_Id, Predef_List);
5624 end if;
5626 -- Ada 2005 (AI-391): If any wrappers were created for nonoverridden
5627 -- inherited functions, then add their bodies to the freeze actions.
5629 if Present (Wrapper_Body_List) then
5630 Append_Freeze_Actions (Def_Id, Wrapper_Body_List);
5631 end if;
5632 end if;
5633 end Freeze_Record_Type;
5635 ------------------------------
5636 -- Freeze_Stream_Operations --
5637 ------------------------------
5639 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
5640 Names : constant array (1 .. 4) of TSS_Name_Type :=
5641 (TSS_Stream_Input,
5642 TSS_Stream_Output,
5643 TSS_Stream_Read,
5644 TSS_Stream_Write);
5645 Stream_Op : Entity_Id;
5647 begin
5648 -- Primitive operations of tagged types are frozen when the dispatch
5649 -- table is constructed.
5651 if not Comes_From_Source (Typ)
5652 or else Is_Tagged_Type (Typ)
5653 then
5654 return;
5655 end if;
5657 for J in Names'Range loop
5658 Stream_Op := TSS (Typ, Names (J));
5660 if Present (Stream_Op)
5661 and then Is_Subprogram (Stream_Op)
5662 and then Nkind (Unit_Declaration_Node (Stream_Op)) =
5663 N_Subprogram_Declaration
5664 and then not Is_Frozen (Stream_Op)
5665 then
5666 Append_Freeze_Actions
5667 (Typ, Freeze_Entity (Stream_Op, Sloc (N)));
5668 end if;
5669 end loop;
5670 end Freeze_Stream_Operations;
5672 -----------------
5673 -- Freeze_Type --
5674 -----------------
5676 -- Full type declarations are expanded at the point at which the type is
5677 -- frozen. The formal N is the Freeze_Node for the type. Any statements or
5678 -- declarations generated by the freezing (e.g. the procedure generated
5679 -- for initialization) are chained in the Actions field list of the freeze
5680 -- node using Append_Freeze_Actions.
5682 function Freeze_Type (N : Node_Id) return Boolean is
5683 Def_Id : constant Entity_Id := Entity (N);
5684 RACW_Seen : Boolean := False;
5685 Result : Boolean := False;
5687 begin
5688 -- Process associated access types needing special processing
5690 if Present (Access_Types_To_Process (N)) then
5691 declare
5692 E : Elmt_Id := First_Elmt (Access_Types_To_Process (N));
5693 begin
5694 while Present (E) loop
5696 if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
5697 Validate_RACW_Primitives (Node (E));
5698 RACW_Seen := True;
5699 end if;
5701 E := Next_Elmt (E);
5702 end loop;
5703 end;
5705 if RACW_Seen then
5707 -- If there are RACWs designating this type, make stubs now
5709 Remote_Types_Tagged_Full_View_Encountered (Def_Id);
5710 end if;
5711 end if;
5713 -- Freeze processing for record types
5715 if Is_Record_Type (Def_Id) then
5716 if Ekind (Def_Id) = E_Record_Type then
5717 Freeze_Record_Type (N);
5719 -- The subtype may have been declared before the type was frozen. If
5720 -- the type has controlled components it is necessary to create the
5721 -- entity for the controller explicitly because it did not exist at
5722 -- the point of the subtype declaration. Only the entity is needed,
5723 -- the back-end will obtain the layout from the type. This is only
5724 -- necessary if this is constrained subtype whose component list is
5725 -- not shared with the base type.
5727 elsif Ekind (Def_Id) = E_Record_Subtype
5728 and then Has_Discriminants (Def_Id)
5729 and then Last_Entity (Def_Id) /= Last_Entity (Base_Type (Def_Id))
5730 and then Present (Controller_Component (Def_Id))
5731 then
5732 declare
5733 Old_C : constant Entity_Id := Controller_Component (Def_Id);
5734 New_C : Entity_Id;
5736 begin
5737 if Scope (Old_C) = Base_Type (Def_Id) then
5739 -- The entity is the one in the parent. Create new one
5741 New_C := New_Copy (Old_C);
5742 Set_Parent (New_C, Parent (Old_C));
5743 Push_Scope (Def_Id);
5744 Enter_Name (New_C);
5745 End_Scope;
5746 end if;
5747 end;
5749 if Is_Itype (Def_Id)
5750 and then Is_Record_Type (Underlying_Type (Scope (Def_Id)))
5751 then
5752 -- The freeze node is only used to introduce the controller,
5753 -- the back-end has no use for it for a discriminated
5754 -- component.
5756 Set_Freeze_Node (Def_Id, Empty);
5757 Set_Has_Delayed_Freeze (Def_Id, False);
5758 Result := True;
5759 end if;
5761 -- Similar process if the controller of the subtype is not present
5762 -- but the parent has it. This can happen with constrained
5763 -- record components where the subtype is an itype.
5765 elsif Ekind (Def_Id) = E_Record_Subtype
5766 and then Is_Itype (Def_Id)
5767 and then No (Controller_Component (Def_Id))
5768 and then Present (Controller_Component (Etype (Def_Id)))
5769 then
5770 declare
5771 Old_C : constant Entity_Id :=
5772 Controller_Component (Etype (Def_Id));
5773 New_C : constant Entity_Id := New_Copy (Old_C);
5775 begin
5776 Set_Next_Entity (New_C, First_Entity (Def_Id));
5777 Set_First_Entity (Def_Id, New_C);
5779 -- The freeze node is only used to introduce the controller,
5780 -- the back-end has no use for it for a discriminated
5781 -- component.
5783 Set_Freeze_Node (Def_Id, Empty);
5784 Set_Has_Delayed_Freeze (Def_Id, False);
5785 Result := True;
5786 end;
5787 end if;
5789 -- Freeze processing for array types
5791 elsif Is_Array_Type (Def_Id) then
5792 Freeze_Array_Type (N);
5794 -- Freeze processing for access types
5796 -- For pool-specific access types, find out the pool object used for
5797 -- this type, needs actual expansion of it in some cases. Here are the
5798 -- different cases :
5800 -- 1. Rep Clause "for Def_Id'Storage_Size use 0;"
5801 -- ---> don't use any storage pool
5803 -- 2. Rep Clause : for Def_Id'Storage_Size use Expr.
5804 -- Expand:
5805 -- Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
5807 -- 3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
5808 -- ---> Storage Pool is the specified one
5810 -- See GNAT Pool packages in the Run-Time for more details
5812 elsif Ekind (Def_Id) = E_Access_Type
5813 or else Ekind (Def_Id) = E_General_Access_Type
5814 then
5815 declare
5816 Loc : constant Source_Ptr := Sloc (N);
5817 Desig_Type : constant Entity_Id := Designated_Type (Def_Id);
5818 Pool_Object : Entity_Id;
5819 Siz_Exp : Node_Id;
5821 Freeze_Action_Typ : Entity_Id;
5823 begin
5824 if Has_Storage_Size_Clause (Def_Id) then
5825 Siz_Exp := Expression (Parent (Storage_Size_Variable (Def_Id)));
5826 else
5827 Siz_Exp := Empty;
5828 end if;
5830 -- Case 1
5832 -- Rep Clause "for Def_Id'Storage_Size use 0;"
5833 -- ---> don't use any storage pool
5835 if Has_Storage_Size_Clause (Def_Id)
5836 and then Compile_Time_Known_Value (Siz_Exp)
5837 and then Expr_Value (Siz_Exp) = 0
5838 then
5839 null;
5841 -- Case 2
5843 -- Rep Clause : for Def_Id'Storage_Size use Expr.
5844 -- ---> Expand:
5845 -- Def_Id__Pool : Stack_Bounded_Pool
5846 -- (Expr, DT'Size, DT'Alignment);
5848 elsif Has_Storage_Size_Clause (Def_Id) then
5849 declare
5850 DT_Size : Node_Id;
5851 DT_Align : Node_Id;
5853 begin
5854 -- For unconstrained composite types we give a size of zero
5855 -- so that the pool knows that it needs a special algorithm
5856 -- for variable size object allocation.
5858 if Is_Composite_Type (Desig_Type)
5859 and then not Is_Constrained (Desig_Type)
5860 then
5861 DT_Size :=
5862 Make_Integer_Literal (Loc, 0);
5864 DT_Align :=
5865 Make_Integer_Literal (Loc, Maximum_Alignment);
5867 else
5868 DT_Size :=
5869 Make_Attribute_Reference (Loc,
5870 Prefix => New_Reference_To (Desig_Type, Loc),
5871 Attribute_Name => Name_Max_Size_In_Storage_Elements);
5873 DT_Align :=
5874 Make_Attribute_Reference (Loc,
5875 Prefix => New_Reference_To (Desig_Type, Loc),
5876 Attribute_Name => Name_Alignment);
5877 end if;
5879 Pool_Object :=
5880 Make_Defining_Identifier (Loc,
5881 Chars => New_External_Name (Chars (Def_Id), 'P'));
5883 -- We put the code associated with the pools in the entity
5884 -- that has the later freeze node, usually the access type
5885 -- but it can also be the designated_type; because the pool
5886 -- code requires both those types to be frozen
5888 if Is_Frozen (Desig_Type)
5889 and then (No (Freeze_Node (Desig_Type))
5890 or else Analyzed (Freeze_Node (Desig_Type)))
5891 then
5892 Freeze_Action_Typ := Def_Id;
5894 -- A Taft amendment type cannot get the freeze actions
5895 -- since the full view is not there.
5897 elsif Is_Incomplete_Or_Private_Type (Desig_Type)
5898 and then No (Full_View (Desig_Type))
5899 then
5900 Freeze_Action_Typ := Def_Id;
5902 else
5903 Freeze_Action_Typ := Desig_Type;
5904 end if;
5906 Append_Freeze_Action (Freeze_Action_Typ,
5907 Make_Object_Declaration (Loc,
5908 Defining_Identifier => Pool_Object,
5909 Object_Definition =>
5910 Make_Subtype_Indication (Loc,
5911 Subtype_Mark =>
5912 New_Reference_To
5913 (RTE (RE_Stack_Bounded_Pool), Loc),
5915 Constraint =>
5916 Make_Index_Or_Discriminant_Constraint (Loc,
5917 Constraints => New_List (
5919 -- First discriminant is the Pool Size
5921 New_Reference_To (
5922 Storage_Size_Variable (Def_Id), Loc),
5924 -- Second discriminant is the element size
5926 DT_Size,
5928 -- Third discriminant is the alignment
5930 DT_Align)))));
5931 end;
5933 Set_Associated_Storage_Pool (Def_Id, Pool_Object);
5935 -- Case 3
5937 -- Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
5938 -- ---> Storage Pool is the specified one
5940 elsif Present (Associated_Storage_Pool (Def_Id)) then
5942 -- Nothing to do the associated storage pool has been attached
5943 -- when analyzing the rep. clause
5945 null;
5946 end if;
5948 -- For access-to-controlled types (including class-wide types and
5949 -- Taft-amendment types which potentially have controlled
5950 -- components), expand the list controller object that will store
5951 -- the dynamically allocated objects. Do not do this
5952 -- transformation for expander-generated access types, but do it
5953 -- for types that are the full view of types derived from other
5954 -- private types. Also suppress the list controller in the case
5955 -- of a designated type with convention Java, since this is used
5956 -- when binding to Java API specs, where there's no equivalent of
5957 -- a finalization list and we don't want to pull in the
5958 -- finalization support if not needed.
5960 if not Comes_From_Source (Def_Id)
5961 and then not Has_Private_Declaration (Def_Id)
5962 then
5963 null;
5965 elsif (Controlled_Type (Desig_Type)
5966 and then Convention (Desig_Type) /= Convention_Java
5967 and then Convention (Desig_Type) /= Convention_CIL)
5968 or else
5969 (Is_Incomplete_Or_Private_Type (Desig_Type)
5970 and then No (Full_View (Desig_Type))
5972 -- An exception is made for types defined in the run-time
5973 -- because Ada.Tags.Tag itself is such a type and cannot
5974 -- afford this unnecessary overhead that would generates a
5975 -- loop in the expansion scheme...
5977 and then not In_Runtime (Def_Id)
5979 -- Another exception is if Restrictions (No_Finalization)
5980 -- is active, since then we know nothing is controlled.
5982 and then not Restriction_Active (No_Finalization))
5984 -- If the designated type is not frozen yet, its controlled
5985 -- status must be retrieved explicitly.
5987 or else (Is_Array_Type (Desig_Type)
5988 and then not Is_Frozen (Desig_Type)
5989 and then Controlled_Type (Component_Type (Desig_Type)))
5991 -- The designated type has controlled anonymous access
5992 -- discriminants.
5994 or else Has_Controlled_Coextensions (Desig_Type)
5995 then
5996 Set_Associated_Final_Chain (Def_Id, Add_Final_Chain (Def_Id));
5997 end if;
5998 end;
6000 -- Freeze processing for enumeration types
6002 elsif Ekind (Def_Id) = E_Enumeration_Type then
6004 -- We only have something to do if we have a non-standard
6005 -- representation (i.e. at least one literal whose pos value
6006 -- is not the same as its representation)
6008 if Has_Non_Standard_Rep (Def_Id) then
6009 Freeze_Enumeration_Type (N);
6010 end if;
6012 -- Private types that are completed by a derivation from a private
6013 -- type have an internally generated full view, that needs to be
6014 -- frozen. This must be done explicitly because the two views share
6015 -- the freeze node, and the underlying full view is not visible when
6016 -- the freeze node is analyzed.
6018 elsif Is_Private_Type (Def_Id)
6019 and then Is_Derived_Type (Def_Id)
6020 and then Present (Full_View (Def_Id))
6021 and then Is_Itype (Full_View (Def_Id))
6022 and then Has_Private_Declaration (Full_View (Def_Id))
6023 and then Freeze_Node (Full_View (Def_Id)) = N
6024 then
6025 Set_Entity (N, Full_View (Def_Id));
6026 Result := Freeze_Type (N);
6027 Set_Entity (N, Def_Id);
6029 -- All other types require no expander action. There are such cases
6030 -- (e.g. task types and protected types). In such cases, the freeze
6031 -- nodes are there for use by Gigi.
6033 end if;
6035 Freeze_Stream_Operations (N, Def_Id);
6036 return Result;
6038 exception
6039 when RE_Not_Available =>
6040 return False;
6041 end Freeze_Type;
6043 -------------------------
6044 -- Get_Simple_Init_Val --
6045 -------------------------
6047 function Get_Simple_Init_Val
6048 (T : Entity_Id;
6049 Loc : Source_Ptr;
6050 Size : Uint := No_Uint) return Node_Id
6052 Val : Node_Id;
6053 Result : Node_Id;
6054 Val_RE : RE_Id;
6056 Size_To_Use : Uint;
6057 -- This is the size to be used for computation of the appropriate
6058 -- initial value for the Normalize_Scalars and Initialize_Scalars case.
6060 Lo_Bound : Uint;
6061 Hi_Bound : Uint;
6062 -- These are the values computed by the procedure Check_Subtype_Bounds
6064 procedure Check_Subtype_Bounds;
6065 -- This procedure examines the subtype T, and its ancestor subtypes and
6066 -- derived types to determine the best known information about the
6067 -- bounds of the subtype. After the call Lo_Bound is set either to
6068 -- No_Uint if no information can be determined, or to a value which
6069 -- represents a known low bound, i.e. a valid value of the subtype can
6070 -- not be less than this value. Hi_Bound is similarly set to a known
6071 -- high bound (valid value cannot be greater than this).
6073 --------------------------
6074 -- Check_Subtype_Bounds --
6075 --------------------------
6077 procedure Check_Subtype_Bounds is
6078 ST1 : Entity_Id;
6079 ST2 : Entity_Id;
6080 Lo : Node_Id;
6081 Hi : Node_Id;
6082 Loval : Uint;
6083 Hival : Uint;
6085 begin
6086 Lo_Bound := No_Uint;
6087 Hi_Bound := No_Uint;
6089 -- Loop to climb ancestor subtypes and derived types
6091 ST1 := T;
6092 loop
6093 if not Is_Discrete_Type (ST1) then
6094 return;
6095 end if;
6097 Lo := Type_Low_Bound (ST1);
6098 Hi := Type_High_Bound (ST1);
6100 if Compile_Time_Known_Value (Lo) then
6101 Loval := Expr_Value (Lo);
6103 if Lo_Bound = No_Uint or else Lo_Bound < Loval then
6104 Lo_Bound := Loval;
6105 end if;
6106 end if;
6108 if Compile_Time_Known_Value (Hi) then
6109 Hival := Expr_Value (Hi);
6111 if Hi_Bound = No_Uint or else Hi_Bound > Hival then
6112 Hi_Bound := Hival;
6113 end if;
6114 end if;
6116 ST2 := Ancestor_Subtype (ST1);
6118 if No (ST2) then
6119 ST2 := Etype (ST1);
6120 end if;
6122 exit when ST1 = ST2;
6123 ST1 := ST2;
6124 end loop;
6125 end Check_Subtype_Bounds;
6127 -- Start of processing for Get_Simple_Init_Val
6129 begin
6130 -- For a private type, we should always have an underlying type
6131 -- (because this was already checked in Needs_Simple_Initialization).
6132 -- What we do is to get the value for the underlying type and then do
6133 -- an Unchecked_Convert to the private type.
6135 if Is_Private_Type (T) then
6136 Val := Get_Simple_Init_Val (Underlying_Type (T), Loc, Size);
6138 -- A special case, if the underlying value is null, then qualify it
6139 -- with the underlying type, so that the null is properly typed
6140 -- Similarly, if it is an aggregate it must be qualified, because an
6141 -- unchecked conversion does not provide a context for it.
6143 if Nkind_In (Val, N_Null, N_Aggregate) then
6144 Val :=
6145 Make_Qualified_Expression (Loc,
6146 Subtype_Mark =>
6147 New_Occurrence_Of (Underlying_Type (T), Loc),
6148 Expression => Val);
6149 end if;
6151 Result := Unchecked_Convert_To (T, Val);
6153 -- Don't truncate result (important for Initialize/Normalize_Scalars)
6155 if Nkind (Result) = N_Unchecked_Type_Conversion
6156 and then Is_Scalar_Type (Underlying_Type (T))
6157 then
6158 Set_No_Truncation (Result);
6159 end if;
6161 return Result;
6163 -- For scalars, we must have normalize/initialize scalars case
6165 elsif Is_Scalar_Type (T) then
6166 pragma Assert (Init_Or_Norm_Scalars);
6168 -- Compute size of object. If it is given by the caller, we can use
6169 -- it directly, otherwise we use Esize (T) as an estimate. As far as
6170 -- we know this covers all cases correctly.
6172 if Size = No_Uint or else Size <= Uint_0 then
6173 Size_To_Use := UI_Max (Uint_1, Esize (T));
6174 else
6175 Size_To_Use := Size;
6176 end if;
6178 -- Maximum size to use is 64 bits, since we will create values
6179 -- of type Unsigned_64 and the range must fit this type.
6181 if Size_To_Use /= No_Uint and then Size_To_Use > Uint_64 then
6182 Size_To_Use := Uint_64;
6183 end if;
6185 -- Check known bounds of subtype
6187 Check_Subtype_Bounds;
6189 -- Processing for Normalize_Scalars case
6191 if Normalize_Scalars then
6193 -- If zero is invalid, it is a convenient value to use that is
6194 -- for sure an appropriate invalid value in all situations.
6196 if Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
6197 Val := Make_Integer_Literal (Loc, 0);
6199 -- Cases where all one bits is the appropriate invalid value
6201 -- For modular types, all 1 bits is either invalid or valid. If
6202 -- it is valid, then there is nothing that can be done since there
6203 -- are no invalid values (we ruled out zero already).
6205 -- For signed integer types that have no negative values, either
6206 -- there is room for negative values, or there is not. If there
6207 -- is, then all 1 bits may be interpreted as minus one, which is
6208 -- certainly invalid. Alternatively it is treated as the largest
6209 -- positive value, in which case the observation for modular types
6210 -- still applies.
6212 -- For float types, all 1-bits is a NaN (not a number), which is
6213 -- certainly an appropriately invalid value.
6215 elsif Is_Unsigned_Type (T)
6216 or else Is_Floating_Point_Type (T)
6217 or else Is_Enumeration_Type (T)
6218 then
6219 Val := Make_Integer_Literal (Loc, 2 ** Size_To_Use - 1);
6221 -- Resolve as Unsigned_64, because the largest number we
6222 -- can generate is out of range of universal integer.
6224 Analyze_And_Resolve (Val, RTE (RE_Unsigned_64));
6226 -- Case of signed types
6228 else
6229 declare
6230 Signed_Size : constant Uint :=
6231 UI_Min (Uint_63, Size_To_Use - 1);
6233 begin
6234 -- Normally we like to use the most negative number. The
6235 -- one exception is when this number is in the known
6236 -- subtype range and the largest positive number is not in
6237 -- the known subtype range.
6239 -- For this exceptional case, use largest positive value
6241 if Lo_Bound /= No_Uint and then Hi_Bound /= No_Uint
6242 and then Lo_Bound <= (-(2 ** Signed_Size))
6243 and then Hi_Bound < 2 ** Signed_Size
6244 then
6245 Val := Make_Integer_Literal (Loc, 2 ** Signed_Size - 1);
6247 -- Normal case of largest negative value
6249 else
6250 Val := Make_Integer_Literal (Loc, -(2 ** Signed_Size));
6251 end if;
6252 end;
6253 end if;
6255 -- Here for Initialize_Scalars case
6257 else
6258 -- For float types, use float values from System.Scalar_Values
6260 if Is_Floating_Point_Type (T) then
6261 if Root_Type (T) = Standard_Short_Float then
6262 Val_RE := RE_IS_Isf;
6263 elsif Root_Type (T) = Standard_Float then
6264 Val_RE := RE_IS_Ifl;
6265 elsif Root_Type (T) = Standard_Long_Float then
6266 Val_RE := RE_IS_Ilf;
6267 else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
6268 Val_RE := RE_IS_Ill;
6269 end if;
6271 -- If zero is invalid, use zero values from System.Scalar_Values
6273 elsif Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
6274 if Size_To_Use <= 8 then
6275 Val_RE := RE_IS_Iz1;
6276 elsif Size_To_Use <= 16 then
6277 Val_RE := RE_IS_Iz2;
6278 elsif Size_To_Use <= 32 then
6279 Val_RE := RE_IS_Iz4;
6280 else
6281 Val_RE := RE_IS_Iz8;
6282 end if;
6284 -- For unsigned, use unsigned values from System.Scalar_Values
6286 elsif Is_Unsigned_Type (T) then
6287 if Size_To_Use <= 8 then
6288 Val_RE := RE_IS_Iu1;
6289 elsif Size_To_Use <= 16 then
6290 Val_RE := RE_IS_Iu2;
6291 elsif Size_To_Use <= 32 then
6292 Val_RE := RE_IS_Iu4;
6293 else
6294 Val_RE := RE_IS_Iu8;
6295 end if;
6297 -- For signed, use signed values from System.Scalar_Values
6299 else
6300 if Size_To_Use <= 8 then
6301 Val_RE := RE_IS_Is1;
6302 elsif Size_To_Use <= 16 then
6303 Val_RE := RE_IS_Is2;
6304 elsif Size_To_Use <= 32 then
6305 Val_RE := RE_IS_Is4;
6306 else
6307 Val_RE := RE_IS_Is8;
6308 end if;
6309 end if;
6311 Val := New_Occurrence_Of (RTE (Val_RE), Loc);
6312 end if;
6314 -- The final expression is obtained by doing an unchecked conversion
6315 -- of this result to the base type of the required subtype. We use
6316 -- the base type to avoid the unchecked conversion from chopping
6317 -- bits, and then we set Kill_Range_Check to preserve the "bad"
6318 -- value.
6320 Result := Unchecked_Convert_To (Base_Type (T), Val);
6322 -- Ensure result is not truncated, since we want the "bad" bits
6323 -- and also kill range check on result.
6325 if Nkind (Result) = N_Unchecked_Type_Conversion then
6326 Set_No_Truncation (Result);
6327 Set_Kill_Range_Check (Result, True);
6328 end if;
6330 return Result;
6332 -- String or Wide_[Wide]_String (must have Initialize_Scalars set)
6334 elsif Root_Type (T) = Standard_String
6335 or else
6336 Root_Type (T) = Standard_Wide_String
6337 or else
6338 Root_Type (T) = Standard_Wide_Wide_String
6339 then
6340 pragma Assert (Init_Or_Norm_Scalars);
6342 return
6343 Make_Aggregate (Loc,
6344 Component_Associations => New_List (
6345 Make_Component_Association (Loc,
6346 Choices => New_List (
6347 Make_Others_Choice (Loc)),
6348 Expression =>
6349 Get_Simple_Init_Val
6350 (Component_Type (T), Loc, Esize (Root_Type (T))))));
6352 -- Access type is initialized to null
6354 elsif Is_Access_Type (T) then
6355 return
6356 Make_Null (Loc);
6358 -- No other possibilities should arise, since we should only be
6359 -- calling Get_Simple_Init_Val if Needs_Simple_Initialization
6360 -- returned True, indicating one of the above cases held.
6362 else
6363 raise Program_Error;
6364 end if;
6366 exception
6367 when RE_Not_Available =>
6368 return Empty;
6369 end Get_Simple_Init_Val;
6371 ------------------------------
6372 -- Has_New_Non_Standard_Rep --
6373 ------------------------------
6375 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
6376 begin
6377 if not Is_Derived_Type (T) then
6378 return Has_Non_Standard_Rep (T)
6379 or else Has_Non_Standard_Rep (Root_Type (T));
6381 -- If Has_Non_Standard_Rep is not set on the derived type, the
6382 -- representation is fully inherited.
6384 elsif not Has_Non_Standard_Rep (T) then
6385 return False;
6387 else
6388 return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
6390 -- May need a more precise check here: the First_Rep_Item may
6391 -- be a stream attribute, which does not affect the representation
6392 -- of the type ???
6393 end if;
6394 end Has_New_Non_Standard_Rep;
6396 ----------------
6397 -- In_Runtime --
6398 ----------------
6400 function In_Runtime (E : Entity_Id) return Boolean is
6401 S1 : Entity_Id;
6403 begin
6404 S1 := Scope (E);
6405 while Scope (S1) /= Standard_Standard loop
6406 S1 := Scope (S1);
6407 end loop;
6409 return Chars (S1) = Name_System or else Chars (S1) = Name_Ada;
6410 end In_Runtime;
6412 ----------------------------
6413 -- Initialization_Warning --
6414 ----------------------------
6416 procedure Initialization_Warning (E : Entity_Id) is
6417 Warning_Needed : Boolean;
6419 begin
6420 Warning_Needed := False;
6422 if Ekind (Current_Scope) = E_Package
6423 and then Static_Elaboration_Desired (Current_Scope)
6424 then
6425 if Is_Type (E) then
6426 if Is_Record_Type (E) then
6427 if Has_Discriminants (E)
6428 or else Is_Limited_Type (E)
6429 or else Has_Non_Standard_Rep (E)
6430 then
6431 Warning_Needed := True;
6433 else
6434 -- Verify that at least one component has an initializtion
6435 -- expression. No need for a warning on a type if all its
6436 -- components have no initialization.
6438 declare
6439 Comp : Entity_Id;
6441 begin
6442 Comp := First_Component (E);
6443 while Present (Comp) loop
6444 if Ekind (Comp) = E_Discriminant
6445 or else
6446 (Nkind (Parent (Comp)) = N_Component_Declaration
6447 and then Present (Expression (Parent (Comp))))
6448 then
6449 Warning_Needed := True;
6450 exit;
6451 end if;
6453 Next_Component (Comp);
6454 end loop;
6455 end;
6456 end if;
6458 if Warning_Needed then
6459 Error_Msg_N
6460 ("Objects of the type cannot be initialized " &
6461 "statically by default?",
6462 Parent (E));
6463 end if;
6464 end if;
6466 else
6467 Error_Msg_N ("Object cannot be initialized statically?", E);
6468 end if;
6469 end if;
6470 end Initialization_Warning;
6472 ------------------
6473 -- Init_Formals --
6474 ------------------
6476 function Init_Formals (Typ : Entity_Id) return List_Id is
6477 Loc : constant Source_Ptr := Sloc (Typ);
6478 Formals : List_Id;
6480 begin
6481 -- First parameter is always _Init : in out typ. Note that we need
6482 -- this to be in/out because in the case of the task record value,
6483 -- there are default record fields (_Priority, _Size, -Task_Info)
6484 -- that may be referenced in the generated initialization routine.
6486 Formals := New_List (
6487 Make_Parameter_Specification (Loc,
6488 Defining_Identifier =>
6489 Make_Defining_Identifier (Loc, Name_uInit),
6490 In_Present => True,
6491 Out_Present => True,
6492 Parameter_Type => New_Reference_To (Typ, Loc)));
6494 -- For task record value, or type that contains tasks, add two more
6495 -- formals, _Master : Master_Id and _Chain : in out Activation_Chain
6496 -- We also add these parameters for the task record type case.
6498 if Has_Task (Typ)
6499 or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
6500 then
6501 Append_To (Formals,
6502 Make_Parameter_Specification (Loc,
6503 Defining_Identifier =>
6504 Make_Defining_Identifier (Loc, Name_uMaster),
6505 Parameter_Type => New_Reference_To (RTE (RE_Master_Id), Loc)));
6507 Append_To (Formals,
6508 Make_Parameter_Specification (Loc,
6509 Defining_Identifier =>
6510 Make_Defining_Identifier (Loc, Name_uChain),
6511 In_Present => True,
6512 Out_Present => True,
6513 Parameter_Type =>
6514 New_Reference_To (RTE (RE_Activation_Chain), Loc)));
6516 Append_To (Formals,
6517 Make_Parameter_Specification (Loc,
6518 Defining_Identifier =>
6519 Make_Defining_Identifier (Loc, Name_uTask_Name),
6520 In_Present => True,
6521 Parameter_Type =>
6522 New_Reference_To (Standard_String, Loc)));
6523 end if;
6525 return Formals;
6527 exception
6528 when RE_Not_Available =>
6529 return Empty_List;
6530 end Init_Formals;
6532 -------------------------
6533 -- Init_Secondary_Tags --
6534 -------------------------
6536 procedure Init_Secondary_Tags
6537 (Typ : Entity_Id;
6538 Target : Node_Id;
6539 Stmts_List : List_Id;
6540 Fixed_Comps : Boolean := True;
6541 Variable_Comps : Boolean := True)
6543 Loc : constant Source_Ptr := Sloc (Target);
6545 procedure Inherit_CPP_Tag
6546 (Typ : Entity_Id;
6547 Iface : Entity_Id;
6548 Tag_Comp : Entity_Id;
6549 Iface_Tag : Node_Id);
6550 -- Inherit the C++ tag of the secondary dispatch table of Typ associated
6551 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
6553 procedure Initialize_Tag
6554 (Typ : Entity_Id;
6555 Iface : Entity_Id;
6556 Tag_Comp : Entity_Id;
6557 Iface_Tag : Node_Id);
6558 -- Initialize the tag of the secondary dispatch table of Typ associated
6559 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
6560 -- Compiling under the CPP full ABI compatibility mode, if the ancestor
6561 -- of Typ CPP tagged type we generate code to inherit the contents of
6562 -- the dispatch table directly from the ancestor.
6564 ---------------------
6565 -- Inherit_CPP_Tag --
6566 ---------------------
6568 procedure Inherit_CPP_Tag
6569 (Typ : Entity_Id;
6570 Iface : Entity_Id;
6571 Tag_Comp : Entity_Id;
6572 Iface_Tag : Node_Id)
6574 begin
6575 pragma Assert (Is_CPP_Class (Etype (Typ)));
6577 Append_To (Stmts_List,
6578 Build_Inherit_Prims (Loc,
6579 Typ => Iface,
6580 Old_Tag_Node =>
6581 Make_Selected_Component (Loc,
6582 Prefix => New_Copy_Tree (Target),
6583 Selector_Name => New_Reference_To (Tag_Comp, Loc)),
6584 New_Tag_Node =>
6585 New_Reference_To (Iface_Tag, Loc),
6586 Num_Prims =>
6587 UI_To_Int (DT_Entry_Count (First_Tag_Component (Iface)))));
6588 end Inherit_CPP_Tag;
6590 --------------------
6591 -- Initialize_Tag --
6592 --------------------
6594 procedure Initialize_Tag
6595 (Typ : Entity_Id;
6596 Iface : Entity_Id;
6597 Tag_Comp : Entity_Id;
6598 Iface_Tag : Node_Id)
6600 Comp_Typ : Entity_Id;
6601 Offset_To_Top_Comp : Entity_Id := Empty;
6603 begin
6604 -- Initialize the pointer to the secondary DT associated with the
6605 -- interface.
6607 if not Is_Parent (Iface, Typ) then
6608 Append_To (Stmts_List,
6609 Make_Assignment_Statement (Loc,
6610 Name =>
6611 Make_Selected_Component (Loc,
6612 Prefix => New_Copy_Tree (Target),
6613 Selector_Name => New_Reference_To (Tag_Comp, Loc)),
6614 Expression =>
6615 New_Reference_To (Iface_Tag, Loc)));
6616 end if;
6618 -- Issue error if Set_Offset_To_Top is not available in a
6619 -- configurable run-time environment.
6621 if not RTE_Available (RE_Set_Offset_To_Top) then
6622 Error_Msg_CRT ("abstract interface types", Typ);
6623 return;
6624 end if;
6626 Comp_Typ := Scope (Tag_Comp);
6628 -- Initialize the entries of the table of interfaces. We generate a
6629 -- different call when the parent of the type has variable size
6630 -- components.
6632 if Comp_Typ /= Etype (Comp_Typ)
6633 and then Is_Variable_Size_Record (Etype (Comp_Typ))
6634 and then Chars (Tag_Comp) /= Name_uTag
6635 then
6636 pragma Assert
6637 (Present (DT_Offset_To_Top_Func (Tag_Comp)));
6639 -- Generate:
6640 -- Set_Offset_To_Top
6641 -- (This => Init,
6642 -- Interface_T => Iface'Tag,
6643 -- Is_Constant => False,
6644 -- Offset_Value => n,
6645 -- Offset_Func => Fn'Address)
6647 Append_To (Stmts_List,
6648 Make_Procedure_Call_Statement (Loc,
6649 Name => New_Reference_To (RTE (RE_Set_Offset_To_Top), Loc),
6650 Parameter_Associations => New_List (
6651 Make_Attribute_Reference (Loc,
6652 Prefix => New_Copy_Tree (Target),
6653 Attribute_Name => Name_Address),
6655 Unchecked_Convert_To (RTE (RE_Tag),
6656 New_Reference_To
6657 (Node (First_Elmt (Access_Disp_Table (Iface))),
6658 Loc)),
6660 New_Occurrence_Of (Standard_False, Loc),
6662 Unchecked_Convert_To
6663 (RTE (RE_Storage_Offset),
6664 Make_Attribute_Reference (Loc,
6665 Prefix =>
6666 Make_Selected_Component (Loc,
6667 Prefix => New_Copy_Tree (Target),
6668 Selector_Name =>
6669 New_Reference_To (Tag_Comp, Loc)),
6670 Attribute_Name => Name_Position)),
6672 Unchecked_Convert_To (RTE (RE_Offset_To_Top_Function_Ptr),
6673 Make_Attribute_Reference (Loc,
6674 Prefix => New_Reference_To
6675 (DT_Offset_To_Top_Func (Tag_Comp), Loc),
6676 Attribute_Name => Name_Address)))));
6678 -- In this case the next component stores the value of the
6679 -- offset to the top.
6681 Offset_To_Top_Comp := Next_Entity (Tag_Comp);
6682 pragma Assert (Present (Offset_To_Top_Comp));
6684 Append_To (Stmts_List,
6685 Make_Assignment_Statement (Loc,
6686 Name =>
6687 Make_Selected_Component (Loc,
6688 Prefix => New_Copy_Tree (Target),
6689 Selector_Name => New_Reference_To
6690 (Offset_To_Top_Comp, Loc)),
6691 Expression =>
6692 Make_Attribute_Reference (Loc,
6693 Prefix =>
6694 Make_Selected_Component (Loc,
6695 Prefix => New_Copy_Tree (Target),
6696 Selector_Name =>
6697 New_Reference_To (Tag_Comp, Loc)),
6698 Attribute_Name => Name_Position)));
6700 -- Normal case: No discriminants in the parent type
6702 else
6703 -- Generate:
6704 -- Set_Offset_To_Top
6705 -- (This => Init,
6706 -- Interface_T => Iface'Tag,
6707 -- Is_Constant => True,
6708 -- Offset_Value => n,
6709 -- Offset_Func => null);
6711 Append_To (Stmts_List,
6712 Make_Procedure_Call_Statement (Loc,
6713 Name => New_Reference_To
6714 (RTE (RE_Set_Offset_To_Top), Loc),
6715 Parameter_Associations => New_List (
6716 Make_Attribute_Reference (Loc,
6717 Prefix => New_Copy_Tree (Target),
6718 Attribute_Name => Name_Address),
6720 Unchecked_Convert_To (RTE (RE_Tag),
6721 New_Reference_To
6722 (Node (First_Elmt
6723 (Access_Disp_Table (Iface))),
6724 Loc)),
6726 New_Occurrence_Of (Standard_True, Loc),
6728 Unchecked_Convert_To
6729 (RTE (RE_Storage_Offset),
6730 Make_Attribute_Reference (Loc,
6731 Prefix =>
6732 Make_Selected_Component (Loc,
6733 Prefix => New_Copy_Tree (Target),
6734 Selector_Name =>
6735 New_Reference_To (Tag_Comp, Loc)),
6736 Attribute_Name => Name_Position)),
6738 Make_Null (Loc))));
6739 end if;
6740 end Initialize_Tag;
6742 -- Local variables
6744 Full_Typ : Entity_Id;
6745 Ifaces_List : Elist_Id;
6746 Ifaces_Comp_List : Elist_Id;
6747 Ifaces_Tag_List : Elist_Id;
6748 Iface_Elmt : Elmt_Id;
6749 Iface_Comp_Elmt : Elmt_Id;
6750 Iface_Tag_Elmt : Elmt_Id;
6751 Tag_Comp : Node_Id;
6752 In_Variable_Pos : Boolean;
6754 -- Start of processing for Init_Secondary_Tags
6756 begin
6757 -- Handle private types
6759 if Present (Full_View (Typ)) then
6760 Full_Typ := Full_View (Typ);
6761 else
6762 Full_Typ := Typ;
6763 end if;
6765 Collect_Interfaces_Info
6766 (Full_Typ, Ifaces_List, Ifaces_Comp_List, Ifaces_Tag_List);
6768 Iface_Elmt := First_Elmt (Ifaces_List);
6769 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
6770 Iface_Tag_Elmt := First_Elmt (Ifaces_Tag_List);
6771 while Present (Iface_Elmt) loop
6772 Tag_Comp := Node (Iface_Comp_Elmt);
6774 -- If we are compiling under the CPP full ABI compatibility mode and
6775 -- the ancestor is a CPP_Pragma tagged type then we generate code to
6776 -- inherit the contents of the dispatch table directly from the
6777 -- ancestor.
6779 if Is_CPP_Class (Etype (Full_Typ)) then
6780 Inherit_CPP_Tag (Full_Typ,
6781 Iface => Node (Iface_Elmt),
6782 Tag_Comp => Tag_Comp,
6783 Iface_Tag => Node (Iface_Tag_Elmt));
6785 -- Otherwise we generate code to initialize the tag
6787 else
6788 -- Check if the parent of the record type has variable size
6789 -- components.
6791 In_Variable_Pos := Scope (Tag_Comp) /= Etype (Scope (Tag_Comp))
6792 and then Is_Variable_Size_Record (Etype (Scope (Tag_Comp)));
6794 if (In_Variable_Pos and then Variable_Comps)
6795 or else (not In_Variable_Pos and then Fixed_Comps)
6796 then
6797 Initialize_Tag (Full_Typ,
6798 Iface => Node (Iface_Elmt),
6799 Tag_Comp => Tag_Comp,
6800 Iface_Tag => Node (Iface_Tag_Elmt));
6801 end if;
6802 end if;
6804 Next_Elmt (Iface_Elmt);
6805 Next_Elmt (Iface_Comp_Elmt);
6806 Next_Elmt (Iface_Tag_Elmt);
6807 end loop;
6808 end Init_Secondary_Tags;
6810 -----------------------------
6811 -- Is_Variable_Size_Record --
6812 -----------------------------
6814 function Is_Variable_Size_Record (E : Entity_Id) return Boolean is
6815 Comp : Entity_Id;
6816 Comp_Typ : Entity_Id;
6817 Idx : Node_Id;
6819 begin
6820 pragma Assert (Is_Record_Type (E));
6822 Comp := First_Entity (E);
6823 while Present (Comp) loop
6824 Comp_Typ := Etype (Comp);
6826 if Is_Record_Type (Comp_Typ) then
6828 -- Recursive call if the record type has discriminants
6830 if Has_Discriminants (Comp_Typ)
6831 and then Is_Variable_Size_Record (Comp_Typ)
6832 then
6833 return True;
6834 end if;
6836 elsif Is_Array_Type (Comp_Typ) then
6838 -- Check if some index is initialized with a non-constant value
6840 Idx := First_Index (Comp_Typ);
6841 while Present (Idx) loop
6842 if Nkind (Idx) = N_Range then
6843 if (Nkind (Low_Bound (Idx)) = N_Identifier
6844 and then Present (Entity (Low_Bound (Idx)))
6845 and then
6846 Ekind (Entity (Low_Bound (Idx))) /= E_Constant)
6847 or else
6848 (Nkind (High_Bound (Idx)) = N_Identifier
6849 and then Present (Entity (High_Bound (Idx)))
6850 and then
6851 Ekind (Entity (High_Bound (Idx))) /= E_Constant)
6852 then
6853 return True;
6854 end if;
6855 end if;
6857 Idx := Next_Index (Idx);
6858 end loop;
6859 end if;
6861 Next_Entity (Comp);
6862 end loop;
6864 return False;
6865 end Is_Variable_Size_Record;
6867 ----------------------------------------
6868 -- Make_Controlling_Function_Wrappers --
6869 ----------------------------------------
6871 procedure Make_Controlling_Function_Wrappers
6872 (Tag_Typ : Entity_Id;
6873 Decl_List : out List_Id;
6874 Body_List : out List_Id)
6876 Loc : constant Source_Ptr := Sloc (Tag_Typ);
6877 Prim_Elmt : Elmt_Id;
6878 Subp : Entity_Id;
6879 Actual_List : List_Id;
6880 Formal_List : List_Id;
6881 Formal : Entity_Id;
6882 Par_Formal : Entity_Id;
6883 Formal_Node : Node_Id;
6884 Func_Body : Node_Id;
6885 Func_Decl : Node_Id;
6886 Func_Spec : Node_Id;
6887 Return_Stmt : Node_Id;
6889 begin
6890 Decl_List := New_List;
6891 Body_List := New_List;
6893 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
6895 while Present (Prim_Elmt) loop
6896 Subp := Node (Prim_Elmt);
6898 -- If a primitive function with a controlling result of the type has
6899 -- not been overridden by the user, then we must create a wrapper
6900 -- function here that effectively overrides it and invokes the
6901 -- (non-abstract) parent function. This can only occur for a null
6902 -- extension. Note that functions with anonymous controlling access
6903 -- results don't qualify and must be overridden. We also exclude
6904 -- Input attributes, since each type will have its own version of
6905 -- Input constructed by the expander. The test for Comes_From_Source
6906 -- is needed to distinguish inherited operations from renamings
6907 -- (which also have Alias set).
6909 -- The function may be abstract, or require_Overriding may be set
6910 -- for it, because tests for null extensions may already have reset
6911 -- the Is_Abstract_Subprogram_Flag. If Requires_Overriding is not
6912 -- set, functions that need wrappers are recognized by having an
6913 -- alias that returns the parent type.
6915 if Comes_From_Source (Subp)
6916 or else No (Alias (Subp))
6917 or else Ekind (Subp) /= E_Function
6918 or else not Has_Controlling_Result (Subp)
6919 or else Is_Access_Type (Etype (Subp))
6920 or else Is_Abstract_Subprogram (Alias (Subp))
6921 or else Is_TSS (Subp, TSS_Stream_Input)
6922 then
6923 goto Next_Prim;
6925 elsif Is_Abstract_Subprogram (Subp)
6926 or else Requires_Overriding (Subp)
6927 or else
6928 (Is_Null_Extension (Etype (Subp))
6929 and then Etype (Alias (Subp)) /= Etype (Subp))
6930 then
6931 Formal_List := No_List;
6932 Formal := First_Formal (Subp);
6934 if Present (Formal) then
6935 Formal_List := New_List;
6937 while Present (Formal) loop
6938 Append
6939 (Make_Parameter_Specification
6940 (Loc,
6941 Defining_Identifier =>
6942 Make_Defining_Identifier (Sloc (Formal),
6943 Chars => Chars (Formal)),
6944 In_Present => In_Present (Parent (Formal)),
6945 Out_Present => Out_Present (Parent (Formal)),
6946 Null_Exclusion_Present =>
6947 Null_Exclusion_Present (Parent (Formal)),
6948 Parameter_Type =>
6949 New_Reference_To (Etype (Formal), Loc),
6950 Expression =>
6951 New_Copy_Tree (Expression (Parent (Formal)))),
6952 Formal_List);
6954 Next_Formal (Formal);
6955 end loop;
6956 end if;
6958 Func_Spec :=
6959 Make_Function_Specification (Loc,
6960 Defining_Unit_Name =>
6961 Make_Defining_Identifier (Loc,
6962 Chars => Chars (Subp)),
6963 Parameter_Specifications => Formal_List,
6964 Result_Definition =>
6965 New_Reference_To (Etype (Subp), Loc));
6967 Func_Decl := Make_Subprogram_Declaration (Loc, Func_Spec);
6968 Append_To (Decl_List, Func_Decl);
6970 -- Build a wrapper body that calls the parent function. The body
6971 -- contains a single return statement that returns an extension
6972 -- aggregate whose ancestor part is a call to the parent function,
6973 -- passing the formals as actuals (with any controlling arguments
6974 -- converted to the types of the corresponding formals of the
6975 -- parent function, which might be anonymous access types), and
6976 -- having a null extension.
6978 Formal := First_Formal (Subp);
6979 Par_Formal := First_Formal (Alias (Subp));
6980 Formal_Node := First (Formal_List);
6982 if Present (Formal) then
6983 Actual_List := New_List;
6984 else
6985 Actual_List := No_List;
6986 end if;
6988 while Present (Formal) loop
6989 if Is_Controlling_Formal (Formal) then
6990 Append_To (Actual_List,
6991 Make_Type_Conversion (Loc,
6992 Subtype_Mark =>
6993 New_Occurrence_Of (Etype (Par_Formal), Loc),
6994 Expression =>
6995 New_Reference_To
6996 (Defining_Identifier (Formal_Node), Loc)));
6997 else
6998 Append_To
6999 (Actual_List,
7000 New_Reference_To
7001 (Defining_Identifier (Formal_Node), Loc));
7002 end if;
7004 Next_Formal (Formal);
7005 Next_Formal (Par_Formal);
7006 Next (Formal_Node);
7007 end loop;
7009 Return_Stmt :=
7010 Make_Simple_Return_Statement (Loc,
7011 Expression =>
7012 Make_Extension_Aggregate (Loc,
7013 Ancestor_Part =>
7014 Make_Function_Call (Loc,
7015 Name => New_Reference_To (Alias (Subp), Loc),
7016 Parameter_Associations => Actual_List),
7017 Null_Record_Present => True));
7019 Func_Body :=
7020 Make_Subprogram_Body (Loc,
7021 Specification => New_Copy_Tree (Func_Spec),
7022 Declarations => Empty_List,
7023 Handled_Statement_Sequence =>
7024 Make_Handled_Sequence_Of_Statements (Loc,
7025 Statements => New_List (Return_Stmt)));
7027 Set_Defining_Unit_Name
7028 (Specification (Func_Body),
7029 Make_Defining_Identifier (Loc, Chars (Subp)));
7031 Append_To (Body_List, Func_Body);
7033 -- Replace the inherited function with the wrapper function
7034 -- in the primitive operations list.
7036 Override_Dispatching_Operation
7037 (Tag_Typ, Subp, New_Op => Defining_Unit_Name (Func_Spec));
7038 end if;
7040 <<Next_Prim>>
7041 Next_Elmt (Prim_Elmt);
7042 end loop;
7043 end Make_Controlling_Function_Wrappers;
7045 ------------------
7046 -- Make_Eq_Case --
7047 ------------------
7049 -- <Make_Eq_if shared components>
7050 -- case X.D1 is
7051 -- when V1 => <Make_Eq_Case> on subcomponents
7052 -- ...
7053 -- when Vn => <Make_Eq_Case> on subcomponents
7054 -- end case;
7056 function Make_Eq_Case
7057 (E : Entity_Id;
7058 CL : Node_Id;
7059 Discr : Entity_Id := Empty) return List_Id
7061 Loc : constant Source_Ptr := Sloc (E);
7062 Result : constant List_Id := New_List;
7063 Variant : Node_Id;
7064 Alt_List : List_Id;
7066 begin
7067 Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
7069 if No (Variant_Part (CL)) then
7070 return Result;
7071 end if;
7073 Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
7075 if No (Variant) then
7076 return Result;
7077 end if;
7079 Alt_List := New_List;
7081 while Present (Variant) loop
7082 Append_To (Alt_List,
7083 Make_Case_Statement_Alternative (Loc,
7084 Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
7085 Statements => Make_Eq_Case (E, Component_List (Variant))));
7087 Next_Non_Pragma (Variant);
7088 end loop;
7090 -- If we have an Unchecked_Union, use one of the parameters that
7091 -- captures the discriminants.
7093 if Is_Unchecked_Union (E) then
7094 Append_To (Result,
7095 Make_Case_Statement (Loc,
7096 Expression => New_Reference_To (Discr, Loc),
7097 Alternatives => Alt_List));
7099 else
7100 Append_To (Result,
7101 Make_Case_Statement (Loc,
7102 Expression =>
7103 Make_Selected_Component (Loc,
7104 Prefix => Make_Identifier (Loc, Name_X),
7105 Selector_Name => New_Copy (Name (Variant_Part (CL)))),
7106 Alternatives => Alt_List));
7107 end if;
7109 return Result;
7110 end Make_Eq_Case;
7112 ----------------
7113 -- Make_Eq_If --
7114 ----------------
7116 -- Generates:
7118 -- if
7119 -- X.C1 /= Y.C1
7120 -- or else
7121 -- X.C2 /= Y.C2
7122 -- ...
7123 -- then
7124 -- return False;
7125 -- end if;
7127 -- or a null statement if the list L is empty
7129 function Make_Eq_If
7130 (E : Entity_Id;
7131 L : List_Id) return Node_Id
7133 Loc : constant Source_Ptr := Sloc (E);
7134 C : Node_Id;
7135 Field_Name : Name_Id;
7136 Cond : Node_Id;
7138 begin
7139 if No (L) then
7140 return Make_Null_Statement (Loc);
7142 else
7143 Cond := Empty;
7145 C := First_Non_Pragma (L);
7146 while Present (C) loop
7147 Field_Name := Chars (Defining_Identifier (C));
7149 -- The tags must not be compared: they are not part of the value.
7150 -- Ditto for the controller component, if present.
7152 -- Note also that in the following, we use Make_Identifier for
7153 -- the component names. Use of New_Reference_To to identify the
7154 -- components would be incorrect because the wrong entities for
7155 -- discriminants could be picked up in the private type case.
7157 if Field_Name /= Name_uTag
7158 and then
7159 Field_Name /= Name_uController
7160 then
7161 Evolve_Or_Else (Cond,
7162 Make_Op_Ne (Loc,
7163 Left_Opnd =>
7164 Make_Selected_Component (Loc,
7165 Prefix => Make_Identifier (Loc, Name_X),
7166 Selector_Name =>
7167 Make_Identifier (Loc, Field_Name)),
7169 Right_Opnd =>
7170 Make_Selected_Component (Loc,
7171 Prefix => Make_Identifier (Loc, Name_Y),
7172 Selector_Name =>
7173 Make_Identifier (Loc, Field_Name))));
7174 end if;
7176 Next_Non_Pragma (C);
7177 end loop;
7179 if No (Cond) then
7180 return Make_Null_Statement (Loc);
7182 else
7183 return
7184 Make_Implicit_If_Statement (E,
7185 Condition => Cond,
7186 Then_Statements => New_List (
7187 Make_Simple_Return_Statement (Loc,
7188 Expression => New_Occurrence_Of (Standard_False, Loc))));
7189 end if;
7190 end if;
7191 end Make_Eq_If;
7193 -------------------------------
7194 -- Make_Null_Procedure_Specs --
7195 -------------------------------
7197 procedure Make_Null_Procedure_Specs
7198 (Tag_Typ : Entity_Id;
7199 Decl_List : out List_Id)
7201 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7202 Formal : Entity_Id;
7203 Formal_List : List_Id;
7204 Parent_Subp : Entity_Id;
7205 Prim_Elmt : Elmt_Id;
7206 Proc_Spec : Node_Id;
7207 Proc_Decl : Node_Id;
7208 Subp : Entity_Id;
7210 function Is_Null_Interface_Primitive (E : Entity_Id) return Boolean;
7211 -- Returns True if E is a null procedure that is an interface primitive
7213 ---------------------------------
7214 -- Is_Null_Interface_Primitive --
7215 ---------------------------------
7217 function Is_Null_Interface_Primitive (E : Entity_Id) return Boolean is
7218 begin
7219 return Comes_From_Source (E)
7220 and then Is_Dispatching_Operation (E)
7221 and then Ekind (E) = E_Procedure
7222 and then Null_Present (Parent (E))
7223 and then Is_Interface (Find_Dispatching_Type (E));
7224 end Is_Null_Interface_Primitive;
7226 -- Start of processing for Make_Null_Procedure_Specs
7228 begin
7229 Decl_List := New_List;
7230 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7231 while Present (Prim_Elmt) loop
7232 Subp := Node (Prim_Elmt);
7234 -- If a null procedure inherited from an interface has not been
7235 -- overridden, then we build a null procedure declaration to
7236 -- override the inherited procedure.
7238 Parent_Subp := Alias (Subp);
7240 if Present (Parent_Subp)
7241 and then Is_Null_Interface_Primitive (Parent_Subp)
7242 then
7243 Formal_List := No_List;
7244 Formal := First_Formal (Subp);
7246 if Present (Formal) then
7247 Formal_List := New_List;
7249 while Present (Formal) loop
7250 Append
7251 (Make_Parameter_Specification (Loc,
7252 Defining_Identifier =>
7253 Make_Defining_Identifier (Sloc (Formal),
7254 Chars => Chars (Formal)),
7255 In_Present => In_Present (Parent (Formal)),
7256 Out_Present => Out_Present (Parent (Formal)),
7257 Null_Exclusion_Present =>
7258 Null_Exclusion_Present (Parent (Formal)),
7259 Parameter_Type =>
7260 New_Reference_To (Etype (Formal), Loc),
7261 Expression =>
7262 New_Copy_Tree (Expression (Parent (Formal)))),
7263 Formal_List);
7265 Next_Formal (Formal);
7266 end loop;
7267 end if;
7269 Proc_Spec :=
7270 Make_Procedure_Specification (Loc,
7271 Defining_Unit_Name =>
7272 Make_Defining_Identifier (Loc, Chars (Subp)),
7273 Parameter_Specifications => Formal_List);
7274 Set_Null_Present (Proc_Spec);
7276 Proc_Decl := Make_Subprogram_Declaration (Loc, Proc_Spec);
7277 Append_To (Decl_List, Proc_Decl);
7278 Analyze (Proc_Decl);
7279 end if;
7281 Next_Elmt (Prim_Elmt);
7282 end loop;
7283 end Make_Null_Procedure_Specs;
7285 -------------------------------------
7286 -- Make_Predefined_Primitive_Specs --
7287 -------------------------------------
7289 procedure Make_Predefined_Primitive_Specs
7290 (Tag_Typ : Entity_Id;
7291 Predef_List : out List_Id;
7292 Renamed_Eq : out Entity_Id)
7294 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7295 Res : constant List_Id := New_List;
7296 Prim : Elmt_Id;
7297 Eq_Needed : Boolean;
7298 Eq_Spec : Node_Id;
7299 Eq_Name : Name_Id := Name_Op_Eq;
7301 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
7302 -- Returns true if Prim is a renaming of an unresolved predefined
7303 -- equality operation.
7305 -------------------------------
7306 -- Is_Predefined_Eq_Renaming --
7307 -------------------------------
7309 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
7310 begin
7311 return Chars (Prim) /= Name_Op_Eq
7312 and then Present (Alias (Prim))
7313 and then Comes_From_Source (Prim)
7314 and then Is_Intrinsic_Subprogram (Alias (Prim))
7315 and then Chars (Alias (Prim)) = Name_Op_Eq;
7316 end Is_Predefined_Eq_Renaming;
7318 -- Start of processing for Make_Predefined_Primitive_Specs
7320 begin
7321 Renamed_Eq := Empty;
7323 -- Spec of _Size
7325 Append_To (Res, Predef_Spec_Or_Body (Loc,
7326 Tag_Typ => Tag_Typ,
7327 Name => Name_uSize,
7328 Profile => New_List (
7329 Make_Parameter_Specification (Loc,
7330 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7331 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7333 Ret_Type => Standard_Long_Long_Integer));
7335 -- Spec of _Alignment
7337 Append_To (Res, Predef_Spec_Or_Body (Loc,
7338 Tag_Typ => Tag_Typ,
7339 Name => Name_uAlignment,
7340 Profile => New_List (
7341 Make_Parameter_Specification (Loc,
7342 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7343 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7345 Ret_Type => Standard_Integer));
7347 -- Specs for dispatching stream attributes
7349 declare
7350 Stream_Op_TSS_Names :
7351 constant array (Integer range <>) of TSS_Name_Type :=
7352 (TSS_Stream_Read,
7353 TSS_Stream_Write,
7354 TSS_Stream_Input,
7355 TSS_Stream_Output);
7357 begin
7358 for Op in Stream_Op_TSS_Names'Range loop
7359 if Stream_Operation_OK (Tag_Typ, Stream_Op_TSS_Names (Op)) then
7360 Append_To (Res,
7361 Predef_Stream_Attr_Spec (Loc, Tag_Typ,
7362 Stream_Op_TSS_Names (Op)));
7363 end if;
7364 end loop;
7365 end;
7367 -- Spec of "=" is expanded if the type is not limited and if a
7368 -- user defined "=" was not already declared for the non-full
7369 -- view of a private extension
7371 if not Is_Limited_Type (Tag_Typ) then
7372 Eq_Needed := True;
7373 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
7374 while Present (Prim) loop
7376 -- If a primitive is encountered that renames the predefined
7377 -- equality operator before reaching any explicit equality
7378 -- primitive, then we still need to create a predefined
7379 -- equality function, because calls to it can occur via
7380 -- the renaming. A new name is created for the equality
7381 -- to avoid conflicting with any user-defined equality.
7382 -- (Note that this doesn't account for renamings of
7383 -- equality nested within subpackages???)
7385 if Is_Predefined_Eq_Renaming (Node (Prim)) then
7386 Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
7388 -- User-defined equality
7390 elsif Chars (Node (Prim)) = Name_Op_Eq
7391 and then (No (Alias (Node (Prim)))
7392 or else Nkind (Unit_Declaration_Node (Node (Prim))) =
7393 N_Subprogram_Renaming_Declaration)
7394 and then Etype (First_Formal (Node (Prim))) =
7395 Etype (Next_Formal (First_Formal (Node (Prim))))
7396 and then Base_Type (Etype (Node (Prim))) = Standard_Boolean
7397 then
7398 Eq_Needed := False;
7399 exit;
7401 -- If the parent is not an interface type and has an abstract
7402 -- equality function, the inherited equality is abstract as well,
7403 -- and no body can be created for it.
7405 elsif Chars (Node (Prim)) = Name_Op_Eq
7406 and then not Is_Interface (Etype (Tag_Typ))
7407 and then Present (Alias (Node (Prim)))
7408 and then Is_Abstract_Subprogram (Alias (Node (Prim)))
7409 then
7410 Eq_Needed := False;
7411 exit;
7412 end if;
7414 Next_Elmt (Prim);
7415 end loop;
7417 -- If a renaming of predefined equality was found but there was no
7418 -- user-defined equality (so Eq_Needed is still true), then set the
7419 -- name back to Name_Op_Eq. But in the case where a user-defined
7420 -- equality was located after such a renaming, then the predefined
7421 -- equality function is still needed, so Eq_Needed must be set back
7422 -- to True.
7424 if Eq_Name /= Name_Op_Eq then
7425 if Eq_Needed then
7426 Eq_Name := Name_Op_Eq;
7427 else
7428 Eq_Needed := True;
7429 end if;
7430 end if;
7432 if Eq_Needed then
7433 Eq_Spec := Predef_Spec_Or_Body (Loc,
7434 Tag_Typ => Tag_Typ,
7435 Name => Eq_Name,
7436 Profile => New_List (
7437 Make_Parameter_Specification (Loc,
7438 Defining_Identifier =>
7439 Make_Defining_Identifier (Loc, Name_X),
7440 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
7441 Make_Parameter_Specification (Loc,
7442 Defining_Identifier =>
7443 Make_Defining_Identifier (Loc, Name_Y),
7444 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7445 Ret_Type => Standard_Boolean);
7446 Append_To (Res, Eq_Spec);
7448 if Eq_Name /= Name_Op_Eq then
7449 Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
7451 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
7452 while Present (Prim) loop
7454 -- Any renamings of equality that appeared before an
7455 -- overriding equality must be updated to refer to the
7456 -- entity for the predefined equality, otherwise calls via
7457 -- the renaming would get incorrectly resolved to call the
7458 -- user-defined equality function.
7460 if Is_Predefined_Eq_Renaming (Node (Prim)) then
7461 Set_Alias (Node (Prim), Renamed_Eq);
7463 -- Exit upon encountering a user-defined equality
7465 elsif Chars (Node (Prim)) = Name_Op_Eq
7466 and then No (Alias (Node (Prim)))
7467 then
7468 exit;
7469 end if;
7471 Next_Elmt (Prim);
7472 end loop;
7473 end if;
7474 end if;
7476 -- Spec for dispatching assignment
7478 Append_To (Res, Predef_Spec_Or_Body (Loc,
7479 Tag_Typ => Tag_Typ,
7480 Name => Name_uAssign,
7481 Profile => New_List (
7482 Make_Parameter_Specification (Loc,
7483 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7484 Out_Present => True,
7485 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
7487 Make_Parameter_Specification (Loc,
7488 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
7489 Parameter_Type => New_Reference_To (Tag_Typ, Loc)))));
7490 end if;
7492 -- Ada 2005: Generate declarations for the following primitive
7493 -- operations for limited interfaces and synchronized types that
7494 -- implement a limited interface.
7496 -- Disp_Asynchronous_Select
7497 -- Disp_Conditional_Select
7498 -- Disp_Get_Prim_Op_Kind
7499 -- Disp_Get_Task_Id
7500 -- Disp_Requeue
7501 -- Disp_Timed_Select
7503 -- These operations cannot be implemented on VM targets, so we simply
7504 -- disable their generation in this case. We also disable generation
7505 -- of these bodies if No_Dispatching_Calls is active.
7507 if Ada_Version >= Ada_05
7508 and then VM_Target = No_VM
7509 then
7510 -- These primitives are defined abstract in interface types
7512 if Is_Interface (Tag_Typ)
7513 and then Is_Limited_Record (Tag_Typ)
7514 then
7515 Append_To (Res,
7516 Make_Abstract_Subprogram_Declaration (Loc,
7517 Specification =>
7518 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
7520 Append_To (Res,
7521 Make_Abstract_Subprogram_Declaration (Loc,
7522 Specification =>
7523 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
7525 Append_To (Res,
7526 Make_Abstract_Subprogram_Declaration (Loc,
7527 Specification =>
7528 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
7530 Append_To (Res,
7531 Make_Abstract_Subprogram_Declaration (Loc,
7532 Specification =>
7533 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
7535 Append_To (Res,
7536 Make_Abstract_Subprogram_Declaration (Loc,
7537 Specification =>
7538 Make_Disp_Requeue_Spec (Tag_Typ)));
7540 Append_To (Res,
7541 Make_Abstract_Subprogram_Declaration (Loc,
7542 Specification =>
7543 Make_Disp_Timed_Select_Spec (Tag_Typ)));
7545 -- If the ancestor is an interface type we declare non-abstract
7546 -- primitives to override the abstract primitives of the interface
7547 -- type.
7549 elsif (not Is_Interface (Tag_Typ)
7550 and then Is_Interface (Etype (Tag_Typ))
7551 and then Is_Limited_Record (Etype (Tag_Typ)))
7552 or else
7553 (Is_Concurrent_Record_Type (Tag_Typ)
7554 and then Has_Abstract_Interfaces (Tag_Typ))
7555 then
7556 Append_To (Res,
7557 Make_Subprogram_Declaration (Loc,
7558 Specification =>
7559 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
7561 Append_To (Res,
7562 Make_Subprogram_Declaration (Loc,
7563 Specification =>
7564 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
7566 Append_To (Res,
7567 Make_Subprogram_Declaration (Loc,
7568 Specification =>
7569 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
7571 Append_To (Res,
7572 Make_Subprogram_Declaration (Loc,
7573 Specification =>
7574 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
7576 Append_To (Res,
7577 Make_Subprogram_Declaration (Loc,
7578 Specification =>
7579 Make_Disp_Requeue_Spec (Tag_Typ)));
7581 Append_To (Res,
7582 Make_Subprogram_Declaration (Loc,
7583 Specification =>
7584 Make_Disp_Timed_Select_Spec (Tag_Typ)));
7585 end if;
7586 end if;
7588 -- Specs for finalization actions that may be required in case a future
7589 -- extension contain a controlled element. We generate those only for
7590 -- root tagged types where they will get dummy bodies or when the type
7591 -- has controlled components and their body must be generated. It is
7592 -- also impossible to provide those for tagged types defined within
7593 -- s-finimp since it would involve circularity problems
7595 if In_Finalization_Root (Tag_Typ) then
7596 null;
7598 -- We also skip these if finalization is not available
7600 elsif Restriction_Active (No_Finalization) then
7601 null;
7603 elsif Etype (Tag_Typ) = Tag_Typ
7604 or else Controlled_Type (Tag_Typ)
7606 -- Ada 2005 (AI-251): We must also generate these subprograms if
7607 -- the immediate ancestor is an interface to ensure the correct
7608 -- initialization of its dispatch table.
7610 or else (not Is_Interface (Tag_Typ)
7611 and then
7612 Is_Interface (Etype (Tag_Typ)))
7613 then
7614 if not Is_Limited_Type (Tag_Typ) then
7615 Append_To (Res,
7616 Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
7617 end if;
7619 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
7620 end if;
7622 Predef_List := Res;
7623 end Make_Predefined_Primitive_Specs;
7625 ---------------------------------
7626 -- Needs_Simple_Initialization --
7627 ---------------------------------
7629 function Needs_Simple_Initialization (T : Entity_Id) return Boolean is
7630 begin
7631 -- Check for private type, in which case test applies to the underlying
7632 -- type of the private type.
7634 if Is_Private_Type (T) then
7635 declare
7636 RT : constant Entity_Id := Underlying_Type (T);
7638 begin
7639 if Present (RT) then
7640 return Needs_Simple_Initialization (RT);
7641 else
7642 return False;
7643 end if;
7644 end;
7646 -- Cases needing simple initialization are access types, and, if pragma
7647 -- Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
7648 -- types.
7650 elsif Is_Access_Type (T)
7651 or else (Init_Or_Norm_Scalars and then (Is_Scalar_Type (T)))
7652 then
7653 return True;
7655 -- If Initialize/Normalize_Scalars is in effect, string objects also
7656 -- need initialization, unless they are created in the course of
7657 -- expanding an aggregate (since in the latter case they will be
7658 -- filled with appropriate initializing values before they are used).
7660 elsif Init_Or_Norm_Scalars
7661 and then
7662 (Root_Type (T) = Standard_String
7663 or else Root_Type (T) = Standard_Wide_String
7664 or else Root_Type (T) = Standard_Wide_Wide_String)
7665 and then
7666 (not Is_Itype (T)
7667 or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
7668 then
7669 return True;
7671 else
7672 return False;
7673 end if;
7674 end Needs_Simple_Initialization;
7676 ----------------------
7677 -- Predef_Deep_Spec --
7678 ----------------------
7680 function Predef_Deep_Spec
7681 (Loc : Source_Ptr;
7682 Tag_Typ : Entity_Id;
7683 Name : TSS_Name_Type;
7684 For_Body : Boolean := False) return Node_Id
7686 Prof : List_Id;
7687 Type_B : Entity_Id;
7689 begin
7690 if Name = TSS_Deep_Finalize then
7691 Prof := New_List;
7692 Type_B := Standard_Boolean;
7694 else
7695 Prof := New_List (
7696 Make_Parameter_Specification (Loc,
7697 Defining_Identifier => Make_Defining_Identifier (Loc, Name_L),
7698 In_Present => True,
7699 Out_Present => True,
7700 Parameter_Type =>
7701 New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
7702 Type_B := Standard_Short_Short_Integer;
7703 end if;
7705 Append_To (Prof,
7706 Make_Parameter_Specification (Loc,
7707 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
7708 In_Present => True,
7709 Out_Present => True,
7710 Parameter_Type => New_Reference_To (Tag_Typ, Loc)));
7712 Append_To (Prof,
7713 Make_Parameter_Specification (Loc,
7714 Defining_Identifier => Make_Defining_Identifier (Loc, Name_B),
7715 Parameter_Type => New_Reference_To (Type_B, Loc)));
7717 return Predef_Spec_Or_Body (Loc,
7718 Name => Make_TSS_Name (Tag_Typ, Name),
7719 Tag_Typ => Tag_Typ,
7720 Profile => Prof,
7721 For_Body => For_Body);
7723 exception
7724 when RE_Not_Available =>
7725 return Empty;
7726 end Predef_Deep_Spec;
7728 -------------------------
7729 -- Predef_Spec_Or_Body --
7730 -------------------------
7732 function Predef_Spec_Or_Body
7733 (Loc : Source_Ptr;
7734 Tag_Typ : Entity_Id;
7735 Name : Name_Id;
7736 Profile : List_Id;
7737 Ret_Type : Entity_Id := Empty;
7738 For_Body : Boolean := False) return Node_Id
7740 Id : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
7741 Spec : Node_Id;
7743 begin
7744 Set_Is_Public (Id, Is_Public (Tag_Typ));
7746 -- The internal flag is set to mark these declarations because they have
7747 -- specific properties. First, they are primitives even if they are not
7748 -- defined in the type scope (the freezing point is not necessarily in
7749 -- the same scope). Second, the predefined equality can be overridden by
7750 -- a user-defined equality, no body will be generated in this case.
7752 Set_Is_Internal (Id);
7754 if not Debug_Generated_Code then
7755 Set_Debug_Info_Off (Id);
7756 end if;
7758 if No (Ret_Type) then
7759 Spec :=
7760 Make_Procedure_Specification (Loc,
7761 Defining_Unit_Name => Id,
7762 Parameter_Specifications => Profile);
7763 else
7764 Spec :=
7765 Make_Function_Specification (Loc,
7766 Defining_Unit_Name => Id,
7767 Parameter_Specifications => Profile,
7768 Result_Definition =>
7769 New_Reference_To (Ret_Type, Loc));
7770 end if;
7772 if Is_Interface (Tag_Typ) then
7773 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
7775 -- If body case, return empty subprogram body. Note that this is ill-
7776 -- formed, because there is not even a null statement, and certainly not
7777 -- a return in the function case. The caller is expected to do surgery
7778 -- on the body to add the appropriate stuff.
7780 elsif For_Body then
7781 return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
7783 -- For the case of an Input attribute predefined for an abstract type,
7784 -- generate an abstract specification. This will never be called, but we
7785 -- need the slot allocated in the dispatching table so that attributes
7786 -- typ'Class'Input and typ'Class'Output will work properly.
7788 elsif Is_TSS (Name, TSS_Stream_Input)
7789 and then Is_Abstract_Type (Tag_Typ)
7790 then
7791 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
7793 -- Normal spec case, where we return a subprogram declaration
7795 else
7796 return Make_Subprogram_Declaration (Loc, Spec);
7797 end if;
7798 end Predef_Spec_Or_Body;
7800 -----------------------------
7801 -- Predef_Stream_Attr_Spec --
7802 -----------------------------
7804 function Predef_Stream_Attr_Spec
7805 (Loc : Source_Ptr;
7806 Tag_Typ : Entity_Id;
7807 Name : TSS_Name_Type;
7808 For_Body : Boolean := False) return Node_Id
7810 Ret_Type : Entity_Id;
7812 begin
7813 if Name = TSS_Stream_Input then
7814 Ret_Type := Tag_Typ;
7815 else
7816 Ret_Type := Empty;
7817 end if;
7819 return Predef_Spec_Or_Body (Loc,
7820 Name => Make_TSS_Name (Tag_Typ, Name),
7821 Tag_Typ => Tag_Typ,
7822 Profile => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
7823 Ret_Type => Ret_Type,
7824 For_Body => For_Body);
7825 end Predef_Stream_Attr_Spec;
7827 ---------------------------------
7828 -- Predefined_Primitive_Bodies --
7829 ---------------------------------
7831 function Predefined_Primitive_Bodies
7832 (Tag_Typ : Entity_Id;
7833 Renamed_Eq : Entity_Id) return List_Id
7835 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7836 Res : constant List_Id := New_List;
7837 Decl : Node_Id;
7838 Prim : Elmt_Id;
7839 Eq_Needed : Boolean;
7840 Eq_Name : Name_Id;
7841 Ent : Entity_Id;
7843 pragma Warnings (Off, Ent);
7845 begin
7846 pragma Assert (not Is_Interface (Tag_Typ));
7848 -- See if we have a predefined "=" operator
7850 if Present (Renamed_Eq) then
7851 Eq_Needed := True;
7852 Eq_Name := Chars (Renamed_Eq);
7854 -- If the parent is an interface type then it has defined all the
7855 -- predefined primitives abstract and we need to check if the type
7856 -- has some user defined "=" function to avoid generating it.
7858 elsif Is_Interface (Etype (Tag_Typ)) then
7859 Eq_Needed := True;
7860 Eq_Name := Name_Op_Eq;
7862 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
7863 while Present (Prim) loop
7864 if Chars (Node (Prim)) = Name_Op_Eq
7865 and then not Is_Internal (Node (Prim))
7866 then
7867 Eq_Needed := False;
7868 Eq_Name := No_Name;
7869 exit;
7870 end if;
7872 Next_Elmt (Prim);
7873 end loop;
7875 else
7876 Eq_Needed := False;
7877 Eq_Name := No_Name;
7879 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
7880 while Present (Prim) loop
7881 if Chars (Node (Prim)) = Name_Op_Eq
7882 and then Is_Internal (Node (Prim))
7883 then
7884 Eq_Needed := True;
7885 Eq_Name := Name_Op_Eq;
7886 exit;
7887 end if;
7889 Next_Elmt (Prim);
7890 end loop;
7891 end if;
7893 -- Body of _Alignment
7895 Decl := Predef_Spec_Or_Body (Loc,
7896 Tag_Typ => Tag_Typ,
7897 Name => Name_uAlignment,
7898 Profile => New_List (
7899 Make_Parameter_Specification (Loc,
7900 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7901 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7903 Ret_Type => Standard_Integer,
7904 For_Body => True);
7906 Set_Handled_Statement_Sequence (Decl,
7907 Make_Handled_Sequence_Of_Statements (Loc, New_List (
7908 Make_Simple_Return_Statement (Loc,
7909 Expression =>
7910 Make_Attribute_Reference (Loc,
7911 Prefix => Make_Identifier (Loc, Name_X),
7912 Attribute_Name => Name_Alignment)))));
7914 Append_To (Res, Decl);
7916 -- Body of _Size
7918 Decl := Predef_Spec_Or_Body (Loc,
7919 Tag_Typ => Tag_Typ,
7920 Name => Name_uSize,
7921 Profile => New_List (
7922 Make_Parameter_Specification (Loc,
7923 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7924 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7926 Ret_Type => Standard_Long_Long_Integer,
7927 For_Body => True);
7929 Set_Handled_Statement_Sequence (Decl,
7930 Make_Handled_Sequence_Of_Statements (Loc, New_List (
7931 Make_Simple_Return_Statement (Loc,
7932 Expression =>
7933 Make_Attribute_Reference (Loc,
7934 Prefix => Make_Identifier (Loc, Name_X),
7935 Attribute_Name => Name_Size)))));
7937 Append_To (Res, Decl);
7939 -- Bodies for Dispatching stream IO routines. We need these only for
7940 -- non-limited types (in the limited case there is no dispatching).
7941 -- We also skip them if dispatching or finalization are not available.
7943 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Read)
7944 and then No (TSS (Tag_Typ, TSS_Stream_Read))
7945 then
7946 Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
7947 Append_To (Res, Decl);
7948 end if;
7950 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Write)
7951 and then No (TSS (Tag_Typ, TSS_Stream_Write))
7952 then
7953 Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
7954 Append_To (Res, Decl);
7955 end if;
7957 -- Skip body of _Input for the abstract case, since the corresponding
7958 -- spec is abstract (see Predef_Spec_Or_Body).
7960 if not Is_Abstract_Type (Tag_Typ)
7961 and then Stream_Operation_OK (Tag_Typ, TSS_Stream_Input)
7962 and then No (TSS (Tag_Typ, TSS_Stream_Input))
7963 then
7964 Build_Record_Or_Elementary_Input_Function
7965 (Loc, Tag_Typ, Decl, Ent);
7966 Append_To (Res, Decl);
7967 end if;
7969 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Output)
7970 and then No (TSS (Tag_Typ, TSS_Stream_Output))
7971 then
7972 Build_Record_Or_Elementary_Output_Procedure
7973 (Loc, Tag_Typ, Decl, Ent);
7974 Append_To (Res, Decl);
7975 end if;
7977 -- Ada 2005: Generate bodies for the following primitive operations for
7978 -- limited interfaces and synchronized types that implement a limited
7979 -- interface.
7981 -- disp_asynchronous_select
7982 -- disp_conditional_select
7983 -- disp_get_prim_op_kind
7984 -- disp_get_task_id
7985 -- disp_timed_select
7987 -- The interface versions will have null bodies
7989 -- These operations cannot be implemented on VM targets, so we simply
7990 -- disable their generation in this case. We also disable generation
7991 -- of these bodies if No_Dispatching_Calls is active.
7993 if Ada_Version >= Ada_05
7994 and then VM_Target = No_VM
7995 and then not Restriction_Active (No_Dispatching_Calls)
7996 and then not Is_Interface (Tag_Typ)
7997 and then
7998 ((Is_Interface (Etype (Tag_Typ))
7999 and then Is_Limited_Record (Etype (Tag_Typ)))
8000 or else (Is_Concurrent_Record_Type (Tag_Typ)
8001 and then Has_Abstract_Interfaces (Tag_Typ)))
8002 then
8003 Append_To (Res, Make_Disp_Asynchronous_Select_Body (Tag_Typ));
8004 Append_To (Res, Make_Disp_Conditional_Select_Body (Tag_Typ));
8005 Append_To (Res, Make_Disp_Get_Prim_Op_Kind_Body (Tag_Typ));
8006 Append_To (Res, Make_Disp_Get_Task_Id_Body (Tag_Typ));
8007 Append_To (Res, Make_Disp_Requeue_Body (Tag_Typ));
8008 Append_To (Res, Make_Disp_Timed_Select_Body (Tag_Typ));
8009 end if;
8011 if not Is_Limited_Type (Tag_Typ)
8012 and then not Is_Interface (Tag_Typ)
8013 then
8014 -- Body for equality
8016 if Eq_Needed then
8017 Decl :=
8018 Predef_Spec_Or_Body (Loc,
8019 Tag_Typ => Tag_Typ,
8020 Name => Eq_Name,
8021 Profile => New_List (
8022 Make_Parameter_Specification (Loc,
8023 Defining_Identifier =>
8024 Make_Defining_Identifier (Loc, Name_X),
8025 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
8027 Make_Parameter_Specification (Loc,
8028 Defining_Identifier =>
8029 Make_Defining_Identifier (Loc, Name_Y),
8030 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8032 Ret_Type => Standard_Boolean,
8033 For_Body => True);
8035 declare
8036 Def : constant Node_Id := Parent (Tag_Typ);
8037 Stmts : constant List_Id := New_List;
8038 Variant_Case : Boolean := Has_Discriminants (Tag_Typ);
8039 Comps : Node_Id := Empty;
8040 Typ_Def : Node_Id := Type_Definition (Def);
8042 begin
8043 if Variant_Case then
8044 if Nkind (Typ_Def) = N_Derived_Type_Definition then
8045 Typ_Def := Record_Extension_Part (Typ_Def);
8046 end if;
8048 if Present (Typ_Def) then
8049 Comps := Component_List (Typ_Def);
8050 end if;
8052 Variant_Case := Present (Comps)
8053 and then Present (Variant_Part (Comps));
8054 end if;
8056 if Variant_Case then
8057 Append_To (Stmts,
8058 Make_Eq_If (Tag_Typ, Discriminant_Specifications (Def)));
8059 Append_List_To (Stmts, Make_Eq_Case (Tag_Typ, Comps));
8060 Append_To (Stmts,
8061 Make_Simple_Return_Statement (Loc,
8062 Expression => New_Reference_To (Standard_True, Loc)));
8064 else
8065 Append_To (Stmts,
8066 Make_Simple_Return_Statement (Loc,
8067 Expression =>
8068 Expand_Record_Equality (Tag_Typ,
8069 Typ => Tag_Typ,
8070 Lhs => Make_Identifier (Loc, Name_X),
8071 Rhs => Make_Identifier (Loc, Name_Y),
8072 Bodies => Declarations (Decl))));
8073 end if;
8075 Set_Handled_Statement_Sequence (Decl,
8076 Make_Handled_Sequence_Of_Statements (Loc, Stmts));
8077 end;
8078 Append_To (Res, Decl);
8079 end if;
8081 -- Body for dispatching assignment
8083 Decl :=
8084 Predef_Spec_Or_Body (Loc,
8085 Tag_Typ => Tag_Typ,
8086 Name => Name_uAssign,
8087 Profile => New_List (
8088 Make_Parameter_Specification (Loc,
8089 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
8090 Out_Present => True,
8091 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
8093 Make_Parameter_Specification (Loc,
8094 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
8095 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8096 For_Body => True);
8098 Set_Handled_Statement_Sequence (Decl,
8099 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8100 Make_Assignment_Statement (Loc,
8101 Name => Make_Identifier (Loc, Name_X),
8102 Expression => Make_Identifier (Loc, Name_Y)))));
8104 Append_To (Res, Decl);
8105 end if;
8107 -- Generate dummy bodies for finalization actions of types that have
8108 -- no controlled components.
8110 -- Skip this processing if we are in the finalization routine in the
8111 -- runtime itself, otherwise we get hopelessly circularly confused!
8113 if In_Finalization_Root (Tag_Typ) then
8114 null;
8116 -- Skip this if finalization is not available
8118 elsif Restriction_Active (No_Finalization) then
8119 null;
8121 elsif (Etype (Tag_Typ) = Tag_Typ
8122 or else Is_Controlled (Tag_Typ)
8124 -- Ada 2005 (AI-251): We must also generate these subprograms
8125 -- if the immediate ancestor of Tag_Typ is an interface to
8126 -- ensure the correct initialization of its dispatch table.
8128 or else (not Is_Interface (Tag_Typ)
8129 and then
8130 Is_Interface (Etype (Tag_Typ))))
8131 and then not Has_Controlled_Component (Tag_Typ)
8132 then
8133 if not Is_Limited_Type (Tag_Typ) then
8134 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
8136 if Is_Controlled (Tag_Typ) then
8137 Set_Handled_Statement_Sequence (Decl,
8138 Make_Handled_Sequence_Of_Statements (Loc,
8139 Make_Adjust_Call (
8140 Ref => Make_Identifier (Loc, Name_V),
8141 Typ => Tag_Typ,
8142 Flist_Ref => Make_Identifier (Loc, Name_L),
8143 With_Attach => Make_Identifier (Loc, Name_B))));
8145 else
8146 Set_Handled_Statement_Sequence (Decl,
8147 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8148 Make_Null_Statement (Loc))));
8149 end if;
8151 Append_To (Res, Decl);
8152 end if;
8154 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
8156 if Is_Controlled (Tag_Typ) then
8157 Set_Handled_Statement_Sequence (Decl,
8158 Make_Handled_Sequence_Of_Statements (Loc,
8159 Make_Final_Call (
8160 Ref => Make_Identifier (Loc, Name_V),
8161 Typ => Tag_Typ,
8162 With_Detach => Make_Identifier (Loc, Name_B))));
8164 else
8165 Set_Handled_Statement_Sequence (Decl,
8166 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8167 Make_Null_Statement (Loc))));
8168 end if;
8170 Append_To (Res, Decl);
8171 end if;
8173 return Res;
8174 end Predefined_Primitive_Bodies;
8176 ---------------------------------
8177 -- Predefined_Primitive_Freeze --
8178 ---------------------------------
8180 function Predefined_Primitive_Freeze
8181 (Tag_Typ : Entity_Id) return List_Id
8183 Loc : constant Source_Ptr := Sloc (Tag_Typ);
8184 Res : constant List_Id := New_List;
8185 Prim : Elmt_Id;
8186 Frnodes : List_Id;
8188 begin
8189 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
8190 while Present (Prim) loop
8191 if Is_Predefined_Dispatching_Operation (Node (Prim)) then
8192 Frnodes := Freeze_Entity (Node (Prim), Loc);
8194 if Present (Frnodes) then
8195 Append_List_To (Res, Frnodes);
8196 end if;
8197 end if;
8199 Next_Elmt (Prim);
8200 end loop;
8202 return Res;
8203 end Predefined_Primitive_Freeze;
8205 -------------------------
8206 -- Stream_Operation_OK --
8207 -------------------------
8209 function Stream_Operation_OK
8210 (Typ : Entity_Id;
8211 Operation : TSS_Name_Type) return Boolean
8213 Has_Predefined_Or_Specified_Stream_Attribute : Boolean := False;
8215 begin
8216 -- Special case of a limited type extension: a default implementation
8217 -- of the stream attributes Read or Write exists if that attribute
8218 -- has been specified or is available for an ancestor type; a default
8219 -- implementation of the attribute Output (resp. Input) exists if the
8220 -- attribute has been specified or Write (resp. Read) is available for
8221 -- an ancestor type. The last condition only applies under Ada 2005.
8223 if Is_Limited_Type (Typ)
8224 and then Is_Tagged_Type (Typ)
8225 then
8226 if Operation = TSS_Stream_Read then
8227 Has_Predefined_Or_Specified_Stream_Attribute :=
8228 Has_Specified_Stream_Read (Typ);
8230 elsif Operation = TSS_Stream_Write then
8231 Has_Predefined_Or_Specified_Stream_Attribute :=
8232 Has_Specified_Stream_Write (Typ);
8234 elsif Operation = TSS_Stream_Input then
8235 Has_Predefined_Or_Specified_Stream_Attribute :=
8236 Has_Specified_Stream_Input (Typ)
8237 or else
8238 (Ada_Version >= Ada_05
8239 and then Stream_Operation_OK (Typ, TSS_Stream_Read));
8241 elsif Operation = TSS_Stream_Output then
8242 Has_Predefined_Or_Specified_Stream_Attribute :=
8243 Has_Specified_Stream_Output (Typ)
8244 or else
8245 (Ada_Version >= Ada_05
8246 and then Stream_Operation_OK (Typ, TSS_Stream_Write));
8247 end if;
8249 -- Case of inherited TSS_Stream_Read or TSS_Stream_Write
8251 if not Has_Predefined_Or_Specified_Stream_Attribute
8252 and then Is_Derived_Type (Typ)
8253 and then (Operation = TSS_Stream_Read
8254 or else Operation = TSS_Stream_Write)
8255 then
8256 Has_Predefined_Or_Specified_Stream_Attribute :=
8257 Present
8258 (Find_Inherited_TSS (Base_Type (Etype (Typ)), Operation));
8259 end if;
8260 end if;
8262 -- If the type is not limited, or else is limited but the attribute is
8263 -- explicitly specified or is predefined for the type, then return True,
8264 -- unless other conditions prevail, such as restrictions prohibiting
8265 -- streams or dispatching operations.
8267 -- We exclude the Input operation from being a predefined subprogram in
8268 -- the case where the associated type is an abstract extension, because
8269 -- the attribute is not callable in that case, per 13.13.2(49/2). Also,
8270 -- we don't want an abstract version created because types derived from
8271 -- the abstract type may not even have Input available (for example if
8272 -- derived from a private view of the abstract type that doesn't have
8273 -- a visible Input), but a VM such as .NET or the Java VM can treat the
8274 -- operation as inherited anyway, and we don't want an abstract function
8275 -- to be (implicitly) inherited in that case because it can lead to a VM
8276 -- exception.
8278 return (not Is_Limited_Type (Typ)
8279 or else Has_Predefined_Or_Specified_Stream_Attribute)
8280 and then (Operation /= TSS_Stream_Input
8281 or else not Is_Abstract_Type (Typ)
8282 or else not Is_Derived_Type (Typ))
8283 and then not Has_Unknown_Discriminants (Typ)
8284 and then not (Is_Interface (Typ)
8285 and then (Is_Task_Interface (Typ)
8286 or else Is_Protected_Interface (Typ)
8287 or else Is_Synchronized_Interface (Typ)))
8288 and then not Restriction_Active (No_Streams)
8289 and then not Restriction_Active (No_Dispatch)
8290 and then not No_Run_Time_Mode
8291 and then RTE_Available (RE_Tag)
8292 and then RTE_Available (RE_Root_Stream_Type);
8293 end Stream_Operation_OK;
8295 end Exp_Ch3;