2010-07-27 Paolo Carlini <paolo.carlini@oracle.com>
[official-gcc/alias-decl.git] / gcc / ada / exp_ch3.adb
blobe2263f3ab8fa5691f7a4e393a8df4b501e21f8fe
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-2010, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Atree; use Atree;
27 with Checks; use Checks;
28 with Einfo; use Einfo;
29 with Errout; use Errout;
30 with Exp_Aggr; use Exp_Aggr;
31 with Exp_Atag; use Exp_Atag;
32 with Exp_Ch4; use Exp_Ch4;
33 with Exp_Ch6; use Exp_Ch6;
34 with Exp_Ch7; use Exp_Ch7;
35 with Exp_Ch9; use Exp_Ch9;
36 with Exp_Ch11; use Exp_Ch11;
37 with Exp_Disp; use Exp_Disp;
38 with Exp_Dist; use Exp_Dist;
39 with Exp_Smem; use Exp_Smem;
40 with Exp_Strm; use Exp_Strm;
41 with Exp_Tss; use Exp_Tss;
42 with Exp_Util; use Exp_Util;
43 with Freeze; use Freeze;
44 with Nlists; use Nlists;
45 with Namet; use Namet;
46 with Nmake; use Nmake;
47 with Opt; use Opt;
48 with Restrict; use Restrict;
49 with Rident; use Rident;
50 with Rtsfind; use Rtsfind;
51 with Sem; use Sem;
52 with Sem_Aux; use Sem_Aux;
53 with Sem_Attr; use Sem_Attr;
54 with Sem_Cat; use Sem_Cat;
55 with Sem_Ch3; use Sem_Ch3;
56 with Sem_Ch6; use Sem_Ch6;
57 with Sem_Ch8; use Sem_Ch8;
58 with Sem_Disp; use Sem_Disp;
59 with Sem_Eval; use Sem_Eval;
60 with Sem_Mech; use Sem_Mech;
61 with Sem_Res; use Sem_Res;
62 with Sem_SCIL; use Sem_SCIL;
63 with Sem_Type; use Sem_Type;
64 with Sem_Util; use Sem_Util;
65 with Sinfo; use Sinfo;
66 with Stand; use Stand;
67 with Snames; use Snames;
68 with Targparm; use Targparm;
69 with Tbuild; use Tbuild;
70 with Ttypes; use Ttypes;
71 with Validsw; use Validsw;
73 package body Exp_Ch3 is
75 -----------------------
76 -- Local Subprograms --
77 -----------------------
79 function Add_Final_Chain (Def_Id : Entity_Id) return Entity_Id;
80 -- Add the declaration of a finalization list to the freeze actions for
81 -- Def_Id, and return its defining identifier.
83 procedure Adjust_Discriminants (Rtype : Entity_Id);
84 -- This is used when freezing a record type. It attempts to construct
85 -- more restrictive subtypes for discriminants so that the max size of
86 -- the record can be calculated more accurately. See the body of this
87 -- procedure for details.
89 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id);
90 -- Build initialization procedure for given array type. Nod is a node
91 -- used for attachment of any actions required in its construction.
92 -- It also supplies the source location used for the procedure.
94 function Build_Discriminant_Formals
95 (Rec_Id : Entity_Id;
96 Use_Dl : Boolean) return List_Id;
97 -- This function uses the discriminants of a type to build a list of
98 -- formal parameters, used in Build_Init_Procedure among other places.
99 -- If the flag Use_Dl is set, the list is built using the already
100 -- defined discriminals of the type, as is the case for concurrent
101 -- types with discriminants. Otherwise new identifiers are created,
102 -- with the source names of the discriminants.
104 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id;
105 -- This function builds a static aggregate that can serve as the initial
106 -- value for an array type whose bounds are static, and whose component
107 -- type is a composite type that has a static equivalent aggregate.
108 -- The equivalent array aggregate is used both for object initialization
109 -- and for component initialization, when used in the following function.
111 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id;
112 -- This function builds a static aggregate that can serve as the initial
113 -- value for a record type whose components are scalar and initialized
114 -- with compile-time values, or arrays with similar initialization or
115 -- defaults. When possible, initialization of an object of the type can
116 -- be achieved by using a copy of the aggregate as an initial value, thus
117 -- removing the implicit call that would otherwise constitute elaboration
118 -- code.
120 function Build_Master_Renaming
121 (N : Node_Id;
122 T : Entity_Id) return Entity_Id;
123 -- If the designated type of an access type is a task type or contains
124 -- tasks, we make sure that a _Master variable is declared in the current
125 -- scope, and then declare a renaming for it:
127 -- atypeM : Master_Id renames _Master;
129 -- where atyp is the name of the access type. This declaration is used when
130 -- an allocator for the access type is expanded. The node is the full
131 -- declaration of the designated type that contains tasks. The renaming
132 -- declaration is inserted before N, and after the Master declaration.
134 procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id);
135 -- Build record initialization procedure. N is the type declaration
136 -- node, and Pe is the corresponding entity for the record type.
138 procedure Build_Slice_Assignment (Typ : Entity_Id);
139 -- Build assignment procedure for one-dimensional arrays of controlled
140 -- types. Other array and slice assignments are expanded in-line, but
141 -- the code expansion for controlled components (when control actions
142 -- are active) can lead to very large blocks that GCC3 handles poorly.
144 procedure Build_Variant_Record_Equality (Typ : Entity_Id);
145 -- Create An Equality function for the non-tagged variant record 'Typ'
146 -- and attach it to the TSS list
148 procedure Check_Stream_Attributes (Typ : Entity_Id);
149 -- Check that if a limited extension has a parent with user-defined stream
150 -- attributes, and does not itself have user-defined stream-attributes,
151 -- then any limited component of the extension also has the corresponding
152 -- user-defined stream attributes.
154 procedure Clean_Task_Names
155 (Typ : Entity_Id;
156 Proc_Id : Entity_Id);
157 -- If an initialization procedure includes calls to generate names
158 -- for task subcomponents, indicate that secondary stack cleanup is
159 -- needed after an initialization. Typ is the component type, and Proc_Id
160 -- the initialization procedure for the enclosing composite type.
162 procedure Expand_Tagged_Root (T : Entity_Id);
163 -- Add a field _Tag at the beginning of the record. This field carries
164 -- the value of the access to the Dispatch table. This procedure is only
165 -- called on root type, the _Tag field being inherited by the descendants.
167 procedure Expand_Record_Controller (T : Entity_Id);
168 -- T must be a record type that Has_Controlled_Component. Add a field
169 -- _controller of type Record_Controller or Limited_Record_Controller
170 -- in the record T.
172 procedure Expand_Freeze_Array_Type (N : Node_Id);
173 -- Freeze an array type. Deals with building the initialization procedure,
174 -- creating the packed array type for a packed array and also with the
175 -- creation of the controlling procedures for the controlled case. The
176 -- argument N is the N_Freeze_Entity node for the type.
178 procedure Expand_Freeze_Enumeration_Type (N : Node_Id);
179 -- Freeze enumeration type with non-standard representation. Builds the
180 -- array and function needed to convert between enumeration pos and
181 -- enumeration representation values. N is the N_Freeze_Entity node
182 -- for the type.
184 procedure Expand_Freeze_Record_Type (N : Node_Id);
185 -- Freeze record type. Builds all necessary discriminant checking
186 -- and other ancillary functions, and builds dispatch tables where
187 -- needed. The argument N is the N_Freeze_Entity node. This processing
188 -- applies only to E_Record_Type entities, not to class wide types,
189 -- record subtypes, or private types.
191 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id);
192 -- Treat user-defined stream operations as renaming_as_body if the
193 -- subprogram they rename is not frozen when the type is frozen.
195 procedure Initialization_Warning (E : Entity_Id);
196 -- If static elaboration of the package is requested, indicate
197 -- when a type does meet the conditions for static initialization. If
198 -- E is a type, it has components that have no static initialization.
199 -- if E is an entity, its initial expression is not compile-time known.
201 function Init_Formals (Typ : Entity_Id) return List_Id;
202 -- This function builds the list of formals for an initialization routine.
203 -- The first formal is always _Init with the given type. For task value
204 -- record types and types containing tasks, three additional formals are
205 -- added:
207 -- _Master : Master_Id
208 -- _Chain : in out Activation_Chain
209 -- _Task_Name : String
211 -- The caller must append additional entries for discriminants if required.
213 function In_Runtime (E : Entity_Id) return Boolean;
214 -- Check if E is defined in the RTL (in a child of Ada or System). Used
215 -- to avoid to bring in the overhead of _Input, _Output for tagged types.
217 function Is_Variable_Size_Record (E : Entity_Id) return Boolean;
218 -- Returns true if E has variable size components
220 function Make_Eq_Case
221 (E : Entity_Id;
222 CL : Node_Id;
223 Discr : Entity_Id := Empty) return List_Id;
224 -- Building block for variant record equality. Defined to share the code
225 -- between the tagged and non-tagged case. Given a Component_List node CL,
226 -- it generates an 'if' followed by a 'case' statement that compares all
227 -- components of local temporaries named X and Y (that are declared as
228 -- formals at some upper level). E provides the Sloc to be used for the
229 -- generated code. Discr is used as the case statement switch in the case
230 -- of Unchecked_Union equality.
232 function Make_Eq_If
233 (E : Entity_Id;
234 L : List_Id) return Node_Id;
235 -- Building block for variant record equality. Defined to share the code
236 -- between the tagged and non-tagged case. Given the list of components
237 -- (or discriminants) L, it generates a return statement that compares all
238 -- components of local temporaries named X and Y (that are declared as
239 -- formals at some upper level). E provides the Sloc to be used for the
240 -- generated code.
242 procedure Make_Predefined_Primitive_Specs
243 (Tag_Typ : Entity_Id;
244 Predef_List : out List_Id;
245 Renamed_Eq : out Entity_Id);
246 -- Create a list with the specs of the predefined primitive operations.
247 -- For tagged types that are interfaces all these primitives are defined
248 -- abstract.
250 -- The following entries are present for all tagged types, and provide
251 -- the results of the corresponding attribute applied to the object.
252 -- Dispatching is required in general, since the result of the attribute
253 -- will vary with the actual object subtype.
255 -- _alignment provides result of 'Alignment attribute
256 -- _size provides result of 'Size attribute
257 -- typSR provides result of 'Read attribute
258 -- typSW provides result of 'Write attribute
259 -- typSI provides result of 'Input attribute
260 -- typSO provides result of 'Output attribute
262 -- The following entries are additionally present for non-limited tagged
263 -- types, and implement additional dispatching operations for predefined
264 -- operations:
266 -- _equality implements "=" operator
267 -- _assign implements assignment operation
268 -- typDF implements deep finalization
269 -- typDA implements deep adjust
271 -- The latter two are empty procedures unless the type contains some
272 -- controlled components that require finalization actions (the deep
273 -- in the name refers to the fact that the action applies to components).
275 -- The list is returned in Predef_List. The Parameter Renamed_Eq either
276 -- returns the value Empty, or else the defining unit name for the
277 -- predefined equality function in the case where the type has a primitive
278 -- operation that is a renaming of predefined equality (but only if there
279 -- is also an overriding user-defined equality function). The returned
280 -- Renamed_Eq will be passed to the corresponding parameter of
281 -- Predefined_Primitive_Bodies.
283 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean;
284 -- returns True if there are representation clauses for type T that are not
285 -- inherited. If the result is false, the init_proc and the discriminant
286 -- checking functions of the parent can be reused by a derived type.
288 procedure Make_Controlling_Function_Wrappers
289 (Tag_Typ : Entity_Id;
290 Decl_List : out List_Id;
291 Body_List : out List_Id);
292 -- Ada 2005 (AI-391): Makes specs and bodies for the wrapper functions
293 -- associated with inherited functions with controlling results which
294 -- are not overridden. The body of each wrapper function consists solely
295 -- of a return statement whose expression is an extension aggregate
296 -- invoking the inherited subprogram's parent subprogram and extended
297 -- with a null association list.
299 procedure Make_Null_Procedure_Specs
300 (Tag_Typ : Entity_Id;
301 Decl_List : out List_Id);
302 -- Ada 2005 (AI-251): Makes specs for null procedures associated with any
303 -- null procedures inherited from an interface type that have not been
304 -- overridden. Only one null procedure will be created for a given set of
305 -- inherited null procedures with homographic profiles.
307 function Predef_Spec_Or_Body
308 (Loc : Source_Ptr;
309 Tag_Typ : Entity_Id;
310 Name : Name_Id;
311 Profile : List_Id;
312 Ret_Type : Entity_Id := Empty;
313 For_Body : Boolean := False) return Node_Id;
314 -- This function generates the appropriate expansion for a predefined
315 -- primitive operation specified by its name, parameter profile and
316 -- return type (Empty means this is a procedure). If For_Body is false,
317 -- then the returned node is a subprogram declaration. If For_Body is
318 -- true, then the returned node is a empty subprogram body containing
319 -- no declarations and no statements.
321 function Predef_Stream_Attr_Spec
322 (Loc : Source_Ptr;
323 Tag_Typ : Entity_Id;
324 Name : TSS_Name_Type;
325 For_Body : Boolean := False) return Node_Id;
326 -- Specialized version of Predef_Spec_Or_Body that apply to read, write,
327 -- input and output attribute whose specs are constructed in Exp_Strm.
329 function Predef_Deep_Spec
330 (Loc : Source_Ptr;
331 Tag_Typ : Entity_Id;
332 Name : TSS_Name_Type;
333 For_Body : Boolean := False) return Node_Id;
334 -- Specialized version of Predef_Spec_Or_Body that apply to _deep_adjust
335 -- and _deep_finalize
337 function Predefined_Primitive_Bodies
338 (Tag_Typ : Entity_Id;
339 Renamed_Eq : Entity_Id) return List_Id;
340 -- Create the bodies of the predefined primitives that are described in
341 -- Predefined_Primitive_Specs. When not empty, Renamed_Eq must denote
342 -- the defining unit name of the type's predefined equality as returned
343 -- by Make_Predefined_Primitive_Specs.
345 function Predefined_Primitive_Freeze (Tag_Typ : Entity_Id) return List_Id;
346 -- Freeze entities of all predefined primitive operations. This is needed
347 -- because the bodies of these operations do not normally do any freezing.
349 function Stream_Operation_OK
350 (Typ : Entity_Id;
351 Operation : TSS_Name_Type) return Boolean;
352 -- Check whether the named stream operation must be emitted for a given
353 -- type. The rules for inheritance of stream attributes by type extensions
354 -- are enforced by this function. Furthermore, various restrictions prevent
355 -- the generation of these operations, as a useful optimization or for
356 -- certification purposes.
358 ---------------------
359 -- Add_Final_Chain --
360 ---------------------
362 function Add_Final_Chain (Def_Id : Entity_Id) return Entity_Id is
363 Loc : constant Source_Ptr := Sloc (Def_Id);
364 Flist : Entity_Id;
366 begin
367 Flist :=
368 Make_Defining_Identifier (Loc,
369 New_External_Name (Chars (Def_Id), 'L'));
371 Append_Freeze_Action (Def_Id,
372 Make_Object_Declaration (Loc,
373 Defining_Identifier => Flist,
374 Object_Definition =>
375 New_Reference_To (RTE (RE_List_Controller), Loc)));
377 return Flist;
378 end Add_Final_Chain;
380 --------------------------
381 -- Adjust_Discriminants --
382 --------------------------
384 -- This procedure attempts to define subtypes for discriminants that are
385 -- more restrictive than those declared. Such a replacement is possible if
386 -- we can demonstrate that values outside the restricted range would cause
387 -- constraint errors in any case. The advantage of restricting the
388 -- discriminant types in this way is that the maximum size of the variant
389 -- record can be calculated more conservatively.
391 -- An example of a situation in which we can perform this type of
392 -- restriction is the following:
394 -- subtype B is range 1 .. 10;
395 -- type Q is array (B range <>) of Integer;
397 -- type V (N : Natural) is record
398 -- C : Q (1 .. N);
399 -- end record;
401 -- In this situation, we can restrict the upper bound of N to 10, since
402 -- any larger value would cause a constraint error in any case.
404 -- There are many situations in which such restriction is possible, but
405 -- for now, we just look for cases like the above, where the component
406 -- in question is a one dimensional array whose upper bound is one of
407 -- the record discriminants. Also the component must not be part of
408 -- any variant part, since then the component does not always exist.
410 procedure Adjust_Discriminants (Rtype : Entity_Id) is
411 Loc : constant Source_Ptr := Sloc (Rtype);
412 Comp : Entity_Id;
413 Ctyp : Entity_Id;
414 Ityp : Entity_Id;
415 Lo : Node_Id;
416 Hi : Node_Id;
417 P : Node_Id;
418 Loval : Uint;
419 Discr : Entity_Id;
420 Dtyp : Entity_Id;
421 Dhi : Node_Id;
422 Dhiv : Uint;
423 Ahi : Node_Id;
424 Ahiv : Uint;
425 Tnn : Entity_Id;
427 begin
428 Comp := First_Component (Rtype);
429 while Present (Comp) loop
431 -- If our parent is a variant, quit, we do not look at components
432 -- that are in variant parts, because they may not always exist.
434 P := Parent (Comp); -- component declaration
435 P := Parent (P); -- component list
437 exit when Nkind (Parent (P)) = N_Variant;
439 -- We are looking for a one dimensional array type
441 Ctyp := Etype (Comp);
443 if not Is_Array_Type (Ctyp)
444 or else Number_Dimensions (Ctyp) > 1
445 then
446 goto Continue;
447 end if;
449 -- The lower bound must be constant, and the upper bound is a
450 -- discriminant (which is a discriminant of the current record).
452 Ityp := Etype (First_Index (Ctyp));
453 Lo := Type_Low_Bound (Ityp);
454 Hi := Type_High_Bound (Ityp);
456 if not Compile_Time_Known_Value (Lo)
457 or else Nkind (Hi) /= N_Identifier
458 or else No (Entity (Hi))
459 or else Ekind (Entity (Hi)) /= E_Discriminant
460 then
461 goto Continue;
462 end if;
464 -- We have an array with appropriate bounds
466 Loval := Expr_Value (Lo);
467 Discr := Entity (Hi);
468 Dtyp := Etype (Discr);
470 -- See if the discriminant has a known upper bound
472 Dhi := Type_High_Bound (Dtyp);
474 if not Compile_Time_Known_Value (Dhi) then
475 goto Continue;
476 end if;
478 Dhiv := Expr_Value (Dhi);
480 -- See if base type of component array has known upper bound
482 Ahi := Type_High_Bound (Etype (First_Index (Base_Type (Ctyp))));
484 if not Compile_Time_Known_Value (Ahi) then
485 goto Continue;
486 end if;
488 Ahiv := Expr_Value (Ahi);
490 -- The condition for doing the restriction is that the high bound
491 -- of the discriminant is greater than the low bound of the array,
492 -- and is also greater than the high bound of the base type index.
494 if Dhiv > Loval and then Dhiv > Ahiv then
496 -- We can reset the upper bound of the discriminant type to
497 -- whichever is larger, the low bound of the component, or
498 -- the high bound of the base type array index.
500 -- We build a subtype that is declared as
502 -- subtype Tnn is discr_type range discr_type'First .. max;
504 -- And insert this declaration into the tree. The type of the
505 -- discriminant is then reset to this more restricted subtype.
507 Tnn := Make_Temporary (Loc, 'T');
509 Insert_Action (Declaration_Node (Rtype),
510 Make_Subtype_Declaration (Loc,
511 Defining_Identifier => Tnn,
512 Subtype_Indication =>
513 Make_Subtype_Indication (Loc,
514 Subtype_Mark => New_Occurrence_Of (Dtyp, Loc),
515 Constraint =>
516 Make_Range_Constraint (Loc,
517 Range_Expression =>
518 Make_Range (Loc,
519 Low_Bound =>
520 Make_Attribute_Reference (Loc,
521 Attribute_Name => Name_First,
522 Prefix => New_Occurrence_Of (Dtyp, Loc)),
523 High_Bound =>
524 Make_Integer_Literal (Loc,
525 Intval => UI_Max (Loval, Ahiv)))))));
527 Set_Etype (Discr, Tnn);
528 end if;
530 <<Continue>>
531 Next_Component (Comp);
532 end loop;
533 end Adjust_Discriminants;
535 ---------------------------
536 -- Build_Array_Init_Proc --
537 ---------------------------
539 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id) is
540 Loc : constant Source_Ptr := Sloc (Nod);
541 Comp_Type : constant Entity_Id := Component_Type (A_Type);
542 Index_List : List_Id;
543 Proc_Id : Entity_Id;
544 Body_Stmts : List_Id;
545 Has_Default_Init : Boolean;
547 function Init_Component return List_Id;
548 -- Create one statement to initialize one array component, designated
549 -- by a full set of indices.
551 function Init_One_Dimension (N : Int) return List_Id;
552 -- Create loop to initialize one dimension of the array. The single
553 -- statement in the loop body initializes the inner dimensions if any,
554 -- or else the single component. Note that this procedure is called
555 -- recursively, with N being the dimension to be initialized. A call
556 -- with N greater than the number of dimensions simply generates the
557 -- component initialization, terminating the recursion.
559 --------------------
560 -- Init_Component --
561 --------------------
563 function Init_Component return List_Id is
564 Comp : Node_Id;
566 begin
567 Comp :=
568 Make_Indexed_Component (Loc,
569 Prefix => Make_Identifier (Loc, Name_uInit),
570 Expressions => Index_List);
572 if Needs_Simple_Initialization (Comp_Type) then
573 Set_Assignment_OK (Comp);
574 return New_List (
575 Make_Assignment_Statement (Loc,
576 Name => Comp,
577 Expression =>
578 Get_Simple_Init_Val
579 (Comp_Type, Nod, Component_Size (A_Type))));
581 else
582 Clean_Task_Names (Comp_Type, Proc_Id);
583 return
584 Build_Initialization_Call
585 (Loc, Comp, Comp_Type,
586 In_Init_Proc => True,
587 Enclos_Type => A_Type);
588 end if;
589 end Init_Component;
591 ------------------------
592 -- Init_One_Dimension --
593 ------------------------
595 function Init_One_Dimension (N : Int) return List_Id is
596 Index : Entity_Id;
598 begin
599 -- If the component does not need initializing, then there is nothing
600 -- to do here, so we return a null body. This occurs when generating
601 -- the dummy Init_Proc needed for Initialize_Scalars processing.
603 if not Has_Non_Null_Base_Init_Proc (Comp_Type)
604 and then not Needs_Simple_Initialization (Comp_Type)
605 and then not Has_Task (Comp_Type)
606 then
607 return New_List (Make_Null_Statement (Loc));
609 -- If all dimensions dealt with, we simply initialize the component
611 elsif N > Number_Dimensions (A_Type) then
612 return Init_Component;
614 -- Here we generate the required loop
616 else
617 Index :=
618 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
620 Append (New_Reference_To (Index, Loc), Index_List);
622 return New_List (
623 Make_Implicit_Loop_Statement (Nod,
624 Identifier => Empty,
625 Iteration_Scheme =>
626 Make_Iteration_Scheme (Loc,
627 Loop_Parameter_Specification =>
628 Make_Loop_Parameter_Specification (Loc,
629 Defining_Identifier => Index,
630 Discrete_Subtype_Definition =>
631 Make_Attribute_Reference (Loc,
632 Prefix => Make_Identifier (Loc, Name_uInit),
633 Attribute_Name => Name_Range,
634 Expressions => New_List (
635 Make_Integer_Literal (Loc, N))))),
636 Statements => Init_One_Dimension (N + 1)));
637 end if;
638 end Init_One_Dimension;
640 -- Start of processing for Build_Array_Init_Proc
642 begin
643 -- Nothing to generate in the following cases:
645 -- 1. Initialization is suppressed for the type
646 -- 2. The type is a value type, in the CIL sense.
647 -- 3. The type has CIL/JVM convention.
648 -- 4. An initialization already exists for the base type
650 if Suppress_Init_Proc (A_Type)
651 or else Is_Value_Type (Comp_Type)
652 or else Convention (A_Type) = Convention_CIL
653 or else Convention (A_Type) = Convention_Java
654 or else Present (Base_Init_Proc (A_Type))
655 then
656 return;
657 end if;
659 Index_List := New_List;
661 -- We need an initialization procedure if any of the following is true:
663 -- 1. The component type has an initialization procedure
664 -- 2. The component type needs simple initialization
665 -- 3. Tasks are present
666 -- 4. The type is marked as a public entity
668 -- The reason for the public entity test is to deal properly with the
669 -- Initialize_Scalars pragma. This pragma can be set in the client and
670 -- not in the declaring package, this means the client will make a call
671 -- to the initialization procedure (because one of conditions 1-3 must
672 -- apply in this case), and we must generate a procedure (even if it is
673 -- null) to satisfy the call in this case.
675 -- Exception: do not build an array init_proc for a type whose root
676 -- type is Standard.String or Standard.Wide_[Wide_]String, since there
677 -- is no place to put the code, and in any case we handle initialization
678 -- of such types (in the Initialize_Scalars case, that's the only time
679 -- the issue arises) in a special manner anyway which does not need an
680 -- init_proc.
682 Has_Default_Init := Has_Non_Null_Base_Init_Proc (Comp_Type)
683 or else Needs_Simple_Initialization (Comp_Type)
684 or else Has_Task (Comp_Type);
686 if Has_Default_Init
687 or else (not Restriction_Active (No_Initialize_Scalars)
688 and then Is_Public (A_Type)
689 and then Root_Type (A_Type) /= Standard_String
690 and then Root_Type (A_Type) /= Standard_Wide_String
691 and then Root_Type (A_Type) /= Standard_Wide_Wide_String)
692 then
693 Proc_Id :=
694 Make_Defining_Identifier (Loc,
695 Chars => Make_Init_Proc_Name (A_Type));
697 -- If No_Default_Initialization restriction is active, then we don't
698 -- want to build an init_proc, but we need to mark that an init_proc
699 -- would be needed if this restriction was not active (so that we can
700 -- detect attempts to call it), so set a dummy init_proc in place.
701 -- This is only done though when actual default initialization is
702 -- needed (and not done when only Is_Public is True), since otherwise
703 -- objects such as arrays of scalars could be wrongly flagged as
704 -- violating the restriction.
706 if Restriction_Active (No_Default_Initialization) then
707 if Has_Default_Init then
708 Set_Init_Proc (A_Type, Proc_Id);
709 end if;
711 return;
712 end if;
714 Body_Stmts := Init_One_Dimension (1);
716 Discard_Node (
717 Make_Subprogram_Body (Loc,
718 Specification =>
719 Make_Procedure_Specification (Loc,
720 Defining_Unit_Name => Proc_Id,
721 Parameter_Specifications => Init_Formals (A_Type)),
722 Declarations => New_List,
723 Handled_Statement_Sequence =>
724 Make_Handled_Sequence_Of_Statements (Loc,
725 Statements => Body_Stmts)));
727 Set_Ekind (Proc_Id, E_Procedure);
728 Set_Is_Public (Proc_Id, Is_Public (A_Type));
729 Set_Is_Internal (Proc_Id);
730 Set_Has_Completion (Proc_Id);
732 if not Debug_Generated_Code then
733 Set_Debug_Info_Off (Proc_Id);
734 end if;
736 -- Set inlined unless controlled stuff or tasks around, in which
737 -- case we do not want to inline, because nested stuff may cause
738 -- difficulties in inter-unit inlining, and furthermore there is
739 -- in any case no point in inlining such complex init procs.
741 if not Has_Task (Proc_Id)
742 and then not Needs_Finalization (Proc_Id)
743 then
744 Set_Is_Inlined (Proc_Id);
745 end if;
747 -- Associate Init_Proc with type, and determine if the procedure
748 -- is null (happens because of the Initialize_Scalars pragma case,
749 -- where we have to generate a null procedure in case it is called
750 -- by a client with Initialize_Scalars set). Such procedures have
751 -- to be generated, but do not have to be called, so we mark them
752 -- as null to suppress the call.
754 Set_Init_Proc (A_Type, Proc_Id);
756 if List_Length (Body_Stmts) = 1
758 -- We must skip SCIL nodes because they may have been added to this
759 -- list by Insert_Actions.
761 and then Nkind (First_Non_SCIL_Node (Body_Stmts)) = N_Null_Statement
762 then
763 Set_Is_Null_Init_Proc (Proc_Id);
765 else
766 -- Try to build a static aggregate to initialize statically
767 -- objects of the type. This can only be done for constrained
768 -- one-dimensional arrays with static bounds.
770 Set_Static_Initialization
771 (Proc_Id,
772 Build_Equivalent_Array_Aggregate (First_Subtype (A_Type)));
773 end if;
774 end if;
775 end Build_Array_Init_Proc;
777 -----------------------------
778 -- Build_Class_Wide_Master --
779 -----------------------------
781 procedure Build_Class_Wide_Master (T : Entity_Id) is
782 Loc : constant Source_Ptr := Sloc (T);
783 M_Id : Entity_Id;
784 Decl : Node_Id;
785 P : Node_Id;
786 Par : Node_Id;
788 begin
789 -- Nothing to do if there is no task hierarchy
791 if Restriction_Active (No_Task_Hierarchy) then
792 return;
793 end if;
795 -- Find declaration that created the access type: either a type
796 -- declaration, or an object declaration with an access definition,
797 -- in which case the type is anonymous.
799 if Is_Itype (T) then
800 P := Associated_Node_For_Itype (T);
801 else
802 P := Parent (T);
803 end if;
805 -- Nothing to do if we already built a master entity for this scope
807 if not Has_Master_Entity (Scope (T)) then
809 -- First build the master entity
810 -- _Master : constant Master_Id := Current_Master.all;
811 -- and insert it just before the current declaration.
813 Decl :=
814 Make_Object_Declaration (Loc,
815 Defining_Identifier =>
816 Make_Defining_Identifier (Loc, Name_uMaster),
817 Constant_Present => True,
818 Object_Definition => New_Reference_To (Standard_Integer, Loc),
819 Expression =>
820 Make_Explicit_Dereference (Loc,
821 New_Reference_To (RTE (RE_Current_Master), Loc)));
823 Insert_Action (P, Decl);
824 Analyze (Decl);
825 Set_Has_Master_Entity (Scope (T));
827 -- Now mark the containing scope as a task master. Masters
828 -- associated with return statements are already marked at
829 -- this stage (see Analyze_Subprogram_Body).
831 if Ekind (Current_Scope) /= E_Return_Statement then
832 Par := P;
833 while Nkind (Par) /= N_Compilation_Unit loop
834 Par := Parent (Par);
836 -- If we fall off the top, we are at the outer level, and the
837 -- environment task is our effective master, so nothing to mark.
839 if Nkind_In
840 (Par, N_Task_Body, N_Block_Statement, N_Subprogram_Body)
841 then
842 Set_Is_Task_Master (Par, True);
843 exit;
844 end if;
845 end loop;
846 end if;
847 end if;
849 -- Now define the renaming of the master_id
851 M_Id :=
852 Make_Defining_Identifier (Loc,
853 New_External_Name (Chars (T), 'M'));
855 Decl :=
856 Make_Object_Renaming_Declaration (Loc,
857 Defining_Identifier => M_Id,
858 Subtype_Mark => New_Reference_To (Standard_Integer, Loc),
859 Name => Make_Identifier (Loc, Name_uMaster));
860 Insert_Before (P, Decl);
861 Analyze (Decl);
863 Set_Master_Id (T, M_Id);
865 exception
866 when RE_Not_Available =>
867 return;
868 end Build_Class_Wide_Master;
870 --------------------------------
871 -- Build_Discr_Checking_Funcs --
872 --------------------------------
874 procedure Build_Discr_Checking_Funcs (N : Node_Id) is
875 Rec_Id : Entity_Id;
876 Loc : Source_Ptr;
877 Enclosing_Func_Id : Entity_Id;
878 Sequence : Nat := 1;
879 Type_Def : Node_Id;
880 V : Node_Id;
882 function Build_Case_Statement
883 (Case_Id : Entity_Id;
884 Variant : Node_Id) return Node_Id;
885 -- Build a case statement containing only two alternatives. The first
886 -- alternative corresponds exactly to the discrete choices given on the
887 -- variant with contains the components that we are generating the
888 -- checks for. If the discriminant is one of these return False. The
889 -- second alternative is an OTHERS choice that will return True
890 -- indicating the discriminant did not match.
892 function Build_Dcheck_Function
893 (Case_Id : Entity_Id;
894 Variant : Node_Id) return Entity_Id;
895 -- Build the discriminant checking function for a given variant
897 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id);
898 -- Builds the discriminant checking function for each variant of the
899 -- given variant part of the record type.
901 --------------------------
902 -- Build_Case_Statement --
903 --------------------------
905 function Build_Case_Statement
906 (Case_Id : Entity_Id;
907 Variant : Node_Id) return Node_Id
909 Alt_List : constant List_Id := New_List;
910 Actuals_List : List_Id;
911 Case_Node : Node_Id;
912 Case_Alt_Node : Node_Id;
913 Choice : Node_Id;
914 Choice_List : List_Id;
915 D : Entity_Id;
916 Return_Node : Node_Id;
918 begin
919 Case_Node := New_Node (N_Case_Statement, Loc);
921 -- Replace the discriminant which controls the variant, with the name
922 -- of the formal of the checking function.
924 Set_Expression (Case_Node,
925 Make_Identifier (Loc, Chars (Case_Id)));
927 Choice := First (Discrete_Choices (Variant));
929 if Nkind (Choice) = N_Others_Choice then
930 Choice_List := New_Copy_List (Others_Discrete_Choices (Choice));
931 else
932 Choice_List := New_Copy_List (Discrete_Choices (Variant));
933 end if;
935 if not Is_Empty_List (Choice_List) then
936 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
937 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
939 -- In case this is a nested variant, we need to return the result
940 -- of the discriminant checking function for the immediately
941 -- enclosing variant.
943 if Present (Enclosing_Func_Id) then
944 Actuals_List := New_List;
946 D := First_Discriminant (Rec_Id);
947 while Present (D) loop
948 Append (Make_Identifier (Loc, Chars (D)), Actuals_List);
949 Next_Discriminant (D);
950 end loop;
952 Return_Node :=
953 Make_Simple_Return_Statement (Loc,
954 Expression =>
955 Make_Function_Call (Loc,
956 Name =>
957 New_Reference_To (Enclosing_Func_Id, Loc),
958 Parameter_Associations =>
959 Actuals_List));
961 else
962 Return_Node :=
963 Make_Simple_Return_Statement (Loc,
964 Expression =>
965 New_Reference_To (Standard_False, Loc));
966 end if;
968 Set_Statements (Case_Alt_Node, New_List (Return_Node));
969 Append (Case_Alt_Node, Alt_List);
970 end if;
972 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
973 Choice_List := New_List (New_Node (N_Others_Choice, Loc));
974 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
976 Return_Node :=
977 Make_Simple_Return_Statement (Loc,
978 Expression =>
979 New_Reference_To (Standard_True, Loc));
981 Set_Statements (Case_Alt_Node, New_List (Return_Node));
982 Append (Case_Alt_Node, Alt_List);
984 Set_Alternatives (Case_Node, Alt_List);
985 return Case_Node;
986 end Build_Case_Statement;
988 ---------------------------
989 -- Build_Dcheck_Function --
990 ---------------------------
992 function Build_Dcheck_Function
993 (Case_Id : Entity_Id;
994 Variant : Node_Id) return Entity_Id
996 Body_Node : Node_Id;
997 Func_Id : Entity_Id;
998 Parameter_List : List_Id;
999 Spec_Node : Node_Id;
1001 begin
1002 Body_Node := New_Node (N_Subprogram_Body, Loc);
1003 Sequence := Sequence + 1;
1005 Func_Id :=
1006 Make_Defining_Identifier (Loc,
1007 Chars => New_External_Name (Chars (Rec_Id), 'D', Sequence));
1009 Spec_Node := New_Node (N_Function_Specification, Loc);
1010 Set_Defining_Unit_Name (Spec_Node, Func_Id);
1012 Parameter_List := Build_Discriminant_Formals (Rec_Id, False);
1014 Set_Parameter_Specifications (Spec_Node, Parameter_List);
1015 Set_Result_Definition (Spec_Node,
1016 New_Reference_To (Standard_Boolean, Loc));
1017 Set_Specification (Body_Node, Spec_Node);
1018 Set_Declarations (Body_Node, New_List);
1020 Set_Handled_Statement_Sequence (Body_Node,
1021 Make_Handled_Sequence_Of_Statements (Loc,
1022 Statements => New_List (
1023 Build_Case_Statement (Case_Id, Variant))));
1025 Set_Ekind (Func_Id, E_Function);
1026 Set_Mechanism (Func_Id, Default_Mechanism);
1027 Set_Is_Inlined (Func_Id, True);
1028 Set_Is_Pure (Func_Id, True);
1029 Set_Is_Public (Func_Id, Is_Public (Rec_Id));
1030 Set_Is_Internal (Func_Id, True);
1032 if not Debug_Generated_Code then
1033 Set_Debug_Info_Off (Func_Id);
1034 end if;
1036 Analyze (Body_Node);
1038 Append_Freeze_Action (Rec_Id, Body_Node);
1039 Set_Dcheck_Function (Variant, Func_Id);
1040 return Func_Id;
1041 end Build_Dcheck_Function;
1043 ----------------------------
1044 -- Build_Dcheck_Functions --
1045 ----------------------------
1047 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id) is
1048 Component_List_Node : Node_Id;
1049 Decl : Entity_Id;
1050 Discr_Name : Entity_Id;
1051 Func_Id : Entity_Id;
1052 Variant : Node_Id;
1053 Saved_Enclosing_Func_Id : Entity_Id;
1055 begin
1056 -- Build the discriminant-checking function for each variant, and
1057 -- label all components of that variant with the function's name.
1058 -- We only Generate a discriminant-checking function when the
1059 -- variant is not empty, to prevent the creation of dead code.
1060 -- The exception to that is when Frontend_Layout_On_Target is set,
1061 -- because the variant record size function generated in package
1062 -- Layout needs to generate calls to all discriminant-checking
1063 -- functions, including those for empty variants.
1065 Discr_Name := Entity (Name (Variant_Part_Node));
1066 Variant := First_Non_Pragma (Variants (Variant_Part_Node));
1068 while Present (Variant) loop
1069 Component_List_Node := Component_List (Variant);
1071 if not Null_Present (Component_List_Node)
1072 or else Frontend_Layout_On_Target
1073 then
1074 Func_Id := Build_Dcheck_Function (Discr_Name, Variant);
1075 Decl :=
1076 First_Non_Pragma (Component_Items (Component_List_Node));
1078 while Present (Decl) loop
1079 Set_Discriminant_Checking_Func
1080 (Defining_Identifier (Decl), Func_Id);
1082 Next_Non_Pragma (Decl);
1083 end loop;
1085 if Present (Variant_Part (Component_List_Node)) then
1086 Saved_Enclosing_Func_Id := Enclosing_Func_Id;
1087 Enclosing_Func_Id := Func_Id;
1088 Build_Dcheck_Functions (Variant_Part (Component_List_Node));
1089 Enclosing_Func_Id := Saved_Enclosing_Func_Id;
1090 end if;
1091 end if;
1093 Next_Non_Pragma (Variant);
1094 end loop;
1095 end Build_Dcheck_Functions;
1097 -- Start of processing for Build_Discr_Checking_Funcs
1099 begin
1100 -- Only build if not done already
1102 if not Discr_Check_Funcs_Built (N) then
1103 Type_Def := Type_Definition (N);
1105 if Nkind (Type_Def) = N_Record_Definition then
1106 if No (Component_List (Type_Def)) then -- null record.
1107 return;
1108 else
1109 V := Variant_Part (Component_List (Type_Def));
1110 end if;
1112 else pragma Assert (Nkind (Type_Def) = N_Derived_Type_Definition);
1113 if No (Component_List (Record_Extension_Part (Type_Def))) then
1114 return;
1115 else
1116 V := Variant_Part
1117 (Component_List (Record_Extension_Part (Type_Def)));
1118 end if;
1119 end if;
1121 Rec_Id := Defining_Identifier (N);
1123 if Present (V) and then not Is_Unchecked_Union (Rec_Id) then
1124 Loc := Sloc (N);
1125 Enclosing_Func_Id := Empty;
1126 Build_Dcheck_Functions (V);
1127 end if;
1129 Set_Discr_Check_Funcs_Built (N);
1130 end if;
1131 end Build_Discr_Checking_Funcs;
1133 --------------------------------
1134 -- Build_Discriminant_Formals --
1135 --------------------------------
1137 function Build_Discriminant_Formals
1138 (Rec_Id : Entity_Id;
1139 Use_Dl : Boolean) return List_Id
1141 Loc : Source_Ptr := Sloc (Rec_Id);
1142 Parameter_List : constant List_Id := New_List;
1143 D : Entity_Id;
1144 Formal : Entity_Id;
1145 Formal_Type : Entity_Id;
1146 Param_Spec_Node : Node_Id;
1148 begin
1149 if Has_Discriminants (Rec_Id) then
1150 D := First_Discriminant (Rec_Id);
1151 while Present (D) loop
1152 Loc := Sloc (D);
1154 if Use_Dl then
1155 Formal := Discriminal (D);
1156 Formal_Type := Etype (Formal);
1157 else
1158 Formal := Make_Defining_Identifier (Loc, Chars (D));
1159 Formal_Type := Etype (D);
1160 end if;
1162 Param_Spec_Node :=
1163 Make_Parameter_Specification (Loc,
1164 Defining_Identifier => Formal,
1165 Parameter_Type =>
1166 New_Reference_To (Formal_Type, Loc));
1167 Append (Param_Spec_Node, Parameter_List);
1168 Next_Discriminant (D);
1169 end loop;
1170 end if;
1172 return Parameter_List;
1173 end Build_Discriminant_Formals;
1175 --------------------------------------
1176 -- Build_Equivalent_Array_Aggregate --
1177 --------------------------------------
1179 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id is
1180 Loc : constant Source_Ptr := Sloc (T);
1181 Comp_Type : constant Entity_Id := Component_Type (T);
1182 Index_Type : constant Entity_Id := Etype (First_Index (T));
1183 Proc : constant Entity_Id := Base_Init_Proc (T);
1184 Lo, Hi : Node_Id;
1185 Aggr : Node_Id;
1186 Expr : Node_Id;
1188 begin
1189 if not Is_Constrained (T)
1190 or else Number_Dimensions (T) > 1
1191 or else No (Proc)
1192 then
1193 Initialization_Warning (T);
1194 return Empty;
1195 end if;
1197 Lo := Type_Low_Bound (Index_Type);
1198 Hi := Type_High_Bound (Index_Type);
1200 if not Compile_Time_Known_Value (Lo)
1201 or else not Compile_Time_Known_Value (Hi)
1202 then
1203 Initialization_Warning (T);
1204 return Empty;
1205 end if;
1207 if Is_Record_Type (Comp_Type)
1208 and then Present (Base_Init_Proc (Comp_Type))
1209 then
1210 Expr := Static_Initialization (Base_Init_Proc (Comp_Type));
1212 if No (Expr) then
1213 Initialization_Warning (T);
1214 return Empty;
1215 end if;
1217 else
1218 Initialization_Warning (T);
1219 return Empty;
1220 end if;
1222 Aggr := Make_Aggregate (Loc, No_List, New_List);
1223 Set_Etype (Aggr, T);
1224 Set_Aggregate_Bounds (Aggr,
1225 Make_Range (Loc,
1226 Low_Bound => New_Copy (Lo),
1227 High_Bound => New_Copy (Hi)));
1228 Set_Parent (Aggr, Parent (Proc));
1230 Append_To (Component_Associations (Aggr),
1231 Make_Component_Association (Loc,
1232 Choices =>
1233 New_List (
1234 Make_Range (Loc,
1235 Low_Bound => New_Copy (Lo),
1236 High_Bound => New_Copy (Hi))),
1237 Expression => Expr));
1239 if Static_Array_Aggregate (Aggr) then
1240 return Aggr;
1241 else
1242 Initialization_Warning (T);
1243 return Empty;
1244 end if;
1245 end Build_Equivalent_Array_Aggregate;
1247 ---------------------------------------
1248 -- Build_Equivalent_Record_Aggregate --
1249 ---------------------------------------
1251 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id is
1252 Agg : Node_Id;
1253 Comp : Entity_Id;
1254 Comp_Type : Entity_Id;
1256 -- Start of processing for Build_Equivalent_Record_Aggregate
1258 begin
1259 if not Is_Record_Type (T)
1260 or else Has_Discriminants (T)
1261 or else Is_Limited_Type (T)
1262 or else Has_Non_Standard_Rep (T)
1263 then
1264 Initialization_Warning (T);
1265 return Empty;
1266 end if;
1268 Comp := First_Component (T);
1270 -- A null record needs no warning
1272 if No (Comp) then
1273 return Empty;
1274 end if;
1276 while Present (Comp) loop
1278 -- Array components are acceptable if initialized by a positional
1279 -- aggregate with static components.
1281 if Is_Array_Type (Etype (Comp)) then
1282 Comp_Type := Component_Type (Etype (Comp));
1284 if Nkind (Parent (Comp)) /= N_Component_Declaration
1285 or else No (Expression (Parent (Comp)))
1286 or else Nkind (Expression (Parent (Comp))) /= N_Aggregate
1287 then
1288 Initialization_Warning (T);
1289 return Empty;
1291 elsif Is_Scalar_Type (Component_Type (Etype (Comp)))
1292 and then
1293 (not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1294 or else
1295 not Compile_Time_Known_Value (Type_High_Bound (Comp_Type)))
1296 then
1297 Initialization_Warning (T);
1298 return Empty;
1300 elsif
1301 not Static_Array_Aggregate (Expression (Parent (Comp)))
1302 then
1303 Initialization_Warning (T);
1304 return Empty;
1305 end if;
1307 elsif Is_Scalar_Type (Etype (Comp)) then
1308 Comp_Type := Etype (Comp);
1310 if Nkind (Parent (Comp)) /= N_Component_Declaration
1311 or else No (Expression (Parent (Comp)))
1312 or else not Compile_Time_Known_Value (Expression (Parent (Comp)))
1313 or else not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1314 or else not
1315 Compile_Time_Known_Value (Type_High_Bound (Comp_Type))
1316 then
1317 Initialization_Warning (T);
1318 return Empty;
1319 end if;
1321 -- For now, other types are excluded
1323 else
1324 Initialization_Warning (T);
1325 return Empty;
1326 end if;
1328 Next_Component (Comp);
1329 end loop;
1331 -- All components have static initialization. Build positional aggregate
1332 -- from the given expressions or defaults.
1334 Agg := Make_Aggregate (Sloc (T), New_List, New_List);
1335 Set_Parent (Agg, Parent (T));
1337 Comp := First_Component (T);
1338 while Present (Comp) loop
1339 Append
1340 (New_Copy_Tree (Expression (Parent (Comp))), Expressions (Agg));
1341 Next_Component (Comp);
1342 end loop;
1344 Analyze_And_Resolve (Agg, T);
1345 return Agg;
1346 end Build_Equivalent_Record_Aggregate;
1348 -------------------------------
1349 -- Build_Initialization_Call --
1350 -------------------------------
1352 -- References to a discriminant inside the record type declaration can
1353 -- appear either in the subtype_indication to constrain a record or an
1354 -- array, or as part of a larger expression given for the initial value
1355 -- of a component. In both of these cases N appears in the record
1356 -- initialization procedure and needs to be replaced by the formal
1357 -- parameter of the initialization procedure which corresponds to that
1358 -- discriminant.
1360 -- In the example below, references to discriminants D1 and D2 in proc_1
1361 -- are replaced by references to formals with the same name
1362 -- (discriminals)
1364 -- A similar replacement is done for calls to any record initialization
1365 -- procedure for any components that are themselves of a record type.
1367 -- type R (D1, D2 : Integer) is record
1368 -- X : Integer := F * D1;
1369 -- Y : Integer := F * D2;
1370 -- end record;
1372 -- procedure proc_1 (Out_2 : out R; D1 : Integer; D2 : Integer) is
1373 -- begin
1374 -- Out_2.D1 := D1;
1375 -- Out_2.D2 := D2;
1376 -- Out_2.X := F * D1;
1377 -- Out_2.Y := F * D2;
1378 -- end;
1380 function Build_Initialization_Call
1381 (Loc : Source_Ptr;
1382 Id_Ref : Node_Id;
1383 Typ : Entity_Id;
1384 In_Init_Proc : Boolean := False;
1385 Enclos_Type : Entity_Id := Empty;
1386 Discr_Map : Elist_Id := New_Elmt_List;
1387 With_Default_Init : Boolean := False;
1388 Constructor_Ref : Node_Id := Empty) return List_Id
1390 Res : constant List_Id := New_List;
1391 Arg : Node_Id;
1392 Args : List_Id;
1393 Controller_Typ : Entity_Id;
1394 Decl : Node_Id;
1395 Decls : List_Id;
1396 Discr : Entity_Id;
1397 First_Arg : Node_Id;
1398 Full_Init_Type : Entity_Id;
1399 Full_Type : Entity_Id := Typ;
1400 Init_Type : Entity_Id;
1401 Proc : Entity_Id;
1403 begin
1404 pragma Assert (Constructor_Ref = Empty
1405 or else Is_CPP_Constructor_Call (Constructor_Ref));
1407 if No (Constructor_Ref) then
1408 Proc := Base_Init_Proc (Typ);
1409 else
1410 Proc := Base_Init_Proc (Typ, Entity (Name (Constructor_Ref)));
1411 end if;
1413 pragma Assert (Present (Proc));
1414 Init_Type := Etype (First_Formal (Proc));
1415 Full_Init_Type := Underlying_Type (Init_Type);
1417 -- Nothing to do if the Init_Proc is null, unless Initialize_Scalars
1418 -- is active (in which case we make the call anyway, since in the
1419 -- actual compiled client it may be non null).
1420 -- Also nothing to do for value types.
1422 if (Is_Null_Init_Proc (Proc) and then not Init_Or_Norm_Scalars)
1423 or else Is_Value_Type (Typ)
1424 or else
1425 (Is_Array_Type (Typ) and then Is_Value_Type (Component_Type (Typ)))
1426 then
1427 return Empty_List;
1428 end if;
1430 -- Go to full view if private type. In the case of successive
1431 -- private derivations, this can require more than one step.
1433 while Is_Private_Type (Full_Type)
1434 and then Present (Full_View (Full_Type))
1435 loop
1436 Full_Type := Full_View (Full_Type);
1437 end loop;
1439 -- If Typ is derived, the procedure is the initialization procedure for
1440 -- the root type. Wrap the argument in an conversion to make it type
1441 -- honest. Actually it isn't quite type honest, because there can be
1442 -- conflicts of views in the private type case. That is why we set
1443 -- Conversion_OK in the conversion node.
1445 if (Is_Record_Type (Typ)
1446 or else Is_Array_Type (Typ)
1447 or else Is_Private_Type (Typ))
1448 and then Init_Type /= Base_Type (Typ)
1449 then
1450 First_Arg := OK_Convert_To (Etype (Init_Type), Id_Ref);
1451 Set_Etype (First_Arg, Init_Type);
1453 else
1454 First_Arg := Id_Ref;
1455 end if;
1457 Args := New_List (Convert_Concurrent (First_Arg, Typ));
1459 -- In the tasks case, add _Master as the value of the _Master parameter
1460 -- and _Chain as the value of the _Chain parameter. At the outer level,
1461 -- these will be variables holding the corresponding values obtained
1462 -- from GNARL. At inner levels, they will be the parameters passed down
1463 -- through the outer routines.
1465 if Has_Task (Full_Type) then
1466 if Restriction_Active (No_Task_Hierarchy) then
1468 -- 3 is System.Tasking.Library_Task_Level
1469 -- (should be rtsfindable constant ???)
1471 Append_To (Args, Make_Integer_Literal (Loc, 3));
1473 else
1474 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1475 end if;
1477 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1479 -- Ada 2005 (AI-287): In case of default initialized components
1480 -- with tasks, we generate a null string actual parameter.
1481 -- This is just a workaround that must be improved later???
1483 if With_Default_Init then
1484 Append_To (Args,
1485 Make_String_Literal (Loc,
1486 Strval => ""));
1488 else
1489 Decls :=
1490 Build_Task_Image_Decls (Loc, Id_Ref, Enclos_Type, In_Init_Proc);
1491 Decl := Last (Decls);
1493 Append_To (Args,
1494 New_Occurrence_Of (Defining_Identifier (Decl), Loc));
1495 Append_List (Decls, Res);
1496 end if;
1498 else
1499 Decls := No_List;
1500 Decl := Empty;
1501 end if;
1503 -- Add discriminant values if discriminants are present
1505 if Has_Discriminants (Full_Init_Type) then
1506 Discr := First_Discriminant (Full_Init_Type);
1508 while Present (Discr) loop
1510 -- If this is a discriminated concurrent type, the init_proc
1511 -- for the corresponding record is being called. Use that type
1512 -- directly to find the discriminant value, to handle properly
1513 -- intervening renamed discriminants.
1515 declare
1516 T : Entity_Id := Full_Type;
1518 begin
1519 if Is_Protected_Type (T) then
1520 T := Corresponding_Record_Type (T);
1522 elsif Is_Private_Type (T)
1523 and then Present (Underlying_Full_View (T))
1524 and then Is_Protected_Type (Underlying_Full_View (T))
1525 then
1526 T := Corresponding_Record_Type (Underlying_Full_View (T));
1527 end if;
1529 Arg :=
1530 Get_Discriminant_Value (
1531 Discr,
1533 Discriminant_Constraint (Full_Type));
1534 end;
1536 if In_Init_Proc then
1538 -- Replace any possible references to the discriminant in the
1539 -- call to the record initialization procedure with references
1540 -- to the appropriate formal parameter.
1542 if Nkind (Arg) = N_Identifier
1543 and then Ekind (Entity (Arg)) = E_Discriminant
1544 then
1545 Arg := New_Reference_To (Discriminal (Entity (Arg)), Loc);
1547 -- Case of access discriminants. We replace the reference
1548 -- to the type by a reference to the actual object
1550 elsif Nkind (Arg) = N_Attribute_Reference
1551 and then Is_Access_Type (Etype (Arg))
1552 and then Is_Entity_Name (Prefix (Arg))
1553 and then Is_Type (Entity (Prefix (Arg)))
1554 then
1555 Arg :=
1556 Make_Attribute_Reference (Loc,
1557 Prefix => New_Copy (Prefix (Id_Ref)),
1558 Attribute_Name => Name_Unrestricted_Access);
1560 -- Otherwise make a copy of the default expression. Note that
1561 -- we use the current Sloc for this, because we do not want the
1562 -- call to appear to be at the declaration point. Within the
1563 -- expression, replace discriminants with their discriminals.
1565 else
1566 Arg :=
1567 New_Copy_Tree (Arg, Map => Discr_Map, New_Sloc => Loc);
1568 end if;
1570 else
1571 if Is_Constrained (Full_Type) then
1572 Arg := Duplicate_Subexpr_No_Checks (Arg);
1573 else
1574 -- The constraints come from the discriminant default exps,
1575 -- they must be reevaluated, so we use New_Copy_Tree but we
1576 -- ensure the proper Sloc (for any embedded calls).
1578 Arg := New_Copy_Tree (Arg, New_Sloc => Loc);
1579 end if;
1580 end if;
1582 -- Ada 2005 (AI-287): In case of default initialized components,
1583 -- if the component is constrained with a discriminant of the
1584 -- enclosing type, we need to generate the corresponding selected
1585 -- component node to access the discriminant value. In other cases
1586 -- this is not required, either because we are inside the init
1587 -- proc and we use the corresponding formal, or else because the
1588 -- component is constrained by an expression.
1590 if With_Default_Init
1591 and then Nkind (Id_Ref) = N_Selected_Component
1592 and then Nkind (Arg) = N_Identifier
1593 and then Ekind (Entity (Arg)) = E_Discriminant
1594 then
1595 Append_To (Args,
1596 Make_Selected_Component (Loc,
1597 Prefix => New_Copy_Tree (Prefix (Id_Ref)),
1598 Selector_Name => Arg));
1599 else
1600 Append_To (Args, Arg);
1601 end if;
1603 Next_Discriminant (Discr);
1604 end loop;
1605 end if;
1607 -- If this is a call to initialize the parent component of a derived
1608 -- tagged type, indicate that the tag should not be set in the parent.
1610 if Is_Tagged_Type (Full_Init_Type)
1611 and then not Is_CPP_Class (Full_Init_Type)
1612 and then Nkind (Id_Ref) = N_Selected_Component
1613 and then Chars (Selector_Name (Id_Ref)) = Name_uParent
1614 then
1615 Append_To (Args, New_Occurrence_Of (Standard_False, Loc));
1617 elsif Present (Constructor_Ref) then
1618 Append_List_To (Args,
1619 New_Copy_List (Parameter_Associations (Constructor_Ref)));
1620 end if;
1622 Append_To (Res,
1623 Make_Procedure_Call_Statement (Loc,
1624 Name => New_Occurrence_Of (Proc, Loc),
1625 Parameter_Associations => Args));
1627 if Needs_Finalization (Typ)
1628 and then Nkind (Id_Ref) = N_Selected_Component
1629 then
1630 if Chars (Selector_Name (Id_Ref)) /= Name_uParent then
1631 Append_List_To (Res,
1632 Make_Init_Call (
1633 Ref => New_Copy_Tree (First_Arg),
1634 Typ => Typ,
1635 Flist_Ref =>
1636 Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1637 With_Attach => Make_Integer_Literal (Loc, 1)));
1639 -- If the enclosing type is an extension with new controlled
1640 -- components, it has his own record controller. If the parent
1641 -- also had a record controller, attach it to the new one.
1643 -- Build_Init_Statements relies on the fact that in this specific
1644 -- case the last statement of the result is the attach call to
1645 -- the controller. If this is changed, it must be synchronized.
1647 elsif Present (Enclos_Type)
1648 and then Has_New_Controlled_Component (Enclos_Type)
1649 and then Has_Controlled_Component (Typ)
1650 then
1651 if Is_Inherently_Limited_Type (Typ) then
1652 Controller_Typ := RTE (RE_Limited_Record_Controller);
1653 else
1654 Controller_Typ := RTE (RE_Record_Controller);
1655 end if;
1657 Append_List_To (Res,
1658 Make_Init_Call (
1659 Ref =>
1660 Make_Selected_Component (Loc,
1661 Prefix => New_Copy_Tree (First_Arg),
1662 Selector_Name => Make_Identifier (Loc, Name_uController)),
1663 Typ => Controller_Typ,
1664 Flist_Ref => Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1665 With_Attach => Make_Integer_Literal (Loc, 1)));
1666 end if;
1667 end if;
1669 return Res;
1671 exception
1672 when RE_Not_Available =>
1673 return Empty_List;
1674 end Build_Initialization_Call;
1676 ---------------------------
1677 -- Build_Master_Renaming --
1678 ---------------------------
1680 function Build_Master_Renaming
1681 (N : Node_Id;
1682 T : Entity_Id) return Entity_Id
1684 Loc : constant Source_Ptr := Sloc (N);
1685 M_Id : Entity_Id;
1686 Decl : Node_Id;
1688 begin
1689 -- Nothing to do if there is no task hierarchy
1691 if Restriction_Active (No_Task_Hierarchy) then
1692 return Empty;
1693 end if;
1695 M_Id :=
1696 Make_Defining_Identifier (Loc,
1697 New_External_Name (Chars (T), 'M'));
1699 Decl :=
1700 Make_Object_Renaming_Declaration (Loc,
1701 Defining_Identifier => M_Id,
1702 Subtype_Mark => New_Reference_To (RTE (RE_Master_Id), Loc),
1703 Name => Make_Identifier (Loc, Name_uMaster));
1704 Insert_Before (N, Decl);
1705 Analyze (Decl);
1706 return M_Id;
1708 exception
1709 when RE_Not_Available =>
1710 return Empty;
1711 end Build_Master_Renaming;
1713 ---------------------------
1714 -- Build_Master_Renaming --
1715 ---------------------------
1717 procedure Build_Master_Renaming (N : Node_Id; T : Entity_Id) is
1718 M_Id : Entity_Id;
1720 begin
1721 -- Nothing to do if there is no task hierarchy
1723 if Restriction_Active (No_Task_Hierarchy) then
1724 return;
1725 end if;
1727 M_Id := Build_Master_Renaming (N, T);
1728 Set_Master_Id (T, M_Id);
1730 exception
1731 when RE_Not_Available =>
1732 return;
1733 end Build_Master_Renaming;
1735 ----------------------------
1736 -- Build_Record_Init_Proc --
1737 ----------------------------
1739 procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id) is
1740 Loc : Source_Ptr := Sloc (N);
1741 Discr_Map : constant Elist_Id := New_Elmt_List;
1742 Proc_Id : Entity_Id;
1743 Rec_Type : Entity_Id;
1744 Set_Tag : Entity_Id := Empty;
1746 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id;
1747 -- Build a assignment statement node which assigns to record component
1748 -- its default expression if defined. The assignment left hand side is
1749 -- marked Assignment_OK so that initialization of limited private
1750 -- records works correctly, Return also the adjustment call for
1751 -- controlled objects
1753 procedure Build_Discriminant_Assignments (Statement_List : List_Id);
1754 -- If the record has discriminants, adds assignment statements to
1755 -- statement list to initialize the discriminant values from the
1756 -- arguments of the initialization procedure.
1758 function Build_Init_Statements (Comp_List : Node_Id) return List_Id;
1759 -- Build a list representing a sequence of statements which initialize
1760 -- components of the given component list. This may involve building
1761 -- case statements for the variant parts.
1763 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id;
1764 -- Given a non-tagged type-derivation that declares discriminants,
1765 -- such as
1767 -- type R (R1, R2 : Integer) is record ... end record;
1769 -- type D (D1 : Integer) is new R (1, D1);
1771 -- we make the _init_proc of D be
1773 -- procedure _init_proc(X : D; D1 : Integer) is
1774 -- begin
1775 -- _init_proc( R(X), 1, D1);
1776 -- end _init_proc;
1778 -- This function builds the call statement in this _init_proc.
1780 procedure Build_Init_Procedure;
1781 -- Build the tree corresponding to the procedure specification and body
1782 -- of the initialization procedure (by calling all the preceding
1783 -- auxiliary routines), and install it as the _init TSS.
1785 procedure Build_Offset_To_Top_Functions;
1786 -- Ada 2005 (AI-251): Build the tree corresponding to the procedure spec
1787 -- and body of the Offset_To_Top function that is generated when the
1788 -- parent of a type with discriminants has secondary dispatch tables.
1790 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id);
1791 -- Add range checks to components of discriminated records. S is a
1792 -- subtype indication of a record component. Check_List is a list
1793 -- to which the check actions are appended.
1795 function Component_Needs_Simple_Initialization
1796 (T : Entity_Id) return Boolean;
1797 -- Determines if a component needs simple initialization, given its type
1798 -- T. This is the same as Needs_Simple_Initialization except for the
1799 -- following difference: the types Tag and Interface_Tag, that are
1800 -- access types which would normally require simple initialization to
1801 -- null, do not require initialization as components, since they are
1802 -- explicitly initialized by other means.
1804 procedure Constrain_Array
1805 (SI : Node_Id;
1806 Check_List : List_Id);
1807 -- Called from Build_Record_Checks.
1808 -- Apply a list of index constraints to an unconstrained array type.
1809 -- The first parameter is the entity for the resulting subtype.
1810 -- Check_List is a list to which the check actions are appended.
1812 procedure Constrain_Index
1813 (Index : Node_Id;
1814 S : Node_Id;
1815 Check_List : List_Id);
1816 -- Process an index constraint in a constrained array declaration.
1817 -- The constraint can be a subtype name, or a range with or without
1818 -- an explicit subtype mark. The index is the corresponding index of the
1819 -- unconstrained array. S is the range expression. Check_List is a list
1820 -- to which the check actions are appended (called from
1821 -- Build_Record_Checks).
1823 function Parent_Subtype_Renaming_Discrims return Boolean;
1824 -- Returns True for base types N that rename discriminants, else False
1826 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean;
1827 -- Determines whether a record initialization procedure needs to be
1828 -- generated for the given record type.
1830 ----------------------
1831 -- Build_Assignment --
1832 ----------------------
1834 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id is
1835 Exp : Node_Id := N;
1836 Lhs : Node_Id;
1837 Typ : constant Entity_Id := Underlying_Type (Etype (Id));
1838 Kind : Node_Kind := Nkind (N);
1839 Res : List_Id;
1841 begin
1842 Loc := Sloc (N);
1843 Lhs :=
1844 Make_Selected_Component (Loc,
1845 Prefix => Make_Identifier (Loc, Name_uInit),
1846 Selector_Name => New_Occurrence_Of (Id, Loc));
1847 Set_Assignment_OK (Lhs);
1849 -- Case of an access attribute applied to the current instance.
1850 -- Replace the reference to the type by a reference to the actual
1851 -- object. (Note that this handles the case of the top level of
1852 -- the expression being given by such an attribute, but does not
1853 -- cover uses nested within an initial value expression. Nested
1854 -- uses are unlikely to occur in practice, but are theoretically
1855 -- possible. It is not clear how to handle them without fully
1856 -- traversing the expression. ???
1858 if Kind = N_Attribute_Reference
1859 and then (Attribute_Name (N) = Name_Unchecked_Access
1860 or else
1861 Attribute_Name (N) = Name_Unrestricted_Access)
1862 and then Is_Entity_Name (Prefix (N))
1863 and then Is_Type (Entity (Prefix (N)))
1864 and then Entity (Prefix (N)) = Rec_Type
1865 then
1866 Exp :=
1867 Make_Attribute_Reference (Loc,
1868 Prefix => Make_Identifier (Loc, Name_uInit),
1869 Attribute_Name => Name_Unrestricted_Access);
1870 end if;
1872 -- Take a copy of Exp to ensure that later copies of this component
1873 -- declaration in derived types see the original tree, not a node
1874 -- rewritten during expansion of the init_proc. If the copy contains
1875 -- itypes, the scope of the new itypes is the init_proc being built.
1877 Exp := New_Copy_Tree (Exp, New_Scope => Proc_Id);
1879 Res := New_List (
1880 Make_Assignment_Statement (Loc,
1881 Name => Lhs,
1882 Expression => Exp));
1884 Set_No_Ctrl_Actions (First (Res));
1886 -- Adjust the tag if tagged (because of possible view conversions).
1887 -- Suppress the tag adjustment when VM_Target because VM tags are
1888 -- represented implicitly in objects.
1890 if Is_Tagged_Type (Typ) and then Tagged_Type_Expansion then
1891 Append_To (Res,
1892 Make_Assignment_Statement (Loc,
1893 Name =>
1894 Make_Selected_Component (Loc,
1895 Prefix => New_Copy_Tree (Lhs, New_Scope => Proc_Id),
1896 Selector_Name =>
1897 New_Reference_To (First_Tag_Component (Typ), Loc)),
1899 Expression =>
1900 Unchecked_Convert_To (RTE (RE_Tag),
1901 New_Reference_To
1902 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc))));
1903 end if;
1905 -- Adjust the component if controlled except if it is an aggregate
1906 -- that will be expanded inline.
1908 if Kind = N_Qualified_Expression then
1909 Kind := Nkind (Expression (N));
1910 end if;
1912 if Needs_Finalization (Typ)
1913 and then not (Nkind_In (Kind, N_Aggregate, N_Extension_Aggregate))
1914 and then not Is_Inherently_Limited_Type (Typ)
1915 then
1916 declare
1917 Ref : constant Node_Id :=
1918 New_Copy_Tree (Lhs, New_Scope => Proc_Id);
1919 begin
1920 Append_List_To (Res,
1921 Make_Adjust_Call (
1922 Ref => Ref,
1923 Typ => Etype (Id),
1924 Flist_Ref => Find_Final_List (Etype (Id), Ref),
1925 With_Attach => Make_Integer_Literal (Loc, 1)));
1926 end;
1927 end if;
1929 return Res;
1931 exception
1932 when RE_Not_Available =>
1933 return Empty_List;
1934 end Build_Assignment;
1936 ------------------------------------
1937 -- Build_Discriminant_Assignments --
1938 ------------------------------------
1940 procedure Build_Discriminant_Assignments (Statement_List : List_Id) is
1941 D : Entity_Id;
1942 Is_Tagged : constant Boolean := Is_Tagged_Type (Rec_Type);
1944 begin
1945 if Has_Discriminants (Rec_Type)
1946 and then not Is_Unchecked_Union (Rec_Type)
1947 then
1948 D := First_Discriminant (Rec_Type);
1950 while Present (D) loop
1952 -- Don't generate the assignment for discriminants in derived
1953 -- tagged types if the discriminant is a renaming of some
1954 -- ancestor discriminant. This initialization will be done
1955 -- when initializing the _parent field of the derived record.
1957 if Is_Tagged and then
1958 Present (Corresponding_Discriminant (D))
1959 then
1960 null;
1962 else
1963 Loc := Sloc (D);
1964 Append_List_To (Statement_List,
1965 Build_Assignment (D,
1966 New_Reference_To (Discriminal (D), Loc)));
1967 end if;
1969 Next_Discriminant (D);
1970 end loop;
1971 end if;
1972 end Build_Discriminant_Assignments;
1974 --------------------------
1975 -- Build_Init_Call_Thru --
1976 --------------------------
1978 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id is
1979 Parent_Proc : constant Entity_Id :=
1980 Base_Init_Proc (Etype (Rec_Type));
1982 Parent_Type : constant Entity_Id :=
1983 Etype (First_Formal (Parent_Proc));
1985 Uparent_Type : constant Entity_Id :=
1986 Underlying_Type (Parent_Type);
1988 First_Discr_Param : Node_Id;
1990 Parent_Discr : Entity_Id;
1991 First_Arg : Node_Id;
1992 Args : List_Id;
1993 Arg : Node_Id;
1994 Res : List_Id;
1996 begin
1997 -- First argument (_Init) is the object to be initialized.
1998 -- ??? not sure where to get a reasonable Loc for First_Arg
2000 First_Arg :=
2001 OK_Convert_To (Parent_Type,
2002 New_Reference_To (Defining_Identifier (First (Parameters)), Loc));
2004 Set_Etype (First_Arg, Parent_Type);
2006 Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
2008 -- In the tasks case,
2009 -- add _Master as the value of the _Master parameter
2010 -- add _Chain as the value of the _Chain parameter.
2011 -- add _Task_Name as the value of the _Task_Name parameter.
2012 -- At the outer level, these will be variables holding the
2013 -- corresponding values obtained from GNARL or the expander.
2015 -- At inner levels, they will be the parameters passed down through
2016 -- the outer routines.
2018 First_Discr_Param := Next (First (Parameters));
2020 if Has_Task (Rec_Type) then
2021 if Restriction_Active (No_Task_Hierarchy) then
2023 -- 3 is System.Tasking.Library_Task_Level
2025 Append_To (Args, Make_Integer_Literal (Loc, 3));
2026 else
2027 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
2028 end if;
2030 Append_To (Args, Make_Identifier (Loc, Name_uChain));
2031 Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
2032 First_Discr_Param := Next (Next (Next (First_Discr_Param)));
2033 end if;
2035 -- Append discriminant values
2037 if Has_Discriminants (Uparent_Type) then
2038 pragma Assert (not Is_Tagged_Type (Uparent_Type));
2040 Parent_Discr := First_Discriminant (Uparent_Type);
2041 while Present (Parent_Discr) loop
2043 -- Get the initial value for this discriminant
2044 -- ??? needs to be cleaned up to use parent_Discr_Constr
2045 -- directly.
2047 declare
2048 Discr_Value : Elmt_Id :=
2049 First_Elmt
2050 (Stored_Constraint (Rec_Type));
2052 Discr : Entity_Id :=
2053 First_Stored_Discriminant (Uparent_Type);
2054 begin
2055 while Original_Record_Component (Parent_Discr) /= Discr loop
2056 Next_Stored_Discriminant (Discr);
2057 Next_Elmt (Discr_Value);
2058 end loop;
2060 Arg := Node (Discr_Value);
2061 end;
2063 -- Append it to the list
2065 if Nkind (Arg) = N_Identifier
2066 and then Ekind (Entity (Arg)) = E_Discriminant
2067 then
2068 Append_To (Args,
2069 New_Reference_To (Discriminal (Entity (Arg)), Loc));
2071 -- Case of access discriminants. We replace the reference
2072 -- to the type by a reference to the actual object.
2074 -- Is above comment right??? Use of New_Copy below seems mighty
2075 -- suspicious ???
2077 else
2078 Append_To (Args, New_Copy (Arg));
2079 end if;
2081 Next_Discriminant (Parent_Discr);
2082 end loop;
2083 end if;
2085 Res :=
2086 New_List (
2087 Make_Procedure_Call_Statement (Loc,
2088 Name => New_Occurrence_Of (Parent_Proc, Loc),
2089 Parameter_Associations => Args));
2091 return Res;
2092 end Build_Init_Call_Thru;
2094 -----------------------------------
2095 -- Build_Offset_To_Top_Functions --
2096 -----------------------------------
2098 procedure Build_Offset_To_Top_Functions is
2100 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id);
2101 -- Generate:
2102 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2103 -- begin
2104 -- return O.Iface_Comp'Position;
2105 -- end Fxx;
2107 ----------------------------------
2108 -- Build_Offset_To_Top_Function --
2109 ----------------------------------
2111 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id) is
2112 Body_Node : Node_Id;
2113 Func_Id : Entity_Id;
2114 Spec_Node : Node_Id;
2116 begin
2117 Func_Id := Make_Temporary (Loc, 'F');
2118 Set_DT_Offset_To_Top_Func (Iface_Comp, Func_Id);
2120 -- Generate
2121 -- function Fxx (O : in Rec_Typ) return Storage_Offset;
2123 Spec_Node := New_Node (N_Function_Specification, Loc);
2124 Set_Defining_Unit_Name (Spec_Node, Func_Id);
2125 Set_Parameter_Specifications (Spec_Node, New_List (
2126 Make_Parameter_Specification (Loc,
2127 Defining_Identifier => Make_Defining_Identifier (Loc, Name_uO),
2128 In_Present => True,
2129 Parameter_Type => New_Reference_To (Rec_Type, Loc))));
2130 Set_Result_Definition (Spec_Node,
2131 New_Reference_To (RTE (RE_Storage_Offset), Loc));
2133 -- Generate
2134 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2135 -- begin
2136 -- return O.Iface_Comp'Position;
2137 -- end Fxx;
2139 Body_Node := New_Node (N_Subprogram_Body, Loc);
2140 Set_Specification (Body_Node, Spec_Node);
2141 Set_Declarations (Body_Node, New_List);
2142 Set_Handled_Statement_Sequence (Body_Node,
2143 Make_Handled_Sequence_Of_Statements (Loc,
2144 Statements => New_List (
2145 Make_Simple_Return_Statement (Loc,
2146 Expression =>
2147 Make_Attribute_Reference (Loc,
2148 Prefix =>
2149 Make_Selected_Component (Loc,
2150 Prefix => Make_Identifier (Loc, Name_uO),
2151 Selector_Name => New_Reference_To
2152 (Iface_Comp, Loc)),
2153 Attribute_Name => Name_Position)))));
2155 Set_Ekind (Func_Id, E_Function);
2156 Set_Mechanism (Func_Id, Default_Mechanism);
2157 Set_Is_Internal (Func_Id, True);
2159 if not Debug_Generated_Code then
2160 Set_Debug_Info_Off (Func_Id);
2161 end if;
2163 Analyze (Body_Node);
2165 Append_Freeze_Action (Rec_Type, Body_Node);
2166 end Build_Offset_To_Top_Function;
2168 -- Local variables
2170 Ifaces_Comp_List : Elist_Id;
2171 Iface_Comp_Elmt : Elmt_Id;
2172 Iface_Comp : Node_Id;
2174 -- Start of processing for Build_Offset_To_Top_Functions
2176 begin
2177 -- Offset_To_Top_Functions are built only for derivations of types
2178 -- with discriminants that cover interface types.
2179 -- Nothing is needed either in case of virtual machines, since
2180 -- interfaces are handled directly by the VM.
2182 if not Is_Tagged_Type (Rec_Type)
2183 or else Etype (Rec_Type) = Rec_Type
2184 or else not Has_Discriminants (Etype (Rec_Type))
2185 or else not Tagged_Type_Expansion
2186 then
2187 return;
2188 end if;
2190 Collect_Interface_Components (Rec_Type, Ifaces_Comp_List);
2192 -- For each interface type with secondary dispatch table we generate
2193 -- the Offset_To_Top_Functions (required to displace the pointer in
2194 -- interface conversions)
2196 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
2197 while Present (Iface_Comp_Elmt) loop
2198 Iface_Comp := Node (Iface_Comp_Elmt);
2199 pragma Assert (Is_Interface (Related_Type (Iface_Comp)));
2201 -- If the interface is a parent of Rec_Type it shares the primary
2202 -- dispatch table and hence there is no need to build the function
2204 if not Is_Ancestor (Related_Type (Iface_Comp), Rec_Type) then
2205 Build_Offset_To_Top_Function (Iface_Comp);
2206 end if;
2208 Next_Elmt (Iface_Comp_Elmt);
2209 end loop;
2210 end Build_Offset_To_Top_Functions;
2212 --------------------------
2213 -- Build_Init_Procedure --
2214 --------------------------
2216 procedure Build_Init_Procedure is
2217 Body_Node : Node_Id;
2218 Handled_Stmt_Node : Node_Id;
2219 Parameters : List_Id;
2220 Proc_Spec_Node : Node_Id;
2221 Body_Stmts : List_Id;
2222 Record_Extension_Node : Node_Id;
2223 Init_Tags_List : List_Id;
2225 begin
2226 Body_Stmts := New_List;
2227 Body_Node := New_Node (N_Subprogram_Body, Loc);
2228 Set_Ekind (Proc_Id, E_Procedure);
2230 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2231 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2233 Parameters := Init_Formals (Rec_Type);
2234 Append_List_To (Parameters,
2235 Build_Discriminant_Formals (Rec_Type, True));
2237 -- For tagged types, we add a flag to indicate whether the routine
2238 -- is called to initialize a parent component in the init_proc of
2239 -- a type extension. If the flag is false, we do not set the tag
2240 -- because it has been set already in the extension.
2242 if Is_Tagged_Type (Rec_Type)
2243 and then not Is_CPP_Class (Rec_Type)
2244 then
2245 Set_Tag := Make_Temporary (Loc, 'P');
2247 Append_To (Parameters,
2248 Make_Parameter_Specification (Loc,
2249 Defining_Identifier => Set_Tag,
2250 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
2251 Expression => New_Occurrence_Of (Standard_True, Loc)));
2252 end if;
2254 Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
2255 Set_Specification (Body_Node, Proc_Spec_Node);
2256 Set_Declarations (Body_Node, New_List);
2258 if Parent_Subtype_Renaming_Discrims then
2260 -- N is a Derived_Type_Definition that renames the parameters
2261 -- of the ancestor type. We initialize it by expanding our
2262 -- discriminants and call the ancestor _init_proc with a
2263 -- type-converted object
2265 Append_List_To (Body_Stmts,
2266 Build_Init_Call_Thru (Parameters));
2268 elsif Nkind (Type_Definition (N)) = N_Record_Definition then
2269 Build_Discriminant_Assignments (Body_Stmts);
2271 if not Null_Present (Type_Definition (N)) then
2272 Append_List_To (Body_Stmts,
2273 Build_Init_Statements (
2274 Component_List (Type_Definition (N))));
2275 end if;
2277 else
2278 -- N is a Derived_Type_Definition with a possible non-empty
2279 -- extension. The initialization of a type extension consists
2280 -- in the initialization of the components in the extension.
2282 Build_Discriminant_Assignments (Body_Stmts);
2284 Record_Extension_Node :=
2285 Record_Extension_Part (Type_Definition (N));
2287 if not Null_Present (Record_Extension_Node) then
2288 declare
2289 Stmts : constant List_Id :=
2290 Build_Init_Statements (
2291 Component_List (Record_Extension_Node));
2293 begin
2294 -- The parent field must be initialized first because
2295 -- the offset of the new discriminants may depend on it
2297 Prepend_To (Body_Stmts, Remove_Head (Stmts));
2298 Append_List_To (Body_Stmts, Stmts);
2299 end;
2300 end if;
2301 end if;
2303 -- Add here the assignment to instantiate the Tag
2305 -- The assignment corresponds to the code:
2307 -- _Init._Tag := Typ'Tag;
2309 -- Suppress the tag assignment when VM_Target because VM tags are
2310 -- represented implicitly in objects. It is also suppressed in case
2311 -- of CPP_Class types because in this case the tag is initialized in
2312 -- the C++ side.
2314 if Is_Tagged_Type (Rec_Type)
2315 and then not Is_CPP_Class (Rec_Type)
2316 and then Tagged_Type_Expansion
2317 and then not No_Run_Time_Mode
2318 then
2319 -- Initialize the primary tag
2321 Init_Tags_List := New_List (
2322 Make_Assignment_Statement (Loc,
2323 Name =>
2324 Make_Selected_Component (Loc,
2325 Prefix => Make_Identifier (Loc, Name_uInit),
2326 Selector_Name =>
2327 New_Reference_To (First_Tag_Component (Rec_Type), Loc)),
2329 Expression =>
2330 New_Reference_To
2331 (Node (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2333 -- Ada 2005 (AI-251): Initialize the secondary tags components
2334 -- located at fixed positions (tags whose position depends on
2335 -- variable size components are initialized later ---see below).
2337 if Ada_Version >= Ada_05
2338 and then not Is_Interface (Rec_Type)
2339 and then Has_Interfaces (Rec_Type)
2340 then
2341 Init_Secondary_Tags
2342 (Typ => Rec_Type,
2343 Target => Make_Identifier (Loc, Name_uInit),
2344 Stmts_List => Init_Tags_List,
2345 Fixed_Comps => True,
2346 Variable_Comps => False);
2347 end if;
2349 -- The tag must be inserted before the assignments to other
2350 -- components, because the initial value of the component may
2351 -- depend on the tag (eg. through a dispatching operation on
2352 -- an access to the current type). The tag assignment is not done
2353 -- when initializing the parent component of a type extension,
2354 -- because in that case the tag is set in the extension.
2356 -- Extensions of imported C++ classes add a final complication,
2357 -- because we cannot inhibit tag setting in the constructor for
2358 -- the parent. In that case we insert the tag initialization
2359 -- after the calls to initialize the parent.
2361 if not Is_CPP_Class (Root_Type (Rec_Type)) then
2362 Prepend_To (Body_Stmts,
2363 Make_If_Statement (Loc,
2364 Condition => New_Occurrence_Of (Set_Tag, Loc),
2365 Then_Statements => Init_Tags_List));
2367 -- CPP_Class derivation: In this case the dispatch table of the
2368 -- parent was built in the C++ side and we copy the table of the
2369 -- parent to initialize the new dispatch table.
2371 else
2372 declare
2373 Nod : Node_Id;
2375 begin
2376 -- We assume the first init_proc call is for the parent
2378 Nod := First (Body_Stmts);
2379 while Present (Next (Nod))
2380 and then (Nkind (Nod) /= N_Procedure_Call_Statement
2381 or else not Is_Init_Proc (Name (Nod)))
2382 loop
2383 Nod := Next (Nod);
2384 end loop;
2386 -- Generate:
2387 -- ancestor_constructor (_init.parent);
2388 -- if Arg2 then
2389 -- inherit_prim_ops (_init._tag, new_dt, num_prims);
2390 -- _init._tag := new_dt;
2391 -- end if;
2393 Prepend_To (Init_Tags_List,
2394 Build_Inherit_Prims (Loc,
2395 Typ => Rec_Type,
2396 Old_Tag_Node =>
2397 Make_Selected_Component (Loc,
2398 Prefix =>
2399 Make_Identifier (Loc,
2400 Chars => Name_uInit),
2401 Selector_Name =>
2402 New_Reference_To
2403 (First_Tag_Component (Rec_Type), Loc)),
2404 New_Tag_Node =>
2405 New_Reference_To
2406 (Node (First_Elmt (Access_Disp_Table (Rec_Type))),
2407 Loc),
2408 Num_Prims =>
2409 UI_To_Int
2410 (DT_Entry_Count (First_Tag_Component (Rec_Type)))));
2412 Insert_After (Nod,
2413 Make_If_Statement (Loc,
2414 Condition => New_Occurrence_Of (Set_Tag, Loc),
2415 Then_Statements => Init_Tags_List));
2417 -- We have inherited table of the parent from the CPP side.
2418 -- Now we fill the slots associated with Ada primitives.
2419 -- This needs more work to avoid its execution each time
2420 -- an object is initialized???
2422 declare
2423 E : Elmt_Id;
2424 Prim : Node_Id;
2426 begin
2427 E := First_Elmt (Primitive_Operations (Rec_Type));
2428 while Present (E) loop
2429 Prim := Node (E);
2431 if not Is_Imported (Prim)
2432 and then Convention (Prim) = Convention_CPP
2433 and then not Present (Interface_Alias (Prim))
2434 then
2435 Append_List_To (Init_Tags_List,
2436 Register_Primitive (Loc, Prim => Prim));
2437 end if;
2439 Next_Elmt (E);
2440 end loop;
2441 end;
2442 end;
2443 end if;
2445 -- Ada 2005 (AI-251): Initialize the secondary tag components
2446 -- located at variable positions. We delay the generation of this
2447 -- code until here because the value of the attribute 'Position
2448 -- applied to variable size components of the parent type that
2449 -- depend on discriminants is only safely read at runtime after
2450 -- the parent components have been initialized.
2452 if Ada_Version >= Ada_05
2453 and then not Is_Interface (Rec_Type)
2454 and then Has_Interfaces (Rec_Type)
2455 and then Has_Discriminants (Etype (Rec_Type))
2456 and then Is_Variable_Size_Record (Etype (Rec_Type))
2457 then
2458 Init_Tags_List := New_List;
2460 Init_Secondary_Tags
2461 (Typ => Rec_Type,
2462 Target => Make_Identifier (Loc, Name_uInit),
2463 Stmts_List => Init_Tags_List,
2464 Fixed_Comps => False,
2465 Variable_Comps => True);
2467 if Is_Non_Empty_List (Init_Tags_List) then
2468 Append_List_To (Body_Stmts, Init_Tags_List);
2469 end if;
2470 end if;
2471 end if;
2473 Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
2474 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2475 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2476 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2478 if not Debug_Generated_Code then
2479 Set_Debug_Info_Off (Proc_Id);
2480 end if;
2482 -- Associate Init_Proc with type, and determine if the procedure
2483 -- is null (happens because of the Initialize_Scalars pragma case,
2484 -- where we have to generate a null procedure in case it is called
2485 -- by a client with Initialize_Scalars set). Such procedures have
2486 -- to be generated, but do not have to be called, so we mark them
2487 -- as null to suppress the call.
2489 Set_Init_Proc (Rec_Type, Proc_Id);
2491 if List_Length (Body_Stmts) = 1
2493 -- We must skip SCIL nodes because they may have been added to this
2494 -- list by Insert_Actions.
2496 and then Nkind (First_Non_SCIL_Node (Body_Stmts)) = N_Null_Statement
2497 and then VM_Target = No_VM
2498 then
2499 -- Even though the init proc may be null at this time it might get
2500 -- some stuff added to it later by the VM backend.
2502 Set_Is_Null_Init_Proc (Proc_Id);
2503 end if;
2504 end Build_Init_Procedure;
2506 ---------------------------
2507 -- Build_Init_Statements --
2508 ---------------------------
2510 function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
2511 Check_List : constant List_Id := New_List;
2512 Alt_List : List_Id;
2513 Decl : Node_Id;
2514 Id : Entity_Id;
2515 Names : Node_Id;
2516 Statement_List : List_Id;
2517 Stmts : List_Id;
2518 Typ : Entity_Id;
2519 Variant : Node_Id;
2521 Per_Object_Constraint_Components : Boolean;
2523 function Has_Access_Constraint (E : Entity_Id) return Boolean;
2524 -- Components with access discriminants that depend on the current
2525 -- instance must be initialized after all other components.
2527 ---------------------------
2528 -- Has_Access_Constraint --
2529 ---------------------------
2531 function Has_Access_Constraint (E : Entity_Id) return Boolean is
2532 Disc : Entity_Id;
2533 T : constant Entity_Id := Etype (E);
2535 begin
2536 if Has_Per_Object_Constraint (E)
2537 and then Has_Discriminants (T)
2538 then
2539 Disc := First_Discriminant (T);
2540 while Present (Disc) loop
2541 if Is_Access_Type (Etype (Disc)) then
2542 return True;
2543 end if;
2545 Next_Discriminant (Disc);
2546 end loop;
2548 return False;
2549 else
2550 return False;
2551 end if;
2552 end Has_Access_Constraint;
2554 -- Start of processing for Build_Init_Statements
2556 begin
2557 if Null_Present (Comp_List) then
2558 return New_List (Make_Null_Statement (Loc));
2559 end if;
2561 Statement_List := New_List;
2563 -- Loop through visible declarations of task types and protected
2564 -- types moving any expanded code from the spec to the body of the
2565 -- init procedure.
2567 if Is_Task_Record_Type (Rec_Type)
2568 or else Is_Protected_Record_Type (Rec_Type)
2569 then
2570 declare
2571 Decl : constant Node_Id :=
2572 Parent (Corresponding_Concurrent_Type (Rec_Type));
2573 Def : Node_Id;
2574 N1 : Node_Id;
2575 N2 : Node_Id;
2577 begin
2578 if Is_Task_Record_Type (Rec_Type) then
2579 Def := Task_Definition (Decl);
2580 else
2581 Def := Protected_Definition (Decl);
2582 end if;
2584 if Present (Def) then
2585 N1 := First (Visible_Declarations (Def));
2586 while Present (N1) loop
2587 N2 := N1;
2588 N1 := Next (N1);
2590 if Nkind (N2) in N_Statement_Other_Than_Procedure_Call
2591 or else Nkind (N2) in N_Raise_xxx_Error
2592 or else Nkind (N2) = N_Procedure_Call_Statement
2593 then
2594 Append_To (Statement_List,
2595 New_Copy_Tree (N2, New_Scope => Proc_Id));
2596 Rewrite (N2, Make_Null_Statement (Sloc (N2)));
2597 Analyze (N2);
2598 end if;
2599 end loop;
2600 end if;
2601 end;
2602 end if;
2604 -- Loop through components, skipping pragmas, in 2 steps. The first
2605 -- step deals with regular components. The second step deals with
2606 -- components have per object constraints, and no explicit initia-
2607 -- lization.
2609 Per_Object_Constraint_Components := False;
2611 -- First step : regular components
2613 Decl := First_Non_Pragma (Component_Items (Comp_List));
2614 while Present (Decl) loop
2615 Loc := Sloc (Decl);
2616 Build_Record_Checks
2617 (Subtype_Indication (Component_Definition (Decl)), Check_List);
2619 Id := Defining_Identifier (Decl);
2620 Typ := Etype (Id);
2622 if Has_Access_Constraint (Id)
2623 and then No (Expression (Decl))
2624 then
2625 -- Skip processing for now and ask for a second pass
2627 Per_Object_Constraint_Components := True;
2629 else
2630 -- Case of explicit initialization
2632 if Present (Expression (Decl)) then
2633 if Is_CPP_Constructor_Call (Expression (Decl)) then
2634 Stmts :=
2635 Build_Initialization_Call
2636 (Loc,
2637 Id_Ref =>
2638 Make_Selected_Component (Loc,
2639 Prefix =>
2640 Make_Identifier (Loc, Name_uInit),
2641 Selector_Name => New_Occurrence_Of (Id, Loc)),
2642 Typ => Typ,
2643 In_Init_Proc => True,
2644 Enclos_Type => Rec_Type,
2645 Discr_Map => Discr_Map,
2646 Constructor_Ref => Expression (Decl));
2647 else
2648 Stmts := Build_Assignment (Id, Expression (Decl));
2649 end if;
2651 -- Case of composite component with its own Init_Proc
2653 elsif not Is_Interface (Typ)
2654 and then Has_Non_Null_Base_Init_Proc (Typ)
2655 then
2656 Stmts :=
2657 Build_Initialization_Call
2658 (Loc,
2659 Id_Ref =>
2660 Make_Selected_Component (Loc,
2661 Prefix => Make_Identifier (Loc, Name_uInit),
2662 Selector_Name => New_Occurrence_Of (Id, Loc)),
2663 Typ => Typ,
2664 In_Init_Proc => True,
2665 Enclos_Type => Rec_Type,
2666 Discr_Map => Discr_Map);
2668 Clean_Task_Names (Typ, Proc_Id);
2670 -- Case of component needing simple initialization
2672 elsif Component_Needs_Simple_Initialization (Typ) then
2673 Stmts :=
2674 Build_Assignment
2675 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id)));
2677 -- Nothing needed for this case
2679 else
2680 Stmts := No_List;
2681 end if;
2683 if Present (Check_List) then
2684 Append_List_To (Statement_List, Check_List);
2685 end if;
2687 if Present (Stmts) then
2689 -- Add the initialization of the record controller before
2690 -- the _Parent field is attached to it when the attachment
2691 -- can occur. It does not work to simply initialize the
2692 -- controller first: it must be initialized after the parent
2693 -- if the parent holds discriminants that can be used to
2694 -- compute the offset of the controller. We assume here that
2695 -- the last statement of the initialization call is the
2696 -- attachment of the parent (see Build_Initialization_Call)
2698 if Chars (Id) = Name_uController
2699 and then Rec_Type /= Etype (Rec_Type)
2700 and then Has_Controlled_Component (Etype (Rec_Type))
2701 and then Has_New_Controlled_Component (Rec_Type)
2702 and then Present (Last (Statement_List))
2703 then
2704 Insert_List_Before (Last (Statement_List), Stmts);
2705 else
2706 Append_List_To (Statement_List, Stmts);
2707 end if;
2708 end if;
2709 end if;
2711 Next_Non_Pragma (Decl);
2712 end loop;
2714 -- Set up tasks and protected object support. This needs to be done
2715 -- before any component with a per-object access discriminant
2716 -- constraint, or any variant part (which may contain such
2717 -- components) is initialized, because the initialization of these
2718 -- components may reference the enclosing concurrent object.
2720 -- For a task record type, add the task create call and calls
2721 -- to bind any interrupt (signal) entries.
2723 if Is_Task_Record_Type (Rec_Type) then
2725 -- In the case of the restricted run time the ATCB has already
2726 -- been preallocated.
2728 if Restricted_Profile then
2729 Append_To (Statement_List,
2730 Make_Assignment_Statement (Loc,
2731 Name => Make_Selected_Component (Loc,
2732 Prefix => Make_Identifier (Loc, Name_uInit),
2733 Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
2734 Expression => Make_Attribute_Reference (Loc,
2735 Prefix =>
2736 Make_Selected_Component (Loc,
2737 Prefix => Make_Identifier (Loc, Name_uInit),
2738 Selector_Name =>
2739 Make_Identifier (Loc, Name_uATCB)),
2740 Attribute_Name => Name_Unchecked_Access)));
2741 end if;
2743 Append_To (Statement_List, Make_Task_Create_Call (Rec_Type));
2745 -- Generate the statements which map a string entry name to a
2746 -- task entry index. Note that the task may not have entries.
2748 if Entry_Names_OK then
2749 Names := Build_Entry_Names (Rec_Type);
2751 if Present (Names) then
2752 Append_To (Statement_List, Names);
2753 end if;
2754 end if;
2756 declare
2757 Task_Type : constant Entity_Id :=
2758 Corresponding_Concurrent_Type (Rec_Type);
2759 Task_Decl : constant Node_Id := Parent (Task_Type);
2760 Task_Def : constant Node_Id := Task_Definition (Task_Decl);
2761 Vis_Decl : Node_Id;
2762 Ent : Entity_Id;
2764 begin
2765 if Present (Task_Def) then
2766 Vis_Decl := First (Visible_Declarations (Task_Def));
2767 while Present (Vis_Decl) loop
2768 Loc := Sloc (Vis_Decl);
2770 if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
2771 if Get_Attribute_Id (Chars (Vis_Decl)) =
2772 Attribute_Address
2773 then
2774 Ent := Entity (Name (Vis_Decl));
2776 if Ekind (Ent) = E_Entry then
2777 Append_To (Statement_List,
2778 Make_Procedure_Call_Statement (Loc,
2779 Name => New_Reference_To (
2780 RTE (RE_Bind_Interrupt_To_Entry), Loc),
2781 Parameter_Associations => New_List (
2782 Make_Selected_Component (Loc,
2783 Prefix =>
2784 Make_Identifier (Loc, Name_uInit),
2785 Selector_Name =>
2786 Make_Identifier (Loc, Name_uTask_Id)),
2787 Entry_Index_Expression (
2788 Loc, Ent, Empty, Task_Type),
2789 Expression (Vis_Decl))));
2790 end if;
2791 end if;
2792 end if;
2794 Next (Vis_Decl);
2795 end loop;
2796 end if;
2797 end;
2798 end if;
2800 -- For a protected type, add statements generated by
2801 -- Make_Initialize_Protection.
2803 if Is_Protected_Record_Type (Rec_Type) then
2804 Append_List_To (Statement_List,
2805 Make_Initialize_Protection (Rec_Type));
2807 -- Generate the statements which map a string entry name to a
2808 -- protected entry index. Note that the protected type may not
2809 -- have entries.
2811 if Entry_Names_OK then
2812 Names := Build_Entry_Names (Rec_Type);
2814 if Present (Names) then
2815 Append_To (Statement_List, Names);
2816 end if;
2817 end if;
2818 end if;
2820 if Per_Object_Constraint_Components then
2822 -- Second pass: components with per-object constraints
2824 Decl := First_Non_Pragma (Component_Items (Comp_List));
2825 while Present (Decl) loop
2826 Loc := Sloc (Decl);
2827 Id := Defining_Identifier (Decl);
2828 Typ := Etype (Id);
2830 if Has_Access_Constraint (Id)
2831 and then No (Expression (Decl))
2832 then
2833 if Has_Non_Null_Base_Init_Proc (Typ) then
2834 Append_List_To (Statement_List,
2835 Build_Initialization_Call (Loc,
2836 Make_Selected_Component (Loc,
2837 Prefix => Make_Identifier (Loc, Name_uInit),
2838 Selector_Name => New_Occurrence_Of (Id, Loc)),
2839 Typ,
2840 In_Init_Proc => True,
2841 Enclos_Type => Rec_Type,
2842 Discr_Map => Discr_Map));
2844 Clean_Task_Names (Typ, Proc_Id);
2846 elsif Component_Needs_Simple_Initialization (Typ) then
2847 Append_List_To (Statement_List,
2848 Build_Assignment
2849 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id))));
2850 end if;
2851 end if;
2853 Next_Non_Pragma (Decl);
2854 end loop;
2855 end if;
2857 -- Process the variant part
2859 if Present (Variant_Part (Comp_List)) then
2860 Alt_List := New_List;
2861 Variant := First_Non_Pragma (Variants (Variant_Part (Comp_List)));
2862 while Present (Variant) loop
2863 Loc := Sloc (Variant);
2864 Append_To (Alt_List,
2865 Make_Case_Statement_Alternative (Loc,
2866 Discrete_Choices =>
2867 New_Copy_List (Discrete_Choices (Variant)),
2868 Statements =>
2869 Build_Init_Statements (Component_List (Variant))));
2870 Next_Non_Pragma (Variant);
2871 end loop;
2873 -- The expression of the case statement which is a reference
2874 -- to one of the discriminants is replaced by the appropriate
2875 -- formal parameter of the initialization procedure.
2877 Append_To (Statement_List,
2878 Make_Case_Statement (Loc,
2879 Expression =>
2880 New_Reference_To (Discriminal (
2881 Entity (Name (Variant_Part (Comp_List)))), Loc),
2882 Alternatives => Alt_List));
2883 end if;
2885 -- If no initializations when generated for component declarations
2886 -- corresponding to this Statement_List, append a null statement
2887 -- to the Statement_List to make it a valid Ada tree.
2889 if Is_Empty_List (Statement_List) then
2890 Append (New_Node (N_Null_Statement, Loc), Statement_List);
2891 end if;
2893 return Statement_List;
2895 exception
2896 when RE_Not_Available =>
2897 return Empty_List;
2898 end Build_Init_Statements;
2900 -------------------------
2901 -- Build_Record_Checks --
2902 -------------------------
2904 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
2905 Subtype_Mark_Id : Entity_Id;
2907 begin
2908 if Nkind (S) = N_Subtype_Indication then
2909 Find_Type (Subtype_Mark (S));
2910 Subtype_Mark_Id := Entity (Subtype_Mark (S));
2912 -- Remaining processing depends on type
2914 case Ekind (Subtype_Mark_Id) is
2916 when Array_Kind =>
2917 Constrain_Array (S, Check_List);
2919 when others =>
2920 null;
2921 end case;
2922 end if;
2923 end Build_Record_Checks;
2925 -------------------------------------------
2926 -- Component_Needs_Simple_Initialization --
2927 -------------------------------------------
2929 function Component_Needs_Simple_Initialization
2930 (T : Entity_Id) return Boolean
2932 begin
2933 return
2934 Needs_Simple_Initialization (T)
2935 and then not Is_RTE (T, RE_Tag)
2937 -- Ada 2005 (AI-251): Check also the tag of abstract interfaces
2939 and then not Is_RTE (T, RE_Interface_Tag);
2940 end Component_Needs_Simple_Initialization;
2942 ---------------------
2943 -- Constrain_Array --
2944 ---------------------
2946 procedure Constrain_Array
2947 (SI : Node_Id;
2948 Check_List : List_Id)
2950 C : constant Node_Id := Constraint (SI);
2951 Number_Of_Constraints : Nat := 0;
2952 Index : Node_Id;
2953 S, T : Entity_Id;
2955 begin
2956 T := Entity (Subtype_Mark (SI));
2958 if Ekind (T) in Access_Kind then
2959 T := Designated_Type (T);
2960 end if;
2962 S := First (Constraints (C));
2964 while Present (S) loop
2965 Number_Of_Constraints := Number_Of_Constraints + 1;
2966 Next (S);
2967 end loop;
2969 -- In either case, the index constraint must provide a discrete
2970 -- range for each index of the array type and the type of each
2971 -- discrete range must be the same as that of the corresponding
2972 -- index. (RM 3.6.1)
2974 S := First (Constraints (C));
2975 Index := First_Index (T);
2976 Analyze (Index);
2978 -- Apply constraints to each index type
2980 for J in 1 .. Number_Of_Constraints loop
2981 Constrain_Index (Index, S, Check_List);
2982 Next (Index);
2983 Next (S);
2984 end loop;
2986 end Constrain_Array;
2988 ---------------------
2989 -- Constrain_Index --
2990 ---------------------
2992 procedure Constrain_Index
2993 (Index : Node_Id;
2994 S : Node_Id;
2995 Check_List : List_Id)
2997 T : constant Entity_Id := Etype (Index);
2999 begin
3000 if Nkind (S) = N_Range then
3001 Process_Range_Expr_In_Decl (S, T, Check_List);
3002 end if;
3003 end Constrain_Index;
3005 --------------------------------------
3006 -- Parent_Subtype_Renaming_Discrims --
3007 --------------------------------------
3009 function Parent_Subtype_Renaming_Discrims return Boolean is
3010 De : Entity_Id;
3011 Dp : Entity_Id;
3013 begin
3014 if Base_Type (Pe) /= Pe then
3015 return False;
3016 end if;
3018 if Etype (Pe) = Pe
3019 or else not Has_Discriminants (Pe)
3020 or else Is_Constrained (Pe)
3021 or else Is_Tagged_Type (Pe)
3022 then
3023 return False;
3024 end if;
3026 -- If there are no explicit stored discriminants we have inherited
3027 -- the root type discriminants so far, so no renamings occurred.
3029 if First_Discriminant (Pe) = First_Stored_Discriminant (Pe) then
3030 return False;
3031 end if;
3033 -- Check if we have done some trivial renaming of the parent
3034 -- discriminants, i.e. something like
3036 -- type DT (X1,X2: int) is new PT (X1,X2);
3038 De := First_Discriminant (Pe);
3039 Dp := First_Discriminant (Etype (Pe));
3041 while Present (De) loop
3042 pragma Assert (Present (Dp));
3044 if Corresponding_Discriminant (De) /= Dp then
3045 return True;
3046 end if;
3048 Next_Discriminant (De);
3049 Next_Discriminant (Dp);
3050 end loop;
3052 return Present (Dp);
3053 end Parent_Subtype_Renaming_Discrims;
3055 ------------------------
3056 -- Requires_Init_Proc --
3057 ------------------------
3059 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
3060 Comp_Decl : Node_Id;
3061 Id : Entity_Id;
3062 Typ : Entity_Id;
3064 begin
3065 -- Definitely do not need one if specifically suppressed
3067 if Suppress_Init_Proc (Rec_Id) then
3068 return False;
3069 end if;
3071 -- If it is a type derived from a type with unknown discriminants,
3072 -- we cannot build an initialization procedure for it.
3074 if Has_Unknown_Discriminants (Rec_Id)
3075 or else Has_Unknown_Discriminants (Etype (Rec_Id))
3076 then
3077 return False;
3078 end if;
3080 -- Otherwise we need to generate an initialization procedure if
3081 -- Is_CPP_Class is False and at least one of the following applies:
3083 -- 1. Discriminants are present, since they need to be initialized
3084 -- with the appropriate discriminant constraint expressions.
3085 -- However, the discriminant of an unchecked union does not
3086 -- count, since the discriminant is not present.
3088 -- 2. The type is a tagged type, since the implicit Tag component
3089 -- needs to be initialized with a pointer to the dispatch table.
3091 -- 3. The type contains tasks
3093 -- 4. One or more components has an initial value
3095 -- 5. One or more components is for a type which itself requires
3096 -- an initialization procedure.
3098 -- 6. One or more components is a type that requires simple
3099 -- initialization (see Needs_Simple_Initialization), except
3100 -- that types Tag and Interface_Tag are excluded, since fields
3101 -- of these types are initialized by other means.
3103 -- 7. The type is the record type built for a task type (since at
3104 -- the very least, Create_Task must be called)
3106 -- 8. The type is the record type built for a protected type (since
3107 -- at least Initialize_Protection must be called)
3109 -- 9. The type is marked as a public entity. The reason we add this
3110 -- case (even if none of the above apply) is to properly handle
3111 -- Initialize_Scalars. If a package is compiled without an IS
3112 -- pragma, and the client is compiled with an IS pragma, then
3113 -- the client will think an initialization procedure is present
3114 -- and call it, when in fact no such procedure is required, but
3115 -- since the call is generated, there had better be a routine
3116 -- at the other end of the call, even if it does nothing!)
3118 -- Note: the reason we exclude the CPP_Class case is because in this
3119 -- case the initialization is performed in the C++ side.
3121 if Is_CPP_Class (Rec_Id) then
3122 return False;
3124 elsif Is_Interface (Rec_Id) then
3125 return False;
3127 elsif (Has_Discriminants (Rec_Id)
3128 and then not Is_Unchecked_Union (Rec_Id))
3129 or else Is_Tagged_Type (Rec_Id)
3130 or else Is_Concurrent_Record_Type (Rec_Id)
3131 or else Has_Task (Rec_Id)
3132 then
3133 return True;
3134 end if;
3136 Id := First_Component (Rec_Id);
3137 while Present (Id) loop
3138 Comp_Decl := Parent (Id);
3139 Typ := Etype (Id);
3141 if Present (Expression (Comp_Decl))
3142 or else Has_Non_Null_Base_Init_Proc (Typ)
3143 or else Component_Needs_Simple_Initialization (Typ)
3144 then
3145 return True;
3146 end if;
3148 Next_Component (Id);
3149 end loop;
3151 -- As explained above, a record initialization procedure is needed
3152 -- for public types in case Initialize_Scalars applies to a client.
3153 -- However, such a procedure is not needed in the case where either
3154 -- of restrictions No_Initialize_Scalars or No_Default_Initialization
3155 -- applies. No_Initialize_Scalars excludes the possibility of using
3156 -- Initialize_Scalars in any partition, and No_Default_Initialization
3157 -- implies that no initialization should ever be done for objects of
3158 -- the type, so is incompatible with Initialize_Scalars.
3160 if not Restriction_Active (No_Initialize_Scalars)
3161 and then not Restriction_Active (No_Default_Initialization)
3162 and then Is_Public (Rec_Id)
3163 then
3164 return True;
3165 end if;
3167 return False;
3168 end Requires_Init_Proc;
3170 -- Start of processing for Build_Record_Init_Proc
3172 begin
3173 -- Check for value type, which means no initialization required
3175 Rec_Type := Defining_Identifier (N);
3177 if Is_Value_Type (Rec_Type) then
3178 return;
3179 end if;
3181 -- This may be full declaration of a private type, in which case
3182 -- the visible entity is a record, and the private entity has been
3183 -- exchanged with it in the private part of the current package.
3184 -- The initialization procedure is built for the record type, which
3185 -- is retrievable from the private entity.
3187 if Is_Incomplete_Or_Private_Type (Rec_Type) then
3188 Rec_Type := Underlying_Type (Rec_Type);
3189 end if;
3191 -- If there are discriminants, build the discriminant map to replace
3192 -- discriminants by their discriminals in complex bound expressions.
3193 -- These only arise for the corresponding records of synchronized types.
3195 if Is_Concurrent_Record_Type (Rec_Type)
3196 and then Has_Discriminants (Rec_Type)
3197 then
3198 declare
3199 Disc : Entity_Id;
3200 begin
3201 Disc := First_Discriminant (Rec_Type);
3202 while Present (Disc) loop
3203 Append_Elmt (Disc, Discr_Map);
3204 Append_Elmt (Discriminal (Disc), Discr_Map);
3205 Next_Discriminant (Disc);
3206 end loop;
3207 end;
3208 end if;
3210 -- Derived types that have no type extension can use the initialization
3211 -- procedure of their parent and do not need a procedure of their own.
3212 -- This is only correct if there are no representation clauses for the
3213 -- type or its parent, and if the parent has in fact been frozen so
3214 -- that its initialization procedure exists.
3216 if Is_Derived_Type (Rec_Type)
3217 and then not Is_Tagged_Type (Rec_Type)
3218 and then not Is_Unchecked_Union (Rec_Type)
3219 and then not Has_New_Non_Standard_Rep (Rec_Type)
3220 and then not Parent_Subtype_Renaming_Discrims
3221 and then Has_Non_Null_Base_Init_Proc (Etype (Rec_Type))
3222 then
3223 Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
3225 -- Otherwise if we need an initialization procedure, then build one,
3226 -- mark it as public and inlinable and as having a completion.
3228 elsif Requires_Init_Proc (Rec_Type)
3229 or else Is_Unchecked_Union (Rec_Type)
3230 then
3231 Proc_Id :=
3232 Make_Defining_Identifier (Loc,
3233 Chars => Make_Init_Proc_Name (Rec_Type));
3235 -- If No_Default_Initialization restriction is active, then we don't
3236 -- want to build an init_proc, but we need to mark that an init_proc
3237 -- would be needed if this restriction was not active (so that we can
3238 -- detect attempts to call it), so set a dummy init_proc in place.
3240 if Restriction_Active (No_Default_Initialization) then
3241 Set_Init_Proc (Rec_Type, Proc_Id);
3242 return;
3243 end if;
3245 Build_Offset_To_Top_Functions;
3246 Build_Init_Procedure;
3247 Set_Is_Public (Proc_Id, Is_Public (Pe));
3249 -- The initialization of protected records is not worth inlining.
3250 -- In addition, when compiled for another unit for inlining purposes,
3251 -- it may make reference to entities that have not been elaborated
3252 -- yet. The initialization of controlled records contains a nested
3253 -- clean-up procedure that makes it impractical to inline as well,
3254 -- and leads to undefined symbols if inlined in a different unit.
3255 -- Similar considerations apply to task types.
3257 if not Is_Concurrent_Type (Rec_Type)
3258 and then not Has_Task (Rec_Type)
3259 and then not Needs_Finalization (Rec_Type)
3260 then
3261 Set_Is_Inlined (Proc_Id);
3262 end if;
3264 Set_Is_Internal (Proc_Id);
3265 Set_Has_Completion (Proc_Id);
3267 if not Debug_Generated_Code then
3268 Set_Debug_Info_Off (Proc_Id);
3269 end if;
3271 declare
3272 Agg : constant Node_Id :=
3273 Build_Equivalent_Record_Aggregate (Rec_Type);
3275 procedure Collect_Itypes (Comp : Node_Id);
3276 -- Generate references to itypes in the aggregate, because
3277 -- the first use of the aggregate may be in a nested scope.
3279 --------------------
3280 -- Collect_Itypes --
3281 --------------------
3283 procedure Collect_Itypes (Comp : Node_Id) is
3284 Ref : Node_Id;
3285 Sub_Aggr : Node_Id;
3286 Typ : constant Entity_Id := Etype (Comp);
3288 begin
3289 if Is_Array_Type (Typ)
3290 and then Is_Itype (Typ)
3291 then
3292 Ref := Make_Itype_Reference (Loc);
3293 Set_Itype (Ref, Typ);
3294 Append_Freeze_Action (Rec_Type, Ref);
3296 Ref := Make_Itype_Reference (Loc);
3297 Set_Itype (Ref, Etype (First_Index (Typ)));
3298 Append_Freeze_Action (Rec_Type, Ref);
3300 Sub_Aggr := First (Expressions (Comp));
3302 -- Recurse on nested arrays
3304 while Present (Sub_Aggr) loop
3305 Collect_Itypes (Sub_Aggr);
3306 Next (Sub_Aggr);
3307 end loop;
3308 end if;
3309 end Collect_Itypes;
3311 begin
3312 -- If there is a static initialization aggregate for the type,
3313 -- generate itype references for the types of its (sub)components,
3314 -- to prevent out-of-scope errors in the resulting tree.
3315 -- The aggregate may have been rewritten as a Raise node, in which
3316 -- case there are no relevant itypes.
3318 if Present (Agg)
3319 and then Nkind (Agg) = N_Aggregate
3320 then
3321 Set_Static_Initialization (Proc_Id, Agg);
3323 declare
3324 Comp : Node_Id;
3325 begin
3326 Comp := First (Component_Associations (Agg));
3327 while Present (Comp) loop
3328 Collect_Itypes (Expression (Comp));
3329 Next (Comp);
3330 end loop;
3331 end;
3332 end if;
3333 end;
3334 end if;
3335 end Build_Record_Init_Proc;
3337 ----------------------------
3338 -- Build_Slice_Assignment --
3339 ----------------------------
3341 -- Generates the following subprogram:
3343 -- procedure Assign
3344 -- (Source, Target : Array_Type,
3345 -- Left_Lo, Left_Hi : Index;
3346 -- Right_Lo, Right_Hi : Index;
3347 -- Rev : Boolean)
3348 -- is
3349 -- Li1 : Index;
3350 -- Ri1 : Index;
3352 -- begin
3354 -- if Left_Hi < Left_Lo then
3355 -- return;
3356 -- end if;
3358 -- if Rev then
3359 -- Li1 := Left_Hi;
3360 -- Ri1 := Right_Hi;
3361 -- else
3362 -- Li1 := Left_Lo;
3363 -- Ri1 := Right_Lo;
3364 -- end if;
3366 -- loop
3367 -- Target (Li1) := Source (Ri1);
3369 -- if Rev then
3370 -- exit when Li1 = Left_Lo;
3371 -- Li1 := Index'pred (Li1);
3372 -- Ri1 := Index'pred (Ri1);
3373 -- else
3374 -- exit when Li1 = Left_Hi;
3375 -- Li1 := Index'succ (Li1);
3376 -- Ri1 := Index'succ (Ri1);
3377 -- end if;
3378 -- end loop;
3379 -- end Assign;
3381 procedure Build_Slice_Assignment (Typ : Entity_Id) is
3382 Loc : constant Source_Ptr := Sloc (Typ);
3383 Index : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
3385 Larray : constant Entity_Id := Make_Temporary (Loc, 'A');
3386 Rarray : constant Entity_Id := Make_Temporary (Loc, 'R');
3387 Left_Lo : constant Entity_Id := Make_Temporary (Loc, 'L');
3388 Left_Hi : constant Entity_Id := Make_Temporary (Loc, 'L');
3389 Right_Lo : constant Entity_Id := Make_Temporary (Loc, 'R');
3390 Right_Hi : constant Entity_Id := Make_Temporary (Loc, 'R');
3391 Rev : constant Entity_Id := Make_Temporary (Loc, 'D');
3392 -- Formal parameters of procedure
3394 Proc_Name : constant Entity_Id :=
3395 Make_Defining_Identifier (Loc,
3396 Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
3398 Lnn : constant Entity_Id := Make_Temporary (Loc, 'L');
3399 Rnn : constant Entity_Id := Make_Temporary (Loc, 'R');
3400 -- Subscripts for left and right sides
3402 Decls : List_Id;
3403 Loops : Node_Id;
3404 Stats : List_Id;
3406 begin
3407 -- Build declarations for indices
3409 Decls := New_List;
3411 Append_To (Decls,
3412 Make_Object_Declaration (Loc,
3413 Defining_Identifier => Lnn,
3414 Object_Definition =>
3415 New_Occurrence_Of (Index, Loc)));
3417 Append_To (Decls,
3418 Make_Object_Declaration (Loc,
3419 Defining_Identifier => Rnn,
3420 Object_Definition =>
3421 New_Occurrence_Of (Index, Loc)));
3423 Stats := New_List;
3425 -- Build test for empty slice case
3427 Append_To (Stats,
3428 Make_If_Statement (Loc,
3429 Condition =>
3430 Make_Op_Lt (Loc,
3431 Left_Opnd => New_Occurrence_Of (Left_Hi, Loc),
3432 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc)),
3433 Then_Statements => New_List (Make_Simple_Return_Statement (Loc))));
3435 -- Build initializations for indices
3437 declare
3438 F_Init : constant List_Id := New_List;
3439 B_Init : constant List_Id := New_List;
3441 begin
3442 Append_To (F_Init,
3443 Make_Assignment_Statement (Loc,
3444 Name => New_Occurrence_Of (Lnn, Loc),
3445 Expression => New_Occurrence_Of (Left_Lo, Loc)));
3447 Append_To (F_Init,
3448 Make_Assignment_Statement (Loc,
3449 Name => New_Occurrence_Of (Rnn, Loc),
3450 Expression => New_Occurrence_Of (Right_Lo, Loc)));
3452 Append_To (B_Init,
3453 Make_Assignment_Statement (Loc,
3454 Name => New_Occurrence_Of (Lnn, Loc),
3455 Expression => New_Occurrence_Of (Left_Hi, Loc)));
3457 Append_To (B_Init,
3458 Make_Assignment_Statement (Loc,
3459 Name => New_Occurrence_Of (Rnn, Loc),
3460 Expression => New_Occurrence_Of (Right_Hi, Loc)));
3462 Append_To (Stats,
3463 Make_If_Statement (Loc,
3464 Condition => New_Occurrence_Of (Rev, Loc),
3465 Then_Statements => B_Init,
3466 Else_Statements => F_Init));
3467 end;
3469 -- Now construct the assignment statement
3471 Loops :=
3472 Make_Loop_Statement (Loc,
3473 Statements => New_List (
3474 Make_Assignment_Statement (Loc,
3475 Name =>
3476 Make_Indexed_Component (Loc,
3477 Prefix => New_Occurrence_Of (Larray, Loc),
3478 Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
3479 Expression =>
3480 Make_Indexed_Component (Loc,
3481 Prefix => New_Occurrence_Of (Rarray, Loc),
3482 Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
3483 End_Label => Empty);
3485 -- Build the exit condition and increment/decrement statements
3487 declare
3488 F_Ass : constant List_Id := New_List;
3489 B_Ass : constant List_Id := New_List;
3491 begin
3492 Append_To (F_Ass,
3493 Make_Exit_Statement (Loc,
3494 Condition =>
3495 Make_Op_Eq (Loc,
3496 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3497 Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
3499 Append_To (F_Ass,
3500 Make_Assignment_Statement (Loc,
3501 Name => New_Occurrence_Of (Lnn, Loc),
3502 Expression =>
3503 Make_Attribute_Reference (Loc,
3504 Prefix =>
3505 New_Occurrence_Of (Index, Loc),
3506 Attribute_Name => Name_Succ,
3507 Expressions => New_List (
3508 New_Occurrence_Of (Lnn, Loc)))));
3510 Append_To (F_Ass,
3511 Make_Assignment_Statement (Loc,
3512 Name => New_Occurrence_Of (Rnn, Loc),
3513 Expression =>
3514 Make_Attribute_Reference (Loc,
3515 Prefix =>
3516 New_Occurrence_Of (Index, Loc),
3517 Attribute_Name => Name_Succ,
3518 Expressions => New_List (
3519 New_Occurrence_Of (Rnn, Loc)))));
3521 Append_To (B_Ass,
3522 Make_Exit_Statement (Loc,
3523 Condition =>
3524 Make_Op_Eq (Loc,
3525 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3526 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
3528 Append_To (B_Ass,
3529 Make_Assignment_Statement (Loc,
3530 Name => New_Occurrence_Of (Lnn, Loc),
3531 Expression =>
3532 Make_Attribute_Reference (Loc,
3533 Prefix =>
3534 New_Occurrence_Of (Index, Loc),
3535 Attribute_Name => Name_Pred,
3536 Expressions => New_List (
3537 New_Occurrence_Of (Lnn, Loc)))));
3539 Append_To (B_Ass,
3540 Make_Assignment_Statement (Loc,
3541 Name => New_Occurrence_Of (Rnn, Loc),
3542 Expression =>
3543 Make_Attribute_Reference (Loc,
3544 Prefix =>
3545 New_Occurrence_Of (Index, Loc),
3546 Attribute_Name => Name_Pred,
3547 Expressions => New_List (
3548 New_Occurrence_Of (Rnn, Loc)))));
3550 Append_To (Statements (Loops),
3551 Make_If_Statement (Loc,
3552 Condition => New_Occurrence_Of (Rev, Loc),
3553 Then_Statements => B_Ass,
3554 Else_Statements => F_Ass));
3555 end;
3557 Append_To (Stats, Loops);
3559 declare
3560 Spec : Node_Id;
3561 Formals : List_Id := New_List;
3563 begin
3564 Formals := New_List (
3565 Make_Parameter_Specification (Loc,
3566 Defining_Identifier => Larray,
3567 Out_Present => True,
3568 Parameter_Type =>
3569 New_Reference_To (Base_Type (Typ), Loc)),
3571 Make_Parameter_Specification (Loc,
3572 Defining_Identifier => Rarray,
3573 Parameter_Type =>
3574 New_Reference_To (Base_Type (Typ), Loc)),
3576 Make_Parameter_Specification (Loc,
3577 Defining_Identifier => Left_Lo,
3578 Parameter_Type =>
3579 New_Reference_To (Index, Loc)),
3581 Make_Parameter_Specification (Loc,
3582 Defining_Identifier => Left_Hi,
3583 Parameter_Type =>
3584 New_Reference_To (Index, Loc)),
3586 Make_Parameter_Specification (Loc,
3587 Defining_Identifier => Right_Lo,
3588 Parameter_Type =>
3589 New_Reference_To (Index, Loc)),
3591 Make_Parameter_Specification (Loc,
3592 Defining_Identifier => Right_Hi,
3593 Parameter_Type =>
3594 New_Reference_To (Index, Loc)));
3596 Append_To (Formals,
3597 Make_Parameter_Specification (Loc,
3598 Defining_Identifier => Rev,
3599 Parameter_Type =>
3600 New_Reference_To (Standard_Boolean, Loc)));
3602 Spec :=
3603 Make_Procedure_Specification (Loc,
3604 Defining_Unit_Name => Proc_Name,
3605 Parameter_Specifications => Formals);
3607 Discard_Node (
3608 Make_Subprogram_Body (Loc,
3609 Specification => Spec,
3610 Declarations => Decls,
3611 Handled_Statement_Sequence =>
3612 Make_Handled_Sequence_Of_Statements (Loc,
3613 Statements => Stats)));
3614 end;
3616 Set_TSS (Typ, Proc_Name);
3617 Set_Is_Pure (Proc_Name);
3618 end Build_Slice_Assignment;
3620 ------------------------------------
3621 -- Build_Variant_Record_Equality --
3622 ------------------------------------
3624 -- Generates:
3626 -- function _Equality (X, Y : T) return Boolean is
3627 -- begin
3628 -- -- Compare discriminants
3630 -- if False or else X.D1 /= Y.D1 or else X.D2 /= Y.D2 then
3631 -- return False;
3632 -- end if;
3634 -- -- Compare components
3636 -- if False or else X.C1 /= Y.C1 or else X.C2 /= Y.C2 then
3637 -- return False;
3638 -- end if;
3640 -- -- Compare variant part
3642 -- case X.D1 is
3643 -- when V1 =>
3644 -- if False or else X.C2 /= Y.C2 or else X.C3 /= Y.C3 then
3645 -- return False;
3646 -- end if;
3647 -- ...
3648 -- when Vn =>
3649 -- if False or else X.Cn /= Y.Cn then
3650 -- return False;
3651 -- end if;
3652 -- end case;
3654 -- return True;
3655 -- end _Equality;
3657 procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
3658 Loc : constant Source_Ptr := Sloc (Typ);
3660 F : constant Entity_Id :=
3661 Make_Defining_Identifier (Loc,
3662 Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
3664 X : constant Entity_Id :=
3665 Make_Defining_Identifier (Loc,
3666 Chars => Name_X);
3668 Y : constant Entity_Id :=
3669 Make_Defining_Identifier (Loc,
3670 Chars => Name_Y);
3672 Def : constant Node_Id := Parent (Typ);
3673 Comps : constant Node_Id := Component_List (Type_Definition (Def));
3674 Stmts : constant List_Id := New_List;
3675 Pspecs : constant List_Id := New_List;
3677 begin
3678 -- Derived Unchecked_Union types no longer inherit the equality function
3679 -- of their parent.
3681 if Is_Derived_Type (Typ)
3682 and then not Is_Unchecked_Union (Typ)
3683 and then not Has_New_Non_Standard_Rep (Typ)
3684 then
3685 declare
3686 Parent_Eq : constant Entity_Id :=
3687 TSS (Root_Type (Typ), TSS_Composite_Equality);
3689 begin
3690 if Present (Parent_Eq) then
3691 Copy_TSS (Parent_Eq, Typ);
3692 return;
3693 end if;
3694 end;
3695 end if;
3697 Discard_Node (
3698 Make_Subprogram_Body (Loc,
3699 Specification =>
3700 Make_Function_Specification (Loc,
3701 Defining_Unit_Name => F,
3702 Parameter_Specifications => Pspecs,
3703 Result_Definition => New_Reference_To (Standard_Boolean, Loc)),
3704 Declarations => New_List,
3705 Handled_Statement_Sequence =>
3706 Make_Handled_Sequence_Of_Statements (Loc,
3707 Statements => Stmts)));
3709 Append_To (Pspecs,
3710 Make_Parameter_Specification (Loc,
3711 Defining_Identifier => X,
3712 Parameter_Type => New_Reference_To (Typ, Loc)));
3714 Append_To (Pspecs,
3715 Make_Parameter_Specification (Loc,
3716 Defining_Identifier => Y,
3717 Parameter_Type => New_Reference_To (Typ, Loc)));
3719 -- Unchecked_Unions require additional machinery to support equality.
3720 -- Two extra parameters (A and B) are added to the equality function
3721 -- parameter list in order to capture the inferred values of the
3722 -- discriminants in later calls.
3724 if Is_Unchecked_Union (Typ) then
3725 declare
3726 Discr_Type : constant Node_Id := Etype (First_Discriminant (Typ));
3728 A : constant Node_Id :=
3729 Make_Defining_Identifier (Loc,
3730 Chars => Name_A);
3732 B : constant Node_Id :=
3733 Make_Defining_Identifier (Loc,
3734 Chars => Name_B);
3736 begin
3737 -- Add A and B to the parameter list
3739 Append_To (Pspecs,
3740 Make_Parameter_Specification (Loc,
3741 Defining_Identifier => A,
3742 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
3744 Append_To (Pspecs,
3745 Make_Parameter_Specification (Loc,
3746 Defining_Identifier => B,
3747 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
3749 -- Generate the following header code to compare the inferred
3750 -- discriminants:
3752 -- if a /= b then
3753 -- return False;
3754 -- end if;
3756 Append_To (Stmts,
3757 Make_If_Statement (Loc,
3758 Condition =>
3759 Make_Op_Ne (Loc,
3760 Left_Opnd => New_Reference_To (A, Loc),
3761 Right_Opnd => New_Reference_To (B, Loc)),
3762 Then_Statements => New_List (
3763 Make_Simple_Return_Statement (Loc,
3764 Expression => New_Occurrence_Of (Standard_False, Loc)))));
3766 -- Generate component-by-component comparison. Note that we must
3767 -- propagate one of the inferred discriminant formals to act as
3768 -- the case statement switch.
3770 Append_List_To (Stmts,
3771 Make_Eq_Case (Typ, Comps, A));
3773 end;
3775 -- Normal case (not unchecked union)
3777 else
3778 Append_To (Stmts,
3779 Make_Eq_If (Typ,
3780 Discriminant_Specifications (Def)));
3782 Append_List_To (Stmts,
3783 Make_Eq_Case (Typ, Comps));
3784 end if;
3786 Append_To (Stmts,
3787 Make_Simple_Return_Statement (Loc,
3788 Expression => New_Reference_To (Standard_True, Loc)));
3790 Set_TSS (Typ, F);
3791 Set_Is_Pure (F);
3793 if not Debug_Generated_Code then
3794 Set_Debug_Info_Off (F);
3795 end if;
3796 end Build_Variant_Record_Equality;
3798 -----------------------------
3799 -- Check_Stream_Attributes --
3800 -----------------------------
3802 procedure Check_Stream_Attributes (Typ : Entity_Id) is
3803 Comp : Entity_Id;
3804 Par_Read : constant Boolean :=
3805 Stream_Attribute_Available (Typ, TSS_Stream_Read)
3806 and then not Has_Specified_Stream_Read (Typ);
3807 Par_Write : constant Boolean :=
3808 Stream_Attribute_Available (Typ, TSS_Stream_Write)
3809 and then not Has_Specified_Stream_Write (Typ);
3811 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type);
3812 -- Check that Comp has a user-specified Nam stream attribute
3814 ----------------
3815 -- Check_Attr --
3816 ----------------
3818 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type) is
3819 begin
3820 if not Stream_Attribute_Available (Etype (Comp), TSS_Nam) then
3821 Error_Msg_Name_1 := Nam;
3822 Error_Msg_N
3823 ("|component& in limited extension must have% attribute", Comp);
3824 end if;
3825 end Check_Attr;
3827 -- Start of processing for Check_Stream_Attributes
3829 begin
3830 if Par_Read or else Par_Write then
3831 Comp := First_Component (Typ);
3832 while Present (Comp) loop
3833 if Comes_From_Source (Comp)
3834 and then Original_Record_Component (Comp) = Comp
3835 and then Is_Limited_Type (Etype (Comp))
3836 then
3837 if Par_Read then
3838 Check_Attr (Name_Read, TSS_Stream_Read);
3839 end if;
3841 if Par_Write then
3842 Check_Attr (Name_Write, TSS_Stream_Write);
3843 end if;
3844 end if;
3846 Next_Component (Comp);
3847 end loop;
3848 end if;
3849 end Check_Stream_Attributes;
3851 -----------------------------
3852 -- Expand_Record_Extension --
3853 -----------------------------
3855 -- Add a field _parent at the beginning of the record extension. This is
3856 -- used to implement inheritance. Here are some examples of expansion:
3858 -- 1. no discriminants
3859 -- type T2 is new T1 with null record;
3860 -- gives
3861 -- type T2 is new T1 with record
3862 -- _Parent : T1;
3863 -- end record;
3865 -- 2. renamed discriminants
3866 -- type T2 (B, C : Int) is new T1 (A => B) with record
3867 -- _Parent : T1 (A => B);
3868 -- D : Int;
3869 -- end;
3871 -- 3. inherited discriminants
3872 -- type T2 is new T1 with record -- discriminant A inherited
3873 -- _Parent : T1 (A);
3874 -- D : Int;
3875 -- end;
3877 procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
3878 Indic : constant Node_Id := Subtype_Indication (Def);
3879 Loc : constant Source_Ptr := Sloc (Def);
3880 Rec_Ext_Part : Node_Id := Record_Extension_Part (Def);
3881 Par_Subtype : Entity_Id;
3882 Comp_List : Node_Id;
3883 Comp_Decl : Node_Id;
3884 Parent_N : Node_Id;
3885 D : Entity_Id;
3886 List_Constr : constant List_Id := New_List;
3888 begin
3889 -- Expand_Record_Extension is called directly from the semantics, so
3890 -- we must check to see whether expansion is active before proceeding
3892 if not Expander_Active then
3893 return;
3894 end if;
3896 -- This may be a derivation of an untagged private type whose full
3897 -- view is tagged, in which case the Derived_Type_Definition has no
3898 -- extension part. Build an empty one now.
3900 if No (Rec_Ext_Part) then
3901 Rec_Ext_Part :=
3902 Make_Record_Definition (Loc,
3903 End_Label => Empty,
3904 Component_List => Empty,
3905 Null_Present => True);
3907 Set_Record_Extension_Part (Def, Rec_Ext_Part);
3908 Mark_Rewrite_Insertion (Rec_Ext_Part);
3909 end if;
3911 Comp_List := Component_List (Rec_Ext_Part);
3913 Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
3915 -- If the derived type inherits its discriminants the type of the
3916 -- _parent field must be constrained by the inherited discriminants
3918 if Has_Discriminants (T)
3919 and then Nkind (Indic) /= N_Subtype_Indication
3920 and then not Is_Constrained (Entity (Indic))
3921 then
3922 D := First_Discriminant (T);
3923 while Present (D) loop
3924 Append_To (List_Constr, New_Occurrence_Of (D, Loc));
3925 Next_Discriminant (D);
3926 end loop;
3928 Par_Subtype :=
3929 Process_Subtype (
3930 Make_Subtype_Indication (Loc,
3931 Subtype_Mark => New_Reference_To (Entity (Indic), Loc),
3932 Constraint =>
3933 Make_Index_Or_Discriminant_Constraint (Loc,
3934 Constraints => List_Constr)),
3935 Def);
3937 -- Otherwise the original subtype_indication is just what is needed
3939 else
3940 Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
3941 end if;
3943 Set_Parent_Subtype (T, Par_Subtype);
3945 Comp_Decl :=
3946 Make_Component_Declaration (Loc,
3947 Defining_Identifier => Parent_N,
3948 Component_Definition =>
3949 Make_Component_Definition (Loc,
3950 Aliased_Present => False,
3951 Subtype_Indication => New_Reference_To (Par_Subtype, Loc)));
3953 if Null_Present (Rec_Ext_Part) then
3954 Set_Component_List (Rec_Ext_Part,
3955 Make_Component_List (Loc,
3956 Component_Items => New_List (Comp_Decl),
3957 Variant_Part => Empty,
3958 Null_Present => False));
3959 Set_Null_Present (Rec_Ext_Part, False);
3961 elsif Null_Present (Comp_List)
3962 or else Is_Empty_List (Component_Items (Comp_List))
3963 then
3964 Set_Component_Items (Comp_List, New_List (Comp_Decl));
3965 Set_Null_Present (Comp_List, False);
3967 else
3968 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
3969 end if;
3971 Analyze (Comp_Decl);
3972 end Expand_Record_Extension;
3974 ------------------------------------
3975 -- Expand_N_Full_Type_Declaration --
3976 ------------------------------------
3978 procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
3979 Def_Id : constant Entity_Id := Defining_Identifier (N);
3980 B_Id : constant Entity_Id := Base_Type (Def_Id);
3981 Par_Id : Entity_Id;
3982 FN : Node_Id;
3984 procedure Build_Master (Def_Id : Entity_Id);
3985 -- Create the master associated with Def_Id
3987 ------------------
3988 -- Build_Master --
3989 ------------------
3991 procedure Build_Master (Def_Id : Entity_Id) is
3992 begin
3993 -- Anonymous access types are created for the components of the
3994 -- record parameter for an entry declaration. No master is created
3995 -- for such a type.
3997 if Has_Task (Designated_Type (Def_Id))
3998 and then Comes_From_Source (N)
3999 then
4000 Build_Master_Entity (Def_Id);
4001 Build_Master_Renaming (Parent (Def_Id), Def_Id);
4003 -- Create a class-wide master because a Master_Id must be generated
4004 -- for access-to-limited-class-wide types whose root may be extended
4005 -- with task components.
4007 -- Note: This code covers access-to-limited-interfaces because they
4008 -- can be used to reference tasks implementing them.
4010 elsif Is_Class_Wide_Type (Designated_Type (Def_Id))
4011 and then Is_Limited_Type (Designated_Type (Def_Id))
4012 and then Tasking_Allowed
4014 -- Do not create a class-wide master for types whose convention is
4015 -- Java since these types cannot embed Ada tasks anyway. Note that
4016 -- the following test cannot catch the following case:
4018 -- package java.lang.Object is
4019 -- type Typ is tagged limited private;
4020 -- type Ref is access all Typ'Class;
4021 -- private
4022 -- type Typ is tagged limited ...;
4023 -- pragma Convention (Typ, Java)
4024 -- end;
4026 -- Because the convention appears after we have done the
4027 -- processing for type Ref.
4029 and then Convention (Designated_Type (Def_Id)) /= Convention_Java
4030 and then Convention (Designated_Type (Def_Id)) /= Convention_CIL
4031 then
4032 Build_Class_Wide_Master (Def_Id);
4033 end if;
4034 end Build_Master;
4036 -- Start of processing for Expand_N_Full_Type_Declaration
4038 begin
4039 if Is_Access_Type (Def_Id) then
4040 Build_Master (Def_Id);
4042 if Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
4043 Expand_Access_Protected_Subprogram_Type (N);
4044 end if;
4046 elsif Ada_Version >= Ada_05
4047 and then Is_Array_Type (Def_Id)
4048 and then Is_Access_Type (Component_Type (Def_Id))
4049 and then Ekind (Component_Type (Def_Id)) = E_Anonymous_Access_Type
4050 then
4051 Build_Master (Component_Type (Def_Id));
4053 elsif Has_Task (Def_Id) then
4054 Expand_Previous_Access_Type (Def_Id);
4056 elsif Ada_Version >= Ada_05
4057 and then
4058 (Is_Record_Type (Def_Id)
4059 or else (Is_Array_Type (Def_Id)
4060 and then Is_Record_Type (Component_Type (Def_Id))))
4061 then
4062 declare
4063 Comp : Entity_Id;
4064 Typ : Entity_Id;
4065 M_Id : Entity_Id;
4067 begin
4068 -- Look for the first anonymous access type component
4070 if Is_Array_Type (Def_Id) then
4071 Comp := First_Entity (Component_Type (Def_Id));
4072 else
4073 Comp := First_Entity (Def_Id);
4074 end if;
4076 while Present (Comp) loop
4077 Typ := Etype (Comp);
4079 exit when Is_Access_Type (Typ)
4080 and then Ekind (Typ) = E_Anonymous_Access_Type;
4082 Next_Entity (Comp);
4083 end loop;
4085 -- If found we add a renaming declaration of master_id and we
4086 -- associate it to each anonymous access type component. Do
4087 -- nothing if the access type already has a master. This will be
4088 -- the case if the array type is the packed array created for a
4089 -- user-defined array type T, where the master_id is created when
4090 -- expanding the declaration for T.
4092 if Present (Comp)
4093 and then Ekind (Typ) = E_Anonymous_Access_Type
4094 and then not Restriction_Active (No_Task_Hierarchy)
4095 and then No (Master_Id (Typ))
4097 -- Do not consider run-times with no tasking support
4099 and then RTE_Available (RE_Current_Master)
4100 and then Has_Task (Non_Limited_Designated_Type (Typ))
4101 then
4102 Build_Master_Entity (Def_Id);
4103 M_Id := Build_Master_Renaming (N, Def_Id);
4105 if Is_Array_Type (Def_Id) then
4106 Comp := First_Entity (Component_Type (Def_Id));
4107 else
4108 Comp := First_Entity (Def_Id);
4109 end if;
4111 while Present (Comp) loop
4112 Typ := Etype (Comp);
4114 if Is_Access_Type (Typ)
4115 and then Ekind (Typ) = E_Anonymous_Access_Type
4116 then
4117 Set_Master_Id (Typ, M_Id);
4118 end if;
4120 Next_Entity (Comp);
4121 end loop;
4122 end if;
4123 end;
4124 end if;
4126 Par_Id := Etype (B_Id);
4128 -- The parent type is private then we need to inherit any TSS operations
4129 -- from the full view.
4131 if Ekind (Par_Id) in Private_Kind
4132 and then Present (Full_View (Par_Id))
4133 then
4134 Par_Id := Base_Type (Full_View (Par_Id));
4135 end if;
4137 if Nkind (Type_Definition (Original_Node (N))) =
4138 N_Derived_Type_Definition
4139 and then not Is_Tagged_Type (Def_Id)
4140 and then Present (Freeze_Node (Par_Id))
4141 and then Present (TSS_Elist (Freeze_Node (Par_Id)))
4142 then
4143 Ensure_Freeze_Node (B_Id);
4144 FN := Freeze_Node (B_Id);
4146 if No (TSS_Elist (FN)) then
4147 Set_TSS_Elist (FN, New_Elmt_List);
4148 end if;
4150 declare
4151 T_E : constant Elist_Id := TSS_Elist (FN);
4152 Elmt : Elmt_Id;
4154 begin
4155 Elmt := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
4156 while Present (Elmt) loop
4157 if Chars (Node (Elmt)) /= Name_uInit then
4158 Append_Elmt (Node (Elmt), T_E);
4159 end if;
4161 Next_Elmt (Elmt);
4162 end loop;
4164 -- If the derived type itself is private with a full view, then
4165 -- associate the full view with the inherited TSS_Elist as well.
4167 if Ekind (B_Id) in Private_Kind
4168 and then Present (Full_View (B_Id))
4169 then
4170 Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
4171 Set_TSS_Elist
4172 (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
4173 end if;
4174 end;
4175 end if;
4176 end Expand_N_Full_Type_Declaration;
4178 ---------------------------------
4179 -- Expand_N_Object_Declaration --
4180 ---------------------------------
4182 -- First we do special processing for objects of a tagged type where this
4183 -- is the point at which the type is frozen. The creation of the dispatch
4184 -- table and the initialization procedure have to be deferred to this
4185 -- point, since we reference previously declared primitive subprograms.
4187 -- For all types, we call an initialization procedure if there is one
4189 procedure Expand_N_Object_Declaration (N : Node_Id) is
4190 Def_Id : constant Entity_Id := Defining_Identifier (N);
4191 Expr : constant Node_Id := Expression (N);
4192 Loc : constant Source_Ptr := Sloc (N);
4193 Typ : constant Entity_Id := Etype (Def_Id);
4194 Base_Typ : constant Entity_Id := Base_Type (Typ);
4195 Expr_Q : Node_Id;
4196 Id_Ref : Node_Id;
4197 New_Ref : Node_Id;
4199 Init_After : Node_Id := N;
4200 -- Node after which the init proc call is to be inserted. This is
4201 -- normally N, except for the case of a shared passive variable, in
4202 -- which case the init proc call must be inserted only after the bodies
4203 -- of the shared variable procedures have been seen.
4205 function Rewrite_As_Renaming return Boolean;
4206 -- Indicate whether to rewrite a declaration with initialization into an
4207 -- object renaming declaration (see below).
4209 -------------------------
4210 -- Rewrite_As_Renaming --
4211 -------------------------
4213 function Rewrite_As_Renaming return Boolean is
4214 begin
4215 return not Aliased_Present (N)
4216 and then Is_Entity_Name (Expr_Q)
4217 and then Ekind (Entity (Expr_Q)) = E_Variable
4218 and then OK_To_Rename (Entity (Expr_Q))
4219 and then Is_Entity_Name (Object_Definition (N));
4220 end Rewrite_As_Renaming;
4222 -- Start of processing for Expand_N_Object_Declaration
4224 begin
4225 -- Don't do anything for deferred constants. All proper actions will be
4226 -- expanded during the full declaration.
4228 if No (Expr) and Constant_Present (N) then
4229 return;
4230 end if;
4232 -- Force construction of dispatch tables of library level tagged types
4234 if Tagged_Type_Expansion
4235 and then Static_Dispatch_Tables
4236 and then Is_Library_Level_Entity (Def_Id)
4237 and then Is_Library_Level_Tagged_Type (Base_Typ)
4238 and then (Ekind (Base_Typ) = E_Record_Type
4239 or else Ekind (Base_Typ) = E_Protected_Type
4240 or else Ekind (Base_Typ) = E_Task_Type)
4241 and then not Has_Dispatch_Table (Base_Typ)
4242 then
4243 declare
4244 New_Nodes : List_Id := No_List;
4246 begin
4247 if Is_Concurrent_Type (Base_Typ) then
4248 New_Nodes := Make_DT (Corresponding_Record_Type (Base_Typ), N);
4249 else
4250 New_Nodes := Make_DT (Base_Typ, N);
4251 end if;
4253 if not Is_Empty_List (New_Nodes) then
4254 Insert_List_Before (N, New_Nodes);
4255 end if;
4256 end;
4257 end if;
4259 -- Make shared memory routines for shared passive variable
4261 if Is_Shared_Passive (Def_Id) then
4262 Init_After := Make_Shared_Var_Procs (N);
4263 end if;
4265 -- If tasks being declared, make sure we have an activation chain
4266 -- defined for the tasks (has no effect if we already have one), and
4267 -- also that a Master variable is established and that the appropriate
4268 -- enclosing construct is established as a task master.
4270 if Has_Task (Typ) then
4271 Build_Activation_Chain_Entity (N);
4272 Build_Master_Entity (Def_Id);
4273 end if;
4275 -- Build a list controller for declarations where the type is anonymous
4276 -- access and the designated type is controlled. Only declarations from
4277 -- source files receive such controllers in order to provide the same
4278 -- lifespan for any potential coextensions that may be associated with
4279 -- the object. Finalization lists of internal controlled anonymous
4280 -- access objects are already handled in Expand_N_Allocator.
4282 if Comes_From_Source (N)
4283 and then Ekind (Typ) = E_Anonymous_Access_Type
4284 and then Is_Controlled (Directly_Designated_Type (Typ))
4285 and then No (Associated_Final_Chain (Typ))
4286 then
4287 Build_Final_List (N, Typ);
4288 end if;
4290 -- Default initialization required, and no expression present
4292 if No (Expr) then
4294 -- Expand Initialize call for controlled objects. One may wonder why
4295 -- the Initialize Call is not done in the regular Init procedure
4296 -- attached to the record type. That's because the init procedure is
4297 -- recursively called on each component, including _Parent, thus the
4298 -- Init call for a controlled object would generate not only one
4299 -- Initialize call as it is required but one for each ancestor of
4300 -- its type. This processing is suppressed if No_Initialization set.
4302 if not Needs_Finalization (Typ)
4303 or else No_Initialization (N)
4304 then
4305 null;
4307 elsif not Abort_Allowed
4308 or else not Comes_From_Source (N)
4309 then
4310 Insert_Actions_After (Init_After,
4311 Make_Init_Call (
4312 Ref => New_Occurrence_Of (Def_Id, Loc),
4313 Typ => Base_Type (Typ),
4314 Flist_Ref => Find_Final_List (Def_Id),
4315 With_Attach => Make_Integer_Literal (Loc, 1)));
4317 -- Abort allowed
4319 else
4320 -- We need to protect the initialize call
4322 -- begin
4323 -- Defer_Abort.all;
4324 -- Initialize (...);
4325 -- at end
4326 -- Undefer_Abort.all;
4327 -- end;
4329 -- ??? this won't protect the initialize call for controlled
4330 -- components which are part of the init proc, so this block
4331 -- should probably also contain the call to _init_proc but this
4332 -- requires some code reorganization...
4334 declare
4335 L : constant List_Id :=
4336 Make_Init_Call
4337 (Ref => New_Occurrence_Of (Def_Id, Loc),
4338 Typ => Base_Type (Typ),
4339 Flist_Ref => Find_Final_List (Def_Id),
4340 With_Attach => Make_Integer_Literal (Loc, 1));
4342 Blk : constant Node_Id :=
4343 Make_Block_Statement (Loc,
4344 Handled_Statement_Sequence =>
4345 Make_Handled_Sequence_Of_Statements (Loc, L));
4347 begin
4348 Prepend_To (L, Build_Runtime_Call (Loc, RE_Abort_Defer));
4349 Set_At_End_Proc (Handled_Statement_Sequence (Blk),
4350 New_Occurrence_Of (RTE (RE_Abort_Undefer_Direct), Loc));
4351 Insert_Actions_After (Init_After, New_List (Blk));
4352 Expand_At_End_Handler
4353 (Handled_Statement_Sequence (Blk), Entity (Identifier (Blk)));
4354 end;
4355 end if;
4357 -- Call type initialization procedure if there is one. We build the
4358 -- call and put it immediately after the object declaration, so that
4359 -- it will be expanded in the usual manner. Note that this will
4360 -- result in proper handling of defaulted discriminants.
4362 -- Need call if there is a base init proc
4364 if Has_Non_Null_Base_Init_Proc (Typ)
4366 -- Suppress call if No_Initialization set on declaration
4368 and then not No_Initialization (N)
4370 -- Suppress call for special case of value type for VM
4372 and then not Is_Value_Type (Typ)
4374 -- Suppress call if Suppress_Init_Proc set on the type. This is
4375 -- needed for the derived type case, where Suppress_Initialization
4376 -- may be set for the derived type, even if there is an init proc
4377 -- defined for the root type.
4379 and then not Suppress_Init_Proc (Typ)
4380 then
4381 -- Return without initializing when No_Default_Initialization
4382 -- applies. Note that the actual restriction check occurs later,
4383 -- when the object is frozen, because we don't know yet whether
4384 -- the object is imported, which is a case where the check does
4385 -- not apply.
4387 if Restriction_Active (No_Default_Initialization) then
4388 return;
4389 end if;
4391 -- The call to the initialization procedure does NOT freeze the
4392 -- object being initialized. This is because the call is not a
4393 -- source level call. This works fine, because the only possible
4394 -- statements depending on freeze status that can appear after the
4395 -- Init_Proc call are rep clauses which can safely appear after
4396 -- actual references to the object. Note that this call may
4397 -- subsequently be removed (if a pragma Import is encountered),
4398 -- or moved to the freeze actions for the object (e.g. if an
4399 -- address clause is applied to the object, causing it to get
4400 -- delayed freezing).
4402 Id_Ref := New_Reference_To (Def_Id, Loc);
4403 Set_Must_Not_Freeze (Id_Ref);
4404 Set_Assignment_OK (Id_Ref);
4406 declare
4407 Init_Expr : constant Node_Id :=
4408 Static_Initialization (Base_Init_Proc (Typ));
4409 begin
4410 if Present (Init_Expr) then
4411 Set_Expression
4412 (N, New_Copy_Tree (Init_Expr, New_Scope => Current_Scope));
4413 return;
4414 else
4415 Initialization_Warning (Id_Ref);
4417 Insert_Actions_After (Init_After,
4418 Build_Initialization_Call (Loc, Id_Ref, Typ));
4419 end if;
4420 end;
4422 -- If simple initialization is required, then set an appropriate
4423 -- simple initialization expression in place. This special
4424 -- initialization is required even though No_Init_Flag is present,
4425 -- but is not needed if there was an explicit initialization.
4427 -- An internally generated temporary needs no initialization because
4428 -- it will be assigned subsequently. In particular, there is no point
4429 -- in applying Initialize_Scalars to such a temporary.
4431 elsif Needs_Simple_Initialization
4432 (Typ,
4433 Initialize_Scalars
4434 and then not Has_Following_Address_Clause (N))
4435 and then not Is_Internal (Def_Id)
4436 and then not Has_Init_Expression (N)
4437 then
4438 Set_No_Initialization (N, False);
4439 Set_Expression (N, Get_Simple_Init_Val (Typ, N, Esize (Def_Id)));
4440 Analyze_And_Resolve (Expression (N), Typ);
4441 end if;
4443 -- Generate attribute for Persistent_BSS if needed
4445 if Persistent_BSS_Mode
4446 and then Comes_From_Source (N)
4447 and then Is_Potentially_Persistent_Type (Typ)
4448 and then not Has_Init_Expression (N)
4449 and then Is_Library_Level_Entity (Def_Id)
4450 then
4451 declare
4452 Prag : Node_Id;
4453 begin
4454 Prag :=
4455 Make_Linker_Section_Pragma
4456 (Def_Id, Sloc (N), ".persistent.bss");
4457 Insert_After (N, Prag);
4458 Analyze (Prag);
4459 end;
4460 end if;
4462 -- If access type, then we know it is null if not initialized
4464 if Is_Access_Type (Typ) then
4465 Set_Is_Known_Null (Def_Id);
4466 end if;
4468 -- Explicit initialization present
4470 else
4471 -- Obtain actual expression from qualified expression
4473 if Nkind (Expr) = N_Qualified_Expression then
4474 Expr_Q := Expression (Expr);
4475 else
4476 Expr_Q := Expr;
4477 end if;
4479 -- When we have the appropriate type of aggregate in the expression
4480 -- (it has been determined during analysis of the aggregate by
4481 -- setting the delay flag), let's perform in place assignment and
4482 -- thus avoid creating a temporary.
4484 if Is_Delayed_Aggregate (Expr_Q) then
4485 Convert_Aggr_In_Object_Decl (N);
4487 -- Ada 2005 (AI-318-02): If the initialization expression is a call
4488 -- to a build-in-place function, then access to the declared object
4489 -- must be passed to the function. Currently we limit such functions
4490 -- to those with constrained limited result subtypes, but eventually
4491 -- plan to expand the allowed forms of functions that are treated as
4492 -- build-in-place.
4494 elsif Ada_Version >= Ada_05
4495 and then Is_Build_In_Place_Function_Call (Expr_Q)
4496 then
4497 Make_Build_In_Place_Call_In_Object_Declaration (N, Expr_Q);
4499 -- The previous call expands the expression initializing the
4500 -- built-in-place object into further code that will be analyzed
4501 -- later. No further expansion needed here.
4503 return;
4505 -- Ada 2005 (AI-251): Rewrite the expression that initializes a
4506 -- class-wide object to ensure that we copy the full object,
4507 -- unless we are targetting a VM where interfaces are handled by
4508 -- VM itself. Note that if the root type of Typ is an ancestor
4509 -- of Expr's type, both types share the same dispatch table and
4510 -- there is no need to displace the pointer.
4512 elsif Comes_From_Source (N)
4513 and then Is_Interface (Typ)
4514 then
4515 pragma Assert (Is_Class_Wide_Type (Typ));
4517 -- If the object is a return object of an inherently limited type,
4518 -- which implies build-in-place treatment, bypass the special
4519 -- treatment of class-wide interface initialization below. In this
4520 -- case, the expansion of the return statement will take care of
4521 -- creating the object (via allocator) and initializing it.
4523 if Is_Return_Object (Def_Id)
4524 and then Is_Inherently_Limited_Type (Typ)
4525 then
4526 null;
4528 elsif Tagged_Type_Expansion then
4529 declare
4530 Iface : constant Entity_Id := Root_Type (Typ);
4531 Expr_N : Node_Id := Expr;
4532 Expr_Typ : Entity_Id;
4534 Decl_1 : Node_Id;
4535 Decl_2 : Node_Id;
4536 New_Expr : Node_Id;
4538 begin
4539 -- If the original node of the expression was a conversion
4540 -- to this specific class-wide interface type then we
4541 -- restore the original node to generate code that
4542 -- statically displaces the pointer to the interface
4543 -- component.
4545 if not Comes_From_Source (Expr_N)
4546 and then Nkind (Expr_N) = N_Unchecked_Type_Conversion
4547 and then Nkind (Original_Node (Expr_N)) = N_Type_Conversion
4548 and then Etype (Original_Node (Expr_N)) = Typ
4549 then
4550 Rewrite (Expr_N, Original_Node (Expression (N)));
4551 end if;
4553 -- Avoid expansion of redundant interface conversion
4555 if Is_Interface (Etype (Expr_N))
4556 and then Nkind (Expr_N) = N_Type_Conversion
4557 and then Etype (Expr_N) = Typ
4558 then
4559 Expr_N := Expression (Expr_N);
4560 Set_Expression (N, Expr_N);
4561 end if;
4563 Expr_Typ := Base_Type (Etype (Expr_N));
4565 if Is_Class_Wide_Type (Expr_Typ) then
4566 Expr_Typ := Root_Type (Expr_Typ);
4567 end if;
4569 -- Replace
4570 -- CW : I'Class := Obj;
4571 -- by
4572 -- Tmp : T := Obj;
4573 -- CW : I'Class renames TiC!(Tmp.I_Tag);
4575 if Comes_From_Source (Expr_N)
4576 and then Nkind (Expr_N) = N_Identifier
4577 and then not Is_Interface (Expr_Typ)
4578 and then (Expr_Typ = Etype (Expr_Typ)
4579 or else not
4580 Is_Variable_Size_Record (Etype (Expr_Typ)))
4581 then
4582 Decl_1 :=
4583 Make_Object_Declaration (Loc,
4584 Defining_Identifier =>
4585 Make_Temporary (Loc, 'D', Expr_N),
4586 Object_Definition =>
4587 New_Occurrence_Of (Expr_Typ, Loc),
4588 Expression =>
4589 Unchecked_Convert_To (Expr_Typ,
4590 Relocate_Node (Expr_N)));
4592 -- Statically reference the tag associated with the
4593 -- interface
4595 Decl_2 :=
4596 Make_Object_Renaming_Declaration (Loc,
4597 Defining_Identifier => Make_Temporary (Loc, 'D'),
4598 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
4599 Name =>
4600 Unchecked_Convert_To (Typ,
4601 Make_Selected_Component (Loc,
4602 Prefix =>
4603 New_Occurrence_Of
4604 (Defining_Identifier (Decl_1), Loc),
4605 Selector_Name =>
4606 New_Reference_To
4607 (Find_Interface_Tag (Expr_Typ, Iface),
4608 Loc))));
4610 -- General case:
4612 -- Replace
4613 -- IW : I'Class := Obj;
4614 -- by
4615 -- type Equiv_Record is record ... end record;
4616 -- implicit subtype CW is <Class_Wide_Subtype>;
4617 -- Temp : CW := CW!(Obj'Address);
4618 -- IW : I'Class renames Displace (Temp, I'Tag);
4620 else
4621 -- Generate the equivalent record type
4623 Expand_Subtype_From_Expr
4624 (N => N,
4625 Unc_Type => Typ,
4626 Subtype_Indic => Object_Definition (N),
4627 Exp => Expression (N));
4629 if not Is_Interface (Etype (Expression (N))) then
4630 New_Expr := Relocate_Node (Expression (N));
4631 else
4632 New_Expr :=
4633 Make_Explicit_Dereference (Loc,
4634 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
4635 Make_Attribute_Reference (Loc,
4636 Prefix => Relocate_Node (Expression (N)),
4637 Attribute_Name => Name_Address)));
4638 end if;
4640 Decl_1 :=
4641 Make_Object_Declaration (Loc,
4642 Defining_Identifier =>
4643 Make_Temporary (Loc, 'D', New_Expr),
4644 Object_Definition =>
4645 New_Occurrence_Of
4646 (Etype (Object_Definition (N)), Loc),
4647 Expression =>
4648 Unchecked_Convert_To
4649 (Etype (Object_Definition (N)), New_Expr));
4651 Decl_2 :=
4652 Make_Object_Renaming_Declaration (Loc,
4653 Defining_Identifier => Make_Temporary (Loc, 'D'),
4654 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
4655 Name =>
4656 Unchecked_Convert_To (Typ,
4657 Make_Explicit_Dereference (Loc,
4658 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
4659 Make_Function_Call (Loc,
4660 Name =>
4661 New_Reference_To (RTE (RE_Displace), Loc),
4662 Parameter_Associations => New_List (
4663 Make_Attribute_Reference (Loc,
4664 Prefix =>
4665 New_Occurrence_Of
4666 (Defining_Identifier (Decl_1), Loc),
4667 Attribute_Name => Name_Address),
4669 Unchecked_Convert_To (RTE (RE_Tag),
4670 New_Reference_To
4671 (Node
4672 (First_Elmt
4673 (Access_Disp_Table (Iface))),
4674 Loc))))))));
4675 end if;
4677 Insert_Action (N, Decl_1);
4678 Rewrite (N, Decl_2);
4679 Analyze (N);
4681 -- Replace internal identifier of Decl_2 by the identifier
4682 -- found in the sources. We also have to exchange entities
4683 -- containing their defining identifiers to ensure the
4684 -- correct replacement of the object declaration by this
4685 -- object renaming declaration (because such definings
4686 -- identifier have been previously added by Enter_Name to
4687 -- the current scope). We must preserve the homonym chain
4688 -- of the source entity as well.
4690 Set_Chars (Defining_Identifier (N), Chars (Def_Id));
4691 Set_Homonym (Defining_Identifier (N), Homonym (Def_Id));
4692 Exchange_Entities (Defining_Identifier (N), Def_Id);
4693 end;
4694 end if;
4696 return;
4698 else
4699 -- In most cases, we must check that the initial value meets any
4700 -- constraint imposed by the declared type. However, there is one
4701 -- very important exception to this rule. If the entity has an
4702 -- unconstrained nominal subtype, then it acquired its constraints
4703 -- from the expression in the first place, and not only does this
4704 -- mean that the constraint check is not needed, but an attempt to
4705 -- perform the constraint check can cause order of elaboration
4706 -- problems.
4708 if not Is_Constr_Subt_For_U_Nominal (Typ) then
4710 -- If this is an allocator for an aggregate that has been
4711 -- allocated in place, delay checks until assignments are
4712 -- made, because the discriminants are not initialized.
4714 if Nkind (Expr) = N_Allocator
4715 and then No_Initialization (Expr)
4716 then
4717 null;
4718 else
4719 Apply_Constraint_Check (Expr, Typ);
4721 -- If the expression has been marked as requiring a range
4722 -- generate it now and reset the flag.
4724 if Do_Range_Check (Expr) then
4725 Set_Do_Range_Check (Expr, False);
4726 Generate_Range_Check (Expr, Typ, CE_Range_Check_Failed);
4727 end if;
4728 end if;
4729 end if;
4731 -- If the type is controlled and not inherently limited, then
4732 -- the target is adjusted after the copy and attached to the
4733 -- finalization list. However, no adjustment is done in the case
4734 -- where the object was initialized by a call to a function whose
4735 -- result is built in place, since no copy occurred. (Eventually
4736 -- we plan to support in-place function results for some cases
4737 -- of nonlimited types. ???) Similarly, no adjustment is required
4738 -- if we are going to rewrite the object declaration into a
4739 -- renaming declaration.
4741 if Needs_Finalization (Typ)
4742 and then not Is_Inherently_Limited_Type (Typ)
4743 and then not Rewrite_As_Renaming
4744 then
4745 Insert_Actions_After (Init_After,
4746 Make_Adjust_Call (
4747 Ref => New_Reference_To (Def_Id, Loc),
4748 Typ => Base_Type (Typ),
4749 Flist_Ref => Find_Final_List (Def_Id),
4750 With_Attach => Make_Integer_Literal (Loc, 1)));
4751 end if;
4753 -- For tagged types, when an init value is given, the tag has to
4754 -- be re-initialized separately in order to avoid the propagation
4755 -- of a wrong tag coming from a view conversion unless the type
4756 -- is class wide (in this case the tag comes from the init value).
4757 -- Suppress the tag assignment when VM_Target because VM tags are
4758 -- represented implicitly in objects. Ditto for types that are
4759 -- CPP_CLASS, and for initializations that are aggregates, because
4760 -- they have to have the right tag.
4762 if Is_Tagged_Type (Typ)
4763 and then not Is_Class_Wide_Type (Typ)
4764 and then not Is_CPP_Class (Typ)
4765 and then Tagged_Type_Expansion
4766 and then Nkind (Expr) /= N_Aggregate
4767 then
4768 -- The re-assignment of the tag has to be done even if the
4769 -- object is a constant.
4771 New_Ref :=
4772 Make_Selected_Component (Loc,
4773 Prefix => New_Reference_To (Def_Id, Loc),
4774 Selector_Name =>
4775 New_Reference_To (First_Tag_Component (Typ), Loc));
4777 Set_Assignment_OK (New_Ref);
4779 Insert_After (Init_After,
4780 Make_Assignment_Statement (Loc,
4781 Name => New_Ref,
4782 Expression =>
4783 Unchecked_Convert_To (RTE (RE_Tag),
4784 New_Reference_To
4785 (Node
4786 (First_Elmt
4787 (Access_Disp_Table (Base_Type (Typ)))),
4788 Loc))));
4790 elsif Is_Tagged_Type (Typ)
4791 and then Is_CPP_Constructor_Call (Expr)
4792 then
4793 -- The call to the initialization procedure does NOT freeze the
4794 -- object being initialized.
4796 Id_Ref := New_Reference_To (Def_Id, Loc);
4797 Set_Must_Not_Freeze (Id_Ref);
4798 Set_Assignment_OK (Id_Ref);
4800 Insert_Actions_After (Init_After,
4801 Build_Initialization_Call (Loc, Id_Ref, Typ,
4802 Constructor_Ref => Expr));
4804 -- We remove here the original call to the constructor
4805 -- to avoid its management in the backend
4807 Set_Expression (N, Empty);
4808 return;
4810 -- For discrete types, set the Is_Known_Valid flag if the
4811 -- initializing value is known to be valid.
4813 elsif Is_Discrete_Type (Typ) and then Expr_Known_Valid (Expr) then
4814 Set_Is_Known_Valid (Def_Id);
4816 elsif Is_Access_Type (Typ) then
4818 -- For access types set the Is_Known_Non_Null flag if the
4819 -- initializing value is known to be non-null. We can also set
4820 -- Can_Never_Be_Null if this is a constant.
4822 if Known_Non_Null (Expr) then
4823 Set_Is_Known_Non_Null (Def_Id, True);
4825 if Constant_Present (N) then
4826 Set_Can_Never_Be_Null (Def_Id);
4827 end if;
4828 end if;
4829 end if;
4831 -- If validity checking on copies, validate initial expression.
4832 -- But skip this if declaration is for a generic type, since it
4833 -- makes no sense to validate generic types. Not clear if this
4834 -- can happen for legal programs, but it definitely can arise
4835 -- from previous instantiation errors.
4837 if Validity_Checks_On
4838 and then Validity_Check_Copies
4839 and then not Is_Generic_Type (Etype (Def_Id))
4840 then
4841 Ensure_Valid (Expr);
4842 Set_Is_Known_Valid (Def_Id);
4843 end if;
4844 end if;
4846 -- Cases where the back end cannot handle the initialization directly
4847 -- In such cases, we expand an assignment that will be appropriately
4848 -- handled by Expand_N_Assignment_Statement.
4850 -- The exclusion of the unconstrained case is wrong, but for now it
4851 -- is too much trouble ???
4853 if (Is_Possibly_Unaligned_Slice (Expr)
4854 or else (Is_Possibly_Unaligned_Object (Expr)
4855 and then not Represented_As_Scalar (Etype (Expr))))
4857 -- The exclusion of the unconstrained case is wrong, but for now
4858 -- it is too much trouble ???
4860 and then not (Is_Array_Type (Etype (Expr))
4861 and then not Is_Constrained (Etype (Expr)))
4862 then
4863 declare
4864 Stat : constant Node_Id :=
4865 Make_Assignment_Statement (Loc,
4866 Name => New_Reference_To (Def_Id, Loc),
4867 Expression => Relocate_Node (Expr));
4868 begin
4869 Set_Expression (N, Empty);
4870 Set_No_Initialization (N);
4871 Set_Assignment_OK (Name (Stat));
4872 Set_No_Ctrl_Actions (Stat);
4873 Insert_After_And_Analyze (Init_After, Stat);
4874 end;
4875 end if;
4877 -- Final transformation, if the initializing expression is an entity
4878 -- for a variable with OK_To_Rename set, then we transform:
4880 -- X : typ := expr;
4882 -- into
4884 -- X : typ renames expr
4886 -- provided that X is not aliased. The aliased case has to be
4887 -- excluded in general because Expr will not be aliased in general.
4889 if Rewrite_As_Renaming then
4890 Rewrite (N,
4891 Make_Object_Renaming_Declaration (Loc,
4892 Defining_Identifier => Defining_Identifier (N),
4893 Subtype_Mark => Object_Definition (N),
4894 Name => Expr_Q));
4896 -- We do not analyze this renaming declaration, because all its
4897 -- components have already been analyzed, and if we were to go
4898 -- ahead and analyze it, we would in effect be trying to generate
4899 -- another declaration of X, which won't do!
4901 Set_Renamed_Object (Defining_Identifier (N), Expr_Q);
4902 Set_Analyzed (N);
4903 end if;
4905 end if;
4907 exception
4908 when RE_Not_Available =>
4909 return;
4910 end Expand_N_Object_Declaration;
4912 ---------------------------------
4913 -- Expand_N_Subtype_Indication --
4914 ---------------------------------
4916 -- Add a check on the range of the subtype. The static case is partially
4917 -- duplicated by Process_Range_Expr_In_Decl in Sem_Ch3, but we still need
4918 -- to check here for the static case in order to avoid generating
4919 -- extraneous expanded code. Also deal with validity checking.
4921 procedure Expand_N_Subtype_Indication (N : Node_Id) is
4922 Ran : constant Node_Id := Range_Expression (Constraint (N));
4923 Typ : constant Entity_Id := Entity (Subtype_Mark (N));
4925 begin
4926 if Nkind (Constraint (N)) = N_Range_Constraint then
4927 Validity_Check_Range (Range_Expression (Constraint (N)));
4928 end if;
4930 if Nkind_In (Parent (N), N_Constrained_Array_Definition, N_Slice) then
4931 Apply_Range_Check (Ran, Typ);
4932 end if;
4933 end Expand_N_Subtype_Indication;
4935 ---------------------------
4936 -- Expand_N_Variant_Part --
4937 ---------------------------
4939 -- If the last variant does not contain the Others choice, replace it with
4940 -- an N_Others_Choice node since Gigi always wants an Others. Note that we
4941 -- do not bother to call Analyze on the modified variant part, since it's
4942 -- only effect would be to compute the Others_Discrete_Choices node
4943 -- laboriously, and of course we already know the list of choices that
4944 -- corresponds to the others choice (it's the list we are replacing!)
4946 procedure Expand_N_Variant_Part (N : Node_Id) is
4947 Last_Var : constant Node_Id := Last_Non_Pragma (Variants (N));
4948 Others_Node : Node_Id;
4949 begin
4950 if Nkind (First (Discrete_Choices (Last_Var))) /= N_Others_Choice then
4951 Others_Node := Make_Others_Choice (Sloc (Last_Var));
4952 Set_Others_Discrete_Choices
4953 (Others_Node, Discrete_Choices (Last_Var));
4954 Set_Discrete_Choices (Last_Var, New_List (Others_Node));
4955 end if;
4956 end Expand_N_Variant_Part;
4958 ---------------------------------
4959 -- Expand_Previous_Access_Type --
4960 ---------------------------------
4962 procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
4963 T : Entity_Id := First_Entity (Current_Scope);
4965 begin
4966 -- Find all access types declared in the current scope, whose
4967 -- designated type is Def_Id. If it does not have a Master_Id,
4968 -- create one now.
4970 while Present (T) loop
4971 if Is_Access_Type (T)
4972 and then Designated_Type (T) = Def_Id
4973 and then No (Master_Id (T))
4974 then
4975 Build_Master_Entity (Def_Id);
4976 Build_Master_Renaming (Parent (Def_Id), T);
4977 end if;
4979 Next_Entity (T);
4980 end loop;
4981 end Expand_Previous_Access_Type;
4983 ------------------------------
4984 -- Expand_Record_Controller --
4985 ------------------------------
4987 procedure Expand_Record_Controller (T : Entity_Id) is
4988 Def : Node_Id := Type_Definition (Parent (T));
4989 Comp_List : Node_Id;
4990 Comp_Decl : Node_Id;
4991 Loc : Source_Ptr;
4992 First_Comp : Node_Id;
4993 Controller_Type : Entity_Id;
4994 Ent : Entity_Id;
4996 begin
4997 if Nkind (Def) = N_Derived_Type_Definition then
4998 Def := Record_Extension_Part (Def);
4999 end if;
5001 if Null_Present (Def) then
5002 Set_Component_List (Def,
5003 Make_Component_List (Sloc (Def),
5004 Component_Items => Empty_List,
5005 Variant_Part => Empty,
5006 Null_Present => True));
5007 end if;
5009 Comp_List := Component_List (Def);
5011 if Null_Present (Comp_List)
5012 or else Is_Empty_List (Component_Items (Comp_List))
5013 then
5014 Loc := Sloc (Comp_List);
5015 else
5016 Loc := Sloc (First (Component_Items (Comp_List)));
5017 end if;
5019 if Is_Inherently_Limited_Type (T) then
5020 Controller_Type := RTE (RE_Limited_Record_Controller);
5021 else
5022 Controller_Type := RTE (RE_Record_Controller);
5023 end if;
5025 Ent := Make_Defining_Identifier (Loc, Name_uController);
5027 Comp_Decl :=
5028 Make_Component_Declaration (Loc,
5029 Defining_Identifier => Ent,
5030 Component_Definition =>
5031 Make_Component_Definition (Loc,
5032 Aliased_Present => False,
5033 Subtype_Indication => New_Reference_To (Controller_Type, Loc)));
5035 if Null_Present (Comp_List)
5036 or else Is_Empty_List (Component_Items (Comp_List))
5037 then
5038 Set_Component_Items (Comp_List, New_List (Comp_Decl));
5039 Set_Null_Present (Comp_List, False);
5041 else
5042 -- The controller cannot be placed before the _Parent field since
5043 -- gigi lays out field in order and _parent must be first to preserve
5044 -- the polymorphism of tagged types.
5046 First_Comp := First (Component_Items (Comp_List));
5048 if not Is_Tagged_Type (T) then
5049 Insert_Before (First_Comp, Comp_Decl);
5051 -- if T is a tagged type, place controller declaration after parent
5052 -- field and after eventual tags of interface types.
5054 else
5055 while Present (First_Comp)
5056 and then
5057 (Chars (Defining_Identifier (First_Comp)) = Name_uParent
5058 or else Is_Tag (Defining_Identifier (First_Comp))
5060 -- Ada 2005 (AI-251): The following condition covers secondary
5061 -- tags but also the adjacent component containing the offset
5062 -- to the base of the object (component generated if the parent
5063 -- has discriminants --- see Add_Interface_Tag_Components).
5064 -- This is required to avoid the addition of the controller
5065 -- between the secondary tag and its adjacent component.
5067 or else Present
5068 (Related_Type
5069 (Defining_Identifier (First_Comp))))
5070 loop
5071 Next (First_Comp);
5072 end loop;
5074 -- An empty tagged extension might consist only of the parent
5075 -- component. Otherwise insert the controller before the first
5076 -- component that is neither parent nor tag.
5078 if Present (First_Comp) then
5079 Insert_Before (First_Comp, Comp_Decl);
5080 else
5081 Append (Comp_Decl, Component_Items (Comp_List));
5082 end if;
5083 end if;
5084 end if;
5086 Push_Scope (T);
5087 Analyze (Comp_Decl);
5088 Set_Ekind (Ent, E_Component);
5089 Init_Component_Location (Ent);
5091 -- Move the _controller entity ahead in the list of internal entities
5092 -- of the enclosing record so that it is selected instead of a
5093 -- potentially inherited one.
5095 declare
5096 E : constant Entity_Id := Last_Entity (T);
5097 Comp : Entity_Id;
5099 begin
5100 pragma Assert (Chars (E) = Name_uController);
5102 Set_Next_Entity (E, First_Entity (T));
5103 Set_First_Entity (T, E);
5105 Comp := Next_Entity (E);
5106 while Next_Entity (Comp) /= E loop
5107 Next_Entity (Comp);
5108 end loop;
5110 Set_Next_Entity (Comp, Empty);
5111 Set_Last_Entity (T, Comp);
5112 end;
5114 End_Scope;
5116 exception
5117 when RE_Not_Available =>
5118 return;
5119 end Expand_Record_Controller;
5121 ------------------------
5122 -- Expand_Tagged_Root --
5123 ------------------------
5125 procedure Expand_Tagged_Root (T : Entity_Id) is
5126 Def : constant Node_Id := Type_Definition (Parent (T));
5127 Comp_List : Node_Id;
5128 Comp_Decl : Node_Id;
5129 Sloc_N : Source_Ptr;
5131 begin
5132 if Null_Present (Def) then
5133 Set_Component_List (Def,
5134 Make_Component_List (Sloc (Def),
5135 Component_Items => Empty_List,
5136 Variant_Part => Empty,
5137 Null_Present => True));
5138 end if;
5140 Comp_List := Component_List (Def);
5142 if Null_Present (Comp_List)
5143 or else Is_Empty_List (Component_Items (Comp_List))
5144 then
5145 Sloc_N := Sloc (Comp_List);
5146 else
5147 Sloc_N := Sloc (First (Component_Items (Comp_List)));
5148 end if;
5150 Comp_Decl :=
5151 Make_Component_Declaration (Sloc_N,
5152 Defining_Identifier => First_Tag_Component (T),
5153 Component_Definition =>
5154 Make_Component_Definition (Sloc_N,
5155 Aliased_Present => False,
5156 Subtype_Indication => New_Reference_To (RTE (RE_Tag), Sloc_N)));
5158 if Null_Present (Comp_List)
5159 or else Is_Empty_List (Component_Items (Comp_List))
5160 then
5161 Set_Component_Items (Comp_List, New_List (Comp_Decl));
5162 Set_Null_Present (Comp_List, False);
5164 else
5165 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
5166 end if;
5168 -- We don't Analyze the whole expansion because the tag component has
5169 -- already been analyzed previously. Here we just insure that the tree
5170 -- is coherent with the semantic decoration
5172 Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
5174 exception
5175 when RE_Not_Available =>
5176 return;
5177 end Expand_Tagged_Root;
5179 ----------------------
5180 -- Clean_Task_Names --
5181 ----------------------
5183 procedure Clean_Task_Names
5184 (Typ : Entity_Id;
5185 Proc_Id : Entity_Id)
5187 begin
5188 if Has_Task (Typ)
5189 and then not Restriction_Active (No_Implicit_Heap_Allocations)
5190 and then not Global_Discard_Names
5191 and then Tagged_Type_Expansion
5192 then
5193 Set_Uses_Sec_Stack (Proc_Id);
5194 end if;
5195 end Clean_Task_Names;
5197 ------------------------------
5198 -- Expand_Freeze_Array_Type --
5199 ------------------------------
5201 procedure Expand_Freeze_Array_Type (N : Node_Id) is
5202 Typ : constant Entity_Id := Entity (N);
5203 Comp_Typ : constant Entity_Id := Component_Type (Typ);
5204 Base : constant Entity_Id := Base_Type (Typ);
5206 begin
5207 if not Is_Bit_Packed_Array (Typ) then
5209 -- If the component contains tasks, so does the array type. This may
5210 -- not be indicated in the array type because the component may have
5211 -- been a private type at the point of definition. Same if component
5212 -- type is controlled.
5214 Set_Has_Task (Base, Has_Task (Comp_Typ));
5215 Set_Has_Controlled_Component (Base,
5216 Has_Controlled_Component (Comp_Typ)
5217 or else Is_Controlled (Comp_Typ));
5219 if No (Init_Proc (Base)) then
5221 -- If this is an anonymous array created for a declaration with
5222 -- an initial value, its init_proc will never be called. The
5223 -- initial value itself may have been expanded into assignments,
5224 -- in which case the object declaration is carries the
5225 -- No_Initialization flag.
5227 if Is_Itype (Base)
5228 and then Nkind (Associated_Node_For_Itype (Base)) =
5229 N_Object_Declaration
5230 and then (Present (Expression (Associated_Node_For_Itype (Base)))
5231 or else
5232 No_Initialization (Associated_Node_For_Itype (Base)))
5233 then
5234 null;
5236 -- We do not need an init proc for string or wide [wide] string,
5237 -- since the only time these need initialization in normalize or
5238 -- initialize scalars mode, and these types are treated specially
5239 -- and do not need initialization procedures.
5241 elsif Root_Type (Base) = Standard_String
5242 or else Root_Type (Base) = Standard_Wide_String
5243 or else Root_Type (Base) = Standard_Wide_Wide_String
5244 then
5245 null;
5247 -- Otherwise we have to build an init proc for the subtype
5249 else
5250 Build_Array_Init_Proc (Base, N);
5251 end if;
5252 end if;
5254 if Typ = Base then
5255 if Has_Controlled_Component (Base) then
5256 Build_Controlling_Procs (Base);
5258 if not Is_Limited_Type (Comp_Typ)
5259 and then Number_Dimensions (Typ) = 1
5260 then
5261 Build_Slice_Assignment (Typ);
5262 end if;
5264 elsif Ekind (Comp_Typ) = E_Anonymous_Access_Type
5265 and then Needs_Finalization (Directly_Designated_Type (Comp_Typ))
5266 then
5267 Set_Associated_Final_Chain (Comp_Typ, Add_Final_Chain (Typ));
5268 end if;
5269 end if;
5271 -- For packed case, default initialization, except if the component type
5272 -- is itself a packed structure with an initialization procedure, or
5273 -- initialize/normalize scalars active, and we have a base type, or the
5274 -- type is public, because in that case a client might specify
5275 -- Normalize_Scalars and there better be a public Init_Proc for it.
5277 elsif (Present (Init_Proc (Component_Type (Base)))
5278 and then No (Base_Init_Proc (Base)))
5279 or else (Init_Or_Norm_Scalars and then Base = Typ)
5280 or else Is_Public (Typ)
5281 then
5282 Build_Array_Init_Proc (Base, N);
5283 end if;
5284 end Expand_Freeze_Array_Type;
5286 ------------------------------------
5287 -- Expand_Freeze_Enumeration_Type --
5288 ------------------------------------
5290 procedure Expand_Freeze_Enumeration_Type (N : Node_Id) is
5291 Typ : constant Entity_Id := Entity (N);
5292 Loc : constant Source_Ptr := Sloc (Typ);
5293 Ent : Entity_Id;
5294 Lst : List_Id;
5295 Num : Nat;
5296 Arr : Entity_Id;
5297 Fent : Entity_Id;
5298 Ityp : Entity_Id;
5299 Is_Contiguous : Boolean;
5300 Pos_Expr : Node_Id;
5301 Last_Repval : Uint;
5303 Func : Entity_Id;
5304 pragma Warnings (Off, Func);
5306 begin
5307 -- Various optimizations possible if given representation is contiguous
5309 Is_Contiguous := True;
5311 Ent := First_Literal (Typ);
5312 Last_Repval := Enumeration_Rep (Ent);
5314 Next_Literal (Ent);
5315 while Present (Ent) loop
5316 if Enumeration_Rep (Ent) - Last_Repval /= 1 then
5317 Is_Contiguous := False;
5318 exit;
5319 else
5320 Last_Repval := Enumeration_Rep (Ent);
5321 end if;
5323 Next_Literal (Ent);
5324 end loop;
5326 if Is_Contiguous then
5327 Set_Has_Contiguous_Rep (Typ);
5328 Ent := First_Literal (Typ);
5329 Num := 1;
5330 Lst := New_List (New_Reference_To (Ent, Sloc (Ent)));
5332 else
5333 -- Build list of literal references
5335 Lst := New_List;
5336 Num := 0;
5338 Ent := First_Literal (Typ);
5339 while Present (Ent) loop
5340 Append_To (Lst, New_Reference_To (Ent, Sloc (Ent)));
5341 Num := Num + 1;
5342 Next_Literal (Ent);
5343 end loop;
5344 end if;
5346 -- Now build an array declaration
5348 -- typA : array (Natural range 0 .. num - 1) of ctype :=
5349 -- (v, v, v, v, v, ....)
5351 -- where ctype is the corresponding integer type. If the representation
5352 -- is contiguous, we only keep the first literal, which provides the
5353 -- offset for Pos_To_Rep computations.
5355 Arr :=
5356 Make_Defining_Identifier (Loc,
5357 Chars => New_External_Name (Chars (Typ), 'A'));
5359 Append_Freeze_Action (Typ,
5360 Make_Object_Declaration (Loc,
5361 Defining_Identifier => Arr,
5362 Constant_Present => True,
5364 Object_Definition =>
5365 Make_Constrained_Array_Definition (Loc,
5366 Discrete_Subtype_Definitions => New_List (
5367 Make_Subtype_Indication (Loc,
5368 Subtype_Mark => New_Reference_To (Standard_Natural, Loc),
5369 Constraint =>
5370 Make_Range_Constraint (Loc,
5371 Range_Expression =>
5372 Make_Range (Loc,
5373 Low_Bound =>
5374 Make_Integer_Literal (Loc, 0),
5375 High_Bound =>
5376 Make_Integer_Literal (Loc, Num - 1))))),
5378 Component_Definition =>
5379 Make_Component_Definition (Loc,
5380 Aliased_Present => False,
5381 Subtype_Indication => New_Reference_To (Typ, Loc))),
5383 Expression =>
5384 Make_Aggregate (Loc,
5385 Expressions => Lst)));
5387 Set_Enum_Pos_To_Rep (Typ, Arr);
5389 -- Now we build the function that converts representation values to
5390 -- position values. This function has the form:
5392 -- function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
5393 -- begin
5394 -- case ityp!(A) is
5395 -- when enum-lit'Enum_Rep => return posval;
5396 -- when enum-lit'Enum_Rep => return posval;
5397 -- ...
5398 -- when others =>
5399 -- [raise Constraint_Error when F "invalid data"]
5400 -- return -1;
5401 -- end case;
5402 -- end;
5404 -- Note: the F parameter determines whether the others case (no valid
5405 -- representation) raises Constraint_Error or returns a unique value
5406 -- of minus one. The latter case is used, e.g. in 'Valid code.
5408 -- Note: the reason we use Enum_Rep values in the case here is to avoid
5409 -- the code generator making inappropriate assumptions about the range
5410 -- of the values in the case where the value is invalid. ityp is a
5411 -- signed or unsigned integer type of appropriate width.
5413 -- Note: if exceptions are not supported, then we suppress the raise
5414 -- and return -1 unconditionally (this is an erroneous program in any
5415 -- case and there is no obligation to raise Constraint_Error here!) We
5416 -- also do this if pragma Restrictions (No_Exceptions) is active.
5418 -- Is this right??? What about No_Exception_Propagation???
5420 -- Representations are signed
5422 if Enumeration_Rep (First_Literal (Typ)) < 0 then
5424 -- The underlying type is signed. Reset the Is_Unsigned_Type
5425 -- explicitly, because it might have been inherited from
5426 -- parent type.
5428 Set_Is_Unsigned_Type (Typ, False);
5430 if Esize (Typ) <= Standard_Integer_Size then
5431 Ityp := Standard_Integer;
5432 else
5433 Ityp := Universal_Integer;
5434 end if;
5436 -- Representations are unsigned
5438 else
5439 if Esize (Typ) <= Standard_Integer_Size then
5440 Ityp := RTE (RE_Unsigned);
5441 else
5442 Ityp := RTE (RE_Long_Long_Unsigned);
5443 end if;
5444 end if;
5446 -- The body of the function is a case statement. First collect case
5447 -- alternatives, or optimize the contiguous case.
5449 Lst := New_List;
5451 -- If representation is contiguous, Pos is computed by subtracting
5452 -- the representation of the first literal.
5454 if Is_Contiguous then
5455 Ent := First_Literal (Typ);
5457 if Enumeration_Rep (Ent) = Last_Repval then
5459 -- Another special case: for a single literal, Pos is zero
5461 Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
5463 else
5464 Pos_Expr :=
5465 Convert_To (Standard_Integer,
5466 Make_Op_Subtract (Loc,
5467 Left_Opnd =>
5468 Unchecked_Convert_To (Ityp,
5469 Make_Identifier (Loc, Name_uA)),
5470 Right_Opnd =>
5471 Make_Integer_Literal (Loc,
5472 Intval =>
5473 Enumeration_Rep (First_Literal (Typ)))));
5474 end if;
5476 Append_To (Lst,
5477 Make_Case_Statement_Alternative (Loc,
5478 Discrete_Choices => New_List (
5479 Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
5480 Low_Bound =>
5481 Make_Integer_Literal (Loc,
5482 Intval => Enumeration_Rep (Ent)),
5483 High_Bound =>
5484 Make_Integer_Literal (Loc, Intval => Last_Repval))),
5486 Statements => New_List (
5487 Make_Simple_Return_Statement (Loc,
5488 Expression => Pos_Expr))));
5490 else
5491 Ent := First_Literal (Typ);
5492 while Present (Ent) loop
5493 Append_To (Lst,
5494 Make_Case_Statement_Alternative (Loc,
5495 Discrete_Choices => New_List (
5496 Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
5497 Intval => Enumeration_Rep (Ent))),
5499 Statements => New_List (
5500 Make_Simple_Return_Statement (Loc,
5501 Expression =>
5502 Make_Integer_Literal (Loc,
5503 Intval => Enumeration_Pos (Ent))))));
5505 Next_Literal (Ent);
5506 end loop;
5507 end if;
5509 -- In normal mode, add the others clause with the test
5511 if not No_Exception_Handlers_Set then
5512 Append_To (Lst,
5513 Make_Case_Statement_Alternative (Loc,
5514 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
5515 Statements => New_List (
5516 Make_Raise_Constraint_Error (Loc,
5517 Condition => Make_Identifier (Loc, Name_uF),
5518 Reason => CE_Invalid_Data),
5519 Make_Simple_Return_Statement (Loc,
5520 Expression =>
5521 Make_Integer_Literal (Loc, -1)))));
5523 -- If either of the restrictions No_Exceptions_Handlers/Propagation is
5524 -- active then return -1 (we cannot usefully raise Constraint_Error in
5525 -- this case). See description above for further details.
5527 else
5528 Append_To (Lst,
5529 Make_Case_Statement_Alternative (Loc,
5530 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
5531 Statements => New_List (
5532 Make_Simple_Return_Statement (Loc,
5533 Expression =>
5534 Make_Integer_Literal (Loc, -1)))));
5535 end if;
5537 -- Now we can build the function body
5539 Fent :=
5540 Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
5542 Func :=
5543 Make_Subprogram_Body (Loc,
5544 Specification =>
5545 Make_Function_Specification (Loc,
5546 Defining_Unit_Name => Fent,
5547 Parameter_Specifications => New_List (
5548 Make_Parameter_Specification (Loc,
5549 Defining_Identifier =>
5550 Make_Defining_Identifier (Loc, Name_uA),
5551 Parameter_Type => New_Reference_To (Typ, Loc)),
5552 Make_Parameter_Specification (Loc,
5553 Defining_Identifier =>
5554 Make_Defining_Identifier (Loc, Name_uF),
5555 Parameter_Type => New_Reference_To (Standard_Boolean, Loc))),
5557 Result_Definition => New_Reference_To (Standard_Integer, Loc)),
5559 Declarations => Empty_List,
5561 Handled_Statement_Sequence =>
5562 Make_Handled_Sequence_Of_Statements (Loc,
5563 Statements => New_List (
5564 Make_Case_Statement (Loc,
5565 Expression =>
5566 Unchecked_Convert_To (Ityp,
5567 Make_Identifier (Loc, Name_uA)),
5568 Alternatives => Lst))));
5570 Set_TSS (Typ, Fent);
5571 Set_Is_Pure (Fent);
5573 if not Debug_Generated_Code then
5574 Set_Debug_Info_Off (Fent);
5575 end if;
5577 exception
5578 when RE_Not_Available =>
5579 return;
5580 end Expand_Freeze_Enumeration_Type;
5582 -------------------------------
5583 -- Expand_Freeze_Record_Type --
5584 -------------------------------
5586 procedure Expand_Freeze_Record_Type (N : Node_Id) is
5587 Def_Id : constant Node_Id := Entity (N);
5588 Type_Decl : constant Node_Id := Parent (Def_Id);
5589 Comp : Entity_Id;
5590 Comp_Typ : Entity_Id;
5591 Has_Static_DT : Boolean := False;
5592 Predef_List : List_Id;
5594 Flist : Entity_Id := Empty;
5595 -- Finalization list allocated for the case of a type with anonymous
5596 -- access components whose designated type is potentially controlled.
5598 Renamed_Eq : Node_Id := Empty;
5599 -- Defining unit name for the predefined equality function in the case
5600 -- where the type has a primitive operation that is a renaming of
5601 -- predefined equality (but only if there is also an overriding
5602 -- user-defined equality function). Used to pass this entity from
5603 -- Make_Predefined_Primitive_Specs to Predefined_Primitive_Bodies.
5605 Wrapper_Decl_List : List_Id := No_List;
5606 Wrapper_Body_List : List_Id := No_List;
5607 Null_Proc_Decl_List : List_Id := No_List;
5609 -- Start of processing for Expand_Freeze_Record_Type
5611 begin
5612 -- Build discriminant checking functions if not a derived type (for
5613 -- derived types that are not tagged types, always use the discriminant
5614 -- checking functions of the parent type). However, for untagged types
5615 -- the derivation may have taken place before the parent was frozen, so
5616 -- we copy explicitly the discriminant checking functions from the
5617 -- parent into the components of the derived type.
5619 if not Is_Derived_Type (Def_Id)
5620 or else Has_New_Non_Standard_Rep (Def_Id)
5621 or else Is_Tagged_Type (Def_Id)
5622 then
5623 Build_Discr_Checking_Funcs (Type_Decl);
5625 elsif Is_Derived_Type (Def_Id)
5626 and then not Is_Tagged_Type (Def_Id)
5628 -- If we have a derived Unchecked_Union, we do not inherit the
5629 -- discriminant checking functions from the parent type since the
5630 -- discriminants are non existent.
5632 and then not Is_Unchecked_Union (Def_Id)
5633 and then Has_Discriminants (Def_Id)
5634 then
5635 declare
5636 Old_Comp : Entity_Id;
5638 begin
5639 Old_Comp :=
5640 First_Component (Base_Type (Underlying_Type (Etype (Def_Id))));
5641 Comp := First_Component (Def_Id);
5642 while Present (Comp) loop
5643 if Ekind (Comp) = E_Component
5644 and then Chars (Comp) = Chars (Old_Comp)
5645 then
5646 Set_Discriminant_Checking_Func (Comp,
5647 Discriminant_Checking_Func (Old_Comp));
5648 end if;
5650 Next_Component (Old_Comp);
5651 Next_Component (Comp);
5652 end loop;
5653 end;
5654 end if;
5656 if Is_Derived_Type (Def_Id)
5657 and then Is_Limited_Type (Def_Id)
5658 and then Is_Tagged_Type (Def_Id)
5659 then
5660 Check_Stream_Attributes (Def_Id);
5661 end if;
5663 -- Update task and controlled component flags, because some of the
5664 -- component types may have been private at the point of the record
5665 -- declaration.
5667 Comp := First_Component (Def_Id);
5669 while Present (Comp) loop
5670 Comp_Typ := Etype (Comp);
5672 if Has_Task (Comp_Typ) then
5673 Set_Has_Task (Def_Id);
5675 -- Do not set Has_Controlled_Component on a class-wide equivalent
5676 -- type. See Make_CW_Equivalent_Type.
5678 elsif not Is_Class_Wide_Equivalent_Type (Def_Id)
5679 and then (Has_Controlled_Component (Comp_Typ)
5680 or else (Chars (Comp) /= Name_uParent
5681 and then Is_Controlled (Comp_Typ)))
5682 then
5683 Set_Has_Controlled_Component (Def_Id);
5685 elsif Ekind (Comp_Typ) = E_Anonymous_Access_Type
5686 and then Needs_Finalization (Directly_Designated_Type (Comp_Typ))
5687 then
5688 if No (Flist) then
5689 Flist := Add_Final_Chain (Def_Id);
5690 end if;
5692 Set_Associated_Final_Chain (Comp_Typ, Flist);
5693 end if;
5695 Next_Component (Comp);
5696 end loop;
5698 -- Handle constructors of non-tagged CPP_Class types
5700 if not Is_Tagged_Type (Def_Id) and then Is_CPP_Class (Def_Id) then
5701 Set_CPP_Constructors (Def_Id);
5702 end if;
5704 -- Creation of the Dispatch Table. Note that a Dispatch Table is built
5705 -- for regular tagged types as well as for Ada types deriving from a C++
5706 -- Class, but not for tagged types directly corresponding to C++ classes
5707 -- In the later case we assume that it is created in the C++ side and we
5708 -- just use it.
5710 if Is_Tagged_Type (Def_Id) then
5711 Has_Static_DT :=
5712 Static_Dispatch_Tables
5713 and then Is_Library_Level_Tagged_Type (Def_Id);
5715 -- Add the _Tag component
5717 if Underlying_Type (Etype (Def_Id)) = Def_Id then
5718 Expand_Tagged_Root (Def_Id);
5719 end if;
5721 if Is_CPP_Class (Def_Id) then
5722 Set_All_DT_Position (Def_Id);
5723 Set_CPP_Constructors (Def_Id);
5725 -- Create the tag entities with a minimum decoration
5727 if Tagged_Type_Expansion then
5728 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
5729 end if;
5731 else
5732 if not Has_Static_DT then
5734 -- Usually inherited primitives are not delayed but the first
5735 -- Ada extension of a CPP_Class is an exception since the
5736 -- address of the inherited subprogram has to be inserted in
5737 -- the new Ada Dispatch Table and this is a freezing action.
5739 -- Similarly, if this is an inherited operation whose parent is
5740 -- not frozen yet, it is not in the DT of the parent, and we
5741 -- generate an explicit freeze node for the inherited operation
5742 -- so that it is properly inserted in the DT of the current
5743 -- type.
5745 declare
5746 Elmt : Elmt_Id := First_Elmt (Primitive_Operations (Def_Id));
5747 Subp : Entity_Id;
5749 begin
5750 while Present (Elmt) loop
5751 Subp := Node (Elmt);
5753 if Present (Alias (Subp)) then
5754 if Is_CPP_Class (Etype (Def_Id)) then
5755 Set_Has_Delayed_Freeze (Subp);
5757 elsif Has_Delayed_Freeze (Alias (Subp))
5758 and then not Is_Frozen (Alias (Subp))
5759 then
5760 Set_Is_Frozen (Subp, False);
5761 Set_Has_Delayed_Freeze (Subp);
5762 end if;
5763 end if;
5765 Next_Elmt (Elmt);
5766 end loop;
5767 end;
5768 end if;
5770 -- Unfreeze momentarily the type to add the predefined primitives
5771 -- operations. The reason we unfreeze is so that these predefined
5772 -- operations will indeed end up as primitive operations (which
5773 -- must be before the freeze point).
5775 Set_Is_Frozen (Def_Id, False);
5777 -- Do not add the spec of predefined primitives in case of
5778 -- CPP tagged type derivations that have convention CPP.
5780 if Is_CPP_Class (Root_Type (Def_Id))
5781 and then Convention (Def_Id) = Convention_CPP
5782 then
5783 null;
5785 -- Do not add the spec of the predefined primitives if we are
5786 -- compiling under restriction No_Dispatching_Calls
5788 elsif not Restriction_Active (No_Dispatching_Calls) then
5789 Make_Predefined_Primitive_Specs
5790 (Def_Id, Predef_List, Renamed_Eq);
5791 Insert_List_Before_And_Analyze (N, Predef_List);
5792 end if;
5794 -- Ada 2005 (AI-391): For a nonabstract null extension, create
5795 -- wrapper functions for each nonoverridden inherited function
5796 -- with a controlling result of the type. The wrapper for such
5797 -- a function returns an extension aggregate that invokes the
5798 -- the parent function.
5800 if Ada_Version >= Ada_05
5801 and then not Is_Abstract_Type (Def_Id)
5802 and then Is_Null_Extension (Def_Id)
5803 then
5804 Make_Controlling_Function_Wrappers
5805 (Def_Id, Wrapper_Decl_List, Wrapper_Body_List);
5806 Insert_List_Before_And_Analyze (N, Wrapper_Decl_List);
5807 end if;
5809 -- Ada 2005 (AI-251): For a nonabstract type extension, build
5810 -- null procedure declarations for each set of homographic null
5811 -- procedures that are inherited from interface types but not
5812 -- overridden. This is done to ensure that the dispatch table
5813 -- entry associated with such null primitives are properly filled.
5815 if Ada_Version >= Ada_05
5816 and then Etype (Def_Id) /= Def_Id
5817 and then not Is_Abstract_Type (Def_Id)
5818 then
5819 Make_Null_Procedure_Specs (Def_Id, Null_Proc_Decl_List);
5820 Insert_Actions (N, Null_Proc_Decl_List);
5821 end if;
5823 Set_Is_Frozen (Def_Id);
5824 Set_All_DT_Position (Def_Id);
5826 -- Add the controlled component before the freezing actions
5827 -- referenced in those actions.
5829 if Has_New_Controlled_Component (Def_Id) then
5830 Expand_Record_Controller (Def_Id);
5831 end if;
5833 -- Create and decorate the tags. Suppress their creation when
5834 -- VM_Target because the dispatching mechanism is handled
5835 -- internally by the VMs.
5837 if Tagged_Type_Expansion then
5838 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
5840 -- Generate dispatch table of locally defined tagged type.
5841 -- Dispatch tables of library level tagged types are built
5842 -- later (see Analyze_Declarations).
5844 if not Has_Static_DT then
5845 Append_Freeze_Actions (Def_Id, Make_DT (Def_Id));
5846 end if;
5847 end if;
5849 -- If the type has unknown discriminants, propagate dispatching
5850 -- information to its underlying record view, which does not get
5851 -- its own dispatch table.
5853 if Is_Derived_Type (Def_Id)
5854 and then Has_Unknown_Discriminants (Def_Id)
5855 and then Present (Underlying_Record_View (Def_Id))
5856 then
5857 declare
5858 Rep : constant Entity_Id :=
5859 Underlying_Record_View (Def_Id);
5860 begin
5861 Set_Access_Disp_Table
5862 (Rep, Access_Disp_Table (Def_Id));
5863 Set_Dispatch_Table_Wrappers
5864 (Rep, Dispatch_Table_Wrappers (Def_Id));
5865 Set_Primitive_Operations
5866 (Rep, Primitive_Operations (Def_Id));
5867 end;
5868 end if;
5870 -- Make sure that the primitives Initialize, Adjust and Finalize
5871 -- are Frozen before other TSS subprograms. We don't want them
5872 -- Frozen inside.
5874 if Is_Controlled (Def_Id) then
5875 if not Is_Limited_Type (Def_Id) then
5876 Append_Freeze_Actions (Def_Id,
5877 Freeze_Entity
5878 (Find_Prim_Op (Def_Id, Name_Adjust), Sloc (Def_Id)));
5879 end if;
5881 Append_Freeze_Actions (Def_Id,
5882 Freeze_Entity
5883 (Find_Prim_Op (Def_Id, Name_Initialize), Sloc (Def_Id)));
5885 Append_Freeze_Actions (Def_Id,
5886 Freeze_Entity
5887 (Find_Prim_Op (Def_Id, Name_Finalize), Sloc (Def_Id)));
5888 end if;
5890 -- Freeze rest of primitive operations. There is no need to handle
5891 -- the predefined primitives if we are compiling under restriction
5892 -- No_Dispatching_Calls
5894 if not Restriction_Active (No_Dispatching_Calls) then
5895 Append_Freeze_Actions
5896 (Def_Id, Predefined_Primitive_Freeze (Def_Id));
5897 end if;
5898 end if;
5900 -- In the non-tagged case, an equality function is provided only for
5901 -- variant records (that are not unchecked unions).
5903 elsif Has_Discriminants (Def_Id)
5904 and then not Is_Limited_Type (Def_Id)
5905 then
5906 declare
5907 Comps : constant Node_Id :=
5908 Component_List (Type_Definition (Type_Decl));
5910 begin
5911 if Present (Comps)
5912 and then Present (Variant_Part (Comps))
5913 then
5914 Build_Variant_Record_Equality (Def_Id);
5915 end if;
5916 end;
5917 end if;
5919 -- Before building the record initialization procedure, if we are
5920 -- dealing with a concurrent record value type, then we must go through
5921 -- the discriminants, exchanging discriminals between the concurrent
5922 -- type and the concurrent record value type. See the section "Handling
5923 -- of Discriminants" in the Einfo spec for details.
5925 if Is_Concurrent_Record_Type (Def_Id)
5926 and then Has_Discriminants (Def_Id)
5927 then
5928 declare
5929 Ctyp : constant Entity_Id :=
5930 Corresponding_Concurrent_Type (Def_Id);
5931 Conc_Discr : Entity_Id;
5932 Rec_Discr : Entity_Id;
5933 Temp : Entity_Id;
5935 begin
5936 Conc_Discr := First_Discriminant (Ctyp);
5937 Rec_Discr := First_Discriminant (Def_Id);
5938 while Present (Conc_Discr) loop
5939 Temp := Discriminal (Conc_Discr);
5940 Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
5941 Set_Discriminal (Rec_Discr, Temp);
5943 Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
5944 Set_Discriminal_Link (Discriminal (Rec_Discr), Rec_Discr);
5946 Next_Discriminant (Conc_Discr);
5947 Next_Discriminant (Rec_Discr);
5948 end loop;
5949 end;
5950 end if;
5952 if Has_Controlled_Component (Def_Id) then
5953 if No (Controller_Component (Def_Id)) then
5954 Expand_Record_Controller (Def_Id);
5955 end if;
5957 Build_Controlling_Procs (Def_Id);
5958 end if;
5960 Adjust_Discriminants (Def_Id);
5962 if Tagged_Type_Expansion or else not Is_Interface (Def_Id) then
5964 -- Do not need init for interfaces on e.g. CIL since they're
5965 -- abstract. Helps operation of peverify (the PE Verify tool).
5967 Build_Record_Init_Proc (Type_Decl, Def_Id);
5968 end if;
5970 -- For tagged type that are not interfaces, build bodies of primitive
5971 -- operations. Note that we do this after building the record
5972 -- initialization procedure, since the primitive operations may need
5973 -- the initialization routine. There is no need to add predefined
5974 -- primitives of interfaces because all their predefined primitives
5975 -- are abstract.
5977 if Is_Tagged_Type (Def_Id)
5978 and then not Is_Interface (Def_Id)
5979 then
5980 -- Do not add the body of predefined primitives in case of
5981 -- CPP tagged type derivations that have convention CPP.
5983 if Is_CPP_Class (Root_Type (Def_Id))
5984 and then Convention (Def_Id) = Convention_CPP
5985 then
5986 null;
5988 -- Do not add the body of the predefined primitives if we are
5989 -- compiling under restriction No_Dispatching_Calls or if we are
5990 -- compiling a CPP tagged type.
5992 elsif not Restriction_Active (No_Dispatching_Calls) then
5993 Predef_List := Predefined_Primitive_Bodies (Def_Id, Renamed_Eq);
5994 Append_Freeze_Actions (Def_Id, Predef_List);
5995 end if;
5997 -- Ada 2005 (AI-391): If any wrappers were created for nonoverridden
5998 -- inherited functions, then add their bodies to the freeze actions.
6000 if Present (Wrapper_Body_List) then
6001 Append_Freeze_Actions (Def_Id, Wrapper_Body_List);
6002 end if;
6004 -- Create extra formals for the primitive operations of the type.
6005 -- This must be done before analyzing the body of the initialization
6006 -- procedure, because a self-referential type might call one of these
6007 -- primitives in the body of the init_proc itself.
6009 declare
6010 Elmt : Elmt_Id;
6011 Subp : Entity_Id;
6013 begin
6014 Elmt := First_Elmt (Primitive_Operations (Def_Id));
6015 while Present (Elmt) loop
6016 Subp := Node (Elmt);
6017 if not Has_Foreign_Convention (Subp)
6018 and then not Is_Predefined_Dispatching_Operation (Subp)
6019 then
6020 Create_Extra_Formals (Subp);
6021 end if;
6023 Next_Elmt (Elmt);
6024 end loop;
6025 end;
6026 end if;
6027 end Expand_Freeze_Record_Type;
6029 ------------------------------
6030 -- Freeze_Stream_Operations --
6031 ------------------------------
6033 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
6034 Names : constant array (1 .. 4) of TSS_Name_Type :=
6035 (TSS_Stream_Input,
6036 TSS_Stream_Output,
6037 TSS_Stream_Read,
6038 TSS_Stream_Write);
6039 Stream_Op : Entity_Id;
6041 begin
6042 -- Primitive operations of tagged types are frozen when the dispatch
6043 -- table is constructed.
6045 if not Comes_From_Source (Typ)
6046 or else Is_Tagged_Type (Typ)
6047 then
6048 return;
6049 end if;
6051 for J in Names'Range loop
6052 Stream_Op := TSS (Typ, Names (J));
6054 if Present (Stream_Op)
6055 and then Is_Subprogram (Stream_Op)
6056 and then Nkind (Unit_Declaration_Node (Stream_Op)) =
6057 N_Subprogram_Declaration
6058 and then not Is_Frozen (Stream_Op)
6059 then
6060 Append_Freeze_Actions
6061 (Typ, Freeze_Entity (Stream_Op, Sloc (N)));
6062 end if;
6063 end loop;
6064 end Freeze_Stream_Operations;
6066 -----------------
6067 -- Freeze_Type --
6068 -----------------
6070 -- Full type declarations are expanded at the point at which the type is
6071 -- frozen. The formal N is the Freeze_Node for the type. Any statements or
6072 -- declarations generated by the freezing (e.g. the procedure generated
6073 -- for initialization) are chained in the Actions field list of the freeze
6074 -- node using Append_Freeze_Actions.
6076 function Freeze_Type (N : Node_Id) return Boolean is
6077 Def_Id : constant Entity_Id := Entity (N);
6078 RACW_Seen : Boolean := False;
6079 Result : Boolean := False;
6081 begin
6082 -- Process associated access types needing special processing
6084 if Present (Access_Types_To_Process (N)) then
6085 declare
6086 E : Elmt_Id := First_Elmt (Access_Types_To_Process (N));
6087 begin
6088 while Present (E) loop
6090 if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
6091 Validate_RACW_Primitives (Node (E));
6092 RACW_Seen := True;
6093 end if;
6095 E := Next_Elmt (E);
6096 end loop;
6097 end;
6099 if RACW_Seen then
6101 -- If there are RACWs designating this type, make stubs now
6103 Remote_Types_Tagged_Full_View_Encountered (Def_Id);
6104 end if;
6105 end if;
6107 -- Freeze processing for record types
6109 if Is_Record_Type (Def_Id) then
6110 if Ekind (Def_Id) = E_Record_Type then
6111 Expand_Freeze_Record_Type (N);
6113 -- The subtype may have been declared before the type was frozen. If
6114 -- the type has controlled components it is necessary to create the
6115 -- entity for the controller explicitly because it did not exist at
6116 -- the point of the subtype declaration. Only the entity is needed,
6117 -- the back-end will obtain the layout from the type. This is only
6118 -- necessary if this is constrained subtype whose component list is
6119 -- not shared with the base type.
6121 elsif Ekind (Def_Id) = E_Record_Subtype
6122 and then Has_Discriminants (Def_Id)
6123 and then Last_Entity (Def_Id) /= Last_Entity (Base_Type (Def_Id))
6124 and then Present (Controller_Component (Def_Id))
6125 then
6126 declare
6127 Old_C : constant Entity_Id := Controller_Component (Def_Id);
6128 New_C : Entity_Id;
6130 begin
6131 if Scope (Old_C) = Base_Type (Def_Id) then
6133 -- The entity is the one in the parent. Create new one
6135 New_C := New_Copy (Old_C);
6136 Set_Parent (New_C, Parent (Old_C));
6137 Push_Scope (Def_Id);
6138 Enter_Name (New_C);
6139 End_Scope;
6140 end if;
6141 end;
6143 if Is_Itype (Def_Id)
6144 and then Is_Record_Type (Underlying_Type (Scope (Def_Id)))
6145 then
6146 -- The freeze node is only used to introduce the controller,
6147 -- the back-end has no use for it for a discriminated
6148 -- component.
6150 Set_Freeze_Node (Def_Id, Empty);
6151 Set_Has_Delayed_Freeze (Def_Id, False);
6152 Result := True;
6153 end if;
6155 -- Similar process if the controller of the subtype is not present
6156 -- but the parent has it. This can happen with constrained
6157 -- record components where the subtype is an itype.
6159 elsif Ekind (Def_Id) = E_Record_Subtype
6160 and then Is_Itype (Def_Id)
6161 and then No (Controller_Component (Def_Id))
6162 and then Present (Controller_Component (Etype (Def_Id)))
6163 then
6164 declare
6165 Old_C : constant Entity_Id :=
6166 Controller_Component (Etype (Def_Id));
6167 New_C : constant Entity_Id := New_Copy (Old_C);
6169 begin
6170 Set_Next_Entity (New_C, First_Entity (Def_Id));
6171 Set_First_Entity (Def_Id, New_C);
6173 -- The freeze node is only used to introduce the controller,
6174 -- the back-end has no use for it for a discriminated
6175 -- component.
6177 Set_Freeze_Node (Def_Id, Empty);
6178 Set_Has_Delayed_Freeze (Def_Id, False);
6179 Result := True;
6180 end;
6181 end if;
6183 -- Freeze processing for array types
6185 elsif Is_Array_Type (Def_Id) then
6186 Expand_Freeze_Array_Type (N);
6188 -- Freeze processing for access types
6190 -- For pool-specific access types, find out the pool object used for
6191 -- this type, needs actual expansion of it in some cases. Here are the
6192 -- different cases :
6194 -- 1. Rep Clause "for Def_Id'Storage_Size use 0;"
6195 -- ---> don't use any storage pool
6197 -- 2. Rep Clause : for Def_Id'Storage_Size use Expr.
6198 -- Expand:
6199 -- Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
6201 -- 3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
6202 -- ---> Storage Pool is the specified one
6204 -- See GNAT Pool packages in the Run-Time for more details
6206 elsif Ekind_In (Def_Id, E_Access_Type, E_General_Access_Type) then
6207 declare
6208 Loc : constant Source_Ptr := Sloc (N);
6209 Desig_Type : constant Entity_Id := Designated_Type (Def_Id);
6210 Pool_Object : Entity_Id;
6212 Freeze_Action_Typ : Entity_Id;
6214 begin
6215 -- Case 1
6217 -- Rep Clause "for Def_Id'Storage_Size use 0;"
6218 -- ---> don't use any storage pool
6220 if No_Pool_Assigned (Def_Id) then
6221 null;
6223 -- Case 2
6225 -- Rep Clause : for Def_Id'Storage_Size use Expr.
6226 -- ---> Expand:
6227 -- Def_Id__Pool : Stack_Bounded_Pool
6228 -- (Expr, DT'Size, DT'Alignment);
6230 elsif Has_Storage_Size_Clause (Def_Id) then
6231 declare
6232 DT_Size : Node_Id;
6233 DT_Align : Node_Id;
6235 begin
6236 -- For unconstrained composite types we give a size of zero
6237 -- so that the pool knows that it needs a special algorithm
6238 -- for variable size object allocation.
6240 if Is_Composite_Type (Desig_Type)
6241 and then not Is_Constrained (Desig_Type)
6242 then
6243 DT_Size :=
6244 Make_Integer_Literal (Loc, 0);
6246 DT_Align :=
6247 Make_Integer_Literal (Loc, Maximum_Alignment);
6249 else
6250 DT_Size :=
6251 Make_Attribute_Reference (Loc,
6252 Prefix => New_Reference_To (Desig_Type, Loc),
6253 Attribute_Name => Name_Max_Size_In_Storage_Elements);
6255 DT_Align :=
6256 Make_Attribute_Reference (Loc,
6257 Prefix => New_Reference_To (Desig_Type, Loc),
6258 Attribute_Name => Name_Alignment);
6259 end if;
6261 Pool_Object :=
6262 Make_Defining_Identifier (Loc,
6263 Chars => New_External_Name (Chars (Def_Id), 'P'));
6265 -- We put the code associated with the pools in the entity
6266 -- that has the later freeze node, usually the access type
6267 -- but it can also be the designated_type; because the pool
6268 -- code requires both those types to be frozen
6270 if Is_Frozen (Desig_Type)
6271 and then (No (Freeze_Node (Desig_Type))
6272 or else Analyzed (Freeze_Node (Desig_Type)))
6273 then
6274 Freeze_Action_Typ := Def_Id;
6276 -- A Taft amendment type cannot get the freeze actions
6277 -- since the full view is not there.
6279 elsif Is_Incomplete_Or_Private_Type (Desig_Type)
6280 and then No (Full_View (Desig_Type))
6281 then
6282 Freeze_Action_Typ := Def_Id;
6284 else
6285 Freeze_Action_Typ := Desig_Type;
6286 end if;
6288 Append_Freeze_Action (Freeze_Action_Typ,
6289 Make_Object_Declaration (Loc,
6290 Defining_Identifier => Pool_Object,
6291 Object_Definition =>
6292 Make_Subtype_Indication (Loc,
6293 Subtype_Mark =>
6294 New_Reference_To
6295 (RTE (RE_Stack_Bounded_Pool), Loc),
6297 Constraint =>
6298 Make_Index_Or_Discriminant_Constraint (Loc,
6299 Constraints => New_List (
6301 -- First discriminant is the Pool Size
6303 New_Reference_To (
6304 Storage_Size_Variable (Def_Id), Loc),
6306 -- Second discriminant is the element size
6308 DT_Size,
6310 -- Third discriminant is the alignment
6312 DT_Align)))));
6313 end;
6315 Set_Associated_Storage_Pool (Def_Id, Pool_Object);
6317 -- Case 3
6319 -- Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
6320 -- ---> Storage Pool is the specified one
6322 elsif Present (Associated_Storage_Pool (Def_Id)) then
6324 -- Nothing to do the associated storage pool has been attached
6325 -- when analyzing the rep. clause
6327 null;
6328 end if;
6330 -- For access-to-controlled types (including class-wide types and
6331 -- Taft-amendment types which potentially have controlled
6332 -- components), expand the list controller object that will store
6333 -- the dynamically allocated objects. Do not do this
6334 -- transformation for expander-generated access types, but do it
6335 -- for types that are the full view of types derived from other
6336 -- private types. Also suppress the list controller in the case
6337 -- of a designated type with convention Java, since this is used
6338 -- when binding to Java API specs, where there's no equivalent of
6339 -- a finalization list and we don't want to pull in the
6340 -- finalization support if not needed.
6342 if not Comes_From_Source (Def_Id)
6343 and then not Has_Private_Declaration (Def_Id)
6344 then
6345 null;
6347 elsif (Needs_Finalization (Desig_Type)
6348 and then Convention (Desig_Type) /= Convention_Java
6349 and then Convention (Desig_Type) /= Convention_CIL)
6350 or else
6351 (Is_Incomplete_Or_Private_Type (Desig_Type)
6352 and then No (Full_View (Desig_Type))
6354 -- An exception is made for types defined in the run-time
6355 -- because Ada.Tags.Tag itself is such a type and cannot
6356 -- afford this unnecessary overhead that would generates a
6357 -- loop in the expansion scheme...
6359 and then not In_Runtime (Def_Id)
6361 -- Another exception is if Restrictions (No_Finalization)
6362 -- is active, since then we know nothing is controlled.
6364 and then not Restriction_Active (No_Finalization))
6366 -- If the designated type is not frozen yet, its controlled
6367 -- status must be retrieved explicitly.
6369 or else (Is_Array_Type (Desig_Type)
6370 and then not Is_Frozen (Desig_Type)
6371 and then Needs_Finalization (Component_Type (Desig_Type)))
6373 -- The designated type has controlled anonymous access
6374 -- discriminants.
6376 or else Has_Controlled_Coextensions (Desig_Type)
6377 then
6378 Set_Associated_Final_Chain (Def_Id, Add_Final_Chain (Def_Id));
6379 end if;
6380 end;
6382 -- Freeze processing for enumeration types
6384 elsif Ekind (Def_Id) = E_Enumeration_Type then
6386 -- We only have something to do if we have a non-standard
6387 -- representation (i.e. at least one literal whose pos value
6388 -- is not the same as its representation)
6390 if Has_Non_Standard_Rep (Def_Id) then
6391 Expand_Freeze_Enumeration_Type (N);
6392 end if;
6394 -- Private types that are completed by a derivation from a private
6395 -- type have an internally generated full view, that needs to be
6396 -- frozen. This must be done explicitly because the two views share
6397 -- the freeze node, and the underlying full view is not visible when
6398 -- the freeze node is analyzed.
6400 elsif Is_Private_Type (Def_Id)
6401 and then Is_Derived_Type (Def_Id)
6402 and then Present (Full_View (Def_Id))
6403 and then Is_Itype (Full_View (Def_Id))
6404 and then Has_Private_Declaration (Full_View (Def_Id))
6405 and then Freeze_Node (Full_View (Def_Id)) = N
6406 then
6407 Set_Entity (N, Full_View (Def_Id));
6408 Result := Freeze_Type (N);
6409 Set_Entity (N, Def_Id);
6411 -- All other types require no expander action. There are such cases
6412 -- (e.g. task types and protected types). In such cases, the freeze
6413 -- nodes are there for use by Gigi.
6415 end if;
6417 Freeze_Stream_Operations (N, Def_Id);
6418 return Result;
6420 exception
6421 when RE_Not_Available =>
6422 return False;
6423 end Freeze_Type;
6425 -------------------------
6426 -- Get_Simple_Init_Val --
6427 -------------------------
6429 function Get_Simple_Init_Val
6430 (T : Entity_Id;
6431 N : Node_Id;
6432 Size : Uint := No_Uint) return Node_Id
6434 Loc : constant Source_Ptr := Sloc (N);
6435 Val : Node_Id;
6436 Result : Node_Id;
6437 Val_RE : RE_Id;
6439 Size_To_Use : Uint;
6440 -- This is the size to be used for computation of the appropriate
6441 -- initial value for the Normalize_Scalars and Initialize_Scalars case.
6443 IV_Attribute : constant Boolean :=
6444 Nkind (N) = N_Attribute_Reference
6445 and then Attribute_Name (N) = Name_Invalid_Value;
6447 Lo_Bound : Uint;
6448 Hi_Bound : Uint;
6449 -- These are the values computed by the procedure Check_Subtype_Bounds
6451 procedure Check_Subtype_Bounds;
6452 -- This procedure examines the subtype T, and its ancestor subtypes and
6453 -- derived types to determine the best known information about the
6454 -- bounds of the subtype. After the call Lo_Bound is set either to
6455 -- No_Uint if no information can be determined, or to a value which
6456 -- represents a known low bound, i.e. a valid value of the subtype can
6457 -- not be less than this value. Hi_Bound is similarly set to a known
6458 -- high bound (valid value cannot be greater than this).
6460 --------------------------
6461 -- Check_Subtype_Bounds --
6462 --------------------------
6464 procedure Check_Subtype_Bounds is
6465 ST1 : Entity_Id;
6466 ST2 : Entity_Id;
6467 Lo : Node_Id;
6468 Hi : Node_Id;
6469 Loval : Uint;
6470 Hival : Uint;
6472 begin
6473 Lo_Bound := No_Uint;
6474 Hi_Bound := No_Uint;
6476 -- Loop to climb ancestor subtypes and derived types
6478 ST1 := T;
6479 loop
6480 if not Is_Discrete_Type (ST1) then
6481 return;
6482 end if;
6484 Lo := Type_Low_Bound (ST1);
6485 Hi := Type_High_Bound (ST1);
6487 if Compile_Time_Known_Value (Lo) then
6488 Loval := Expr_Value (Lo);
6490 if Lo_Bound = No_Uint or else Lo_Bound < Loval then
6491 Lo_Bound := Loval;
6492 end if;
6493 end if;
6495 if Compile_Time_Known_Value (Hi) then
6496 Hival := Expr_Value (Hi);
6498 if Hi_Bound = No_Uint or else Hi_Bound > Hival then
6499 Hi_Bound := Hival;
6500 end if;
6501 end if;
6503 ST2 := Ancestor_Subtype (ST1);
6505 if No (ST2) then
6506 ST2 := Etype (ST1);
6507 end if;
6509 exit when ST1 = ST2;
6510 ST1 := ST2;
6511 end loop;
6512 end Check_Subtype_Bounds;
6514 -- Start of processing for Get_Simple_Init_Val
6516 begin
6517 -- For a private type, we should always have an underlying type
6518 -- (because this was already checked in Needs_Simple_Initialization).
6519 -- What we do is to get the value for the underlying type and then do
6520 -- an Unchecked_Convert to the private type.
6522 if Is_Private_Type (T) then
6523 Val := Get_Simple_Init_Val (Underlying_Type (T), N, Size);
6525 -- A special case, if the underlying value is null, then qualify it
6526 -- with the underlying type, so that the null is properly typed
6527 -- Similarly, if it is an aggregate it must be qualified, because an
6528 -- unchecked conversion does not provide a context for it.
6530 if Nkind_In (Val, N_Null, N_Aggregate) then
6531 Val :=
6532 Make_Qualified_Expression (Loc,
6533 Subtype_Mark =>
6534 New_Occurrence_Of (Underlying_Type (T), Loc),
6535 Expression => Val);
6536 end if;
6538 Result := Unchecked_Convert_To (T, Val);
6540 -- Don't truncate result (important for Initialize/Normalize_Scalars)
6542 if Nkind (Result) = N_Unchecked_Type_Conversion
6543 and then Is_Scalar_Type (Underlying_Type (T))
6544 then
6545 Set_No_Truncation (Result);
6546 end if;
6548 return Result;
6550 -- For scalars, we must have normalize/initialize scalars case, or
6551 -- if the node N is an 'Invalid_Value attribute node.
6553 elsif Is_Scalar_Type (T) then
6554 pragma Assert (Init_Or_Norm_Scalars or IV_Attribute);
6556 -- Compute size of object. If it is given by the caller, we can use
6557 -- it directly, otherwise we use Esize (T) as an estimate. As far as
6558 -- we know this covers all cases correctly.
6560 if Size = No_Uint or else Size <= Uint_0 then
6561 Size_To_Use := UI_Max (Uint_1, Esize (T));
6562 else
6563 Size_To_Use := Size;
6564 end if;
6566 -- Maximum size to use is 64 bits, since we will create values
6567 -- of type Unsigned_64 and the range must fit this type.
6569 if Size_To_Use /= No_Uint and then Size_To_Use > Uint_64 then
6570 Size_To_Use := Uint_64;
6571 end if;
6573 -- Check known bounds of subtype
6575 Check_Subtype_Bounds;
6577 -- Processing for Normalize_Scalars case
6579 if Normalize_Scalars and then not IV_Attribute then
6581 -- If zero is invalid, it is a convenient value to use that is
6582 -- for sure an appropriate invalid value in all situations.
6584 if Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
6585 Val := Make_Integer_Literal (Loc, 0);
6587 -- Cases where all one bits is the appropriate invalid value
6589 -- For modular types, all 1 bits is either invalid or valid. If
6590 -- it is valid, then there is nothing that can be done since there
6591 -- are no invalid values (we ruled out zero already).
6593 -- For signed integer types that have no negative values, either
6594 -- there is room for negative values, or there is not. If there
6595 -- is, then all 1 bits may be interpreted as minus one, which is
6596 -- certainly invalid. Alternatively it is treated as the largest
6597 -- positive value, in which case the observation for modular types
6598 -- still applies.
6600 -- For float types, all 1-bits is a NaN (not a number), which is
6601 -- certainly an appropriately invalid value.
6603 elsif Is_Unsigned_Type (T)
6604 or else Is_Floating_Point_Type (T)
6605 or else Is_Enumeration_Type (T)
6606 then
6607 Val := Make_Integer_Literal (Loc, 2 ** Size_To_Use - 1);
6609 -- Resolve as Unsigned_64, because the largest number we
6610 -- can generate is out of range of universal integer.
6612 Analyze_And_Resolve (Val, RTE (RE_Unsigned_64));
6614 -- Case of signed types
6616 else
6617 declare
6618 Signed_Size : constant Uint :=
6619 UI_Min (Uint_63, Size_To_Use - 1);
6621 begin
6622 -- Normally we like to use the most negative number. The
6623 -- one exception is when this number is in the known
6624 -- subtype range and the largest positive number is not in
6625 -- the known subtype range.
6627 -- For this exceptional case, use largest positive value
6629 if Lo_Bound /= No_Uint and then Hi_Bound /= No_Uint
6630 and then Lo_Bound <= (-(2 ** Signed_Size))
6631 and then Hi_Bound < 2 ** Signed_Size
6632 then
6633 Val := Make_Integer_Literal (Loc, 2 ** Signed_Size - 1);
6635 -- Normal case of largest negative value
6637 else
6638 Val := Make_Integer_Literal (Loc, -(2 ** Signed_Size));
6639 end if;
6640 end;
6641 end if;
6643 -- Here for Initialize_Scalars case (or Invalid_Value attribute used)
6645 else
6646 -- For float types, use float values from System.Scalar_Values
6648 if Is_Floating_Point_Type (T) then
6649 if Root_Type (T) = Standard_Short_Float then
6650 Val_RE := RE_IS_Isf;
6651 elsif Root_Type (T) = Standard_Float then
6652 Val_RE := RE_IS_Ifl;
6653 elsif Root_Type (T) = Standard_Long_Float then
6654 Val_RE := RE_IS_Ilf;
6655 else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
6656 Val_RE := RE_IS_Ill;
6657 end if;
6659 -- If zero is invalid, use zero values from System.Scalar_Values
6661 elsif Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
6662 if Size_To_Use <= 8 then
6663 Val_RE := RE_IS_Iz1;
6664 elsif Size_To_Use <= 16 then
6665 Val_RE := RE_IS_Iz2;
6666 elsif Size_To_Use <= 32 then
6667 Val_RE := RE_IS_Iz4;
6668 else
6669 Val_RE := RE_IS_Iz8;
6670 end if;
6672 -- For unsigned, use unsigned values from System.Scalar_Values
6674 elsif Is_Unsigned_Type (T) then
6675 if Size_To_Use <= 8 then
6676 Val_RE := RE_IS_Iu1;
6677 elsif Size_To_Use <= 16 then
6678 Val_RE := RE_IS_Iu2;
6679 elsif Size_To_Use <= 32 then
6680 Val_RE := RE_IS_Iu4;
6681 else
6682 Val_RE := RE_IS_Iu8;
6683 end if;
6685 -- For signed, use signed values from System.Scalar_Values
6687 else
6688 if Size_To_Use <= 8 then
6689 Val_RE := RE_IS_Is1;
6690 elsif Size_To_Use <= 16 then
6691 Val_RE := RE_IS_Is2;
6692 elsif Size_To_Use <= 32 then
6693 Val_RE := RE_IS_Is4;
6694 else
6695 Val_RE := RE_IS_Is8;
6696 end if;
6697 end if;
6699 Val := New_Occurrence_Of (RTE (Val_RE), Loc);
6700 end if;
6702 -- The final expression is obtained by doing an unchecked conversion
6703 -- of this result to the base type of the required subtype. We use
6704 -- the base type to avoid the unchecked conversion from chopping
6705 -- bits, and then we set Kill_Range_Check to preserve the "bad"
6706 -- value.
6708 Result := Unchecked_Convert_To (Base_Type (T), Val);
6710 -- Ensure result is not truncated, since we want the "bad" bits
6711 -- and also kill range check on result.
6713 if Nkind (Result) = N_Unchecked_Type_Conversion then
6714 Set_No_Truncation (Result);
6715 Set_Kill_Range_Check (Result, True);
6716 end if;
6718 return Result;
6720 -- String or Wide_[Wide]_String (must have Initialize_Scalars set)
6722 elsif Root_Type (T) = Standard_String
6723 or else
6724 Root_Type (T) = Standard_Wide_String
6725 or else
6726 Root_Type (T) = Standard_Wide_Wide_String
6727 then
6728 pragma Assert (Init_Or_Norm_Scalars);
6730 return
6731 Make_Aggregate (Loc,
6732 Component_Associations => New_List (
6733 Make_Component_Association (Loc,
6734 Choices => New_List (
6735 Make_Others_Choice (Loc)),
6736 Expression =>
6737 Get_Simple_Init_Val
6738 (Component_Type (T), N, Esize (Root_Type (T))))));
6740 -- Access type is initialized to null
6742 elsif Is_Access_Type (T) then
6743 return
6744 Make_Null (Loc);
6746 -- No other possibilities should arise, since we should only be
6747 -- calling Get_Simple_Init_Val if Needs_Simple_Initialization
6748 -- returned True, indicating one of the above cases held.
6750 else
6751 raise Program_Error;
6752 end if;
6754 exception
6755 when RE_Not_Available =>
6756 return Empty;
6757 end Get_Simple_Init_Val;
6759 ------------------------------
6760 -- Has_New_Non_Standard_Rep --
6761 ------------------------------
6763 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
6764 begin
6765 if not Is_Derived_Type (T) then
6766 return Has_Non_Standard_Rep (T)
6767 or else Has_Non_Standard_Rep (Root_Type (T));
6769 -- If Has_Non_Standard_Rep is not set on the derived type, the
6770 -- representation is fully inherited.
6772 elsif not Has_Non_Standard_Rep (T) then
6773 return False;
6775 else
6776 return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
6778 -- May need a more precise check here: the First_Rep_Item may
6779 -- be a stream attribute, which does not affect the representation
6780 -- of the type ???
6781 end if;
6782 end Has_New_Non_Standard_Rep;
6784 ----------------
6785 -- In_Runtime --
6786 ----------------
6788 function In_Runtime (E : Entity_Id) return Boolean is
6789 S1 : Entity_Id;
6791 begin
6792 S1 := Scope (E);
6793 while Scope (S1) /= Standard_Standard loop
6794 S1 := Scope (S1);
6795 end loop;
6797 return Chars (S1) = Name_System or else Chars (S1) = Name_Ada;
6798 end In_Runtime;
6800 ----------------------------
6801 -- Initialization_Warning --
6802 ----------------------------
6804 procedure Initialization_Warning (E : Entity_Id) is
6805 Warning_Needed : Boolean;
6807 begin
6808 Warning_Needed := False;
6810 if Ekind (Current_Scope) = E_Package
6811 and then Static_Elaboration_Desired (Current_Scope)
6812 then
6813 if Is_Type (E) then
6814 if Is_Record_Type (E) then
6815 if Has_Discriminants (E)
6816 or else Is_Limited_Type (E)
6817 or else Has_Non_Standard_Rep (E)
6818 then
6819 Warning_Needed := True;
6821 else
6822 -- Verify that at least one component has an initialization
6823 -- expression. No need for a warning on a type if all its
6824 -- components have no initialization.
6826 declare
6827 Comp : Entity_Id;
6829 begin
6830 Comp := First_Component (E);
6831 while Present (Comp) loop
6832 if Ekind (Comp) = E_Discriminant
6833 or else
6834 (Nkind (Parent (Comp)) = N_Component_Declaration
6835 and then Present (Expression (Parent (Comp))))
6836 then
6837 Warning_Needed := True;
6838 exit;
6839 end if;
6841 Next_Component (Comp);
6842 end loop;
6843 end;
6844 end if;
6846 if Warning_Needed then
6847 Error_Msg_N
6848 ("Objects of the type cannot be initialized " &
6849 "statically by default?",
6850 Parent (E));
6851 end if;
6852 end if;
6854 else
6855 Error_Msg_N ("Object cannot be initialized statically?", E);
6856 end if;
6857 end if;
6858 end Initialization_Warning;
6860 ------------------
6861 -- Init_Formals --
6862 ------------------
6864 function Init_Formals (Typ : Entity_Id) return List_Id is
6865 Loc : constant Source_Ptr := Sloc (Typ);
6866 Formals : List_Id;
6868 begin
6869 -- First parameter is always _Init : in out typ. Note that we need
6870 -- this to be in/out because in the case of the task record value,
6871 -- there are default record fields (_Priority, _Size, -Task_Info)
6872 -- that may be referenced in the generated initialization routine.
6874 Formals := New_List (
6875 Make_Parameter_Specification (Loc,
6876 Defining_Identifier =>
6877 Make_Defining_Identifier (Loc, Name_uInit),
6878 In_Present => True,
6879 Out_Present => True,
6880 Parameter_Type => New_Reference_To (Typ, Loc)));
6882 -- For task record value, or type that contains tasks, add two more
6883 -- formals, _Master : Master_Id and _Chain : in out Activation_Chain
6884 -- We also add these parameters for the task record type case.
6886 if Has_Task (Typ)
6887 or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
6888 then
6889 Append_To (Formals,
6890 Make_Parameter_Specification (Loc,
6891 Defining_Identifier =>
6892 Make_Defining_Identifier (Loc, Name_uMaster),
6893 Parameter_Type => New_Reference_To (RTE (RE_Master_Id), Loc)));
6895 Append_To (Formals,
6896 Make_Parameter_Specification (Loc,
6897 Defining_Identifier =>
6898 Make_Defining_Identifier (Loc, Name_uChain),
6899 In_Present => True,
6900 Out_Present => True,
6901 Parameter_Type =>
6902 New_Reference_To (RTE (RE_Activation_Chain), Loc)));
6904 Append_To (Formals,
6905 Make_Parameter_Specification (Loc,
6906 Defining_Identifier =>
6907 Make_Defining_Identifier (Loc, Name_uTask_Name),
6908 In_Present => True,
6909 Parameter_Type =>
6910 New_Reference_To (Standard_String, Loc)));
6911 end if;
6913 return Formals;
6915 exception
6916 when RE_Not_Available =>
6917 return Empty_List;
6918 end Init_Formals;
6920 -------------------------
6921 -- Init_Secondary_Tags --
6922 -------------------------
6924 procedure Init_Secondary_Tags
6925 (Typ : Entity_Id;
6926 Target : Node_Id;
6927 Stmts_List : List_Id;
6928 Fixed_Comps : Boolean := True;
6929 Variable_Comps : Boolean := True)
6931 Loc : constant Source_Ptr := Sloc (Target);
6933 procedure Inherit_CPP_Tag
6934 (Typ : Entity_Id;
6935 Iface : Entity_Id;
6936 Tag_Comp : Entity_Id;
6937 Iface_Tag : Node_Id);
6938 -- Inherit the C++ tag of the secondary dispatch table of Typ associated
6939 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
6941 procedure Initialize_Tag
6942 (Typ : Entity_Id;
6943 Iface : Entity_Id;
6944 Tag_Comp : Entity_Id;
6945 Iface_Tag : Node_Id);
6946 -- Initialize the tag of the secondary dispatch table of Typ associated
6947 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
6948 -- Compiling under the CPP full ABI compatibility mode, if the ancestor
6949 -- of Typ CPP tagged type we generate code to inherit the contents of
6950 -- the dispatch table directly from the ancestor.
6952 ---------------------
6953 -- Inherit_CPP_Tag --
6954 ---------------------
6956 procedure Inherit_CPP_Tag
6957 (Typ : Entity_Id;
6958 Iface : Entity_Id;
6959 Tag_Comp : Entity_Id;
6960 Iface_Tag : Node_Id)
6962 begin
6963 pragma Assert (Is_CPP_Class (Etype (Typ)));
6965 Append_To (Stmts_List,
6966 Build_Inherit_Prims (Loc,
6967 Typ => Iface,
6968 Old_Tag_Node =>
6969 Make_Selected_Component (Loc,
6970 Prefix => New_Copy_Tree (Target),
6971 Selector_Name => New_Reference_To (Tag_Comp, Loc)),
6972 New_Tag_Node =>
6973 New_Reference_To (Iface_Tag, Loc),
6974 Num_Prims =>
6975 UI_To_Int (DT_Entry_Count (First_Tag_Component (Iface)))));
6976 end Inherit_CPP_Tag;
6978 --------------------
6979 -- Initialize_Tag --
6980 --------------------
6982 procedure Initialize_Tag
6983 (Typ : Entity_Id;
6984 Iface : Entity_Id;
6985 Tag_Comp : Entity_Id;
6986 Iface_Tag : Node_Id)
6988 Comp_Typ : Entity_Id;
6989 Offset_To_Top_Comp : Entity_Id := Empty;
6991 begin
6992 -- Initialize the pointer to the secondary DT associated with the
6993 -- interface.
6995 if not Is_Ancestor (Iface, Typ) then
6996 Append_To (Stmts_List,
6997 Make_Assignment_Statement (Loc,
6998 Name =>
6999 Make_Selected_Component (Loc,
7000 Prefix => New_Copy_Tree (Target),
7001 Selector_Name => New_Reference_To (Tag_Comp, Loc)),
7002 Expression =>
7003 New_Reference_To (Iface_Tag, Loc)));
7004 end if;
7006 Comp_Typ := Scope (Tag_Comp);
7008 -- Initialize the entries of the table of interfaces. We generate a
7009 -- different call when the parent of the type has variable size
7010 -- components.
7012 if Comp_Typ /= Etype (Comp_Typ)
7013 and then Is_Variable_Size_Record (Etype (Comp_Typ))
7014 and then Chars (Tag_Comp) /= Name_uTag
7015 then
7016 pragma Assert (Present (DT_Offset_To_Top_Func (Tag_Comp)));
7018 -- Issue error if Set_Dynamic_Offset_To_Top is not available in a
7019 -- configurable run-time environment.
7021 if not RTE_Available (RE_Set_Dynamic_Offset_To_Top) then
7022 Error_Msg_CRT
7023 ("variable size record with interface types", Typ);
7024 return;
7025 end if;
7027 -- Generate:
7028 -- Set_Dynamic_Offset_To_Top
7029 -- (This => Init,
7030 -- Interface_T => Iface'Tag,
7031 -- Offset_Value => n,
7032 -- Offset_Func => Fn'Address)
7034 Append_To (Stmts_List,
7035 Make_Procedure_Call_Statement (Loc,
7036 Name => New_Reference_To
7037 (RTE (RE_Set_Dynamic_Offset_To_Top), Loc),
7038 Parameter_Associations => New_List (
7039 Make_Attribute_Reference (Loc,
7040 Prefix => New_Copy_Tree (Target),
7041 Attribute_Name => Name_Address),
7043 Unchecked_Convert_To (RTE (RE_Tag),
7044 New_Reference_To
7045 (Node (First_Elmt (Access_Disp_Table (Iface))),
7046 Loc)),
7048 Unchecked_Convert_To
7049 (RTE (RE_Storage_Offset),
7050 Make_Attribute_Reference (Loc,
7051 Prefix =>
7052 Make_Selected_Component (Loc,
7053 Prefix => New_Copy_Tree (Target),
7054 Selector_Name =>
7055 New_Reference_To (Tag_Comp, Loc)),
7056 Attribute_Name => Name_Position)),
7058 Unchecked_Convert_To (RTE (RE_Offset_To_Top_Function_Ptr),
7059 Make_Attribute_Reference (Loc,
7060 Prefix => New_Reference_To
7061 (DT_Offset_To_Top_Func (Tag_Comp), Loc),
7062 Attribute_Name => Name_Address)))));
7064 -- In this case the next component stores the value of the
7065 -- offset to the top.
7067 Offset_To_Top_Comp := Next_Entity (Tag_Comp);
7068 pragma Assert (Present (Offset_To_Top_Comp));
7070 Append_To (Stmts_List,
7071 Make_Assignment_Statement (Loc,
7072 Name =>
7073 Make_Selected_Component (Loc,
7074 Prefix => New_Copy_Tree (Target),
7075 Selector_Name => New_Reference_To
7076 (Offset_To_Top_Comp, Loc)),
7077 Expression =>
7078 Make_Attribute_Reference (Loc,
7079 Prefix =>
7080 Make_Selected_Component (Loc,
7081 Prefix => New_Copy_Tree (Target),
7082 Selector_Name =>
7083 New_Reference_To (Tag_Comp, Loc)),
7084 Attribute_Name => Name_Position)));
7086 -- Normal case: No discriminants in the parent type
7088 else
7089 -- Don't need to set any value if this interface shares
7090 -- the primary dispatch table.
7092 if not Is_Ancestor (Iface, Typ) then
7093 Append_To (Stmts_List,
7094 Build_Set_Static_Offset_To_Top (Loc,
7095 Iface_Tag => New_Reference_To (Iface_Tag, Loc),
7096 Offset_Value =>
7097 Unchecked_Convert_To (RTE (RE_Storage_Offset),
7098 Make_Attribute_Reference (Loc,
7099 Prefix =>
7100 Make_Selected_Component (Loc,
7101 Prefix => New_Copy_Tree (Target),
7102 Selector_Name =>
7103 New_Reference_To (Tag_Comp, Loc)),
7104 Attribute_Name => Name_Position))));
7105 end if;
7107 -- Generate:
7108 -- Register_Interface_Offset
7109 -- (This => Init,
7110 -- Interface_T => Iface'Tag,
7111 -- Is_Constant => True,
7112 -- Offset_Value => n,
7113 -- Offset_Func => null);
7115 if RTE_Available (RE_Register_Interface_Offset) then
7116 Append_To (Stmts_List,
7117 Make_Procedure_Call_Statement (Loc,
7118 Name => New_Reference_To
7119 (RTE (RE_Register_Interface_Offset), Loc),
7120 Parameter_Associations => New_List (
7121 Make_Attribute_Reference (Loc,
7122 Prefix => New_Copy_Tree (Target),
7123 Attribute_Name => Name_Address),
7125 Unchecked_Convert_To (RTE (RE_Tag),
7126 New_Reference_To
7127 (Node (First_Elmt (Access_Disp_Table (Iface))), Loc)),
7129 New_Occurrence_Of (Standard_True, Loc),
7131 Unchecked_Convert_To
7132 (RTE (RE_Storage_Offset),
7133 Make_Attribute_Reference (Loc,
7134 Prefix =>
7135 Make_Selected_Component (Loc,
7136 Prefix => New_Copy_Tree (Target),
7137 Selector_Name =>
7138 New_Reference_To (Tag_Comp, Loc)),
7139 Attribute_Name => Name_Position)),
7141 Make_Null (Loc))));
7142 end if;
7143 end if;
7144 end Initialize_Tag;
7146 -- Local variables
7148 Full_Typ : Entity_Id;
7149 Ifaces_List : Elist_Id;
7150 Ifaces_Comp_List : Elist_Id;
7151 Ifaces_Tag_List : Elist_Id;
7152 Iface_Elmt : Elmt_Id;
7153 Iface_Comp_Elmt : Elmt_Id;
7154 Iface_Tag_Elmt : Elmt_Id;
7155 Tag_Comp : Node_Id;
7156 In_Variable_Pos : Boolean;
7158 -- Start of processing for Init_Secondary_Tags
7160 begin
7161 -- Handle private types
7163 if Present (Full_View (Typ)) then
7164 Full_Typ := Full_View (Typ);
7165 else
7166 Full_Typ := Typ;
7167 end if;
7169 Collect_Interfaces_Info
7170 (Full_Typ, Ifaces_List, Ifaces_Comp_List, Ifaces_Tag_List);
7172 Iface_Elmt := First_Elmt (Ifaces_List);
7173 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
7174 Iface_Tag_Elmt := First_Elmt (Ifaces_Tag_List);
7175 while Present (Iface_Elmt) loop
7176 Tag_Comp := Node (Iface_Comp_Elmt);
7178 -- If we are compiling under the CPP full ABI compatibility mode and
7179 -- the ancestor is a CPP_Pragma tagged type then we generate code to
7180 -- inherit the contents of the dispatch table directly from the
7181 -- ancestor.
7183 if Is_CPP_Class (Etype (Full_Typ)) then
7184 Inherit_CPP_Tag (Full_Typ,
7185 Iface => Node (Iface_Elmt),
7186 Tag_Comp => Tag_Comp,
7187 Iface_Tag => Node (Iface_Tag_Elmt));
7189 -- Otherwise generate code to initialize the tag
7191 else
7192 -- Check if the parent of the record type has variable size
7193 -- components.
7195 In_Variable_Pos := Scope (Tag_Comp) /= Etype (Scope (Tag_Comp))
7196 and then Is_Variable_Size_Record (Etype (Scope (Tag_Comp)));
7198 if (In_Variable_Pos and then Variable_Comps)
7199 or else (not In_Variable_Pos and then Fixed_Comps)
7200 then
7201 Initialize_Tag (Full_Typ,
7202 Iface => Node (Iface_Elmt),
7203 Tag_Comp => Tag_Comp,
7204 Iface_Tag => Node (Iface_Tag_Elmt));
7205 end if;
7206 end if;
7208 Next_Elmt (Iface_Elmt);
7209 Next_Elmt (Iface_Comp_Elmt);
7210 Next_Elmt (Iface_Tag_Elmt);
7211 end loop;
7212 end Init_Secondary_Tags;
7214 -----------------------------
7215 -- Is_Variable_Size_Record --
7216 -----------------------------
7218 function Is_Variable_Size_Record (E : Entity_Id) return Boolean is
7219 Comp : Entity_Id;
7220 Comp_Typ : Entity_Id;
7221 Idx : Node_Id;
7223 function Is_Constant_Bound (Exp : Node_Id) return Boolean;
7224 -- To simplify handling of array components. Determines whether the
7225 -- given bound is constant (a constant or enumeration literal, or an
7226 -- integer literal) as opposed to per-object, through an expression
7227 -- or a discriminant.
7229 -----------------------
7230 -- Is_Constant_Bound --
7231 -----------------------
7233 function Is_Constant_Bound (Exp : Node_Id) return Boolean is
7234 begin
7235 if Nkind (Exp) = N_Integer_Literal then
7236 return True;
7237 else
7238 return
7239 Is_Entity_Name (Exp)
7240 and then Present (Entity (Exp))
7241 and then
7242 (Ekind (Entity (Exp)) = E_Constant
7243 or else Ekind (Entity (Exp)) = E_Enumeration_Literal);
7244 end if;
7245 end Is_Constant_Bound;
7247 -- Start of processing for Is_Variable_Sized_Record
7249 begin
7250 pragma Assert (Is_Record_Type (E));
7252 Comp := First_Entity (E);
7253 while Present (Comp) loop
7254 Comp_Typ := Etype (Comp);
7256 if Is_Record_Type (Comp_Typ) then
7258 -- Recursive call if the record type has discriminants
7260 if Has_Discriminants (Comp_Typ)
7261 and then Is_Variable_Size_Record (Comp_Typ)
7262 then
7263 return True;
7264 end if;
7266 elsif Is_Array_Type (Comp_Typ) then
7268 -- Check if some index is initialized with a non-constant value
7270 Idx := First_Index (Comp_Typ);
7271 while Present (Idx) loop
7272 if Nkind (Idx) = N_Range then
7273 if not Is_Constant_Bound (Low_Bound (Idx))
7274 or else
7275 not Is_Constant_Bound (High_Bound (Idx))
7276 then
7277 return True;
7278 end if;
7279 end if;
7281 Idx := Next_Index (Idx);
7282 end loop;
7283 end if;
7285 Next_Entity (Comp);
7286 end loop;
7288 return False;
7289 end Is_Variable_Size_Record;
7291 ----------------------------------------
7292 -- Make_Controlling_Function_Wrappers --
7293 ----------------------------------------
7295 procedure Make_Controlling_Function_Wrappers
7296 (Tag_Typ : Entity_Id;
7297 Decl_List : out List_Id;
7298 Body_List : out List_Id)
7300 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7301 Prim_Elmt : Elmt_Id;
7302 Subp : Entity_Id;
7303 Actual_List : List_Id;
7304 Formal_List : List_Id;
7305 Formal : Entity_Id;
7306 Par_Formal : Entity_Id;
7307 Formal_Node : Node_Id;
7308 Func_Body : Node_Id;
7309 Func_Decl : Node_Id;
7310 Func_Spec : Node_Id;
7311 Return_Stmt : Node_Id;
7313 begin
7314 Decl_List := New_List;
7315 Body_List := New_List;
7317 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7319 while Present (Prim_Elmt) loop
7320 Subp := Node (Prim_Elmt);
7322 -- If a primitive function with a controlling result of the type has
7323 -- not been overridden by the user, then we must create a wrapper
7324 -- function here that effectively overrides it and invokes the
7325 -- (non-abstract) parent function. This can only occur for a null
7326 -- extension. Note that functions with anonymous controlling access
7327 -- results don't qualify and must be overridden. We also exclude
7328 -- Input attributes, since each type will have its own version of
7329 -- Input constructed by the expander. The test for Comes_From_Source
7330 -- is needed to distinguish inherited operations from renamings
7331 -- (which also have Alias set).
7333 -- The function may be abstract, or require_Overriding may be set
7334 -- for it, because tests for null extensions may already have reset
7335 -- the Is_Abstract_Subprogram_Flag. If Requires_Overriding is not
7336 -- set, functions that need wrappers are recognized by having an
7337 -- alias that returns the parent type.
7339 if Comes_From_Source (Subp)
7340 or else No (Alias (Subp))
7341 or else Ekind (Subp) /= E_Function
7342 or else not Has_Controlling_Result (Subp)
7343 or else Is_Access_Type (Etype (Subp))
7344 or else Is_Abstract_Subprogram (Alias (Subp))
7345 or else Is_TSS (Subp, TSS_Stream_Input)
7346 then
7347 goto Next_Prim;
7349 elsif Is_Abstract_Subprogram (Subp)
7350 or else Requires_Overriding (Subp)
7351 or else
7352 (Is_Null_Extension (Etype (Subp))
7353 and then Etype (Alias (Subp)) /= Etype (Subp))
7354 then
7355 Formal_List := No_List;
7356 Formal := First_Formal (Subp);
7358 if Present (Formal) then
7359 Formal_List := New_List;
7361 while Present (Formal) loop
7362 Append
7363 (Make_Parameter_Specification
7364 (Loc,
7365 Defining_Identifier =>
7366 Make_Defining_Identifier (Sloc (Formal),
7367 Chars => Chars (Formal)),
7368 In_Present => In_Present (Parent (Formal)),
7369 Out_Present => Out_Present (Parent (Formal)),
7370 Null_Exclusion_Present =>
7371 Null_Exclusion_Present (Parent (Formal)),
7372 Parameter_Type =>
7373 New_Reference_To (Etype (Formal), Loc),
7374 Expression =>
7375 New_Copy_Tree (Expression (Parent (Formal)))),
7376 Formal_List);
7378 Next_Formal (Formal);
7379 end loop;
7380 end if;
7382 Func_Spec :=
7383 Make_Function_Specification (Loc,
7384 Defining_Unit_Name =>
7385 Make_Defining_Identifier (Loc,
7386 Chars => Chars (Subp)),
7387 Parameter_Specifications => Formal_List,
7388 Result_Definition =>
7389 New_Reference_To (Etype (Subp), Loc));
7391 Func_Decl := Make_Subprogram_Declaration (Loc, Func_Spec);
7392 Append_To (Decl_List, Func_Decl);
7394 -- Build a wrapper body that calls the parent function. The body
7395 -- contains a single return statement that returns an extension
7396 -- aggregate whose ancestor part is a call to the parent function,
7397 -- passing the formals as actuals (with any controlling arguments
7398 -- converted to the types of the corresponding formals of the
7399 -- parent function, which might be anonymous access types), and
7400 -- having a null extension.
7402 Formal := First_Formal (Subp);
7403 Par_Formal := First_Formal (Alias (Subp));
7404 Formal_Node := First (Formal_List);
7406 if Present (Formal) then
7407 Actual_List := New_List;
7408 else
7409 Actual_List := No_List;
7410 end if;
7412 while Present (Formal) loop
7413 if Is_Controlling_Formal (Formal) then
7414 Append_To (Actual_List,
7415 Make_Type_Conversion (Loc,
7416 Subtype_Mark =>
7417 New_Occurrence_Of (Etype (Par_Formal), Loc),
7418 Expression =>
7419 New_Reference_To
7420 (Defining_Identifier (Formal_Node), Loc)));
7421 else
7422 Append_To
7423 (Actual_List,
7424 New_Reference_To
7425 (Defining_Identifier (Formal_Node), Loc));
7426 end if;
7428 Next_Formal (Formal);
7429 Next_Formal (Par_Formal);
7430 Next (Formal_Node);
7431 end loop;
7433 Return_Stmt :=
7434 Make_Simple_Return_Statement (Loc,
7435 Expression =>
7436 Make_Extension_Aggregate (Loc,
7437 Ancestor_Part =>
7438 Make_Function_Call (Loc,
7439 Name => New_Reference_To (Alias (Subp), Loc),
7440 Parameter_Associations => Actual_List),
7441 Null_Record_Present => True));
7443 Func_Body :=
7444 Make_Subprogram_Body (Loc,
7445 Specification => New_Copy_Tree (Func_Spec),
7446 Declarations => Empty_List,
7447 Handled_Statement_Sequence =>
7448 Make_Handled_Sequence_Of_Statements (Loc,
7449 Statements => New_List (Return_Stmt)));
7451 Set_Defining_Unit_Name
7452 (Specification (Func_Body),
7453 Make_Defining_Identifier (Loc, Chars (Subp)));
7455 Append_To (Body_List, Func_Body);
7457 -- Replace the inherited function with the wrapper function
7458 -- in the primitive operations list.
7460 Override_Dispatching_Operation
7461 (Tag_Typ, Subp, New_Op => Defining_Unit_Name (Func_Spec));
7462 end if;
7464 <<Next_Prim>>
7465 Next_Elmt (Prim_Elmt);
7466 end loop;
7467 end Make_Controlling_Function_Wrappers;
7469 ------------------
7470 -- Make_Eq_Case --
7471 ------------------
7473 -- <Make_Eq_If shared components>
7474 -- case X.D1 is
7475 -- when V1 => <Make_Eq_Case> on subcomponents
7476 -- ...
7477 -- when Vn => <Make_Eq_Case> on subcomponents
7478 -- end case;
7480 function Make_Eq_Case
7481 (E : Entity_Id;
7482 CL : Node_Id;
7483 Discr : Entity_Id := Empty) return List_Id
7485 Loc : constant Source_Ptr := Sloc (E);
7486 Result : constant List_Id := New_List;
7487 Variant : Node_Id;
7488 Alt_List : List_Id;
7490 begin
7491 Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
7493 if No (Variant_Part (CL)) then
7494 return Result;
7495 end if;
7497 Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
7499 if No (Variant) then
7500 return Result;
7501 end if;
7503 Alt_List := New_List;
7505 while Present (Variant) loop
7506 Append_To (Alt_List,
7507 Make_Case_Statement_Alternative (Loc,
7508 Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
7509 Statements => Make_Eq_Case (E, Component_List (Variant))));
7511 Next_Non_Pragma (Variant);
7512 end loop;
7514 -- If we have an Unchecked_Union, use one of the parameters that
7515 -- captures the discriminants.
7517 if Is_Unchecked_Union (E) then
7518 Append_To (Result,
7519 Make_Case_Statement (Loc,
7520 Expression => New_Reference_To (Discr, Loc),
7521 Alternatives => Alt_List));
7523 else
7524 Append_To (Result,
7525 Make_Case_Statement (Loc,
7526 Expression =>
7527 Make_Selected_Component (Loc,
7528 Prefix => Make_Identifier (Loc, Name_X),
7529 Selector_Name => New_Copy (Name (Variant_Part (CL)))),
7530 Alternatives => Alt_List));
7531 end if;
7533 return Result;
7534 end Make_Eq_Case;
7536 ----------------
7537 -- Make_Eq_If --
7538 ----------------
7540 -- Generates:
7542 -- if
7543 -- X.C1 /= Y.C1
7544 -- or else
7545 -- X.C2 /= Y.C2
7546 -- ...
7547 -- then
7548 -- return False;
7549 -- end if;
7551 -- or a null statement if the list L is empty
7553 function Make_Eq_If
7554 (E : Entity_Id;
7555 L : List_Id) return Node_Id
7557 Loc : constant Source_Ptr := Sloc (E);
7558 C : Node_Id;
7559 Field_Name : Name_Id;
7560 Cond : Node_Id;
7562 begin
7563 if No (L) then
7564 return Make_Null_Statement (Loc);
7566 else
7567 Cond := Empty;
7569 C := First_Non_Pragma (L);
7570 while Present (C) loop
7571 Field_Name := Chars (Defining_Identifier (C));
7573 -- The tags must not be compared: they are not part of the value.
7574 -- Ditto for the controller component, if present.
7576 -- Note also that in the following, we use Make_Identifier for
7577 -- the component names. Use of New_Reference_To to identify the
7578 -- components would be incorrect because the wrong entities for
7579 -- discriminants could be picked up in the private type case.
7581 if Field_Name /= Name_uTag
7582 and then
7583 Field_Name /= Name_uController
7584 then
7585 Evolve_Or_Else (Cond,
7586 Make_Op_Ne (Loc,
7587 Left_Opnd =>
7588 Make_Selected_Component (Loc,
7589 Prefix => Make_Identifier (Loc, Name_X),
7590 Selector_Name =>
7591 Make_Identifier (Loc, Field_Name)),
7593 Right_Opnd =>
7594 Make_Selected_Component (Loc,
7595 Prefix => Make_Identifier (Loc, Name_Y),
7596 Selector_Name =>
7597 Make_Identifier (Loc, Field_Name))));
7598 end if;
7600 Next_Non_Pragma (C);
7601 end loop;
7603 if No (Cond) then
7604 return Make_Null_Statement (Loc);
7606 else
7607 return
7608 Make_Implicit_If_Statement (E,
7609 Condition => Cond,
7610 Then_Statements => New_List (
7611 Make_Simple_Return_Statement (Loc,
7612 Expression => New_Occurrence_Of (Standard_False, Loc))));
7613 end if;
7614 end if;
7615 end Make_Eq_If;
7617 -------------------------------
7618 -- Make_Null_Procedure_Specs --
7619 -------------------------------
7621 procedure Make_Null_Procedure_Specs
7622 (Tag_Typ : Entity_Id;
7623 Decl_List : out List_Id)
7625 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7627 Formal : Entity_Id;
7628 Formal_List : List_Id;
7629 New_Param_Spec : Node_Id;
7630 Parent_Subp : Entity_Id;
7631 Prim_Elmt : Elmt_Id;
7632 Proc_Decl : Node_Id;
7633 Subp : Entity_Id;
7635 function Is_Null_Interface_Primitive (E : Entity_Id) return Boolean;
7636 -- Returns True if E is a null procedure that is an interface primitive
7638 ---------------------------------
7639 -- Is_Null_Interface_Primitive --
7640 ---------------------------------
7642 function Is_Null_Interface_Primitive (E : Entity_Id) return Boolean is
7643 begin
7644 return Comes_From_Source (E)
7645 and then Is_Dispatching_Operation (E)
7646 and then Ekind (E) = E_Procedure
7647 and then Null_Present (Parent (E))
7648 and then Is_Interface (Find_Dispatching_Type (E));
7649 end Is_Null_Interface_Primitive;
7651 -- Start of processing for Make_Null_Procedure_Specs
7653 begin
7654 Decl_List := New_List;
7655 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7656 while Present (Prim_Elmt) loop
7657 Subp := Node (Prim_Elmt);
7659 -- If a null procedure inherited from an interface has not been
7660 -- overridden, then we build a null procedure declaration to
7661 -- override the inherited procedure.
7663 Parent_Subp := Alias (Subp);
7665 if Present (Parent_Subp)
7666 and then Is_Null_Interface_Primitive (Parent_Subp)
7667 then
7668 Formal_List := No_List;
7669 Formal := First_Formal (Subp);
7671 if Present (Formal) then
7672 Formal_List := New_List;
7674 while Present (Formal) loop
7676 -- Copy the parameter spec including default expressions
7678 New_Param_Spec :=
7679 New_Copy_Tree (Parent (Formal), New_Sloc => Loc);
7681 -- Generate a new defining identifier for the new formal.
7682 -- required because New_Copy_Tree does not duplicate
7683 -- semantic fields (except itypes).
7685 Set_Defining_Identifier (New_Param_Spec,
7686 Make_Defining_Identifier (Sloc (Formal),
7687 Chars => Chars (Formal)));
7689 -- For controlling arguments we must change their
7690 -- parameter type to reference the tagged type (instead
7691 -- of the interface type)
7693 if Is_Controlling_Formal (Formal) then
7694 if Nkind (Parameter_Type (Parent (Formal)))
7695 = N_Identifier
7696 then
7697 Set_Parameter_Type (New_Param_Spec,
7698 New_Occurrence_Of (Tag_Typ, Loc));
7700 else pragma Assert
7701 (Nkind (Parameter_Type (Parent (Formal)))
7702 = N_Access_Definition);
7703 Set_Subtype_Mark (Parameter_Type (New_Param_Spec),
7704 New_Occurrence_Of (Tag_Typ, Loc));
7705 end if;
7706 end if;
7708 Append (New_Param_Spec, Formal_List);
7710 Next_Formal (Formal);
7711 end loop;
7712 end if;
7714 Proc_Decl :=
7715 Make_Subprogram_Declaration (Loc,
7716 Make_Procedure_Specification (Loc,
7717 Defining_Unit_Name =>
7718 Make_Defining_Identifier (Loc, Chars (Subp)),
7719 Parameter_Specifications => Formal_List,
7720 Null_Present => True));
7721 Append_To (Decl_List, Proc_Decl);
7722 Analyze (Proc_Decl);
7723 end if;
7725 Next_Elmt (Prim_Elmt);
7726 end loop;
7727 end Make_Null_Procedure_Specs;
7729 -------------------------------------
7730 -- Make_Predefined_Primitive_Specs --
7731 -------------------------------------
7733 procedure Make_Predefined_Primitive_Specs
7734 (Tag_Typ : Entity_Id;
7735 Predef_List : out List_Id;
7736 Renamed_Eq : out Entity_Id)
7738 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7739 Res : constant List_Id := New_List;
7740 Prim : Elmt_Id;
7741 Eq_Needed : Boolean;
7742 Eq_Spec : Node_Id;
7743 Eq_Name : Name_Id := Name_Op_Eq;
7745 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
7746 -- Returns true if Prim is a renaming of an unresolved predefined
7747 -- equality operation.
7749 -------------------------------
7750 -- Is_Predefined_Eq_Renaming --
7751 -------------------------------
7753 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
7754 begin
7755 return Chars (Prim) /= Name_Op_Eq
7756 and then Present (Alias (Prim))
7757 and then Comes_From_Source (Prim)
7758 and then Is_Intrinsic_Subprogram (Alias (Prim))
7759 and then Chars (Alias (Prim)) = Name_Op_Eq;
7760 end Is_Predefined_Eq_Renaming;
7762 -- Start of processing for Make_Predefined_Primitive_Specs
7764 begin
7765 Renamed_Eq := Empty;
7767 -- Spec of _Size
7769 Append_To (Res, Predef_Spec_Or_Body (Loc,
7770 Tag_Typ => Tag_Typ,
7771 Name => Name_uSize,
7772 Profile => New_List (
7773 Make_Parameter_Specification (Loc,
7774 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7775 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7777 Ret_Type => Standard_Long_Long_Integer));
7779 -- Spec of _Alignment
7781 Append_To (Res, Predef_Spec_Or_Body (Loc,
7782 Tag_Typ => Tag_Typ,
7783 Name => Name_uAlignment,
7784 Profile => New_List (
7785 Make_Parameter_Specification (Loc,
7786 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7787 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7789 Ret_Type => Standard_Integer));
7791 -- Specs for dispatching stream attributes
7793 declare
7794 Stream_Op_TSS_Names :
7795 constant array (Integer range <>) of TSS_Name_Type :=
7796 (TSS_Stream_Read,
7797 TSS_Stream_Write,
7798 TSS_Stream_Input,
7799 TSS_Stream_Output);
7801 begin
7802 for Op in Stream_Op_TSS_Names'Range loop
7803 if Stream_Operation_OK (Tag_Typ, Stream_Op_TSS_Names (Op)) then
7804 Append_To (Res,
7805 Predef_Stream_Attr_Spec (Loc, Tag_Typ,
7806 Stream_Op_TSS_Names (Op)));
7807 end if;
7808 end loop;
7809 end;
7811 -- Spec of "=" is expanded if the type is not limited and if a
7812 -- user defined "=" was not already declared for the non-full
7813 -- view of a private extension
7815 if not Is_Limited_Type (Tag_Typ) then
7816 Eq_Needed := True;
7817 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
7818 while Present (Prim) loop
7820 -- If a primitive is encountered that renames the predefined
7821 -- equality operator before reaching any explicit equality
7822 -- primitive, then we still need to create a predefined equality
7823 -- function, because calls to it can occur via the renaming. A new
7824 -- name is created for the equality to avoid conflicting with any
7825 -- user-defined equality. (Note that this doesn't account for
7826 -- renamings of equality nested within subpackages???)
7828 if Is_Predefined_Eq_Renaming (Node (Prim)) then
7829 Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
7831 -- User-defined equality
7833 elsif Chars (Node (Prim)) = Name_Op_Eq
7834 and then Etype (First_Formal (Node (Prim))) =
7835 Etype (Next_Formal (First_Formal (Node (Prim))))
7836 and then Base_Type (Etype (Node (Prim))) = Standard_Boolean
7837 then
7838 if No (Alias (Node (Prim)))
7839 or else Nkind (Unit_Declaration_Node (Node (Prim))) =
7840 N_Subprogram_Renaming_Declaration
7841 then
7842 Eq_Needed := False;
7843 exit;
7845 -- If the parent is not an interface type and has an abstract
7846 -- equality function, the inherited equality is abstract as
7847 -- well, and no body can be created for it.
7849 elsif not Is_Interface (Etype (Tag_Typ))
7850 and then Present (Alias (Node (Prim)))
7851 and then Is_Abstract_Subprogram (Alias (Node (Prim)))
7852 then
7853 Eq_Needed := False;
7854 exit;
7856 -- If the type has an equality function corresponding with
7857 -- a primitive defined in an interface type, the inherited
7858 -- equality is abstract as well, and no body can be created
7859 -- for it.
7861 elsif Present (Alias (Node (Prim)))
7862 and then Comes_From_Source (Ultimate_Alias (Node (Prim)))
7863 and then
7864 Is_Interface
7865 (Find_Dispatching_Type (Ultimate_Alias (Node (Prim))))
7866 then
7867 Eq_Needed := False;
7868 exit;
7869 end if;
7870 end if;
7872 Next_Elmt (Prim);
7873 end loop;
7875 -- If a renaming of predefined equality was found but there was no
7876 -- user-defined equality (so Eq_Needed is still true), then set the
7877 -- name back to Name_Op_Eq. But in the case where a user-defined
7878 -- equality was located after such a renaming, then the predefined
7879 -- equality function is still needed, so Eq_Needed must be set back
7880 -- to True.
7882 if Eq_Name /= Name_Op_Eq then
7883 if Eq_Needed then
7884 Eq_Name := Name_Op_Eq;
7885 else
7886 Eq_Needed := True;
7887 end if;
7888 end if;
7890 if Eq_Needed then
7891 Eq_Spec := Predef_Spec_Or_Body (Loc,
7892 Tag_Typ => Tag_Typ,
7893 Name => Eq_Name,
7894 Profile => New_List (
7895 Make_Parameter_Specification (Loc,
7896 Defining_Identifier =>
7897 Make_Defining_Identifier (Loc, Name_X),
7898 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
7899 Make_Parameter_Specification (Loc,
7900 Defining_Identifier =>
7901 Make_Defining_Identifier (Loc, Name_Y),
7902 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7903 Ret_Type => Standard_Boolean);
7904 Append_To (Res, Eq_Spec);
7906 if Eq_Name /= Name_Op_Eq then
7907 Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
7909 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
7910 while Present (Prim) loop
7912 -- Any renamings of equality that appeared before an
7913 -- overriding equality must be updated to refer to the
7914 -- entity for the predefined equality, otherwise calls via
7915 -- the renaming would get incorrectly resolved to call the
7916 -- user-defined equality function.
7918 if Is_Predefined_Eq_Renaming (Node (Prim)) then
7919 Set_Alias (Node (Prim), Renamed_Eq);
7921 -- Exit upon encountering a user-defined equality
7923 elsif Chars (Node (Prim)) = Name_Op_Eq
7924 and then No (Alias (Node (Prim)))
7925 then
7926 exit;
7927 end if;
7929 Next_Elmt (Prim);
7930 end loop;
7931 end if;
7932 end if;
7934 -- Spec for dispatching assignment
7936 Append_To (Res, Predef_Spec_Or_Body (Loc,
7937 Tag_Typ => Tag_Typ,
7938 Name => Name_uAssign,
7939 Profile => New_List (
7940 Make_Parameter_Specification (Loc,
7941 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7942 Out_Present => True,
7943 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
7945 Make_Parameter_Specification (Loc,
7946 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
7947 Parameter_Type => New_Reference_To (Tag_Typ, Loc)))));
7948 end if;
7950 -- Ada 2005: Generate declarations for the following primitive
7951 -- operations for limited interfaces and synchronized types that
7952 -- implement a limited interface.
7954 -- Disp_Asynchronous_Select
7955 -- Disp_Conditional_Select
7956 -- Disp_Get_Prim_Op_Kind
7957 -- Disp_Get_Task_Id
7958 -- Disp_Requeue
7959 -- Disp_Timed_Select
7961 -- These operations cannot be implemented on VM targets, so we simply
7962 -- disable their generation in this case. Disable the generation of
7963 -- these bodies if No_Dispatching_Calls, Ravenscar or ZFP is active.
7965 if Ada_Version >= Ada_05
7966 and then Tagged_Type_Expansion
7967 and then not Restriction_Active (No_Dispatching_Calls)
7968 and then not Restriction_Active (No_Select_Statements)
7969 and then RTE_Available (RE_Select_Specific_Data)
7970 then
7971 -- These primitives are defined abstract in interface types
7973 if Is_Interface (Tag_Typ)
7974 and then Is_Limited_Record (Tag_Typ)
7975 then
7976 Append_To (Res,
7977 Make_Abstract_Subprogram_Declaration (Loc,
7978 Specification =>
7979 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
7981 Append_To (Res,
7982 Make_Abstract_Subprogram_Declaration (Loc,
7983 Specification =>
7984 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
7986 Append_To (Res,
7987 Make_Abstract_Subprogram_Declaration (Loc,
7988 Specification =>
7989 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
7991 Append_To (Res,
7992 Make_Abstract_Subprogram_Declaration (Loc,
7993 Specification =>
7994 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
7996 Append_To (Res,
7997 Make_Abstract_Subprogram_Declaration (Loc,
7998 Specification =>
7999 Make_Disp_Requeue_Spec (Tag_Typ)));
8001 Append_To (Res,
8002 Make_Abstract_Subprogram_Declaration (Loc,
8003 Specification =>
8004 Make_Disp_Timed_Select_Spec (Tag_Typ)));
8006 -- If the ancestor is an interface type we declare non-abstract
8007 -- primitives to override the abstract primitives of the interface
8008 -- type.
8010 elsif (not Is_Interface (Tag_Typ)
8011 and then Is_Interface (Etype (Tag_Typ))
8012 and then Is_Limited_Record (Etype (Tag_Typ)))
8013 or else
8014 (Is_Concurrent_Record_Type (Tag_Typ)
8015 and then Has_Interfaces (Tag_Typ))
8016 then
8017 Append_To (Res,
8018 Make_Subprogram_Declaration (Loc,
8019 Specification =>
8020 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
8022 Append_To (Res,
8023 Make_Subprogram_Declaration (Loc,
8024 Specification =>
8025 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
8027 Append_To (Res,
8028 Make_Subprogram_Declaration (Loc,
8029 Specification =>
8030 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
8032 Append_To (Res,
8033 Make_Subprogram_Declaration (Loc,
8034 Specification =>
8035 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
8037 Append_To (Res,
8038 Make_Subprogram_Declaration (Loc,
8039 Specification =>
8040 Make_Disp_Requeue_Spec (Tag_Typ)));
8042 Append_To (Res,
8043 Make_Subprogram_Declaration (Loc,
8044 Specification =>
8045 Make_Disp_Timed_Select_Spec (Tag_Typ)));
8046 end if;
8047 end if;
8049 -- Specs for finalization actions that may be required in case a future
8050 -- extension contain a controlled element. We generate those only for
8051 -- root tagged types where they will get dummy bodies or when the type
8052 -- has controlled components and their body must be generated. It is
8053 -- also impossible to provide those for tagged types defined within
8054 -- s-finimp since it would involve circularity problems
8056 if In_Finalization_Root (Tag_Typ) then
8057 null;
8059 -- We also skip these if finalization is not available
8061 elsif Restriction_Active (No_Finalization) then
8062 null;
8064 -- Skip these for CIL Value types, where finalization is not available
8066 elsif Is_Value_Type (Tag_Typ) then
8067 null;
8069 elsif Etype (Tag_Typ) = Tag_Typ
8070 or else Needs_Finalization (Tag_Typ)
8072 -- Ada 2005 (AI-251): We must also generate these subprograms if
8073 -- the immediate ancestor is an interface to ensure the correct
8074 -- initialization of its dispatch table.
8076 or else (not Is_Interface (Tag_Typ)
8077 and then Is_Interface (Etype (Tag_Typ)))
8079 -- Ada 205 (AI-251): We must also generate these subprograms if
8080 -- the parent of an nonlimited interface is a limited interface
8082 or else (Is_Interface (Tag_Typ)
8083 and then not Is_Limited_Interface (Tag_Typ)
8084 and then Is_Limited_Interface (Etype (Tag_Typ)))
8085 then
8086 if not Is_Limited_Type (Tag_Typ) then
8087 Append_To (Res,
8088 Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
8089 end if;
8091 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
8092 end if;
8094 Predef_List := Res;
8095 end Make_Predefined_Primitive_Specs;
8097 ---------------------------------
8098 -- Needs_Simple_Initialization --
8099 ---------------------------------
8101 function Needs_Simple_Initialization
8102 (T : Entity_Id;
8103 Consider_IS : Boolean := True) return Boolean
8105 Consider_IS_NS : constant Boolean :=
8106 Normalize_Scalars
8107 or (Initialize_Scalars and Consider_IS);
8109 begin
8110 -- Check for private type, in which case test applies to the underlying
8111 -- type of the private type.
8113 if Is_Private_Type (T) then
8114 declare
8115 RT : constant Entity_Id := Underlying_Type (T);
8117 begin
8118 if Present (RT) then
8119 return Needs_Simple_Initialization (RT);
8120 else
8121 return False;
8122 end if;
8123 end;
8125 -- Cases needing simple initialization are access types, and, if pragma
8126 -- Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
8127 -- types.
8129 elsif Is_Access_Type (T)
8130 or else (Consider_IS_NS and then (Is_Scalar_Type (T)))
8131 then
8132 return True;
8134 -- If Initialize/Normalize_Scalars is in effect, string objects also
8135 -- need initialization, unless they are created in the course of
8136 -- expanding an aggregate (since in the latter case they will be
8137 -- filled with appropriate initializing values before they are used).
8139 elsif Consider_IS_NS
8140 and then
8141 (Root_Type (T) = Standard_String
8142 or else Root_Type (T) = Standard_Wide_String
8143 or else Root_Type (T) = Standard_Wide_Wide_String)
8144 and then
8145 (not Is_Itype (T)
8146 or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
8147 then
8148 return True;
8150 else
8151 return False;
8152 end if;
8153 end Needs_Simple_Initialization;
8155 ----------------------
8156 -- Predef_Deep_Spec --
8157 ----------------------
8159 function Predef_Deep_Spec
8160 (Loc : Source_Ptr;
8161 Tag_Typ : Entity_Id;
8162 Name : TSS_Name_Type;
8163 For_Body : Boolean := False) return Node_Id
8165 Prof : List_Id;
8166 Type_B : Entity_Id;
8168 begin
8169 if Name = TSS_Deep_Finalize then
8170 Prof := New_List;
8171 Type_B := Standard_Boolean;
8173 else
8174 Prof := New_List (
8175 Make_Parameter_Specification (Loc,
8176 Defining_Identifier => Make_Defining_Identifier (Loc, Name_L),
8177 In_Present => True,
8178 Out_Present => True,
8179 Parameter_Type =>
8180 New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
8181 Type_B := Standard_Short_Short_Integer;
8182 end if;
8184 Append_To (Prof,
8185 Make_Parameter_Specification (Loc,
8186 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
8187 In_Present => True,
8188 Out_Present => True,
8189 Parameter_Type => New_Reference_To (Tag_Typ, Loc)));
8191 Append_To (Prof,
8192 Make_Parameter_Specification (Loc,
8193 Defining_Identifier => Make_Defining_Identifier (Loc, Name_B),
8194 Parameter_Type => New_Reference_To (Type_B, Loc)));
8196 return Predef_Spec_Or_Body (Loc,
8197 Name => Make_TSS_Name (Tag_Typ, Name),
8198 Tag_Typ => Tag_Typ,
8199 Profile => Prof,
8200 For_Body => For_Body);
8202 exception
8203 when RE_Not_Available =>
8204 return Empty;
8205 end Predef_Deep_Spec;
8207 -------------------------
8208 -- Predef_Spec_Or_Body --
8209 -------------------------
8211 function Predef_Spec_Or_Body
8212 (Loc : Source_Ptr;
8213 Tag_Typ : Entity_Id;
8214 Name : Name_Id;
8215 Profile : List_Id;
8216 Ret_Type : Entity_Id := Empty;
8217 For_Body : Boolean := False) return Node_Id
8219 Id : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
8220 Spec : Node_Id;
8222 begin
8223 Set_Is_Public (Id, Is_Public (Tag_Typ));
8225 -- The internal flag is set to mark these declarations because they have
8226 -- specific properties. First, they are primitives even if they are not
8227 -- defined in the type scope (the freezing point is not necessarily in
8228 -- the same scope). Second, the predefined equality can be overridden by
8229 -- a user-defined equality, no body will be generated in this case.
8231 Set_Is_Internal (Id);
8233 if not Debug_Generated_Code then
8234 Set_Debug_Info_Off (Id);
8235 end if;
8237 if No (Ret_Type) then
8238 Spec :=
8239 Make_Procedure_Specification (Loc,
8240 Defining_Unit_Name => Id,
8241 Parameter_Specifications => Profile);
8242 else
8243 Spec :=
8244 Make_Function_Specification (Loc,
8245 Defining_Unit_Name => Id,
8246 Parameter_Specifications => Profile,
8247 Result_Definition =>
8248 New_Reference_To (Ret_Type, Loc));
8249 end if;
8251 if Is_Interface (Tag_Typ) then
8252 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
8254 -- If body case, return empty subprogram body. Note that this is ill-
8255 -- formed, because there is not even a null statement, and certainly not
8256 -- a return in the function case. The caller is expected to do surgery
8257 -- on the body to add the appropriate stuff.
8259 elsif For_Body then
8260 return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
8262 -- For the case of an Input attribute predefined for an abstract type,
8263 -- generate an abstract specification. This will never be called, but we
8264 -- need the slot allocated in the dispatching table so that attributes
8265 -- typ'Class'Input and typ'Class'Output will work properly.
8267 elsif Is_TSS (Name, TSS_Stream_Input)
8268 and then Is_Abstract_Type (Tag_Typ)
8269 then
8270 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
8272 -- Normal spec case, where we return a subprogram declaration
8274 else
8275 return Make_Subprogram_Declaration (Loc, Spec);
8276 end if;
8277 end Predef_Spec_Or_Body;
8279 -----------------------------
8280 -- Predef_Stream_Attr_Spec --
8281 -----------------------------
8283 function Predef_Stream_Attr_Spec
8284 (Loc : Source_Ptr;
8285 Tag_Typ : Entity_Id;
8286 Name : TSS_Name_Type;
8287 For_Body : Boolean := False) return Node_Id
8289 Ret_Type : Entity_Id;
8291 begin
8292 if Name = TSS_Stream_Input then
8293 Ret_Type := Tag_Typ;
8294 else
8295 Ret_Type := Empty;
8296 end if;
8298 return Predef_Spec_Or_Body (Loc,
8299 Name => Make_TSS_Name (Tag_Typ, Name),
8300 Tag_Typ => Tag_Typ,
8301 Profile => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
8302 Ret_Type => Ret_Type,
8303 For_Body => For_Body);
8304 end Predef_Stream_Attr_Spec;
8306 ---------------------------------
8307 -- Predefined_Primitive_Bodies --
8308 ---------------------------------
8310 function Predefined_Primitive_Bodies
8311 (Tag_Typ : Entity_Id;
8312 Renamed_Eq : Entity_Id) return List_Id
8314 Loc : constant Source_Ptr := Sloc (Tag_Typ);
8315 Res : constant List_Id := New_List;
8316 Decl : Node_Id;
8317 Prim : Elmt_Id;
8318 Eq_Needed : Boolean;
8319 Eq_Name : Name_Id;
8320 Ent : Entity_Id;
8322 pragma Warnings (Off, Ent);
8324 begin
8325 pragma Assert (not Is_Interface (Tag_Typ));
8327 -- See if we have a predefined "=" operator
8329 if Present (Renamed_Eq) then
8330 Eq_Needed := True;
8331 Eq_Name := Chars (Renamed_Eq);
8333 -- If the parent is an interface type then it has defined all the
8334 -- predefined primitives abstract and we need to check if the type
8335 -- has some user defined "=" function to avoid generating it.
8337 elsif Is_Interface (Etype (Tag_Typ)) then
8338 Eq_Needed := True;
8339 Eq_Name := Name_Op_Eq;
8341 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
8342 while Present (Prim) loop
8343 if Chars (Node (Prim)) = Name_Op_Eq
8344 and then not Is_Internal (Node (Prim))
8345 then
8346 Eq_Needed := False;
8347 Eq_Name := No_Name;
8348 exit;
8349 end if;
8351 Next_Elmt (Prim);
8352 end loop;
8354 else
8355 Eq_Needed := False;
8356 Eq_Name := No_Name;
8358 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
8359 while Present (Prim) loop
8360 if Chars (Node (Prim)) = Name_Op_Eq
8361 and then Is_Internal (Node (Prim))
8362 then
8363 Eq_Needed := True;
8364 Eq_Name := Name_Op_Eq;
8365 exit;
8366 end if;
8368 Next_Elmt (Prim);
8369 end loop;
8370 end if;
8372 -- Body of _Alignment
8374 Decl := Predef_Spec_Or_Body (Loc,
8375 Tag_Typ => Tag_Typ,
8376 Name => Name_uAlignment,
8377 Profile => New_List (
8378 Make_Parameter_Specification (Loc,
8379 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
8380 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8382 Ret_Type => Standard_Integer,
8383 For_Body => True);
8385 Set_Handled_Statement_Sequence (Decl,
8386 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8387 Make_Simple_Return_Statement (Loc,
8388 Expression =>
8389 Make_Attribute_Reference (Loc,
8390 Prefix => Make_Identifier (Loc, Name_X),
8391 Attribute_Name => Name_Alignment)))));
8393 Append_To (Res, Decl);
8395 -- Body of _Size
8397 Decl := Predef_Spec_Or_Body (Loc,
8398 Tag_Typ => Tag_Typ,
8399 Name => Name_uSize,
8400 Profile => New_List (
8401 Make_Parameter_Specification (Loc,
8402 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
8403 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8405 Ret_Type => Standard_Long_Long_Integer,
8406 For_Body => True);
8408 Set_Handled_Statement_Sequence (Decl,
8409 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8410 Make_Simple_Return_Statement (Loc,
8411 Expression =>
8412 Make_Attribute_Reference (Loc,
8413 Prefix => Make_Identifier (Loc, Name_X),
8414 Attribute_Name => Name_Size)))));
8416 Append_To (Res, Decl);
8418 -- Bodies for Dispatching stream IO routines. We need these only for
8419 -- non-limited types (in the limited case there is no dispatching).
8420 -- We also skip them if dispatching or finalization are not available.
8422 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Read)
8423 and then No (TSS (Tag_Typ, TSS_Stream_Read))
8424 then
8425 Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
8426 Append_To (Res, Decl);
8427 end if;
8429 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Write)
8430 and then No (TSS (Tag_Typ, TSS_Stream_Write))
8431 then
8432 Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
8433 Append_To (Res, Decl);
8434 end if;
8436 -- Skip body of _Input for the abstract case, since the corresponding
8437 -- spec is abstract (see Predef_Spec_Or_Body).
8439 if not Is_Abstract_Type (Tag_Typ)
8440 and then Stream_Operation_OK (Tag_Typ, TSS_Stream_Input)
8441 and then No (TSS (Tag_Typ, TSS_Stream_Input))
8442 then
8443 Build_Record_Or_Elementary_Input_Function
8444 (Loc, Tag_Typ, Decl, Ent);
8445 Append_To (Res, Decl);
8446 end if;
8448 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Output)
8449 and then No (TSS (Tag_Typ, TSS_Stream_Output))
8450 then
8451 Build_Record_Or_Elementary_Output_Procedure
8452 (Loc, Tag_Typ, Decl, Ent);
8453 Append_To (Res, Decl);
8454 end if;
8456 -- Ada 2005: Generate bodies for the following primitive operations for
8457 -- limited interfaces and synchronized types that implement a limited
8458 -- interface.
8460 -- disp_asynchronous_select
8461 -- disp_conditional_select
8462 -- disp_get_prim_op_kind
8463 -- disp_get_task_id
8464 -- disp_timed_select
8466 -- The interface versions will have null bodies
8468 -- These operations cannot be implemented on VM targets, so we simply
8469 -- disable their generation in this case. Disable the generation of
8470 -- these bodies if No_Dispatching_Calls, Ravenscar or ZFP is active.
8472 if Ada_Version >= Ada_05
8473 and then Tagged_Type_Expansion
8474 and then not Is_Interface (Tag_Typ)
8475 and then
8476 ((Is_Interface (Etype (Tag_Typ))
8477 and then Is_Limited_Record (Etype (Tag_Typ)))
8478 or else (Is_Concurrent_Record_Type (Tag_Typ)
8479 and then Has_Interfaces (Tag_Typ)))
8480 and then not Restriction_Active (No_Dispatching_Calls)
8481 and then not Restriction_Active (No_Select_Statements)
8482 and then RTE_Available (RE_Select_Specific_Data)
8483 then
8484 Append_To (Res, Make_Disp_Asynchronous_Select_Body (Tag_Typ));
8485 Append_To (Res, Make_Disp_Conditional_Select_Body (Tag_Typ));
8486 Append_To (Res, Make_Disp_Get_Prim_Op_Kind_Body (Tag_Typ));
8487 Append_To (Res, Make_Disp_Get_Task_Id_Body (Tag_Typ));
8488 Append_To (Res, Make_Disp_Requeue_Body (Tag_Typ));
8489 Append_To (Res, Make_Disp_Timed_Select_Body (Tag_Typ));
8490 end if;
8492 if not Is_Limited_Type (Tag_Typ)
8493 and then not Is_Interface (Tag_Typ)
8494 then
8495 -- Body for equality
8497 if Eq_Needed then
8498 Decl :=
8499 Predef_Spec_Or_Body (Loc,
8500 Tag_Typ => Tag_Typ,
8501 Name => Eq_Name,
8502 Profile => New_List (
8503 Make_Parameter_Specification (Loc,
8504 Defining_Identifier =>
8505 Make_Defining_Identifier (Loc, Name_X),
8506 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
8508 Make_Parameter_Specification (Loc,
8509 Defining_Identifier =>
8510 Make_Defining_Identifier (Loc, Name_Y),
8511 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8513 Ret_Type => Standard_Boolean,
8514 For_Body => True);
8516 declare
8517 Def : constant Node_Id := Parent (Tag_Typ);
8518 Stmts : constant List_Id := New_List;
8519 Variant_Case : Boolean := Has_Discriminants (Tag_Typ);
8520 Comps : Node_Id := Empty;
8521 Typ_Def : Node_Id := Type_Definition (Def);
8523 begin
8524 if Variant_Case then
8525 if Nkind (Typ_Def) = N_Derived_Type_Definition then
8526 Typ_Def := Record_Extension_Part (Typ_Def);
8527 end if;
8529 if Present (Typ_Def) then
8530 Comps := Component_List (Typ_Def);
8531 end if;
8533 Variant_Case := Present (Comps)
8534 and then Present (Variant_Part (Comps));
8535 end if;
8537 if Variant_Case then
8538 Append_To (Stmts,
8539 Make_Eq_If (Tag_Typ, Discriminant_Specifications (Def)));
8540 Append_List_To (Stmts, Make_Eq_Case (Tag_Typ, Comps));
8541 Append_To (Stmts,
8542 Make_Simple_Return_Statement (Loc,
8543 Expression => New_Reference_To (Standard_True, Loc)));
8545 else
8546 Append_To (Stmts,
8547 Make_Simple_Return_Statement (Loc,
8548 Expression =>
8549 Expand_Record_Equality (Tag_Typ,
8550 Typ => Tag_Typ,
8551 Lhs => Make_Identifier (Loc, Name_X),
8552 Rhs => Make_Identifier (Loc, Name_Y),
8553 Bodies => Declarations (Decl))));
8554 end if;
8556 Set_Handled_Statement_Sequence (Decl,
8557 Make_Handled_Sequence_Of_Statements (Loc, Stmts));
8558 end;
8559 Append_To (Res, Decl);
8560 end if;
8562 -- Body for dispatching assignment
8564 Decl :=
8565 Predef_Spec_Or_Body (Loc,
8566 Tag_Typ => Tag_Typ,
8567 Name => Name_uAssign,
8568 Profile => New_List (
8569 Make_Parameter_Specification (Loc,
8570 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
8571 Out_Present => True,
8572 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
8574 Make_Parameter_Specification (Loc,
8575 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
8576 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8577 For_Body => True);
8579 Set_Handled_Statement_Sequence (Decl,
8580 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8581 Make_Assignment_Statement (Loc,
8582 Name => Make_Identifier (Loc, Name_X),
8583 Expression => Make_Identifier (Loc, Name_Y)))));
8585 Append_To (Res, Decl);
8586 end if;
8588 -- Generate dummy bodies for finalization actions of types that have
8589 -- no controlled components.
8591 -- Skip this processing if we are in the finalization routine in the
8592 -- runtime itself, otherwise we get hopelessly circularly confused!
8594 if In_Finalization_Root (Tag_Typ) then
8595 null;
8597 -- Skip this if finalization is not available
8599 elsif Restriction_Active (No_Finalization) then
8600 null;
8602 elsif (Etype (Tag_Typ) = Tag_Typ
8603 or else Is_Controlled (Tag_Typ)
8605 -- Ada 2005 (AI-251): We must also generate these subprograms
8606 -- if the immediate ancestor of Tag_Typ is an interface to
8607 -- ensure the correct initialization of its dispatch table.
8609 or else (not Is_Interface (Tag_Typ)
8610 and then
8611 Is_Interface (Etype (Tag_Typ))))
8612 and then not Has_Controlled_Component (Tag_Typ)
8613 then
8614 if not Is_Limited_Type (Tag_Typ) then
8615 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
8617 if Is_Controlled (Tag_Typ) then
8618 Set_Handled_Statement_Sequence (Decl,
8619 Make_Handled_Sequence_Of_Statements (Loc,
8620 Make_Adjust_Call (
8621 Ref => Make_Identifier (Loc, Name_V),
8622 Typ => Tag_Typ,
8623 Flist_Ref => Make_Identifier (Loc, Name_L),
8624 With_Attach => Make_Identifier (Loc, Name_B))));
8626 else
8627 Set_Handled_Statement_Sequence (Decl,
8628 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8629 Make_Null_Statement (Loc))));
8630 end if;
8632 Append_To (Res, Decl);
8633 end if;
8635 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
8637 if Is_Controlled (Tag_Typ) then
8638 Set_Handled_Statement_Sequence (Decl,
8639 Make_Handled_Sequence_Of_Statements (Loc,
8640 Make_Final_Call (
8641 Ref => Make_Identifier (Loc, Name_V),
8642 Typ => Tag_Typ,
8643 With_Detach => Make_Identifier (Loc, Name_B))));
8645 else
8646 Set_Handled_Statement_Sequence (Decl,
8647 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8648 Make_Null_Statement (Loc))));
8649 end if;
8651 Append_To (Res, Decl);
8652 end if;
8654 return Res;
8655 end Predefined_Primitive_Bodies;
8657 ---------------------------------
8658 -- Predefined_Primitive_Freeze --
8659 ---------------------------------
8661 function Predefined_Primitive_Freeze
8662 (Tag_Typ : Entity_Id) return List_Id
8664 Loc : constant Source_Ptr := Sloc (Tag_Typ);
8665 Res : constant List_Id := New_List;
8666 Prim : Elmt_Id;
8667 Frnodes : List_Id;
8669 begin
8670 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
8671 while Present (Prim) loop
8672 if Is_Predefined_Dispatching_Operation (Node (Prim)) then
8673 Frnodes := Freeze_Entity (Node (Prim), Loc);
8675 if Present (Frnodes) then
8676 Append_List_To (Res, Frnodes);
8677 end if;
8678 end if;
8680 Next_Elmt (Prim);
8681 end loop;
8683 return Res;
8684 end Predefined_Primitive_Freeze;
8686 -------------------------
8687 -- Stream_Operation_OK --
8688 -------------------------
8690 function Stream_Operation_OK
8691 (Typ : Entity_Id;
8692 Operation : TSS_Name_Type) return Boolean
8694 Has_Predefined_Or_Specified_Stream_Attribute : Boolean := False;
8696 begin
8697 -- Special case of a limited type extension: a default implementation
8698 -- of the stream attributes Read or Write exists if that attribute
8699 -- has been specified or is available for an ancestor type; a default
8700 -- implementation of the attribute Output (resp. Input) exists if the
8701 -- attribute has been specified or Write (resp. Read) is available for
8702 -- an ancestor type. The last condition only applies under Ada 2005.
8704 if Is_Limited_Type (Typ)
8705 and then Is_Tagged_Type (Typ)
8706 then
8707 if Operation = TSS_Stream_Read then
8708 Has_Predefined_Or_Specified_Stream_Attribute :=
8709 Has_Specified_Stream_Read (Typ);
8711 elsif Operation = TSS_Stream_Write then
8712 Has_Predefined_Or_Specified_Stream_Attribute :=
8713 Has_Specified_Stream_Write (Typ);
8715 elsif Operation = TSS_Stream_Input then
8716 Has_Predefined_Or_Specified_Stream_Attribute :=
8717 Has_Specified_Stream_Input (Typ)
8718 or else
8719 (Ada_Version >= Ada_05
8720 and then Stream_Operation_OK (Typ, TSS_Stream_Read));
8722 elsif Operation = TSS_Stream_Output then
8723 Has_Predefined_Or_Specified_Stream_Attribute :=
8724 Has_Specified_Stream_Output (Typ)
8725 or else
8726 (Ada_Version >= Ada_05
8727 and then Stream_Operation_OK (Typ, TSS_Stream_Write));
8728 end if;
8730 -- Case of inherited TSS_Stream_Read or TSS_Stream_Write
8732 if not Has_Predefined_Or_Specified_Stream_Attribute
8733 and then Is_Derived_Type (Typ)
8734 and then (Operation = TSS_Stream_Read
8735 or else Operation = TSS_Stream_Write)
8736 then
8737 Has_Predefined_Or_Specified_Stream_Attribute :=
8738 Present
8739 (Find_Inherited_TSS (Base_Type (Etype (Typ)), Operation));
8740 end if;
8741 end if;
8743 -- If the type is not limited, or else is limited but the attribute is
8744 -- explicitly specified or is predefined for the type, then return True,
8745 -- unless other conditions prevail, such as restrictions prohibiting
8746 -- streams or dispatching operations. We also return True for limited
8747 -- interfaces, because they may be extended by nonlimited types and
8748 -- permit inheritance in this case (addresses cases where an abstract
8749 -- extension doesn't get 'Input declared, as per comments below, but
8750 -- 'Class'Input must still be allowed). Note that attempts to apply
8751 -- stream attributes to a limited interface or its class-wide type
8752 -- (or limited extensions thereof) will still get properly rejected
8753 -- by Check_Stream_Attribute.
8755 -- We exclude the Input operation from being a predefined subprogram in
8756 -- the case where the associated type is an abstract extension, because
8757 -- the attribute is not callable in that case, per 13.13.2(49/2). Also,
8758 -- we don't want an abstract version created because types derived from
8759 -- the abstract type may not even have Input available (for example if
8760 -- derived from a private view of the abstract type that doesn't have
8761 -- a visible Input), but a VM such as .NET or the Java VM can treat the
8762 -- operation as inherited anyway, and we don't want an abstract function
8763 -- to be (implicitly) inherited in that case because it can lead to a VM
8764 -- exception.
8766 return (not Is_Limited_Type (Typ)
8767 or else Is_Interface (Typ)
8768 or else Has_Predefined_Or_Specified_Stream_Attribute)
8769 and then (Operation /= TSS_Stream_Input
8770 or else not Is_Abstract_Type (Typ)
8771 or else not Is_Derived_Type (Typ))
8772 and then not Has_Unknown_Discriminants (Typ)
8773 and then not (Is_Interface (Typ)
8774 and then (Is_Task_Interface (Typ)
8775 or else Is_Protected_Interface (Typ)
8776 or else Is_Synchronized_Interface (Typ)))
8777 and then not Restriction_Active (No_Streams)
8778 and then not Restriction_Active (No_Dispatch)
8779 and then not No_Run_Time_Mode
8780 and then RTE_Available (RE_Tag)
8781 and then RTE_Available (RE_Root_Stream_Type);
8782 end Stream_Operation_OK;
8784 end Exp_Ch3;