2007-06-06 Benjamin Kosnik <bkoz@redhat.com>
[official-gcc.git] / gcc / ada / exp_ch3.adb
blob9f2a60b7375d05ea1439d6213b46848ba405fd99
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- E X P _ C H 3 --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2007, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 2, 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 COPYING. If not, write --
19 -- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
20 -- Boston, MA 02110-1301, USA. --
21 -- --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 -- --
25 ------------------------------------------------------------------------------
27 with Atree; use Atree;
28 with Checks; use Checks;
29 with Einfo; use Einfo;
30 with Errout; use Errout;
31 with Exp_Aggr; use Exp_Aggr;
32 with Exp_Atag; use Exp_Atag;
33 with Exp_Ch4; use Exp_Ch4;
34 with Exp_Ch6; use Exp_Ch6;
35 with Exp_Ch7; use Exp_Ch7;
36 with Exp_Ch9; use Exp_Ch9;
37 with Exp_Ch11; use Exp_Ch11;
38 with Exp_Disp; use Exp_Disp;
39 with Exp_Dist; use Exp_Dist;
40 with Exp_Smem; use Exp_Smem;
41 with Exp_Strm; use Exp_Strm;
42 with Exp_Tss; use Exp_Tss;
43 with Exp_Util; use Exp_Util;
44 with Freeze; use Freeze;
45 with Nlists; use Nlists;
46 with Namet; use Namet;
47 with Nmake; use Nmake;
48 with Opt; use Opt;
49 with Restrict; use Restrict;
50 with Rident; use Rident;
51 with Rtsfind; use Rtsfind;
52 with Sem; use Sem;
53 with Sem_Attr; use Sem_Attr;
54 with Sem_Cat; use Sem_Cat;
55 with Sem_Ch3; use Sem_Ch3;
56 with Sem_Ch8; use Sem_Ch8;
57 with Sem_Disp; use Sem_Disp;
58 with Sem_Eval; use Sem_Eval;
59 with Sem_Mech; use Sem_Mech;
60 with Sem_Res; use Sem_Res;
61 with Sem_Util; use Sem_Util;
62 with Sinfo; use Sinfo;
63 with Stand; use Stand;
64 with Snames; use Snames;
65 with Targparm; use Targparm;
66 with Tbuild; use Tbuild;
67 with Ttypes; use Ttypes;
68 with Validsw; use Validsw;
70 package body Exp_Ch3 is
72 -----------------------
73 -- Local Subprograms --
74 -----------------------
76 procedure Adjust_Discriminants (Rtype : Entity_Id);
77 -- This is used when freezing a record type. It attempts to construct
78 -- more restrictive subtypes for discriminants so that the max size of
79 -- the record can be calculated more accurately. See the body of this
80 -- procedure for details.
82 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id);
83 -- Build initialization procedure for given array type. Nod is a node
84 -- used for attachment of any actions required in its construction.
85 -- It also supplies the source location used for the procedure.
87 function Build_Discriminant_Formals
88 (Rec_Id : Entity_Id;
89 Use_Dl : Boolean) return List_Id;
90 -- This function uses the discriminants of a type to build a list of
91 -- formal parameters, used in the following function. If the flag Use_Dl
92 -- is set, the list is built using the already defined discriminals
93 -- of the type. Otherwise new identifiers are created, with the source
94 -- names of the discriminants.
96 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id;
97 -- This function builds a static aggregate that can serve as the initial
98 -- value for an array type whose bounds are static, and whose component
99 -- type is a composite type that has a static equivalent aggregate.
100 -- The equivalent array aggregate is used both for object initialization
101 -- and for component initialization, when used in the following function.
103 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id;
104 -- This function builds a static aggregate that can serve as the initial
105 -- value for a record type whose components are scalar and initialized
106 -- with compile-time values, or arrays with similarc initialization or
107 -- defaults. When possible, initialization of an object of the type can
108 -- be achieved by using a copy of the aggregate as an initial value, thus
109 -- removing the implicit call that would otherwise constitute elaboration
110 -- code.
112 function Build_Master_Renaming
113 (N : Node_Id;
114 T : Entity_Id) return Entity_Id;
115 -- If the designated type of an access type is a task type or contains
116 -- tasks, we make sure that a _Master variable is declared in the current
117 -- scope, and then declare a renaming for it:
119 -- atypeM : Master_Id renames _Master;
121 -- where atyp is the name of the access type. This declaration is used when
122 -- an allocator for the access type is expanded. The node is the full
123 -- declaration of the designated type that contains tasks. The renaming
124 -- declaration is inserted before N, and after the Master declaration.
126 procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id);
127 -- Build record initialization procedure. N is the type declaration
128 -- node, and Pe is the corresponding entity for the record type.
130 procedure Build_Slice_Assignment (Typ : Entity_Id);
131 -- Build assignment procedure for one-dimensional arrays of controlled
132 -- types. Other array and slice assignments are expanded in-line, but
133 -- the code expansion for controlled components (when control actions
134 -- are active) can lead to very large blocks that GCC3 handles poorly.
136 procedure Build_Variant_Record_Equality (Typ : Entity_Id);
137 -- Create An Equality function for the non-tagged variant record 'Typ'
138 -- and attach it to the TSS list
140 procedure Check_Stream_Attributes (Typ : Entity_Id);
141 -- Check that if a limited extension has a parent with user-defined stream
142 -- attributes, and does not itself have user-defined stream-attributes,
143 -- then any limited component of the extension also has the corresponding
144 -- user-defined stream attributes.
146 procedure Clean_Task_Names
147 (Typ : Entity_Id;
148 Proc_Id : Entity_Id);
149 -- If an initialization procedure includes calls to generate names
150 -- for task subcomponents, indicate that secondary stack cleanup is
151 -- needed after an initialization. Typ is the component type, and Proc_Id
152 -- the initialization procedure for the enclosing composite type.
154 procedure Expand_Tagged_Root (T : Entity_Id);
155 -- Add a field _Tag at the beginning of the record. This field carries
156 -- the value of the access to the Dispatch table. This procedure is only
157 -- called on root type, the _Tag field being inherited by the descendants.
159 procedure Expand_Record_Controller (T : Entity_Id);
160 -- T must be a record type that Has_Controlled_Component. Add a field
161 -- _controller of type Record_Controller or Limited_Record_Controller
162 -- in the record T.
164 procedure Freeze_Array_Type (N : Node_Id);
165 -- Freeze an array type. Deals with building the initialization procedure,
166 -- creating the packed array type for a packed array and also with the
167 -- creation of the controlling procedures for the controlled case. The
168 -- argument N is the N_Freeze_Entity node for the type.
170 procedure Freeze_Enumeration_Type (N : Node_Id);
171 -- Freeze enumeration type with non-standard representation. Builds the
172 -- array and function needed to convert between enumeration pos and
173 -- enumeration representation values. N is the N_Freeze_Entity node
174 -- for the type.
176 procedure Freeze_Record_Type (N : Node_Id);
177 -- Freeze record type. Builds all necessary discriminant checking
178 -- and other ancillary functions, and builds dispatch tables where
179 -- needed. The argument N is the N_Freeze_Entity node. This processing
180 -- applies only to E_Record_Type entities, not to class wide types,
181 -- record subtypes, or private types.
183 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id);
184 -- Treat user-defined stream operations as renaming_as_body if the
185 -- subprogram they rename is not frozen when the type is frozen.
187 procedure Initialization_Warning (E : Entity_Id);
188 -- If static elaboration of the package is requested, indicate
189 -- when a type does meet the conditions for static initialization. If
190 -- E is a type, it has components that have no static initialization.
191 -- if E is an entity, its initial expression is not compile-time known.
193 function Init_Formals (Typ : Entity_Id) return List_Id;
194 -- This function builds the list of formals for an initialization routine.
195 -- The first formal is always _Init with the given type. For task value
196 -- record types and types containing tasks, three additional formals are
197 -- added:
199 -- _Master : Master_Id
200 -- _Chain : in out Activation_Chain
201 -- _Task_Name : String
203 -- The caller must append additional entries for discriminants if required.
205 function In_Runtime (E : Entity_Id) return Boolean;
206 -- Check if E is defined in the RTL (in a child of Ada or System). Used
207 -- to avoid to bring in the overhead of _Input, _Output for tagged types.
209 function Make_Eq_Case
210 (E : Entity_Id;
211 CL : Node_Id;
212 Discr : Entity_Id := Empty) return List_Id;
213 -- Building block for variant record equality. Defined to share the code
214 -- between the tagged and non-tagged case. Given a Component_List node CL,
215 -- it generates an 'if' followed by a 'case' statement that compares all
216 -- components of local temporaries named X and Y (that are declared as
217 -- formals at some upper level). E provides the Sloc to be used for the
218 -- generated code. Discr is used as the case statement switch in the case
219 -- of Unchecked_Union equality.
221 function Make_Eq_If
222 (E : Entity_Id;
223 L : List_Id) return Node_Id;
224 -- Building block for variant record equality. Defined to share the code
225 -- between the tagged and non-tagged case. Given the list of components
226 -- (or discriminants) L, it generates a return 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.
231 procedure Make_Predefined_Primitive_Specs
232 (Tag_Typ : Entity_Id;
233 Predef_List : out List_Id;
234 Renamed_Eq : out Node_Id);
235 -- Create a list with the specs of the predefined primitive operations.
236 -- The following entries are present for all tagged types, and provide
237 -- the results of the corresponding attribute applied to the object.
238 -- Dispatching is required in general, since the result of the attribute
239 -- will vary with the actual object subtype.
241 -- _alignment provides result of 'Alignment attribute
242 -- _size provides result of 'Size attribute
243 -- typSR provides result of 'Read attribute
244 -- typSW provides result of 'Write attribute
245 -- typSI provides result of 'Input attribute
246 -- typSO provides result of 'Output attribute
248 -- The following entries are additionally present for non-limited tagged
249 -- types, and implement additional dispatching operations for predefined
250 -- operations:
252 -- _equality implements "=" operator
253 -- _assign implements assignment operation
254 -- typDF implements deep finalization
255 -- typDA implements deep adjust
257 -- The latter two are empty procedures unless the type contains some
258 -- controlled components that require finalization actions (the deep
259 -- in the name refers to the fact that the action applies to components).
261 -- The list is returned in Predef_List. The Parameter Renamed_Eq either
262 -- returns the value Empty, or else the defining unit name for the
263 -- predefined equality function in the case where the type has a primitive
264 -- operation that is a renaming of predefined equality (but only if there
265 -- is also an overriding user-defined equality function). The returned
266 -- Renamed_Eq will be passed to the corresponding parameter of
267 -- Predefined_Primitive_Bodies.
269 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean;
270 -- returns True if there are representation clauses for type T that are not
271 -- inherited. If the result is false, the init_proc and the discriminant
272 -- checking functions of the parent can be reused by a derived type.
274 procedure Make_Controlling_Function_Wrappers
275 (Tag_Typ : Entity_Id;
276 Decl_List : out List_Id;
277 Body_List : out List_Id);
278 -- Ada 2005 (AI-391): Makes specs and bodies for the wrapper functions
279 -- associated with inherited functions with controlling results which
280 -- are not overridden. The body of each wrapper function consists solely
281 -- of a return statement whose expression is an extension aggregate
282 -- invoking the inherited subprogram's parent subprogram and extended
283 -- with a null association list.
285 procedure Make_Null_Procedure_Specs
286 (Tag_Typ : Entity_Id;
287 Decl_List : out List_Id);
288 -- Ada 2005 (AI-251): Makes specs for null procedures associated with any
289 -- null procedures inherited from an interface type that have not been
290 -- overridden. Only one null procedure will be created for a given set of
291 -- inherited null procedures with homographic profiles.
293 function Predef_Spec_Or_Body
294 (Loc : Source_Ptr;
295 Tag_Typ : Entity_Id;
296 Name : Name_Id;
297 Profile : List_Id;
298 Ret_Type : Entity_Id := Empty;
299 For_Body : Boolean := False) return Node_Id;
300 -- This function generates the appropriate expansion for a predefined
301 -- primitive operation specified by its name, parameter profile and
302 -- return type (Empty means this is a procedure). If For_Body is false,
303 -- then the returned node is a subprogram declaration. If For_Body is
304 -- true, then the returned node is a empty subprogram body containing
305 -- no declarations and no statements.
307 function Predef_Stream_Attr_Spec
308 (Loc : Source_Ptr;
309 Tag_Typ : Entity_Id;
310 Name : TSS_Name_Type;
311 For_Body : Boolean := False) return Node_Id;
312 -- Specialized version of Predef_Spec_Or_Body that apply to read, write,
313 -- input and output attribute whose specs are constructed in Exp_Strm.
315 function Predef_Deep_Spec
316 (Loc : Source_Ptr;
317 Tag_Typ : Entity_Id;
318 Name : TSS_Name_Type;
319 For_Body : Boolean := False) return Node_Id;
320 -- Specialized version of Predef_Spec_Or_Body that apply to _deep_adjust
321 -- and _deep_finalize
323 function Predefined_Primitive_Bodies
324 (Tag_Typ : Entity_Id;
325 Renamed_Eq : Node_Id) return List_Id;
326 -- Create the bodies of the predefined primitives that are described in
327 -- Predefined_Primitive_Specs. When not empty, Renamed_Eq must denote
328 -- the defining unit name of the type's predefined equality as returned
329 -- by Make_Predefined_Primitive_Specs.
331 function Predefined_Primitive_Freeze (Tag_Typ : Entity_Id) return List_Id;
332 -- Freeze entities of all predefined primitive operations. This is needed
333 -- because the bodies of these operations do not normally do any freezing.
335 function Stream_Operation_OK
336 (Typ : Entity_Id;
337 Operation : TSS_Name_Type) return Boolean;
338 -- Check whether the named stream operation must be emitted for a given
339 -- type. The rules for inheritance of stream attributes by type extensions
340 -- are enforced by this function. Furthermore, various restrictions prevent
341 -- the generation of these operations, as a useful optimization or for
342 -- certification purposes.
344 --------------------------
345 -- Adjust_Discriminants --
346 --------------------------
348 -- This procedure attempts to define subtypes for discriminants that are
349 -- more restrictive than those declared. Such a replacement is possible if
350 -- we can demonstrate that values outside the restricted range would cause
351 -- constraint errors in any case. The advantage of restricting the
352 -- discriminant types in this way is that the maximum size of the variant
353 -- record can be calculated more conservatively.
355 -- An example of a situation in which we can perform this type of
356 -- restriction is the following:
358 -- subtype B is range 1 .. 10;
359 -- type Q is array (B range <>) of Integer;
361 -- type V (N : Natural) is record
362 -- C : Q (1 .. N);
363 -- end record;
365 -- In this situation, we can restrict the upper bound of N to 10, since
366 -- any larger value would cause a constraint error in any case.
368 -- There are many situations in which such restriction is possible, but
369 -- for now, we just look for cases like the above, where the component
370 -- in question is a one dimensional array whose upper bound is one of
371 -- the record discriminants. Also the component must not be part of
372 -- any variant part, since then the component does not always exist.
374 procedure Adjust_Discriminants (Rtype : Entity_Id) is
375 Loc : constant Source_Ptr := Sloc (Rtype);
376 Comp : Entity_Id;
377 Ctyp : Entity_Id;
378 Ityp : Entity_Id;
379 Lo : Node_Id;
380 Hi : Node_Id;
381 P : Node_Id;
382 Loval : Uint;
383 Discr : Entity_Id;
384 Dtyp : Entity_Id;
385 Dhi : Node_Id;
386 Dhiv : Uint;
387 Ahi : Node_Id;
388 Ahiv : Uint;
389 Tnn : Entity_Id;
391 begin
392 Comp := First_Component (Rtype);
393 while Present (Comp) loop
395 -- If our parent is a variant, quit, we do not look at components
396 -- that are in variant parts, because they may not always exist.
398 P := Parent (Comp); -- component declaration
399 P := Parent (P); -- component list
401 exit when Nkind (Parent (P)) = N_Variant;
403 -- We are looking for a one dimensional array type
405 Ctyp := Etype (Comp);
407 if not Is_Array_Type (Ctyp)
408 or else Number_Dimensions (Ctyp) > 1
409 then
410 goto Continue;
411 end if;
413 -- The lower bound must be constant, and the upper bound is a
414 -- discriminant (which is a discriminant of the current record).
416 Ityp := Etype (First_Index (Ctyp));
417 Lo := Type_Low_Bound (Ityp);
418 Hi := Type_High_Bound (Ityp);
420 if not Compile_Time_Known_Value (Lo)
421 or else Nkind (Hi) /= N_Identifier
422 or else No (Entity (Hi))
423 or else Ekind (Entity (Hi)) /= E_Discriminant
424 then
425 goto Continue;
426 end if;
428 -- We have an array with appropriate bounds
430 Loval := Expr_Value (Lo);
431 Discr := Entity (Hi);
432 Dtyp := Etype (Discr);
434 -- See if the discriminant has a known upper bound
436 Dhi := Type_High_Bound (Dtyp);
438 if not Compile_Time_Known_Value (Dhi) then
439 goto Continue;
440 end if;
442 Dhiv := Expr_Value (Dhi);
444 -- See if base type of component array has known upper bound
446 Ahi := Type_High_Bound (Etype (First_Index (Base_Type (Ctyp))));
448 if not Compile_Time_Known_Value (Ahi) then
449 goto Continue;
450 end if;
452 Ahiv := Expr_Value (Ahi);
454 -- The condition for doing the restriction is that the high bound
455 -- of the discriminant is greater than the low bound of the array,
456 -- and is also greater than the high bound of the base type index.
458 if Dhiv > Loval and then Dhiv > Ahiv then
460 -- We can reset the upper bound of the discriminant type to
461 -- whichever is larger, the low bound of the component, or
462 -- the high bound of the base type array index.
464 -- We build a subtype that is declared as
466 -- subtype Tnn is discr_type range discr_type'First .. max;
468 -- And insert this declaration into the tree. The type of the
469 -- discriminant is then reset to this more restricted subtype.
471 Tnn := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
473 Insert_Action (Declaration_Node (Rtype),
474 Make_Subtype_Declaration (Loc,
475 Defining_Identifier => Tnn,
476 Subtype_Indication =>
477 Make_Subtype_Indication (Loc,
478 Subtype_Mark => New_Occurrence_Of (Dtyp, Loc),
479 Constraint =>
480 Make_Range_Constraint (Loc,
481 Range_Expression =>
482 Make_Range (Loc,
483 Low_Bound =>
484 Make_Attribute_Reference (Loc,
485 Attribute_Name => Name_First,
486 Prefix => New_Occurrence_Of (Dtyp, Loc)),
487 High_Bound =>
488 Make_Integer_Literal (Loc,
489 Intval => UI_Max (Loval, Ahiv)))))));
491 Set_Etype (Discr, Tnn);
492 end if;
494 <<Continue>>
495 Next_Component (Comp);
496 end loop;
497 end Adjust_Discriminants;
499 ---------------------------
500 -- Build_Array_Init_Proc --
501 ---------------------------
503 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id) is
504 Loc : constant Source_Ptr := Sloc (Nod);
505 Comp_Type : constant Entity_Id := Component_Type (A_Type);
506 Index_List : List_Id;
507 Proc_Id : Entity_Id;
508 Body_Stmts : List_Id;
510 function Init_Component return List_Id;
511 -- Create one statement to initialize one array component, designated
512 -- by a full set of indices.
514 function Init_One_Dimension (N : Int) return List_Id;
515 -- Create loop to initialize one dimension of the array. The single
516 -- statement in the loop body initializes the inner dimensions if any,
517 -- or else the single component. Note that this procedure is called
518 -- recursively, with N being the dimension to be initialized. A call
519 -- with N greater than the number of dimensions simply generates the
520 -- component initialization, terminating the recursion.
522 --------------------
523 -- Init_Component --
524 --------------------
526 function Init_Component return List_Id is
527 Comp : Node_Id;
529 begin
530 Comp :=
531 Make_Indexed_Component (Loc,
532 Prefix => Make_Identifier (Loc, Name_uInit),
533 Expressions => Index_List);
535 if Needs_Simple_Initialization (Comp_Type) then
536 Set_Assignment_OK (Comp);
537 return New_List (
538 Make_Assignment_Statement (Loc,
539 Name => Comp,
540 Expression =>
541 Get_Simple_Init_Val
542 (Comp_Type, Loc, Component_Size (A_Type))));
544 else
545 Clean_Task_Names (Comp_Type, Proc_Id);
546 return
547 Build_Initialization_Call
548 (Loc, Comp, Comp_Type,
549 In_Init_Proc => True,
550 Enclos_Type => A_Type);
551 end if;
552 end Init_Component;
554 ------------------------
555 -- Init_One_Dimension --
556 ------------------------
558 function Init_One_Dimension (N : Int) return List_Id is
559 Index : Entity_Id;
561 begin
562 -- If the component does not need initializing, then there is nothing
563 -- to do here, so we return a null body. This occurs when generating
564 -- the dummy Init_Proc needed for Initialize_Scalars processing.
566 if not Has_Non_Null_Base_Init_Proc (Comp_Type)
567 and then not Needs_Simple_Initialization (Comp_Type)
568 and then not Has_Task (Comp_Type)
569 then
570 return New_List (Make_Null_Statement (Loc));
572 -- If all dimensions dealt with, we simply initialize the component
574 elsif N > Number_Dimensions (A_Type) then
575 return Init_Component;
577 -- Here we generate the required loop
579 else
580 Index :=
581 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
583 Append (New_Reference_To (Index, Loc), Index_List);
585 return New_List (
586 Make_Implicit_Loop_Statement (Nod,
587 Identifier => Empty,
588 Iteration_Scheme =>
589 Make_Iteration_Scheme (Loc,
590 Loop_Parameter_Specification =>
591 Make_Loop_Parameter_Specification (Loc,
592 Defining_Identifier => Index,
593 Discrete_Subtype_Definition =>
594 Make_Attribute_Reference (Loc,
595 Prefix => Make_Identifier (Loc, Name_uInit),
596 Attribute_Name => Name_Range,
597 Expressions => New_List (
598 Make_Integer_Literal (Loc, N))))),
599 Statements => Init_One_Dimension (N + 1)));
600 end if;
601 end Init_One_Dimension;
603 -- Start of processing for Build_Array_Init_Proc
605 begin
606 if Suppress_Init_Proc (A_Type) or else Is_Value_Type (Comp_Type) then
607 return;
608 end if;
610 Index_List := New_List;
612 -- We need an initialization procedure if any of the following is true:
614 -- 1. The component type has an initialization procedure
615 -- 2. The component type needs simple initialization
616 -- 3. Tasks are present
617 -- 4. The type is marked as a public entity
619 -- The reason for the public entity test is to deal properly with the
620 -- Initialize_Scalars pragma. This pragma can be set in the client and
621 -- not in the declaring package, this means the client will make a call
622 -- to the initialization procedure (because one of conditions 1-3 must
623 -- apply in this case), and we must generate a procedure (even if it is
624 -- null) to satisfy the call in this case.
626 -- Exception: do not build an array init_proc for a type whose root
627 -- type is Standard.String or Standard.Wide_[Wide_]String, since there
628 -- is no place to put the code, and in any case we handle initialization
629 -- of such types (in the Initialize_Scalars case, that's the only time
630 -- the issue arises) in a special manner anyway which does not need an
631 -- init_proc.
633 if Has_Non_Null_Base_Init_Proc (Comp_Type)
634 or else Needs_Simple_Initialization (Comp_Type)
635 or else Has_Task (Comp_Type)
636 or else (not Restriction_Active (No_Initialize_Scalars)
637 and then Is_Public (A_Type)
638 and then Root_Type (A_Type) /= Standard_String
639 and then Root_Type (A_Type) /= Standard_Wide_String
640 and then Root_Type (A_Type) /= Standard_Wide_Wide_String)
641 then
642 Proc_Id :=
643 Make_Defining_Identifier (Loc, Make_Init_Proc_Name (A_Type));
645 Body_Stmts := Init_One_Dimension (1);
647 Discard_Node (
648 Make_Subprogram_Body (Loc,
649 Specification =>
650 Make_Procedure_Specification (Loc,
651 Defining_Unit_Name => Proc_Id,
652 Parameter_Specifications => Init_Formals (A_Type)),
653 Declarations => New_List,
654 Handled_Statement_Sequence =>
655 Make_Handled_Sequence_Of_Statements (Loc,
656 Statements => Body_Stmts)));
658 Set_Ekind (Proc_Id, E_Procedure);
659 Set_Is_Public (Proc_Id, Is_Public (A_Type));
660 Set_Is_Internal (Proc_Id);
661 Set_Has_Completion (Proc_Id);
663 if not Debug_Generated_Code then
664 Set_Debug_Info_Off (Proc_Id);
665 end if;
667 -- Set inlined unless controlled stuff or tasks around, in which
668 -- case we do not want to inline, because nested stuff may cause
669 -- difficulties in inter-unit inlining, and furthermore there is
670 -- in any case no point in inlining such complex init procs.
672 if not Has_Task (Proc_Id)
673 and then not Controlled_Type (Proc_Id)
674 then
675 Set_Is_Inlined (Proc_Id);
676 end if;
678 -- Associate Init_Proc with type, and determine if the procedure
679 -- is null (happens because of the Initialize_Scalars pragma case,
680 -- where we have to generate a null procedure in case it is called
681 -- by a client with Initialize_Scalars set). Such procedures have
682 -- to be generated, but do not have to be called, so we mark them
683 -- as null to suppress the call.
685 Set_Init_Proc (A_Type, Proc_Id);
687 if List_Length (Body_Stmts) = 1
688 and then Nkind (First (Body_Stmts)) = N_Null_Statement
689 then
690 Set_Is_Null_Init_Proc (Proc_Id);
692 else
693 -- Try to build a static aggregate to initialize statically
694 -- objects of the type. This can only be done for constrained
695 -- one-dimensional arrays with static bounds.
697 Set_Static_Initialization
698 (Proc_Id,
699 Build_Equivalent_Array_Aggregate (First_Subtype (A_Type)));
700 end if;
701 end if;
702 end Build_Array_Init_Proc;
704 -----------------------------
705 -- Build_Class_Wide_Master --
706 -----------------------------
708 procedure Build_Class_Wide_Master (T : Entity_Id) is
709 Loc : constant Source_Ptr := Sloc (T);
710 M_Id : Entity_Id;
711 Decl : Node_Id;
712 P : Node_Id;
713 Par : Node_Id;
715 begin
716 -- Nothing to do if there is no task hierarchy
718 if Restriction_Active (No_Task_Hierarchy) then
719 return;
720 end if;
722 -- Find declaration that created the access type: either a type
723 -- declaration, or an object declaration with an access definition,
724 -- in which case the type is anonymous.
726 if Is_Itype (T) then
727 P := Associated_Node_For_Itype (T);
728 else
729 P := Parent (T);
730 end if;
732 -- Nothing to do if we already built a master entity for this scope
734 if not Has_Master_Entity (Scope (T)) then
736 -- First build the master entity
737 -- _Master : constant Master_Id := Current_Master.all;
738 -- and insert it just before the current declaration.
740 Decl :=
741 Make_Object_Declaration (Loc,
742 Defining_Identifier =>
743 Make_Defining_Identifier (Loc, Name_uMaster),
744 Constant_Present => True,
745 Object_Definition => New_Reference_To (Standard_Integer, Loc),
746 Expression =>
747 Make_Explicit_Dereference (Loc,
748 New_Reference_To (RTE (RE_Current_Master), Loc)));
750 Insert_Action (P, Decl);
751 Analyze (Decl);
752 Set_Has_Master_Entity (Scope (T));
754 -- Now mark the containing scope as a task master
756 Par := P;
757 while Nkind (Par) /= N_Compilation_Unit loop
758 Par := Parent (Par);
760 -- If we fall off the top, we are at the outer level, and the
761 -- environment task is our effective master, so nothing to mark.
763 if Nkind (Par) = N_Task_Body
764 or else Nkind (Par) = N_Block_Statement
765 or else Nkind (Par) = N_Subprogram_Body
766 then
767 Set_Is_Task_Master (Par, True);
768 exit;
769 end if;
770 end loop;
771 end if;
773 -- Now define the renaming of the master_id
775 M_Id :=
776 Make_Defining_Identifier (Loc,
777 New_External_Name (Chars (T), 'M'));
779 Decl :=
780 Make_Object_Renaming_Declaration (Loc,
781 Defining_Identifier => M_Id,
782 Subtype_Mark => New_Reference_To (Standard_Integer, Loc),
783 Name => Make_Identifier (Loc, Name_uMaster));
784 Insert_Before (P, Decl);
785 Analyze (Decl);
787 Set_Master_Id (T, M_Id);
789 exception
790 when RE_Not_Available =>
791 return;
792 end Build_Class_Wide_Master;
794 --------------------------------
795 -- Build_Discr_Checking_Funcs --
796 --------------------------------
798 procedure Build_Discr_Checking_Funcs (N : Node_Id) is
799 Rec_Id : Entity_Id;
800 Loc : Source_Ptr;
801 Enclosing_Func_Id : Entity_Id;
802 Sequence : Nat := 1;
803 Type_Def : Node_Id;
804 V : Node_Id;
806 function Build_Case_Statement
807 (Case_Id : Entity_Id;
808 Variant : Node_Id) return Node_Id;
809 -- Build a case statement containing only two alternatives. The first
810 -- alternative corresponds exactly to the discrete choices given on the
811 -- variant with contains the components that we are generating the
812 -- checks for. If the discriminant is one of these return False. The
813 -- second alternative is an OTHERS choice that will return True
814 -- indicating the discriminant did not match.
816 function Build_Dcheck_Function
817 (Case_Id : Entity_Id;
818 Variant : Node_Id) return Entity_Id;
819 -- Build the discriminant checking function for a given variant
821 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id);
822 -- Builds the discriminant checking function for each variant of the
823 -- given variant part of the record type.
825 --------------------------
826 -- Build_Case_Statement --
827 --------------------------
829 function Build_Case_Statement
830 (Case_Id : Entity_Id;
831 Variant : Node_Id) return Node_Id
833 Alt_List : constant List_Id := New_List;
834 Actuals_List : List_Id;
835 Case_Node : Node_Id;
836 Case_Alt_Node : Node_Id;
837 Choice : Node_Id;
838 Choice_List : List_Id;
839 D : Entity_Id;
840 Return_Node : Node_Id;
842 begin
843 Case_Node := New_Node (N_Case_Statement, Loc);
845 -- Replace the discriminant which controls the variant, with the name
846 -- of the formal of the checking function.
848 Set_Expression (Case_Node,
849 Make_Identifier (Loc, Chars (Case_Id)));
851 Choice := First (Discrete_Choices (Variant));
853 if Nkind (Choice) = N_Others_Choice then
854 Choice_List := New_Copy_List (Others_Discrete_Choices (Choice));
855 else
856 Choice_List := New_Copy_List (Discrete_Choices (Variant));
857 end if;
859 if not Is_Empty_List (Choice_List) then
860 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
861 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
863 -- In case this is a nested variant, we need to return the result
864 -- of the discriminant checking function for the immediately
865 -- enclosing variant.
867 if Present (Enclosing_Func_Id) then
868 Actuals_List := New_List;
870 D := First_Discriminant (Rec_Id);
871 while Present (D) loop
872 Append (Make_Identifier (Loc, Chars (D)), Actuals_List);
873 Next_Discriminant (D);
874 end loop;
876 Return_Node :=
877 Make_Return_Statement (Loc,
878 Expression =>
879 Make_Function_Call (Loc,
880 Name =>
881 New_Reference_To (Enclosing_Func_Id, Loc),
882 Parameter_Associations =>
883 Actuals_List));
885 else
886 Return_Node :=
887 Make_Return_Statement (Loc,
888 Expression =>
889 New_Reference_To (Standard_False, Loc));
890 end if;
892 Set_Statements (Case_Alt_Node, New_List (Return_Node));
893 Append (Case_Alt_Node, Alt_List);
894 end if;
896 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
897 Choice_List := New_List (New_Node (N_Others_Choice, Loc));
898 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
900 Return_Node :=
901 Make_Return_Statement (Loc,
902 Expression =>
903 New_Reference_To (Standard_True, Loc));
905 Set_Statements (Case_Alt_Node, New_List (Return_Node));
906 Append (Case_Alt_Node, Alt_List);
908 Set_Alternatives (Case_Node, Alt_List);
909 return Case_Node;
910 end Build_Case_Statement;
912 ---------------------------
913 -- Build_Dcheck_Function --
914 ---------------------------
916 function Build_Dcheck_Function
917 (Case_Id : Entity_Id;
918 Variant : Node_Id) return Entity_Id
920 Body_Node : Node_Id;
921 Func_Id : Entity_Id;
922 Parameter_List : List_Id;
923 Spec_Node : Node_Id;
925 begin
926 Body_Node := New_Node (N_Subprogram_Body, Loc);
927 Sequence := Sequence + 1;
929 Func_Id :=
930 Make_Defining_Identifier (Loc,
931 Chars => New_External_Name (Chars (Rec_Id), 'D', Sequence));
933 Spec_Node := New_Node (N_Function_Specification, Loc);
934 Set_Defining_Unit_Name (Spec_Node, Func_Id);
936 Parameter_List := Build_Discriminant_Formals (Rec_Id, False);
938 Set_Parameter_Specifications (Spec_Node, Parameter_List);
939 Set_Result_Definition (Spec_Node,
940 New_Reference_To (Standard_Boolean, Loc));
941 Set_Specification (Body_Node, Spec_Node);
942 Set_Declarations (Body_Node, New_List);
944 Set_Handled_Statement_Sequence (Body_Node,
945 Make_Handled_Sequence_Of_Statements (Loc,
946 Statements => New_List (
947 Build_Case_Statement (Case_Id, Variant))));
949 Set_Ekind (Func_Id, E_Function);
950 Set_Mechanism (Func_Id, Default_Mechanism);
951 Set_Is_Inlined (Func_Id, True);
952 Set_Is_Pure (Func_Id, True);
953 Set_Is_Public (Func_Id, Is_Public (Rec_Id));
954 Set_Is_Internal (Func_Id, True);
956 if not Debug_Generated_Code then
957 Set_Debug_Info_Off (Func_Id);
958 end if;
960 Analyze (Body_Node);
962 Append_Freeze_Action (Rec_Id, Body_Node);
963 Set_Dcheck_Function (Variant, Func_Id);
964 return Func_Id;
965 end Build_Dcheck_Function;
967 ----------------------------
968 -- Build_Dcheck_Functions --
969 ----------------------------
971 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id) is
972 Component_List_Node : Node_Id;
973 Decl : Entity_Id;
974 Discr_Name : Entity_Id;
975 Func_Id : Entity_Id;
976 Variant : Node_Id;
977 Saved_Enclosing_Func_Id : Entity_Id;
979 begin
980 -- Build the discriminant checking function for each variant, label
981 -- all components of that variant with the function's name.
983 Discr_Name := Entity (Name (Variant_Part_Node));
984 Variant := First_Non_Pragma (Variants (Variant_Part_Node));
986 while Present (Variant) loop
987 Func_Id := Build_Dcheck_Function (Discr_Name, Variant);
988 Component_List_Node := Component_List (Variant);
990 if not Null_Present (Component_List_Node) then
991 Decl :=
992 First_Non_Pragma (Component_Items (Component_List_Node));
994 while Present (Decl) loop
995 Set_Discriminant_Checking_Func
996 (Defining_Identifier (Decl), Func_Id);
998 Next_Non_Pragma (Decl);
999 end loop;
1001 if Present (Variant_Part (Component_List_Node)) then
1002 Saved_Enclosing_Func_Id := Enclosing_Func_Id;
1003 Enclosing_Func_Id := Func_Id;
1004 Build_Dcheck_Functions (Variant_Part (Component_List_Node));
1005 Enclosing_Func_Id := Saved_Enclosing_Func_Id;
1006 end if;
1007 end if;
1009 Next_Non_Pragma (Variant);
1010 end loop;
1011 end Build_Dcheck_Functions;
1013 -- Start of processing for Build_Discr_Checking_Funcs
1015 begin
1016 -- Only build if not done already
1018 if not Discr_Check_Funcs_Built (N) then
1019 Type_Def := Type_Definition (N);
1021 if Nkind (Type_Def) = N_Record_Definition then
1022 if No (Component_List (Type_Def)) then -- null record.
1023 return;
1024 else
1025 V := Variant_Part (Component_List (Type_Def));
1026 end if;
1028 else pragma Assert (Nkind (Type_Def) = N_Derived_Type_Definition);
1029 if No (Component_List (Record_Extension_Part (Type_Def))) then
1030 return;
1031 else
1032 V := Variant_Part
1033 (Component_List (Record_Extension_Part (Type_Def)));
1034 end if;
1035 end if;
1037 Rec_Id := Defining_Identifier (N);
1039 if Present (V) and then not Is_Unchecked_Union (Rec_Id) then
1040 Loc := Sloc (N);
1041 Enclosing_Func_Id := Empty;
1042 Build_Dcheck_Functions (V);
1043 end if;
1045 Set_Discr_Check_Funcs_Built (N);
1046 end if;
1047 end Build_Discr_Checking_Funcs;
1049 --------------------------------
1050 -- Build_Discriminant_Formals --
1051 --------------------------------
1053 function Build_Discriminant_Formals
1054 (Rec_Id : Entity_Id;
1055 Use_Dl : Boolean) return List_Id
1057 Loc : Source_Ptr := Sloc (Rec_Id);
1058 Parameter_List : constant List_Id := New_List;
1059 D : Entity_Id;
1060 Formal : Entity_Id;
1061 Param_Spec_Node : Node_Id;
1063 begin
1064 if Has_Discriminants (Rec_Id) then
1065 D := First_Discriminant (Rec_Id);
1066 while Present (D) loop
1067 Loc := Sloc (D);
1069 if Use_Dl then
1070 Formal := Discriminal (D);
1071 else
1072 Formal := Make_Defining_Identifier (Loc, Chars (D));
1073 end if;
1075 Param_Spec_Node :=
1076 Make_Parameter_Specification (Loc,
1077 Defining_Identifier => Formal,
1078 Parameter_Type =>
1079 New_Reference_To (Etype (D), Loc));
1080 Append (Param_Spec_Node, Parameter_List);
1081 Next_Discriminant (D);
1082 end loop;
1083 end if;
1085 return Parameter_List;
1086 end Build_Discriminant_Formals;
1088 --------------------------------------
1089 -- Build_Equivalent_Array_Aggregate --
1090 --------------------------------------
1092 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id is
1093 Loc : constant Source_Ptr := Sloc (T);
1094 Comp_Type : constant Entity_Id := Component_Type (T);
1095 Index_Type : constant Entity_Id := Etype (First_Index (T));
1096 Proc : constant Entity_Id := Base_Init_Proc (T);
1097 Lo, Hi : Node_Id;
1098 Aggr : Node_Id;
1099 Expr : Node_Id;
1101 begin
1102 if not Is_Constrained (T)
1103 or else Number_Dimensions (T) > 1
1104 or else No (Proc)
1105 then
1106 Initialization_Warning (T);
1107 return Empty;
1108 end if;
1110 Lo := Type_Low_Bound (Index_Type);
1111 Hi := Type_High_Bound (Index_Type);
1113 if not Compile_Time_Known_Value (Lo)
1114 or else not Compile_Time_Known_Value (Hi)
1115 then
1116 Initialization_Warning (T);
1117 return Empty;
1118 end if;
1120 if Is_Record_Type (Comp_Type)
1121 and then Present (Base_Init_Proc (Comp_Type))
1122 then
1123 Expr := Static_Initialization (Base_Init_Proc (Comp_Type));
1125 if No (Expr) then
1126 Initialization_Warning (T);
1127 return Empty;
1128 end if;
1130 else
1131 Initialization_Warning (T);
1132 return Empty;
1133 end if;
1135 Aggr := Make_Aggregate (Loc, No_List, New_List);
1136 Set_Etype (Aggr, T);
1137 Set_Aggregate_Bounds (Aggr,
1138 Make_Range (Loc,
1139 Low_Bound => New_Copy (Lo),
1140 High_Bound => New_Copy (Hi)));
1141 Set_Parent (Aggr, Parent (Proc));
1143 Append_To (Component_Associations (Aggr),
1144 Make_Component_Association (Loc,
1145 Choices =>
1146 New_List (
1147 Make_Range (Loc,
1148 Low_Bound => New_Copy (Lo),
1149 High_Bound => New_Copy (Hi))),
1150 Expression => Expr));
1152 if Static_Array_Aggregate (Aggr) then
1153 return Aggr;
1154 else
1155 Initialization_Warning (T);
1156 return Empty;
1157 end if;
1158 end Build_Equivalent_Array_Aggregate;
1160 ---------------------------------------
1161 -- Build_Equivalent_Record_Aggregate --
1162 ---------------------------------------
1164 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id is
1165 Agg : Node_Id;
1166 Comp : Entity_Id;
1168 -- Start of processing for Build_Equivalent_Record_Aggregate
1170 begin
1171 if not Is_Record_Type (T)
1172 or else Has_Discriminants (T)
1173 or else Is_Limited_Type (T)
1174 or else Has_Non_Standard_Rep (T)
1175 then
1176 Initialization_Warning (T);
1177 return Empty;
1178 end if;
1180 Comp := First_Component (T);
1182 -- A null record needs no warning
1184 if No (Comp) then
1185 return Empty;
1186 end if;
1188 while Present (Comp) loop
1190 -- Array components are acceptable if initialized by a positional
1191 -- aggregate with static components.
1193 if Is_Array_Type (Etype (Comp)) then
1194 declare
1195 Comp_Type : constant Entity_Id := Component_Type (Etype (Comp));
1197 begin
1198 if Nkind (Parent (Comp)) /= N_Component_Declaration
1199 or else No (Expression (Parent (Comp)))
1200 or else Nkind (Expression (Parent (Comp))) /= N_Aggregate
1201 then
1202 Initialization_Warning (T);
1203 return Empty;
1205 elsif Is_Scalar_Type (Component_Type (Etype (Comp)))
1206 and then
1207 (not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1208 or else not Compile_Time_Known_Value
1209 (Type_High_Bound (Comp_Type)))
1210 then
1211 Initialization_Warning (T);
1212 return Empty;
1214 elsif
1215 not Static_Array_Aggregate (Expression (Parent (Comp)))
1216 then
1217 Initialization_Warning (T);
1218 return Empty;
1219 end if;
1220 end;
1222 elsif Is_Scalar_Type (Etype (Comp)) then
1223 if Nkind (Parent (Comp)) /= N_Component_Declaration
1224 or else No (Expression (Parent (Comp)))
1225 or else not Compile_Time_Known_Value (Expression (Parent (Comp)))
1226 then
1227 Initialization_Warning (T);
1228 return Empty;
1229 end if;
1231 -- For now, other types are excluded
1233 else
1234 Initialization_Warning (T);
1235 return Empty;
1236 end if;
1238 Next_Component (Comp);
1239 end loop;
1241 -- All components have static initialization. Build positional
1242 -- aggregate from the given expressions or defaults.
1244 Agg := Make_Aggregate (Sloc (T), New_List, New_List);
1245 Set_Parent (Agg, Parent (T));
1247 Comp := First_Component (T);
1248 while Present (Comp) loop
1249 Append
1250 (New_Copy_Tree (Expression (Parent (Comp))), Expressions (Agg));
1251 Next_Component (Comp);
1252 end loop;
1254 Analyze_And_Resolve (Agg, T);
1255 return Agg;
1256 end Build_Equivalent_Record_Aggregate;
1258 -------------------------------
1259 -- Build_Initialization_Call --
1260 -------------------------------
1262 -- References to a discriminant inside the record type declaration can
1263 -- appear either in the subtype_indication to constrain a record or an
1264 -- array, or as part of a larger expression given for the initial value
1265 -- of a component. In both of these cases N appears in the record
1266 -- initialization procedure and needs to be replaced by the formal
1267 -- parameter of the initialization procedure which corresponds to that
1268 -- discriminant.
1270 -- In the example below, references to discriminants D1 and D2 in proc_1
1271 -- are replaced by references to formals with the same name
1272 -- (discriminals)
1274 -- A similar replacement is done for calls to any record initialization
1275 -- procedure for any components that are themselves of a record type.
1277 -- type R (D1, D2 : Integer) is record
1278 -- X : Integer := F * D1;
1279 -- Y : Integer := F * D2;
1280 -- end record;
1282 -- procedure proc_1 (Out_2 : out R; D1 : Integer; D2 : Integer) is
1283 -- begin
1284 -- Out_2.D1 := D1;
1285 -- Out_2.D2 := D2;
1286 -- Out_2.X := F * D1;
1287 -- Out_2.Y := F * D2;
1288 -- end;
1290 function Build_Initialization_Call
1291 (Loc : Source_Ptr;
1292 Id_Ref : Node_Id;
1293 Typ : Entity_Id;
1294 In_Init_Proc : Boolean := False;
1295 Enclos_Type : Entity_Id := Empty;
1296 Discr_Map : Elist_Id := New_Elmt_List;
1297 With_Default_Init : Boolean := False) return List_Id
1299 First_Arg : Node_Id;
1300 Args : List_Id;
1301 Decls : List_Id;
1302 Decl : Node_Id;
1303 Discr : Entity_Id;
1304 Arg : Node_Id;
1305 Proc : constant Entity_Id := Base_Init_Proc (Typ);
1306 Init_Type : constant Entity_Id := Etype (First_Formal (Proc));
1307 Full_Init_Type : constant Entity_Id := Underlying_Type (Init_Type);
1308 Res : constant List_Id := New_List;
1309 Full_Type : Entity_Id := Typ;
1310 Controller_Typ : Entity_Id;
1312 begin
1313 -- Nothing to do if the Init_Proc is null, unless Initialize_Scalars
1314 -- is active (in which case we make the call anyway, since in the
1315 -- actual compiled client it may be non null).
1316 -- Also nothing to do for value types.
1318 if (Is_Null_Init_Proc (Proc) and then not Init_Or_Norm_Scalars)
1319 or else Is_Value_Type (Typ)
1320 or else Is_Value_Type (Component_Type (Typ))
1321 then
1322 return Empty_List;
1323 end if;
1325 -- Go to full view if private type. In the case of successive
1326 -- private derivations, this can require more than one step.
1328 while Is_Private_Type (Full_Type)
1329 and then Present (Full_View (Full_Type))
1330 loop
1331 Full_Type := Full_View (Full_Type);
1332 end loop;
1334 -- If Typ is derived, the procedure is the initialization procedure for
1335 -- the root type. Wrap the argument in an conversion to make it type
1336 -- honest. Actually it isn't quite type honest, because there can be
1337 -- conflicts of views in the private type case. That is why we set
1338 -- Conversion_OK in the conversion node.
1340 if (Is_Record_Type (Typ)
1341 or else Is_Array_Type (Typ)
1342 or else Is_Private_Type (Typ))
1343 and then Init_Type /= Base_Type (Typ)
1344 then
1345 First_Arg := OK_Convert_To (Etype (Init_Type), Id_Ref);
1346 Set_Etype (First_Arg, Init_Type);
1348 else
1349 First_Arg := Id_Ref;
1350 end if;
1352 Args := New_List (Convert_Concurrent (First_Arg, Typ));
1354 -- In the tasks case, add _Master as the value of the _Master parameter
1355 -- and _Chain as the value of the _Chain parameter. At the outer level,
1356 -- these will be variables holding the corresponding values obtained
1357 -- from GNARL. At inner levels, they will be the parameters passed down
1358 -- through the outer routines.
1360 if Has_Task (Full_Type) then
1361 if Restriction_Active (No_Task_Hierarchy) then
1363 -- See comments in System.Tasking.Initialization.Init_RTS
1364 -- for the value 3 (should be rtsfindable constant ???)
1366 Append_To (Args, Make_Integer_Literal (Loc, 3));
1368 else
1369 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1370 end if;
1372 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1374 -- Ada 2005 (AI-287): In case of default initialized components
1375 -- with tasks, we generate a null string actual parameter.
1376 -- This is just a workaround that must be improved later???
1378 if With_Default_Init then
1379 Append_To (Args,
1380 Make_String_Literal (Loc,
1381 Strval => ""));
1383 else
1384 Decls :=
1385 Build_Task_Image_Decls (Loc, Id_Ref, Enclos_Type, In_Init_Proc);
1386 Decl := Last (Decls);
1388 Append_To (Args,
1389 New_Occurrence_Of (Defining_Identifier (Decl), Loc));
1390 Append_List (Decls, Res);
1391 end if;
1393 else
1394 Decls := No_List;
1395 Decl := Empty;
1396 end if;
1398 -- Add discriminant values if discriminants are present
1400 if Has_Discriminants (Full_Init_Type) then
1401 Discr := First_Discriminant (Full_Init_Type);
1403 while Present (Discr) loop
1405 -- If this is a discriminated concurrent type, the init_proc
1406 -- for the corresponding record is being called. Use that type
1407 -- directly to find the discriminant value, to handle properly
1408 -- intervening renamed discriminants.
1410 declare
1411 T : Entity_Id := Full_Type;
1413 begin
1414 if Is_Protected_Type (T) then
1415 T := Corresponding_Record_Type (T);
1417 elsif Is_Private_Type (T)
1418 and then Present (Underlying_Full_View (T))
1419 and then Is_Protected_Type (Underlying_Full_View (T))
1420 then
1421 T := Corresponding_Record_Type (Underlying_Full_View (T));
1422 end if;
1424 Arg :=
1425 Get_Discriminant_Value (
1426 Discr,
1428 Discriminant_Constraint (Full_Type));
1429 end;
1431 if In_Init_Proc then
1433 -- Replace any possible references to the discriminant in the
1434 -- call to the record initialization procedure with references
1435 -- to the appropriate formal parameter.
1437 if Nkind (Arg) = N_Identifier
1438 and then Ekind (Entity (Arg)) = E_Discriminant
1439 then
1440 Arg := New_Reference_To (Discriminal (Entity (Arg)), Loc);
1442 -- Case of access discriminants. We replace the reference
1443 -- to the type by a reference to the actual object
1445 elsif Nkind (Arg) = N_Attribute_Reference
1446 and then Is_Access_Type (Etype (Arg))
1447 and then Is_Entity_Name (Prefix (Arg))
1448 and then Is_Type (Entity (Prefix (Arg)))
1449 then
1450 Arg :=
1451 Make_Attribute_Reference (Loc,
1452 Prefix => New_Copy (Prefix (Id_Ref)),
1453 Attribute_Name => Name_Unrestricted_Access);
1455 -- Otherwise make a copy of the default expression. Note that
1456 -- we use the current Sloc for this, because we do not want the
1457 -- call to appear to be at the declaration point. Within the
1458 -- expression, replace discriminants with their discriminals.
1460 else
1461 Arg :=
1462 New_Copy_Tree (Arg, Map => Discr_Map, New_Sloc => Loc);
1463 end if;
1465 else
1466 if Is_Constrained (Full_Type) then
1467 Arg := Duplicate_Subexpr_No_Checks (Arg);
1468 else
1469 -- The constraints come from the discriminant default exps,
1470 -- they must be reevaluated, so we use New_Copy_Tree but we
1471 -- ensure the proper Sloc (for any embedded calls).
1473 Arg := New_Copy_Tree (Arg, New_Sloc => Loc);
1474 end if;
1475 end if;
1477 -- Ada 2005 (AI-287) In case of default initialized components,
1478 -- we need to generate the corresponding selected component node
1479 -- to access the discriminant value. In other cases this is not
1480 -- required because we are inside the init proc and we use the
1481 -- corresponding formal.
1483 if With_Default_Init
1484 and then Nkind (Id_Ref) = N_Selected_Component
1485 and then Nkind (Arg) = N_Identifier
1486 then
1487 Append_To (Args,
1488 Make_Selected_Component (Loc,
1489 Prefix => New_Copy_Tree (Prefix (Id_Ref)),
1490 Selector_Name => Arg));
1491 else
1492 Append_To (Args, Arg);
1493 end if;
1495 Next_Discriminant (Discr);
1496 end loop;
1497 end if;
1499 -- If this is a call to initialize the parent component of a derived
1500 -- tagged type, indicate that the tag should not be set in the parent.
1502 if Is_Tagged_Type (Full_Init_Type)
1503 and then not Is_CPP_Class (Full_Init_Type)
1504 and then Nkind (Id_Ref) = N_Selected_Component
1505 and then Chars (Selector_Name (Id_Ref)) = Name_uParent
1506 then
1507 Append_To (Args, New_Occurrence_Of (Standard_False, Loc));
1508 end if;
1510 Append_To (Res,
1511 Make_Procedure_Call_Statement (Loc,
1512 Name => New_Occurrence_Of (Proc, Loc),
1513 Parameter_Associations => Args));
1515 if Controlled_Type (Typ)
1516 and then Nkind (Id_Ref) = N_Selected_Component
1517 then
1518 if Chars (Selector_Name (Id_Ref)) /= Name_uParent then
1519 Append_List_To (Res,
1520 Make_Init_Call (
1521 Ref => New_Copy_Tree (First_Arg),
1522 Typ => Typ,
1523 Flist_Ref =>
1524 Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1525 With_Attach => Make_Integer_Literal (Loc, 1)));
1527 -- If the enclosing type is an extension with new controlled
1528 -- components, it has his own record controller. If the parent
1529 -- also had a record controller, attach it to the new one.
1531 -- Build_Init_Statements relies on the fact that in this specific
1532 -- case the last statement of the result is the attach call to
1533 -- the controller. If this is changed, it must be synchronized.
1535 elsif Present (Enclos_Type)
1536 and then Has_New_Controlled_Component (Enclos_Type)
1537 and then Has_Controlled_Component (Typ)
1538 then
1539 if Is_Inherently_Limited_Type (Typ) then
1540 Controller_Typ := RTE (RE_Limited_Record_Controller);
1541 else
1542 Controller_Typ := RTE (RE_Record_Controller);
1543 end if;
1545 Append_List_To (Res,
1546 Make_Init_Call (
1547 Ref =>
1548 Make_Selected_Component (Loc,
1549 Prefix => New_Copy_Tree (First_Arg),
1550 Selector_Name => Make_Identifier (Loc, Name_uController)),
1551 Typ => Controller_Typ,
1552 Flist_Ref => Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1553 With_Attach => Make_Integer_Literal (Loc, 1)));
1554 end if;
1555 end if;
1557 return Res;
1559 exception
1560 when RE_Not_Available =>
1561 return Empty_List;
1562 end Build_Initialization_Call;
1564 ---------------------------
1565 -- Build_Master_Renaming --
1566 ---------------------------
1568 function Build_Master_Renaming
1569 (N : Node_Id;
1570 T : Entity_Id) return Entity_Id
1572 Loc : constant Source_Ptr := Sloc (N);
1573 M_Id : Entity_Id;
1574 Decl : Node_Id;
1576 begin
1577 -- Nothing to do if there is no task hierarchy
1579 if Restriction_Active (No_Task_Hierarchy) then
1580 return Empty;
1581 end if;
1583 M_Id :=
1584 Make_Defining_Identifier (Loc,
1585 New_External_Name (Chars (T), 'M'));
1587 Decl :=
1588 Make_Object_Renaming_Declaration (Loc,
1589 Defining_Identifier => M_Id,
1590 Subtype_Mark => New_Reference_To (RTE (RE_Master_Id), Loc),
1591 Name => Make_Identifier (Loc, Name_uMaster));
1592 Insert_Before (N, Decl);
1593 Analyze (Decl);
1594 return M_Id;
1596 exception
1597 when RE_Not_Available =>
1598 return Empty;
1599 end Build_Master_Renaming;
1601 ---------------------------
1602 -- Build_Master_Renaming --
1603 ---------------------------
1605 procedure Build_Master_Renaming (N : Node_Id; T : Entity_Id) is
1606 M_Id : Entity_Id;
1608 begin
1609 -- Nothing to do if there is no task hierarchy
1611 if Restriction_Active (No_Task_Hierarchy) then
1612 return;
1613 end if;
1615 M_Id := Build_Master_Renaming (N, T);
1616 Set_Master_Id (T, M_Id);
1618 exception
1619 when RE_Not_Available =>
1620 return;
1621 end Build_Master_Renaming;
1623 ----------------------------
1624 -- Build_Record_Init_Proc --
1625 ----------------------------
1627 procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id) is
1628 Loc : Source_Ptr := Sloc (N);
1629 Discr_Map : constant Elist_Id := New_Elmt_List;
1630 Proc_Id : Entity_Id;
1631 Rec_Type : Entity_Id;
1632 Set_Tag : Entity_Id := Empty;
1634 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id;
1635 -- Build a assignment statement node which assigns to record component
1636 -- its default expression if defined. The assignment left hand side is
1637 -- marked Assignment_OK so that initialization of limited private
1638 -- records works correctly, Return also the adjustment call for
1639 -- controlled objects
1641 procedure Build_Discriminant_Assignments (Statement_List : List_Id);
1642 -- If the record has discriminants, adds assignment statements to
1643 -- statement list to initialize the discriminant values from the
1644 -- arguments of the initialization procedure.
1646 function Build_Init_Statements (Comp_List : Node_Id) return List_Id;
1647 -- Build a list representing a sequence of statements which initialize
1648 -- components of the given component list. This may involve building
1649 -- case statements for the variant parts.
1651 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id;
1652 -- Given a non-tagged type-derivation that declares discriminants,
1653 -- such as
1655 -- type R (R1, R2 : Integer) is record ... end record;
1657 -- type D (D1 : Integer) is new R (1, D1);
1659 -- we make the _init_proc of D be
1661 -- procedure _init_proc(X : D; D1 : Integer) is
1662 -- begin
1663 -- _init_proc( R(X), 1, D1);
1664 -- end _init_proc;
1666 -- This function builds the call statement in this _init_proc.
1668 procedure Build_Init_Procedure;
1669 -- Build the tree corresponding to the procedure specification and body
1670 -- of the initialization procedure (by calling all the preceding
1671 -- auxiliary routines), and install it as the _init TSS.
1673 procedure Build_Offset_To_Top_Functions;
1674 -- Ada 2005 (AI-251): Build the tree corresponding to the procedure spec
1675 -- and body of the Offset_To_Top function that is generated when the
1676 -- parent of a type with discriminants has secondary dispatch tables.
1678 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id);
1679 -- Add range checks to components of discriminated records. S is a
1680 -- subtype indication of a record component. Check_List is a list
1681 -- to which the check actions are appended.
1683 function Component_Needs_Simple_Initialization
1684 (T : Entity_Id) return Boolean;
1685 -- Determines if a component needs simple initialization, given its type
1686 -- T. This is the same as Needs_Simple_Initialization except for the
1687 -- following difference: the types Tag and Interface_Tag, that are
1688 -- access types which would normally require simple initialization to
1689 -- null, do not require initialization as components, since they are
1690 -- explicitly initialized by other means.
1692 procedure Constrain_Array
1693 (SI : Node_Id;
1694 Check_List : List_Id);
1695 -- Called from Build_Record_Checks.
1696 -- Apply a list of index constraints to an unconstrained array type.
1697 -- The first parameter is the entity for the resulting subtype.
1698 -- Check_List is a list to which the check actions are appended.
1700 procedure Constrain_Index
1701 (Index : Node_Id;
1702 S : Node_Id;
1703 Check_List : List_Id);
1704 -- Process an index constraint in a constrained array declaration.
1705 -- The constraint can be a subtype name, or a range with or without
1706 -- an explicit subtype mark. The index is the corresponding index of the
1707 -- unconstrained array. S is the range expression. Check_List is a list
1708 -- to which the check actions are appended (called from
1709 -- Build_Record_Checks).
1711 function Parent_Subtype_Renaming_Discrims return Boolean;
1712 -- Returns True for base types N that rename discriminants, else False
1714 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean;
1715 -- Determines whether a record initialization procedure needs to be
1716 -- generated for the given record type.
1718 ----------------------
1719 -- Build_Assignment --
1720 ----------------------
1722 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id is
1723 Exp : Node_Id := N;
1724 Lhs : Node_Id;
1725 Typ : constant Entity_Id := Underlying_Type (Etype (Id));
1726 Kind : Node_Kind := Nkind (N);
1727 Res : List_Id;
1729 begin
1730 Loc := Sloc (N);
1731 Lhs :=
1732 Make_Selected_Component (Loc,
1733 Prefix => Make_Identifier (Loc, Name_uInit),
1734 Selector_Name => New_Occurrence_Of (Id, Loc));
1735 Set_Assignment_OK (Lhs);
1737 -- Case of an access attribute applied to the current instance.
1738 -- Replace the reference to the type by a reference to the actual
1739 -- object. (Note that this handles the case of the top level of
1740 -- the expression being given by such an attribute, but does not
1741 -- cover uses nested within an initial value expression. Nested
1742 -- uses are unlikely to occur in practice, but are theoretically
1743 -- possible. It is not clear how to handle them without fully
1744 -- traversing the expression. ???
1746 if Kind = N_Attribute_Reference
1747 and then (Attribute_Name (N) = Name_Unchecked_Access
1748 or else
1749 Attribute_Name (N) = Name_Unrestricted_Access)
1750 and then Is_Entity_Name (Prefix (N))
1751 and then Is_Type (Entity (Prefix (N)))
1752 and then Entity (Prefix (N)) = Rec_Type
1753 then
1754 Exp :=
1755 Make_Attribute_Reference (Loc,
1756 Prefix => Make_Identifier (Loc, Name_uInit),
1757 Attribute_Name => Name_Unrestricted_Access);
1758 end if;
1760 -- Ada 2005 (AI-231): Add the run-time check if required
1762 if Ada_Version >= Ada_05
1763 and then Can_Never_Be_Null (Etype (Id)) -- Lhs
1764 then
1765 if Nkind (Exp) = N_Null then
1766 return New_List (
1767 Make_Raise_Constraint_Error (Sloc (Exp),
1768 Reason => CE_Null_Not_Allowed));
1770 elsif Present (Etype (Exp))
1771 and then not Can_Never_Be_Null (Etype (Exp))
1772 then
1773 Install_Null_Excluding_Check (Exp);
1774 end if;
1775 end if;
1777 -- Take a copy of Exp to ensure that later copies of this component
1778 -- declaration in derived types see the original tree, not a node
1779 -- rewritten during expansion of the init_proc.
1781 Exp := New_Copy_Tree (Exp);
1783 Res := New_List (
1784 Make_Assignment_Statement (Loc,
1785 Name => Lhs,
1786 Expression => Exp));
1788 Set_No_Ctrl_Actions (First (Res));
1790 -- Adjust the tag if tagged (because of possible view conversions).
1791 -- Suppress the tag adjustment when VM_Target because VM tags are
1792 -- represented implicitly in objects.
1794 if Is_Tagged_Type (Typ) and then VM_Target = No_VM then
1795 Append_To (Res,
1796 Make_Assignment_Statement (Loc,
1797 Name =>
1798 Make_Selected_Component (Loc,
1799 Prefix => New_Copy_Tree (Lhs),
1800 Selector_Name =>
1801 New_Reference_To (First_Tag_Component (Typ), Loc)),
1803 Expression =>
1804 Unchecked_Convert_To (RTE (RE_Tag),
1805 New_Reference_To
1806 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc))));
1807 end if;
1809 -- Adjust the component if controlled except if it is an aggregate
1810 -- that will be expanded inline
1812 if Kind = N_Qualified_Expression then
1813 Kind := Nkind (Expression (N));
1814 end if;
1816 if Controlled_Type (Typ)
1817 and then not (Kind = N_Aggregate or else Kind = N_Extension_Aggregate)
1818 and then not Is_Inherently_Limited_Type (Typ)
1819 then
1820 Append_List_To (Res,
1821 Make_Adjust_Call (
1822 Ref => New_Copy_Tree (Lhs),
1823 Typ => Etype (Id),
1824 Flist_Ref =>
1825 Find_Final_List (Etype (Id), New_Copy_Tree (Lhs)),
1826 With_Attach => Make_Integer_Literal (Loc, 1)));
1827 end if;
1829 return Res;
1831 exception
1832 when RE_Not_Available =>
1833 return Empty_List;
1834 end Build_Assignment;
1836 ------------------------------------
1837 -- Build_Discriminant_Assignments --
1838 ------------------------------------
1840 procedure Build_Discriminant_Assignments (Statement_List : List_Id) is
1841 D : Entity_Id;
1842 Is_Tagged : constant Boolean := Is_Tagged_Type (Rec_Type);
1844 begin
1845 if Has_Discriminants (Rec_Type)
1846 and then not Is_Unchecked_Union (Rec_Type)
1847 then
1848 D := First_Discriminant (Rec_Type);
1850 while Present (D) loop
1851 -- Don't generate the assignment for discriminants in derived
1852 -- tagged types if the discriminant is a renaming of some
1853 -- ancestor discriminant. This initialization will be done
1854 -- when initializing the _parent field of the derived record.
1856 if Is_Tagged and then
1857 Present (Corresponding_Discriminant (D))
1858 then
1859 null;
1861 else
1862 Loc := Sloc (D);
1863 Append_List_To (Statement_List,
1864 Build_Assignment (D,
1865 New_Reference_To (Discriminal (D), Loc)));
1866 end if;
1868 Next_Discriminant (D);
1869 end loop;
1870 end if;
1871 end Build_Discriminant_Assignments;
1873 --------------------------
1874 -- Build_Init_Call_Thru --
1875 --------------------------
1877 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id is
1878 Parent_Proc : constant Entity_Id :=
1879 Base_Init_Proc (Etype (Rec_Type));
1881 Parent_Type : constant Entity_Id :=
1882 Etype (First_Formal (Parent_Proc));
1884 Uparent_Type : constant Entity_Id :=
1885 Underlying_Type (Parent_Type);
1887 First_Discr_Param : Node_Id;
1889 Parent_Discr : Entity_Id;
1890 First_Arg : Node_Id;
1891 Args : List_Id;
1892 Arg : Node_Id;
1893 Res : List_Id;
1895 begin
1896 -- First argument (_Init) is the object to be initialized.
1897 -- ??? not sure where to get a reasonable Loc for First_Arg
1899 First_Arg :=
1900 OK_Convert_To (Parent_Type,
1901 New_Reference_To (Defining_Identifier (First (Parameters)), Loc));
1903 Set_Etype (First_Arg, Parent_Type);
1905 Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
1907 -- In the tasks case,
1908 -- add _Master as the value of the _Master parameter
1909 -- add _Chain as the value of the _Chain parameter.
1910 -- add _Task_Name as the value of the _Task_Name parameter.
1911 -- At the outer level, these will be variables holding the
1912 -- corresponding values obtained from GNARL or the expander.
1914 -- At inner levels, they will be the parameters passed down through
1915 -- the outer routines.
1917 First_Discr_Param := Next (First (Parameters));
1919 if Has_Task (Rec_Type) then
1920 if Restriction_Active (No_Task_Hierarchy) then
1922 -- See comments in System.Tasking.Initialization.Init_RTS
1923 -- for the value 3.
1925 Append_To (Args, Make_Integer_Literal (Loc, 3));
1926 else
1927 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1928 end if;
1930 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1931 Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
1932 First_Discr_Param := Next (Next (Next (First_Discr_Param)));
1933 end if;
1935 -- Append discriminant values
1937 if Has_Discriminants (Uparent_Type) then
1938 pragma Assert (not Is_Tagged_Type (Uparent_Type));
1940 Parent_Discr := First_Discriminant (Uparent_Type);
1941 while Present (Parent_Discr) loop
1943 -- Get the initial value for this discriminant
1944 -- ??? needs to be cleaned up to use parent_Discr_Constr
1945 -- directly.
1947 declare
1948 Discr_Value : Elmt_Id :=
1949 First_Elmt
1950 (Stored_Constraint (Rec_Type));
1952 Discr : Entity_Id :=
1953 First_Stored_Discriminant (Uparent_Type);
1954 begin
1955 while Original_Record_Component (Parent_Discr) /= Discr loop
1956 Next_Stored_Discriminant (Discr);
1957 Next_Elmt (Discr_Value);
1958 end loop;
1960 Arg := Node (Discr_Value);
1961 end;
1963 -- Append it to the list
1965 if Nkind (Arg) = N_Identifier
1966 and then Ekind (Entity (Arg)) = E_Discriminant
1967 then
1968 Append_To (Args,
1969 New_Reference_To (Discriminal (Entity (Arg)), Loc));
1971 -- Case of access discriminants. We replace the reference
1972 -- to the type by a reference to the actual object.
1974 -- Is above comment right??? Use of New_Copy below seems mighty
1975 -- suspicious ???
1977 else
1978 Append_To (Args, New_Copy (Arg));
1979 end if;
1981 Next_Discriminant (Parent_Discr);
1982 end loop;
1983 end if;
1985 Res :=
1986 New_List (
1987 Make_Procedure_Call_Statement (Loc,
1988 Name => New_Occurrence_Of (Parent_Proc, Loc),
1989 Parameter_Associations => Args));
1991 return Res;
1992 end Build_Init_Call_Thru;
1994 -----------------------------------
1995 -- Build_Offset_To_Top_Functions --
1996 -----------------------------------
1998 procedure Build_Offset_To_Top_Functions is
1999 ADT : Elmt_Id;
2000 Body_Node : Node_Id;
2001 Func_Id : Entity_Id;
2002 Spec_Node : Node_Id;
2003 E : Entity_Id;
2005 procedure Build_Offset_To_Top_Internal (Typ : Entity_Id);
2006 -- Internal subprogram used to recursively traverse all the ancestors
2008 ----------------------------------
2009 -- Build_Offset_To_Top_Internal --
2010 ----------------------------------
2012 procedure Build_Offset_To_Top_Internal (Typ : Entity_Id) is
2013 begin
2014 -- Climb to the ancestor (if any) handling synchronized interface
2015 -- derivations and private types
2017 if Is_Concurrent_Record_Type (Typ) then
2018 declare
2019 Iface_List : constant List_Id :=
2020 Abstract_Interface_List (Typ);
2021 begin
2022 if Is_Non_Empty_List (Iface_List) then
2023 Build_Offset_To_Top_Internal (Etype (First (Iface_List)));
2024 end if;
2025 end;
2027 elsif Present (Full_View (Etype (Typ))) then
2028 if Full_View (Etype (Typ)) /= Typ then
2029 Build_Offset_To_Top_Internal (Full_View (Etype (Typ)));
2030 end if;
2032 elsif Etype (Typ) /= Typ then
2033 Build_Offset_To_Top_Internal (Etype (Typ));
2034 end if;
2036 if Present (Abstract_Interfaces (Typ))
2037 and then not Is_Empty_Elmt_List (Abstract_Interfaces (Typ))
2038 then
2039 E := First_Entity (Typ);
2040 while Present (E) loop
2041 if Is_Tag (E)
2042 and then Chars (E) /= Name_uTag
2043 then
2044 if Typ = Rec_Type then
2045 Body_Node := New_Node (N_Subprogram_Body, Loc);
2047 Func_Id :=
2048 Make_Defining_Identifier (Loc,
2049 Chars => New_Internal_Name ('F'));
2051 Set_DT_Offset_To_Top_Func (E, Func_Id);
2053 Spec_Node := New_Node (N_Function_Specification, Loc);
2054 Set_Defining_Unit_Name (Spec_Node, Func_Id);
2055 Set_Parameter_Specifications (Spec_Node, New_List (
2056 Make_Parameter_Specification (Loc,
2057 Defining_Identifier =>
2058 Make_Defining_Identifier (Loc, Name_uO),
2059 In_Present => True,
2060 Parameter_Type => New_Reference_To (Typ, Loc))));
2061 Set_Result_Definition (Spec_Node,
2062 New_Reference_To (RTE (RE_Storage_Offset), Loc));
2064 Set_Specification (Body_Node, Spec_Node);
2065 Set_Declarations (Body_Node, New_List);
2066 Set_Handled_Statement_Sequence (Body_Node,
2067 Make_Handled_Sequence_Of_Statements (Loc,
2068 Statements => New_List (
2069 Make_Return_Statement (Loc,
2070 Expression =>
2071 Make_Attribute_Reference (Loc,
2072 Prefix =>
2073 Make_Selected_Component (Loc,
2074 Prefix => Make_Identifier (Loc,
2075 Name_uO),
2076 Selector_Name => New_Reference_To
2077 (E, Loc)),
2078 Attribute_Name => Name_Position)))));
2080 Set_Ekind (Func_Id, E_Function);
2081 Set_Mechanism (Func_Id, Default_Mechanism);
2082 Set_Is_Internal (Func_Id, True);
2084 if not Debug_Generated_Code then
2085 Set_Debug_Info_Off (Func_Id);
2086 end if;
2088 Analyze (Body_Node);
2090 Append_Freeze_Action (Rec_Type, Body_Node);
2091 end if;
2093 Next_Elmt (ADT);
2094 end if;
2096 Next_Entity (E);
2097 end loop;
2098 end if;
2099 end Build_Offset_To_Top_Internal;
2101 -- Start of processing for Build_Offset_To_Top_Functions
2103 begin
2104 if Is_Concurrent_Record_Type (Rec_Type)
2105 and then Is_Empty_List (Abstract_Interface_List (Rec_Type))
2106 then
2107 return;
2109 elsif Etype (Rec_Type) = Rec_Type
2110 or else not Has_Discriminants (Etype (Rec_Type))
2111 or else No (Abstract_Interfaces (Rec_Type))
2112 or else Is_Empty_Elmt_List (Abstract_Interfaces (Rec_Type))
2113 then
2114 return;
2115 end if;
2117 -- Skip the first _Tag, which is the main tag of the tagged type.
2118 -- Following tags correspond with abstract interfaces.
2120 ADT := Next_Elmt (First_Elmt (Access_Disp_Table (Rec_Type)));
2122 -- Handle private types
2124 if Present (Full_View (Rec_Type)) then
2125 Build_Offset_To_Top_Internal (Full_View (Rec_Type));
2126 else
2127 Build_Offset_To_Top_Internal (Rec_Type);
2128 end if;
2129 end Build_Offset_To_Top_Functions;
2131 --------------------------
2132 -- Build_Init_Procedure --
2133 --------------------------
2135 procedure Build_Init_Procedure is
2136 Body_Node : Node_Id;
2137 Handled_Stmt_Node : Node_Id;
2138 Parameters : List_Id;
2139 Proc_Spec_Node : Node_Id;
2140 Body_Stmts : List_Id;
2141 Record_Extension_Node : Node_Id;
2142 Init_Tag : Node_Id;
2144 begin
2145 Body_Stmts := New_List;
2146 Body_Node := New_Node (N_Subprogram_Body, Loc);
2148 Proc_Id :=
2149 Make_Defining_Identifier (Loc,
2150 Chars => Make_Init_Proc_Name (Rec_Type));
2151 Set_Ekind (Proc_Id, E_Procedure);
2153 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2154 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2156 Parameters := Init_Formals (Rec_Type);
2157 Append_List_To (Parameters,
2158 Build_Discriminant_Formals (Rec_Type, True));
2160 -- For tagged types, we add a flag to indicate whether the routine
2161 -- is called to initialize a parent component in the init_proc of
2162 -- a type extension. If the flag is false, we do not set the tag
2163 -- because it has been set already in the extension.
2165 if Is_Tagged_Type (Rec_Type)
2166 and then not Is_CPP_Class (Rec_Type)
2167 then
2168 Set_Tag :=
2169 Make_Defining_Identifier (Loc,
2170 Chars => New_Internal_Name ('P'));
2172 Append_To (Parameters,
2173 Make_Parameter_Specification (Loc,
2174 Defining_Identifier => Set_Tag,
2175 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
2176 Expression => New_Occurrence_Of (Standard_True, Loc)));
2177 end if;
2179 Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
2180 Set_Specification (Body_Node, Proc_Spec_Node);
2181 Set_Declarations (Body_Node, New_List);
2183 if Parent_Subtype_Renaming_Discrims then
2185 -- N is a Derived_Type_Definition that renames the parameters
2186 -- of the ancestor type. We initialize it by expanding our
2187 -- discriminants and call the ancestor _init_proc with a
2188 -- type-converted object
2190 Append_List_To (Body_Stmts,
2191 Build_Init_Call_Thru (Parameters));
2193 elsif Nkind (Type_Definition (N)) = N_Record_Definition then
2194 Build_Discriminant_Assignments (Body_Stmts);
2196 if not Null_Present (Type_Definition (N)) then
2197 Append_List_To (Body_Stmts,
2198 Build_Init_Statements (
2199 Component_List (Type_Definition (N))));
2200 end if;
2202 else
2203 -- N is a Derived_Type_Definition with a possible non-empty
2204 -- extension. The initialization of a type extension consists
2205 -- in the initialization of the components in the extension.
2207 Build_Discriminant_Assignments (Body_Stmts);
2209 Record_Extension_Node :=
2210 Record_Extension_Part (Type_Definition (N));
2212 if not Null_Present (Record_Extension_Node) then
2213 declare
2214 Stmts : constant List_Id :=
2215 Build_Init_Statements (
2216 Component_List (Record_Extension_Node));
2218 begin
2219 -- The parent field must be initialized first because
2220 -- the offset of the new discriminants may depend on it
2222 Prepend_To (Body_Stmts, Remove_Head (Stmts));
2223 Append_List_To (Body_Stmts, Stmts);
2224 end;
2225 end if;
2226 end if;
2228 -- Add here the assignment to instantiate the Tag
2230 -- The assignment corresponds to the code:
2232 -- _Init._Tag := Typ'Tag;
2234 -- Suppress the tag assignment when VM_Target because VM tags are
2235 -- represented implicitly in objects. It is also suppressed in case
2236 -- of CPP_Class types because in this case the tag is initialized in
2237 -- the C++ side.
2239 if Is_Tagged_Type (Rec_Type)
2240 and then not Is_CPP_Class (Rec_Type)
2241 and then VM_Target = No_VM
2242 and then not No_Run_Time_Mode
2243 then
2244 Init_Tag :=
2245 Make_Assignment_Statement (Loc,
2246 Name =>
2247 Make_Selected_Component (Loc,
2248 Prefix => Make_Identifier (Loc, Name_uInit),
2249 Selector_Name =>
2250 New_Reference_To (First_Tag_Component (Rec_Type), Loc)),
2252 Expression =>
2253 New_Reference_To
2254 (Node (First_Elmt (Access_Disp_Table (Rec_Type))), Loc));
2256 -- The tag must be inserted before the assignments to other
2257 -- components, because the initial value of the component may
2258 -- depend on the tag (eg. through a dispatching operation on
2259 -- an access to the current type). The tag assignment is not done
2260 -- when initializing the parent component of a type extension,
2261 -- because in that case the tag is set in the extension.
2263 -- Extensions of imported C++ classes add a final complication,
2264 -- because we cannot inhibit tag setting in the constructor for
2265 -- the parent. In that case we insert the tag initialization
2266 -- after the calls to initialize the parent.
2268 if not Is_CPP_Class (Etype (Rec_Type)) then
2269 Init_Tag :=
2270 Make_If_Statement (Loc,
2271 Condition => New_Occurrence_Of (Set_Tag, Loc),
2272 Then_Statements => New_List (Init_Tag));
2274 Prepend_To (Body_Stmts, Init_Tag);
2276 -- CPP_Class: In this case the dispatch table of the parent was
2277 -- built in the C++ side and we copy the table of the parent to
2278 -- initialize the new dispatch table.
2280 else
2281 declare
2282 Nod : Node_Id := First (Body_Stmts);
2283 New_N : Node_Id;
2285 begin
2286 -- We assume the first init_proc call is for the parent
2288 while Present (Next (Nod))
2289 and then (Nkind (Nod) /= N_Procedure_Call_Statement
2290 or else not Is_Init_Proc (Name (Nod)))
2291 loop
2292 Nod := Next (Nod);
2293 end loop;
2295 -- Generate:
2296 -- ancestor_constructor (_init.parent);
2297 -- if Arg2 then
2298 -- inherit_prim_ops (_init._tag, new_dt, num_prims);
2299 -- _init._tag := new_dt;
2300 -- end if;
2302 New_N :=
2303 Build_Inherit_Prims (Loc,
2304 Old_Tag_Node =>
2305 Make_Selected_Component (Loc,
2306 Prefix => Make_Identifier (Loc, Name_uInit),
2307 Selector_Name =>
2308 New_Reference_To
2309 (First_Tag_Component (Rec_Type), Loc)),
2310 New_Tag_Node =>
2311 New_Reference_To
2312 (Node (First_Elmt (Access_Disp_Table (Rec_Type))),
2313 Loc),
2314 Num_Prims =>
2315 UI_To_Int
2316 (DT_Entry_Count (First_Tag_Component (Rec_Type))));
2318 Init_Tag :=
2319 Make_If_Statement (Loc,
2320 Condition => New_Occurrence_Of (Set_Tag, Loc),
2321 Then_Statements => New_List (New_N, Init_Tag));
2323 Insert_After (Nod, Init_Tag);
2325 -- We have inherited table of the parent from the CPP side.
2326 -- Now we fill the slots associated with Ada primitives.
2327 -- This needs more work to avoid its execution each time
2328 -- an object is initialized???
2330 declare
2331 E : Elmt_Id;
2332 Prim : Node_Id;
2334 begin
2335 E := First_Elmt (Primitive_Operations (Rec_Type));
2336 while Present (E) loop
2337 Prim := Node (E);
2339 if not Is_Imported (Prim)
2340 and then Convention (Prim) = Convention_CPP
2341 and then not Present (Abstract_Interface_Alias
2342 (Prim))
2343 then
2344 Register_Primitive (Loc,
2345 Prim => Prim,
2346 Ins_Nod => Init_Tag);
2347 end if;
2349 Next_Elmt (E);
2350 end loop;
2351 end;
2352 end;
2353 end if;
2355 -- Ada 2005 (AI-251): Initialization of all the tags corresponding
2356 -- with abstract interfaces
2358 if VM_Target = No_VM
2359 and then Ada_Version >= Ada_05
2360 and then not Is_Interface (Rec_Type)
2361 and then Has_Abstract_Interfaces (Rec_Type)
2362 then
2363 Init_Secondary_Tags
2364 (Typ => Rec_Type,
2365 Target => Make_Identifier (Loc, Name_uInit),
2366 Stmts_List => Body_Stmts);
2367 end if;
2368 end if;
2370 Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
2371 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2372 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2373 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2375 if not Debug_Generated_Code then
2376 Set_Debug_Info_Off (Proc_Id);
2377 end if;
2379 -- Associate Init_Proc with type, and determine if the procedure
2380 -- is null (happens because of the Initialize_Scalars pragma case,
2381 -- where we have to generate a null procedure in case it is called
2382 -- by a client with Initialize_Scalars set). Such procedures have
2383 -- to be generated, but do not have to be called, so we mark them
2384 -- as null to suppress the call.
2386 Set_Init_Proc (Rec_Type, Proc_Id);
2388 if List_Length (Body_Stmts) = 1
2389 and then Nkind (First (Body_Stmts)) = N_Null_Statement
2390 and then VM_Target /= CLI_Target
2391 then
2392 -- Even though the init proc may be null at this time it might get
2393 -- some stuff added to it later by the CIL backend, so always keep
2394 -- it when VM_Target = CLI_Target.
2396 Set_Is_Null_Init_Proc (Proc_Id);
2397 end if;
2398 end Build_Init_Procedure;
2400 ---------------------------
2401 -- Build_Init_Statements --
2402 ---------------------------
2404 function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
2405 Check_List : constant List_Id := New_List;
2406 Alt_List : List_Id;
2407 Statement_List : List_Id;
2408 Stmts : List_Id;
2410 Per_Object_Constraint_Components : Boolean;
2412 Decl : Node_Id;
2413 Variant : Node_Id;
2415 Id : Entity_Id;
2416 Typ : Entity_Id;
2418 function Has_Access_Constraint (E : Entity_Id) return Boolean;
2419 -- Components with access discriminants that depend on the current
2420 -- instance must be initialized after all other components.
2422 ---------------------------
2423 -- Has_Access_Constraint --
2424 ---------------------------
2426 function Has_Access_Constraint (E : Entity_Id) return Boolean is
2427 Disc : Entity_Id;
2428 T : constant Entity_Id := Etype (E);
2430 begin
2431 if Has_Per_Object_Constraint (E)
2432 and then Has_Discriminants (T)
2433 then
2434 Disc := First_Discriminant (T);
2435 while Present (Disc) loop
2436 if Is_Access_Type (Etype (Disc)) then
2437 return True;
2438 end if;
2440 Next_Discriminant (Disc);
2441 end loop;
2443 return False;
2444 else
2445 return False;
2446 end if;
2447 end Has_Access_Constraint;
2449 -- Start of processing for Build_Init_Statements
2451 begin
2452 if Null_Present (Comp_List) then
2453 return New_List (Make_Null_Statement (Loc));
2454 end if;
2456 Statement_List := New_List;
2458 -- Loop through components, skipping pragmas, in 2 steps. The first
2459 -- step deals with regular components. The second step deals with
2460 -- components have per object constraints, and no explicit initia-
2461 -- lization.
2463 Per_Object_Constraint_Components := False;
2465 -- First step : regular components
2467 Decl := First_Non_Pragma (Component_Items (Comp_List));
2468 while Present (Decl) loop
2469 Loc := Sloc (Decl);
2470 Build_Record_Checks
2471 (Subtype_Indication (Component_Definition (Decl)), Check_List);
2473 Id := Defining_Identifier (Decl);
2474 Typ := Etype (Id);
2476 if Has_Access_Constraint (Id)
2477 and then No (Expression (Decl))
2478 then
2479 -- Skip processing for now and ask for a second pass
2481 Per_Object_Constraint_Components := True;
2483 else
2484 -- Case of explicit initialization
2486 if Present (Expression (Decl)) then
2487 Stmts := Build_Assignment (Id, Expression (Decl));
2489 -- Case of composite component with its own Init_Proc
2491 elsif not Is_Interface (Typ)
2492 and then Has_Non_Null_Base_Init_Proc (Typ)
2493 then
2494 Stmts :=
2495 Build_Initialization_Call
2496 (Loc,
2497 Make_Selected_Component (Loc,
2498 Prefix => Make_Identifier (Loc, Name_uInit),
2499 Selector_Name => New_Occurrence_Of (Id, Loc)),
2500 Typ,
2501 In_Init_Proc => True,
2502 Enclos_Type => Rec_Type,
2503 Discr_Map => Discr_Map);
2505 Clean_Task_Names (Typ, Proc_Id);
2507 -- Case of component needing simple initialization
2509 elsif Component_Needs_Simple_Initialization (Typ) then
2510 Stmts :=
2511 Build_Assignment
2512 (Id, Get_Simple_Init_Val (Typ, Loc, Esize (Id)));
2514 -- Nothing needed for this case
2516 else
2517 Stmts := No_List;
2518 end if;
2520 if Present (Check_List) then
2521 Append_List_To (Statement_List, Check_List);
2522 end if;
2524 if Present (Stmts) then
2526 -- Add the initialization of the record controller before
2527 -- the _Parent field is attached to it when the attachment
2528 -- can occur. It does not work to simply initialize the
2529 -- controller first: it must be initialized after the parent
2530 -- if the parent holds discriminants that can be used to
2531 -- compute the offset of the controller. We assume here that
2532 -- the last statement of the initialization call is the
2533 -- attachment of the parent (see Build_Initialization_Call)
2535 if Chars (Id) = Name_uController
2536 and then Rec_Type /= Etype (Rec_Type)
2537 and then Has_Controlled_Component (Etype (Rec_Type))
2538 and then Has_New_Controlled_Component (Rec_Type)
2539 and then Present (Last (Statement_List))
2540 then
2541 Insert_List_Before (Last (Statement_List), Stmts);
2542 else
2543 Append_List_To (Statement_List, Stmts);
2544 end if;
2545 end if;
2546 end if;
2548 Next_Non_Pragma (Decl);
2549 end loop;
2551 if Per_Object_Constraint_Components then
2553 -- Second pass: components with per-object constraints
2555 Decl := First_Non_Pragma (Component_Items (Comp_List));
2556 while Present (Decl) loop
2557 Loc := Sloc (Decl);
2558 Id := Defining_Identifier (Decl);
2559 Typ := Etype (Id);
2561 if Has_Access_Constraint (Id)
2562 and then No (Expression (Decl))
2563 then
2564 if Has_Non_Null_Base_Init_Proc (Typ) then
2565 Append_List_To (Statement_List,
2566 Build_Initialization_Call (Loc,
2567 Make_Selected_Component (Loc,
2568 Prefix => Make_Identifier (Loc, Name_uInit),
2569 Selector_Name => New_Occurrence_Of (Id, Loc)),
2570 Typ,
2571 In_Init_Proc => True,
2572 Enclos_Type => Rec_Type,
2573 Discr_Map => Discr_Map));
2575 Clean_Task_Names (Typ, Proc_Id);
2577 elsif Component_Needs_Simple_Initialization (Typ) then
2578 Append_List_To (Statement_List,
2579 Build_Assignment
2580 (Id, Get_Simple_Init_Val (Typ, Loc, Esize (Id))));
2581 end if;
2582 end if;
2584 Next_Non_Pragma (Decl);
2585 end loop;
2586 end if;
2588 -- Process the variant part
2590 if Present (Variant_Part (Comp_List)) then
2591 Alt_List := New_List;
2592 Variant := First_Non_Pragma (Variants (Variant_Part (Comp_List)));
2593 while Present (Variant) loop
2594 Loc := Sloc (Variant);
2595 Append_To (Alt_List,
2596 Make_Case_Statement_Alternative (Loc,
2597 Discrete_Choices =>
2598 New_Copy_List (Discrete_Choices (Variant)),
2599 Statements =>
2600 Build_Init_Statements (Component_List (Variant))));
2601 Next_Non_Pragma (Variant);
2602 end loop;
2604 -- The expression of the case statement which is a reference
2605 -- to one of the discriminants is replaced by the appropriate
2606 -- formal parameter of the initialization procedure.
2608 Append_To (Statement_List,
2609 Make_Case_Statement (Loc,
2610 Expression =>
2611 New_Reference_To (Discriminal (
2612 Entity (Name (Variant_Part (Comp_List)))), Loc),
2613 Alternatives => Alt_List));
2614 end if;
2616 -- For a task record type, add the task create call and calls
2617 -- to bind any interrupt (signal) entries.
2619 if Is_Task_Record_Type (Rec_Type) then
2621 -- In the case of the restricted run time the ATCB has already
2622 -- been preallocated.
2624 if Restricted_Profile then
2625 Append_To (Statement_List,
2626 Make_Assignment_Statement (Loc,
2627 Name => Make_Selected_Component (Loc,
2628 Prefix => Make_Identifier (Loc, Name_uInit),
2629 Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
2630 Expression => Make_Attribute_Reference (Loc,
2631 Prefix =>
2632 Make_Selected_Component (Loc,
2633 Prefix => Make_Identifier (Loc, Name_uInit),
2634 Selector_Name =>
2635 Make_Identifier (Loc, Name_uATCB)),
2636 Attribute_Name => Name_Unchecked_Access)));
2637 end if;
2639 Append_To (Statement_List, Make_Task_Create_Call (Rec_Type));
2641 declare
2642 Task_Type : constant Entity_Id :=
2643 Corresponding_Concurrent_Type (Rec_Type);
2644 Task_Decl : constant Node_Id := Parent (Task_Type);
2645 Task_Def : constant Node_Id := Task_Definition (Task_Decl);
2646 Vis_Decl : Node_Id;
2647 Ent : Entity_Id;
2649 begin
2650 if Present (Task_Def) then
2651 Vis_Decl := First (Visible_Declarations (Task_Def));
2652 while Present (Vis_Decl) loop
2653 Loc := Sloc (Vis_Decl);
2655 if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
2656 if Get_Attribute_Id (Chars (Vis_Decl)) =
2657 Attribute_Address
2658 then
2659 Ent := Entity (Name (Vis_Decl));
2661 if Ekind (Ent) = E_Entry then
2662 Append_To (Statement_List,
2663 Make_Procedure_Call_Statement (Loc,
2664 Name => New_Reference_To (
2665 RTE (RE_Bind_Interrupt_To_Entry), Loc),
2666 Parameter_Associations => New_List (
2667 Make_Selected_Component (Loc,
2668 Prefix =>
2669 Make_Identifier (Loc, Name_uInit),
2670 Selector_Name =>
2671 Make_Identifier (Loc, Name_uTask_Id)),
2672 Entry_Index_Expression (
2673 Loc, Ent, Empty, Task_Type),
2674 Expression (Vis_Decl))));
2675 end if;
2676 end if;
2677 end if;
2679 Next (Vis_Decl);
2680 end loop;
2681 end if;
2682 end;
2683 end if;
2685 -- For a protected type, add statements generated by
2686 -- Make_Initialize_Protection.
2688 if Is_Protected_Record_Type (Rec_Type) then
2689 Append_List_To (Statement_List,
2690 Make_Initialize_Protection (Rec_Type));
2691 end if;
2693 -- If no initializations when generated for component declarations
2694 -- corresponding to this Statement_List, append a null statement
2695 -- to the Statement_List to make it a valid Ada tree.
2697 if Is_Empty_List (Statement_List) then
2698 Append (New_Node (N_Null_Statement, Loc), Statement_List);
2699 end if;
2701 return Statement_List;
2703 exception
2704 when RE_Not_Available =>
2705 return Empty_List;
2706 end Build_Init_Statements;
2708 -------------------------
2709 -- Build_Record_Checks --
2710 -------------------------
2712 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
2713 Subtype_Mark_Id : Entity_Id;
2715 begin
2716 if Nkind (S) = N_Subtype_Indication then
2717 Find_Type (Subtype_Mark (S));
2718 Subtype_Mark_Id := Entity (Subtype_Mark (S));
2720 -- Remaining processing depends on type
2722 case Ekind (Subtype_Mark_Id) is
2724 when Array_Kind =>
2725 Constrain_Array (S, Check_List);
2727 when others =>
2728 null;
2729 end case;
2730 end if;
2731 end Build_Record_Checks;
2733 -------------------------------------------
2734 -- Component_Needs_Simple_Initialization --
2735 -------------------------------------------
2737 function Component_Needs_Simple_Initialization
2738 (T : Entity_Id) return Boolean
2740 begin
2741 return
2742 Needs_Simple_Initialization (T)
2743 and then not Is_RTE (T, RE_Tag)
2745 -- Ada 2005 (AI-251): Check also the tag of abstract interfaces
2747 and then not Is_RTE (T, RE_Interface_Tag);
2748 end Component_Needs_Simple_Initialization;
2750 ---------------------
2751 -- Constrain_Array --
2752 ---------------------
2754 procedure Constrain_Array
2755 (SI : Node_Id;
2756 Check_List : List_Id)
2758 C : constant Node_Id := Constraint (SI);
2759 Number_Of_Constraints : Nat := 0;
2760 Index : Node_Id;
2761 S, T : Entity_Id;
2763 begin
2764 T := Entity (Subtype_Mark (SI));
2766 if Ekind (T) in Access_Kind then
2767 T := Designated_Type (T);
2768 end if;
2770 S := First (Constraints (C));
2772 while Present (S) loop
2773 Number_Of_Constraints := Number_Of_Constraints + 1;
2774 Next (S);
2775 end loop;
2777 -- In either case, the index constraint must provide a discrete
2778 -- range for each index of the array type and the type of each
2779 -- discrete range must be the same as that of the corresponding
2780 -- index. (RM 3.6.1)
2782 S := First (Constraints (C));
2783 Index := First_Index (T);
2784 Analyze (Index);
2786 -- Apply constraints to each index type
2788 for J in 1 .. Number_Of_Constraints loop
2789 Constrain_Index (Index, S, Check_List);
2790 Next (Index);
2791 Next (S);
2792 end loop;
2794 end Constrain_Array;
2796 ---------------------
2797 -- Constrain_Index --
2798 ---------------------
2800 procedure Constrain_Index
2801 (Index : Node_Id;
2802 S : Node_Id;
2803 Check_List : List_Id)
2805 T : constant Entity_Id := Etype (Index);
2807 begin
2808 if Nkind (S) = N_Range then
2809 Process_Range_Expr_In_Decl (S, T, Check_List);
2810 end if;
2811 end Constrain_Index;
2813 --------------------------------------
2814 -- Parent_Subtype_Renaming_Discrims --
2815 --------------------------------------
2817 function Parent_Subtype_Renaming_Discrims return Boolean is
2818 De : Entity_Id;
2819 Dp : Entity_Id;
2821 begin
2822 if Base_Type (Pe) /= Pe then
2823 return False;
2824 end if;
2826 if Etype (Pe) = Pe
2827 or else not Has_Discriminants (Pe)
2828 or else Is_Constrained (Pe)
2829 or else Is_Tagged_Type (Pe)
2830 then
2831 return False;
2832 end if;
2834 -- If there are no explicit stored discriminants we have inherited
2835 -- the root type discriminants so far, so no renamings occurred.
2837 if First_Discriminant (Pe) = First_Stored_Discriminant (Pe) then
2838 return False;
2839 end if;
2841 -- Check if we have done some trivial renaming of the parent
2842 -- discriminants, i.e. something like
2844 -- type DT (X1,X2: int) is new PT (X1,X2);
2846 De := First_Discriminant (Pe);
2847 Dp := First_Discriminant (Etype (Pe));
2849 while Present (De) loop
2850 pragma Assert (Present (Dp));
2852 if Corresponding_Discriminant (De) /= Dp then
2853 return True;
2854 end if;
2856 Next_Discriminant (De);
2857 Next_Discriminant (Dp);
2858 end loop;
2860 return Present (Dp);
2861 end Parent_Subtype_Renaming_Discrims;
2863 ------------------------
2864 -- Requires_Init_Proc --
2865 ------------------------
2867 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
2868 Comp_Decl : Node_Id;
2869 Id : Entity_Id;
2870 Typ : Entity_Id;
2872 begin
2873 -- Definitely do not need one if specifically suppressed
2875 if Suppress_Init_Proc (Rec_Id) then
2876 return False;
2877 end if;
2879 -- If it is a type derived from a type with unknown discriminants,
2880 -- we cannot build an initialization procedure for it.
2882 if Has_Unknown_Discriminants (Rec_Id) then
2883 return False;
2884 end if;
2886 -- Otherwise we need to generate an initialization procedure if
2887 -- Is_CPP_Class is False and at least one of the following applies:
2889 -- 1. Discriminants are present, since they need to be initialized
2890 -- with the appropriate discriminant constraint expressions.
2891 -- However, the discriminant of an unchecked union does not
2892 -- count, since the discriminant is not present.
2894 -- 2. The type is a tagged type, since the implicit Tag component
2895 -- needs to be initialized with a pointer to the dispatch table.
2897 -- 3. The type contains tasks
2899 -- 4. One or more components has an initial value
2901 -- 5. One or more components is for a type which itself requires
2902 -- an initialization procedure.
2904 -- 6. One or more components is a type that requires simple
2905 -- initialization (see Needs_Simple_Initialization), except
2906 -- that types Tag and Interface_Tag are excluded, since fields
2907 -- of these types are initialized by other means.
2909 -- 7. The type is the record type built for a task type (since at
2910 -- the very least, Create_Task must be called)
2912 -- 8. The type is the record type built for a protected type (since
2913 -- at least Initialize_Protection must be called)
2915 -- 9. The type is marked as a public entity. The reason we add this
2916 -- case (even if none of the above apply) is to properly handle
2917 -- Initialize_Scalars. If a package is compiled without an IS
2918 -- pragma, and the client is compiled with an IS pragma, then
2919 -- the client will think an initialization procedure is present
2920 -- and call it, when in fact no such procedure is required, but
2921 -- since the call is generated, there had better be a routine
2922 -- at the other end of the call, even if it does nothing!)
2924 -- Note: the reason we exclude the CPP_Class case is because in this
2925 -- case the initialization is performed in the C++ side.
2927 if Is_CPP_Class (Rec_Id) then
2928 return False;
2930 elsif Is_Interface (Rec_Id) then
2931 return False;
2933 elsif not Restriction_Active (No_Initialize_Scalars)
2934 and then Is_Public (Rec_Id)
2935 then
2936 return True;
2938 elsif (Has_Discriminants (Rec_Id)
2939 and then not Is_Unchecked_Union (Rec_Id))
2940 or else Is_Tagged_Type (Rec_Id)
2941 or else Is_Concurrent_Record_Type (Rec_Id)
2942 or else Has_Task (Rec_Id)
2943 then
2944 return True;
2945 end if;
2947 Id := First_Component (Rec_Id);
2949 while Present (Id) loop
2950 Comp_Decl := Parent (Id);
2951 Typ := Etype (Id);
2953 if Present (Expression (Comp_Decl))
2954 or else Has_Non_Null_Base_Init_Proc (Typ)
2955 or else Component_Needs_Simple_Initialization (Typ)
2956 then
2957 return True;
2958 end if;
2960 Next_Component (Id);
2961 end loop;
2963 return False;
2964 end Requires_Init_Proc;
2966 -- Start of processing for Build_Record_Init_Proc
2968 begin
2969 Rec_Type := Defining_Identifier (N);
2971 if Is_Value_Type (Rec_Type) then
2972 return;
2973 end if;
2975 -- This may be full declaration of a private type, in which case
2976 -- the visible entity is a record, and the private entity has been
2977 -- exchanged with it in the private part of the current package.
2978 -- The initialization procedure is built for the record type, which
2979 -- is retrievable from the private entity.
2981 if Is_Incomplete_Or_Private_Type (Rec_Type) then
2982 Rec_Type := Underlying_Type (Rec_Type);
2983 end if;
2985 -- If there are discriminants, build the discriminant map to replace
2986 -- discriminants by their discriminals in complex bound expressions.
2987 -- These only arise for the corresponding records of protected types.
2989 if Is_Concurrent_Record_Type (Rec_Type)
2990 and then Has_Discriminants (Rec_Type)
2991 then
2992 declare
2993 Disc : Entity_Id;
2994 begin
2995 Disc := First_Discriminant (Rec_Type);
2996 while Present (Disc) loop
2997 Append_Elmt (Disc, Discr_Map);
2998 Append_Elmt (Discriminal (Disc), Discr_Map);
2999 Next_Discriminant (Disc);
3000 end loop;
3001 end;
3002 end if;
3004 -- Derived types that have no type extension can use the initialization
3005 -- procedure of their parent and do not need a procedure of their own.
3006 -- This is only correct if there are no representation clauses for the
3007 -- type or its parent, and if the parent has in fact been frozen so
3008 -- that its initialization procedure exists.
3010 if Is_Derived_Type (Rec_Type)
3011 and then not Is_Tagged_Type (Rec_Type)
3012 and then not Is_Unchecked_Union (Rec_Type)
3013 and then not Has_New_Non_Standard_Rep (Rec_Type)
3014 and then not Parent_Subtype_Renaming_Discrims
3015 and then Has_Non_Null_Base_Init_Proc (Etype (Rec_Type))
3016 then
3017 Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
3019 -- Otherwise if we need an initialization procedure, then build one,
3020 -- mark it as public and inlinable and as having a completion.
3022 elsif Requires_Init_Proc (Rec_Type)
3023 or else Is_Unchecked_Union (Rec_Type)
3024 then
3025 Build_Offset_To_Top_Functions;
3026 Build_Init_Procedure;
3027 Set_Is_Public (Proc_Id, Is_Public (Pe));
3029 -- The initialization of protected records is not worth inlining.
3030 -- In addition, when compiled for another unit for inlining purposes,
3031 -- it may make reference to entities that have not been elaborated
3032 -- yet. The initialization of controlled records contains a nested
3033 -- clean-up procedure that makes it impractical to inline as well,
3034 -- and leads to undefined symbols if inlined in a different unit.
3035 -- Similar considerations apply to task types.
3037 if not Is_Concurrent_Type (Rec_Type)
3038 and then not Has_Task (Rec_Type)
3039 and then not Controlled_Type (Rec_Type)
3040 then
3041 Set_Is_Inlined (Proc_Id);
3042 end if;
3044 Set_Is_Internal (Proc_Id);
3045 Set_Has_Completion (Proc_Id);
3047 if not Debug_Generated_Code then
3048 Set_Debug_Info_Off (Proc_Id);
3049 end if;
3051 Set_Static_Initialization
3052 (Proc_Id, Build_Equivalent_Record_Aggregate (Rec_Type));
3053 end if;
3054 end Build_Record_Init_Proc;
3056 ----------------------------
3057 -- Build_Slice_Assignment --
3058 ----------------------------
3060 -- Generates the following subprogram:
3062 -- procedure Assign
3063 -- (Source, Target : Array_Type,
3064 -- Left_Lo, Left_Hi : Index;
3065 -- Right_Lo, Right_Hi : Index;
3066 -- Rev : Boolean)
3067 -- is
3068 -- Li1 : Index;
3069 -- Ri1 : Index;
3071 -- begin
3072 -- if Rev then
3073 -- Li1 := Left_Hi;
3074 -- Ri1 := Right_Hi;
3075 -- else
3076 -- Li1 := Left_Lo;
3077 -- Ri1 := Right_Lo;
3078 -- end if;
3080 -- loop
3081 -- if Rev then
3082 -- exit when Li1 < Left_Lo;
3083 -- else
3084 -- exit when Li1 > Left_Hi;
3085 -- end if;
3087 -- Target (Li1) := Source (Ri1);
3089 -- if Rev then
3090 -- Li1 := Index'pred (Li1);
3091 -- Ri1 := Index'pred (Ri1);
3092 -- else
3093 -- Li1 := Index'succ (Li1);
3094 -- Ri1 := Index'succ (Ri1);
3095 -- end if;
3096 -- end loop;
3097 -- end Assign;
3099 procedure Build_Slice_Assignment (Typ : Entity_Id) is
3100 Loc : constant Source_Ptr := Sloc (Typ);
3101 Index : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
3103 -- Build formal parameters of procedure
3105 Larray : constant Entity_Id :=
3106 Make_Defining_Identifier
3107 (Loc, Chars => New_Internal_Name ('A'));
3108 Rarray : constant Entity_Id :=
3109 Make_Defining_Identifier
3110 (Loc, Chars => New_Internal_Name ('R'));
3111 Left_Lo : constant Entity_Id :=
3112 Make_Defining_Identifier
3113 (Loc, Chars => New_Internal_Name ('L'));
3114 Left_Hi : constant Entity_Id :=
3115 Make_Defining_Identifier
3116 (Loc, Chars => New_Internal_Name ('L'));
3117 Right_Lo : constant Entity_Id :=
3118 Make_Defining_Identifier
3119 (Loc, Chars => New_Internal_Name ('R'));
3120 Right_Hi : constant Entity_Id :=
3121 Make_Defining_Identifier
3122 (Loc, Chars => New_Internal_Name ('R'));
3123 Rev : constant Entity_Id :=
3124 Make_Defining_Identifier
3125 (Loc, Chars => New_Internal_Name ('D'));
3126 Proc_Name : constant Entity_Id :=
3127 Make_Defining_Identifier (Loc,
3128 Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
3130 Lnn : constant Entity_Id :=
3131 Make_Defining_Identifier (Loc, New_Internal_Name ('L'));
3132 Rnn : constant Entity_Id :=
3133 Make_Defining_Identifier (Loc, New_Internal_Name ('R'));
3134 -- Subscripts for left and right sides
3136 Decls : List_Id;
3137 Loops : Node_Id;
3138 Stats : List_Id;
3140 begin
3141 -- Build declarations for indices
3143 Decls := New_List;
3145 Append_To (Decls,
3146 Make_Object_Declaration (Loc,
3147 Defining_Identifier => Lnn,
3148 Object_Definition =>
3149 New_Occurrence_Of (Index, Loc)));
3151 Append_To (Decls,
3152 Make_Object_Declaration (Loc,
3153 Defining_Identifier => Rnn,
3154 Object_Definition =>
3155 New_Occurrence_Of (Index, Loc)));
3157 Stats := New_List;
3159 -- Build initializations for indices
3161 declare
3162 F_Init : constant List_Id := New_List;
3163 B_Init : constant List_Id := New_List;
3165 begin
3166 Append_To (F_Init,
3167 Make_Assignment_Statement (Loc,
3168 Name => New_Occurrence_Of (Lnn, Loc),
3169 Expression => New_Occurrence_Of (Left_Lo, Loc)));
3171 Append_To (F_Init,
3172 Make_Assignment_Statement (Loc,
3173 Name => New_Occurrence_Of (Rnn, Loc),
3174 Expression => New_Occurrence_Of (Right_Lo, Loc)));
3176 Append_To (B_Init,
3177 Make_Assignment_Statement (Loc,
3178 Name => New_Occurrence_Of (Lnn, Loc),
3179 Expression => New_Occurrence_Of (Left_Hi, Loc)));
3181 Append_To (B_Init,
3182 Make_Assignment_Statement (Loc,
3183 Name => New_Occurrence_Of (Rnn, Loc),
3184 Expression => New_Occurrence_Of (Right_Hi, Loc)));
3186 Append_To (Stats,
3187 Make_If_Statement (Loc,
3188 Condition => New_Occurrence_Of (Rev, Loc),
3189 Then_Statements => B_Init,
3190 Else_Statements => F_Init));
3191 end;
3193 -- Now construct the assignment statement
3195 Loops :=
3196 Make_Loop_Statement (Loc,
3197 Statements => New_List (
3198 Make_Assignment_Statement (Loc,
3199 Name =>
3200 Make_Indexed_Component (Loc,
3201 Prefix => New_Occurrence_Of (Larray, Loc),
3202 Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
3203 Expression =>
3204 Make_Indexed_Component (Loc,
3205 Prefix => New_Occurrence_Of (Rarray, Loc),
3206 Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
3207 End_Label => Empty);
3209 -- Build exit condition
3211 declare
3212 F_Ass : constant List_Id := New_List;
3213 B_Ass : constant List_Id := New_List;
3215 begin
3216 Append_To (F_Ass,
3217 Make_Exit_Statement (Loc,
3218 Condition =>
3219 Make_Op_Gt (Loc,
3220 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3221 Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
3223 Append_To (B_Ass,
3224 Make_Exit_Statement (Loc,
3225 Condition =>
3226 Make_Op_Lt (Loc,
3227 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3228 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
3230 Prepend_To (Statements (Loops),
3231 Make_If_Statement (Loc,
3232 Condition => New_Occurrence_Of (Rev, Loc),
3233 Then_Statements => B_Ass,
3234 Else_Statements => F_Ass));
3235 end;
3237 -- Build the increment/decrement statements
3239 declare
3240 F_Ass : constant List_Id := New_List;
3241 B_Ass : constant List_Id := New_List;
3243 begin
3244 Append_To (F_Ass,
3245 Make_Assignment_Statement (Loc,
3246 Name => New_Occurrence_Of (Lnn, Loc),
3247 Expression =>
3248 Make_Attribute_Reference (Loc,
3249 Prefix =>
3250 New_Occurrence_Of (Index, Loc),
3251 Attribute_Name => Name_Succ,
3252 Expressions => New_List (
3253 New_Occurrence_Of (Lnn, Loc)))));
3255 Append_To (F_Ass,
3256 Make_Assignment_Statement (Loc,
3257 Name => New_Occurrence_Of (Rnn, Loc),
3258 Expression =>
3259 Make_Attribute_Reference (Loc,
3260 Prefix =>
3261 New_Occurrence_Of (Index, Loc),
3262 Attribute_Name => Name_Succ,
3263 Expressions => New_List (
3264 New_Occurrence_Of (Rnn, Loc)))));
3266 Append_To (B_Ass,
3267 Make_Assignment_Statement (Loc,
3268 Name => New_Occurrence_Of (Lnn, Loc),
3269 Expression =>
3270 Make_Attribute_Reference (Loc,
3271 Prefix =>
3272 New_Occurrence_Of (Index, Loc),
3273 Attribute_Name => Name_Pred,
3274 Expressions => New_List (
3275 New_Occurrence_Of (Lnn, Loc)))));
3277 Append_To (B_Ass,
3278 Make_Assignment_Statement (Loc,
3279 Name => New_Occurrence_Of (Rnn, Loc),
3280 Expression =>
3281 Make_Attribute_Reference (Loc,
3282 Prefix =>
3283 New_Occurrence_Of (Index, Loc),
3284 Attribute_Name => Name_Pred,
3285 Expressions => New_List (
3286 New_Occurrence_Of (Rnn, Loc)))));
3288 Append_To (Statements (Loops),
3289 Make_If_Statement (Loc,
3290 Condition => New_Occurrence_Of (Rev, Loc),
3291 Then_Statements => B_Ass,
3292 Else_Statements => F_Ass));
3293 end;
3295 Append_To (Stats, Loops);
3297 declare
3298 Spec : Node_Id;
3299 Formals : List_Id := New_List;
3301 begin
3302 Formals := New_List (
3303 Make_Parameter_Specification (Loc,
3304 Defining_Identifier => Larray,
3305 Out_Present => True,
3306 Parameter_Type =>
3307 New_Reference_To (Base_Type (Typ), Loc)),
3309 Make_Parameter_Specification (Loc,
3310 Defining_Identifier => Rarray,
3311 Parameter_Type =>
3312 New_Reference_To (Base_Type (Typ), Loc)),
3314 Make_Parameter_Specification (Loc,
3315 Defining_Identifier => Left_Lo,
3316 Parameter_Type =>
3317 New_Reference_To (Index, Loc)),
3319 Make_Parameter_Specification (Loc,
3320 Defining_Identifier => Left_Hi,
3321 Parameter_Type =>
3322 New_Reference_To (Index, Loc)),
3324 Make_Parameter_Specification (Loc,
3325 Defining_Identifier => Right_Lo,
3326 Parameter_Type =>
3327 New_Reference_To (Index, Loc)),
3329 Make_Parameter_Specification (Loc,
3330 Defining_Identifier => Right_Hi,
3331 Parameter_Type =>
3332 New_Reference_To (Index, Loc)));
3334 Append_To (Formals,
3335 Make_Parameter_Specification (Loc,
3336 Defining_Identifier => Rev,
3337 Parameter_Type =>
3338 New_Reference_To (Standard_Boolean, Loc)));
3340 Spec :=
3341 Make_Procedure_Specification (Loc,
3342 Defining_Unit_Name => Proc_Name,
3343 Parameter_Specifications => Formals);
3345 Discard_Node (
3346 Make_Subprogram_Body (Loc,
3347 Specification => Spec,
3348 Declarations => Decls,
3349 Handled_Statement_Sequence =>
3350 Make_Handled_Sequence_Of_Statements (Loc,
3351 Statements => Stats)));
3352 end;
3354 Set_TSS (Typ, Proc_Name);
3355 Set_Is_Pure (Proc_Name);
3356 end Build_Slice_Assignment;
3358 ------------------------------------
3359 -- Build_Variant_Record_Equality --
3360 ------------------------------------
3362 -- Generates:
3364 -- function _Equality (X, Y : T) return Boolean is
3365 -- begin
3366 -- -- Compare discriminants
3368 -- if False or else X.D1 /= Y.D1 or else X.D2 /= Y.D2 then
3369 -- return False;
3370 -- end if;
3372 -- -- Compare components
3374 -- if False or else X.C1 /= Y.C1 or else X.C2 /= Y.C2 then
3375 -- return False;
3376 -- end if;
3378 -- -- Compare variant part
3380 -- case X.D1 is
3381 -- when V1 =>
3382 -- if False or else X.C2 /= Y.C2 or else X.C3 /= Y.C3 then
3383 -- return False;
3384 -- end if;
3385 -- ...
3386 -- when Vn =>
3387 -- if False or else X.Cn /= Y.Cn then
3388 -- return False;
3389 -- end if;
3390 -- end case;
3392 -- return True;
3393 -- end _Equality;
3395 procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
3396 Loc : constant Source_Ptr := Sloc (Typ);
3398 F : constant Entity_Id :=
3399 Make_Defining_Identifier (Loc,
3400 Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
3402 X : constant Entity_Id :=
3403 Make_Defining_Identifier (Loc,
3404 Chars => Name_X);
3406 Y : constant Entity_Id :=
3407 Make_Defining_Identifier (Loc,
3408 Chars => Name_Y);
3410 Def : constant Node_Id := Parent (Typ);
3411 Comps : constant Node_Id := Component_List (Type_Definition (Def));
3412 Stmts : constant List_Id := New_List;
3413 Pspecs : constant List_Id := New_List;
3415 begin
3416 -- Derived Unchecked_Union types no longer inherit the equality function
3417 -- of their parent.
3419 if Is_Derived_Type (Typ)
3420 and then not Is_Unchecked_Union (Typ)
3421 and then not Has_New_Non_Standard_Rep (Typ)
3422 then
3423 declare
3424 Parent_Eq : constant Entity_Id :=
3425 TSS (Root_Type (Typ), TSS_Composite_Equality);
3427 begin
3428 if Present (Parent_Eq) then
3429 Copy_TSS (Parent_Eq, Typ);
3430 return;
3431 end if;
3432 end;
3433 end if;
3435 Discard_Node (
3436 Make_Subprogram_Body (Loc,
3437 Specification =>
3438 Make_Function_Specification (Loc,
3439 Defining_Unit_Name => F,
3440 Parameter_Specifications => Pspecs,
3441 Result_Definition => New_Reference_To (Standard_Boolean, Loc)),
3442 Declarations => New_List,
3443 Handled_Statement_Sequence =>
3444 Make_Handled_Sequence_Of_Statements (Loc,
3445 Statements => Stmts)));
3447 Append_To (Pspecs,
3448 Make_Parameter_Specification (Loc,
3449 Defining_Identifier => X,
3450 Parameter_Type => New_Reference_To (Typ, Loc)));
3452 Append_To (Pspecs,
3453 Make_Parameter_Specification (Loc,
3454 Defining_Identifier => Y,
3455 Parameter_Type => New_Reference_To (Typ, Loc)));
3457 -- Unchecked_Unions require additional machinery to support equality.
3458 -- Two extra parameters (A and B) are added to the equality function
3459 -- parameter list in order to capture the inferred values of the
3460 -- discriminants in later calls.
3462 if Is_Unchecked_Union (Typ) then
3463 declare
3464 Discr_Type : constant Node_Id := Etype (First_Discriminant (Typ));
3466 A : constant Node_Id :=
3467 Make_Defining_Identifier (Loc,
3468 Chars => Name_A);
3470 B : constant Node_Id :=
3471 Make_Defining_Identifier (Loc,
3472 Chars => Name_B);
3474 begin
3475 -- Add A and B to the parameter list
3477 Append_To (Pspecs,
3478 Make_Parameter_Specification (Loc,
3479 Defining_Identifier => A,
3480 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
3482 Append_To (Pspecs,
3483 Make_Parameter_Specification (Loc,
3484 Defining_Identifier => B,
3485 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
3487 -- Generate the following header code to compare the inferred
3488 -- discriminants:
3490 -- if a /= b then
3491 -- return False;
3492 -- end if;
3494 Append_To (Stmts,
3495 Make_If_Statement (Loc,
3496 Condition =>
3497 Make_Op_Ne (Loc,
3498 Left_Opnd => New_Reference_To (A, Loc),
3499 Right_Opnd => New_Reference_To (B, Loc)),
3500 Then_Statements => New_List (
3501 Make_Return_Statement (Loc,
3502 Expression => New_Occurrence_Of (Standard_False, Loc)))));
3504 -- Generate component-by-component comparison. Note that we must
3505 -- propagate one of the inferred discriminant formals to act as
3506 -- the case statement switch.
3508 Append_List_To (Stmts,
3509 Make_Eq_Case (Typ, Comps, A));
3511 end;
3513 -- Normal case (not unchecked union)
3515 else
3516 Append_To (Stmts,
3517 Make_Eq_If (Typ,
3518 Discriminant_Specifications (Def)));
3520 Append_List_To (Stmts,
3521 Make_Eq_Case (Typ, Comps));
3522 end if;
3524 Append_To (Stmts,
3525 Make_Return_Statement (Loc,
3526 Expression => New_Reference_To (Standard_True, Loc)));
3528 Set_TSS (Typ, F);
3529 Set_Is_Pure (F);
3531 if not Debug_Generated_Code then
3532 Set_Debug_Info_Off (F);
3533 end if;
3534 end Build_Variant_Record_Equality;
3536 -----------------------------
3537 -- Check_Stream_Attributes --
3538 -----------------------------
3540 procedure Check_Stream_Attributes (Typ : Entity_Id) is
3541 Comp : Entity_Id;
3542 Par_Read : constant Boolean :=
3543 Stream_Attribute_Available (Typ, TSS_Stream_Read)
3544 and then not Has_Specified_Stream_Read (Typ);
3545 Par_Write : constant Boolean :=
3546 Stream_Attribute_Available (Typ, TSS_Stream_Write)
3547 and then not Has_Specified_Stream_Write (Typ);
3549 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type);
3550 -- Check that Comp has a user-specified Nam stream attribute
3552 ----------------
3553 -- Check_Attr --
3554 ----------------
3556 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type) is
3557 begin
3558 if not Stream_Attribute_Available (Etype (Comp), TSS_Nam) then
3559 Error_Msg_Name_1 := Nam;
3560 Error_Msg_N
3561 ("|component& in limited extension must have% attribute", Comp);
3562 end if;
3563 end Check_Attr;
3565 -- Start of processing for Check_Stream_Attributes
3567 begin
3568 if Par_Read or else Par_Write then
3569 Comp := First_Component (Typ);
3570 while Present (Comp) loop
3571 if Comes_From_Source (Comp)
3572 and then Original_Record_Component (Comp) = Comp
3573 and then Is_Limited_Type (Etype (Comp))
3574 then
3575 if Par_Read then
3576 Check_Attr (Name_Read, TSS_Stream_Read);
3577 end if;
3579 if Par_Write then
3580 Check_Attr (Name_Write, TSS_Stream_Write);
3581 end if;
3582 end if;
3584 Next_Component (Comp);
3585 end loop;
3586 end if;
3587 end Check_Stream_Attributes;
3589 -----------------------------
3590 -- Expand_Record_Extension --
3591 -----------------------------
3593 -- Add a field _parent at the beginning of the record extension. This is
3594 -- used to implement inheritance. Here are some examples of expansion:
3596 -- 1. no discriminants
3597 -- type T2 is new T1 with null record;
3598 -- gives
3599 -- type T2 is new T1 with record
3600 -- _Parent : T1;
3601 -- end record;
3603 -- 2. renamed discriminants
3604 -- type T2 (B, C : Int) is new T1 (A => B) with record
3605 -- _Parent : T1 (A => B);
3606 -- D : Int;
3607 -- end;
3609 -- 3. inherited discriminants
3610 -- type T2 is new T1 with record -- discriminant A inherited
3611 -- _Parent : T1 (A);
3612 -- D : Int;
3613 -- end;
3615 procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
3616 Indic : constant Node_Id := Subtype_Indication (Def);
3617 Loc : constant Source_Ptr := Sloc (Def);
3618 Rec_Ext_Part : Node_Id := Record_Extension_Part (Def);
3619 Par_Subtype : Entity_Id;
3620 Comp_List : Node_Id;
3621 Comp_Decl : Node_Id;
3622 Parent_N : Node_Id;
3623 D : Entity_Id;
3624 List_Constr : constant List_Id := New_List;
3626 begin
3627 -- Expand_Record_Extension is called directly from the semantics, so
3628 -- we must check to see whether expansion is active before proceeding
3630 if not Expander_Active then
3631 return;
3632 end if;
3634 -- This may be a derivation of an untagged private type whose full
3635 -- view is tagged, in which case the Derived_Type_Definition has no
3636 -- extension part. Build an empty one now.
3638 if No (Rec_Ext_Part) then
3639 Rec_Ext_Part :=
3640 Make_Record_Definition (Loc,
3641 End_Label => Empty,
3642 Component_List => Empty,
3643 Null_Present => True);
3645 Set_Record_Extension_Part (Def, Rec_Ext_Part);
3646 Mark_Rewrite_Insertion (Rec_Ext_Part);
3647 end if;
3649 Comp_List := Component_List (Rec_Ext_Part);
3651 Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
3653 -- If the derived type inherits its discriminants the type of the
3654 -- _parent field must be constrained by the inherited discriminants
3656 if Has_Discriminants (T)
3657 and then Nkind (Indic) /= N_Subtype_Indication
3658 and then not Is_Constrained (Entity (Indic))
3659 then
3660 D := First_Discriminant (T);
3661 while Present (D) loop
3662 Append_To (List_Constr, New_Occurrence_Of (D, Loc));
3663 Next_Discriminant (D);
3664 end loop;
3666 Par_Subtype :=
3667 Process_Subtype (
3668 Make_Subtype_Indication (Loc,
3669 Subtype_Mark => New_Reference_To (Entity (Indic), Loc),
3670 Constraint =>
3671 Make_Index_Or_Discriminant_Constraint (Loc,
3672 Constraints => List_Constr)),
3673 Def);
3675 -- Otherwise the original subtype_indication is just what is needed
3677 else
3678 Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
3679 end if;
3681 Set_Parent_Subtype (T, Par_Subtype);
3683 Comp_Decl :=
3684 Make_Component_Declaration (Loc,
3685 Defining_Identifier => Parent_N,
3686 Component_Definition =>
3687 Make_Component_Definition (Loc,
3688 Aliased_Present => False,
3689 Subtype_Indication => New_Reference_To (Par_Subtype, Loc)));
3691 if Null_Present (Rec_Ext_Part) then
3692 Set_Component_List (Rec_Ext_Part,
3693 Make_Component_List (Loc,
3694 Component_Items => New_List (Comp_Decl),
3695 Variant_Part => Empty,
3696 Null_Present => False));
3697 Set_Null_Present (Rec_Ext_Part, False);
3699 elsif Null_Present (Comp_List)
3700 or else Is_Empty_List (Component_Items (Comp_List))
3701 then
3702 Set_Component_Items (Comp_List, New_List (Comp_Decl));
3703 Set_Null_Present (Comp_List, False);
3705 else
3706 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
3707 end if;
3709 Analyze (Comp_Decl);
3710 end Expand_Record_Extension;
3712 ------------------------------------
3713 -- Expand_N_Full_Type_Declaration --
3714 ------------------------------------
3716 procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
3717 Def_Id : constant Entity_Id := Defining_Identifier (N);
3718 B_Id : constant Entity_Id := Base_Type (Def_Id);
3719 Par_Id : Entity_Id;
3720 FN : Node_Id;
3722 procedure Build_Master (Def_Id : Entity_Id);
3723 -- Create the master associated with Def_Id
3725 ------------------
3726 -- Build_Master --
3727 ------------------
3729 procedure Build_Master (Def_Id : Entity_Id) is
3730 begin
3731 -- Anonymous access types are created for the components of the
3732 -- record parameter for an entry declaration. No master is created
3733 -- for such a type.
3735 if Has_Task (Designated_Type (Def_Id))
3736 and then Comes_From_Source (N)
3737 then
3738 Build_Master_Entity (Def_Id);
3739 Build_Master_Renaming (Parent (Def_Id), Def_Id);
3741 -- Create a class-wide master because a Master_Id must be generated
3742 -- for access-to-limited-class-wide types whose root may be extended
3743 -- with task components, and for access-to-limited-interfaces because
3744 -- they can be used to reference tasks implementing such interface.
3746 elsif Is_Class_Wide_Type (Designated_Type (Def_Id))
3747 and then (Is_Limited_Type (Designated_Type (Def_Id))
3748 or else
3749 (Is_Interface (Designated_Type (Def_Id))
3750 and then
3751 Is_Limited_Interface (Designated_Type (Def_Id))))
3752 and then Tasking_Allowed
3754 -- Do not create a class-wide master for types whose convention is
3755 -- Java since these types cannot embed Ada tasks anyway. Note that
3756 -- the following test cannot catch the following case:
3758 -- package java.lang.Object is
3759 -- type Typ is tagged limited private;
3760 -- type Ref is access all Typ'Class;
3761 -- private
3762 -- type Typ is tagged limited ...;
3763 -- pragma Convention (Typ, Java)
3764 -- end;
3766 -- Because the convention appears after we have done the
3767 -- processing for type Ref.
3769 and then Convention (Designated_Type (Def_Id)) /= Convention_Java
3770 and then Convention (Designated_Type (Def_Id)) /= Convention_CIL
3771 then
3772 Build_Class_Wide_Master (Def_Id);
3773 end if;
3774 end Build_Master;
3776 -- Start of processing for Expand_N_Full_Type_Declaration
3778 begin
3779 if Is_Access_Type (Def_Id) then
3780 Build_Master (Def_Id);
3782 if Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
3783 Expand_Access_Protected_Subprogram_Type (N);
3784 end if;
3786 elsif Ada_Version >= Ada_05
3787 and then Is_Array_Type (Def_Id)
3788 and then Is_Access_Type (Component_Type (Def_Id))
3789 and then Ekind (Component_Type (Def_Id)) = E_Anonymous_Access_Type
3790 then
3791 Build_Master (Component_Type (Def_Id));
3793 elsif Has_Task (Def_Id) then
3794 Expand_Previous_Access_Type (Def_Id);
3796 elsif Ada_Version >= Ada_05
3797 and then
3798 (Is_Record_Type (Def_Id)
3799 or else (Is_Array_Type (Def_Id)
3800 and then Is_Record_Type (Component_Type (Def_Id))))
3801 then
3802 declare
3803 Comp : Entity_Id;
3804 Typ : Entity_Id;
3805 M_Id : Entity_Id;
3807 begin
3808 -- Look for the first anonymous access type component
3810 if Is_Array_Type (Def_Id) then
3811 Comp := First_Entity (Component_Type (Def_Id));
3812 else
3813 Comp := First_Entity (Def_Id);
3814 end if;
3816 while Present (Comp) loop
3817 Typ := Etype (Comp);
3819 exit when Is_Access_Type (Typ)
3820 and then Ekind (Typ) = E_Anonymous_Access_Type;
3822 Next_Entity (Comp);
3823 end loop;
3825 -- If found we add a renaming declaration of master_id and we
3826 -- associate it to each anonymous access type component. Do
3827 -- nothing if the access type already has a master. This will be
3828 -- the case if the array type is the packed array created for a
3829 -- user-defined array type T, where the master_id is created when
3830 -- expanding the declaration for T.
3832 if Present (Comp)
3833 and then Ekind (Typ) = E_Anonymous_Access_Type
3834 and then not Restriction_Active (No_Task_Hierarchy)
3835 and then No (Master_Id (Typ))
3837 -- Do not consider run-times with no tasking support
3839 and then RTE_Available (RE_Current_Master)
3840 and then Has_Task (Non_Limited_Designated_Type (Typ))
3841 then
3842 Build_Master_Entity (Def_Id);
3843 M_Id := Build_Master_Renaming (N, Def_Id);
3845 if Is_Array_Type (Def_Id) then
3846 Comp := First_Entity (Component_Type (Def_Id));
3847 else
3848 Comp := First_Entity (Def_Id);
3849 end if;
3851 while Present (Comp) loop
3852 Typ := Etype (Comp);
3854 if Is_Access_Type (Typ)
3855 and then Ekind (Typ) = E_Anonymous_Access_Type
3856 then
3857 Set_Master_Id (Typ, M_Id);
3858 end if;
3860 Next_Entity (Comp);
3861 end loop;
3862 end if;
3863 end;
3864 end if;
3866 Par_Id := Etype (B_Id);
3868 -- The parent type is private then we need to inherit any TSS operations
3869 -- from the full view.
3871 if Ekind (Par_Id) in Private_Kind
3872 and then Present (Full_View (Par_Id))
3873 then
3874 Par_Id := Base_Type (Full_View (Par_Id));
3875 end if;
3877 if Nkind (Type_Definition (Original_Node (N))) =
3878 N_Derived_Type_Definition
3879 and then not Is_Tagged_Type (Def_Id)
3880 and then Present (Freeze_Node (Par_Id))
3881 and then Present (TSS_Elist (Freeze_Node (Par_Id)))
3882 then
3883 Ensure_Freeze_Node (B_Id);
3884 FN := Freeze_Node (B_Id);
3886 if No (TSS_Elist (FN)) then
3887 Set_TSS_Elist (FN, New_Elmt_List);
3888 end if;
3890 declare
3891 T_E : constant Elist_Id := TSS_Elist (FN);
3892 Elmt : Elmt_Id;
3894 begin
3895 Elmt := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
3896 while Present (Elmt) loop
3897 if Chars (Node (Elmt)) /= Name_uInit then
3898 Append_Elmt (Node (Elmt), T_E);
3899 end if;
3901 Next_Elmt (Elmt);
3902 end loop;
3904 -- If the derived type itself is private with a full view, then
3905 -- associate the full view with the inherited TSS_Elist as well.
3907 if Ekind (B_Id) in Private_Kind
3908 and then Present (Full_View (B_Id))
3909 then
3910 Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
3911 Set_TSS_Elist
3912 (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
3913 end if;
3914 end;
3915 end if;
3916 end Expand_N_Full_Type_Declaration;
3918 ---------------------------------
3919 -- Expand_N_Object_Declaration --
3920 ---------------------------------
3922 -- First we do special processing for objects of a tagged type where this
3923 -- is the point at which the type is frozen. The creation of the dispatch
3924 -- table and the initialization procedure have to be deferred to this
3925 -- point, since we reference previously declared primitive subprograms.
3927 -- For all types, we call an initialization procedure if there is one
3929 procedure Expand_N_Object_Declaration (N : Node_Id) is
3930 Def_Id : constant Entity_Id := Defining_Identifier (N);
3931 Expr : constant Node_Id := Expression (N);
3932 Loc : constant Source_Ptr := Sloc (N);
3933 Typ : constant Entity_Id := Etype (Def_Id);
3934 Expr_Q : Node_Id;
3935 Id_Ref : Node_Id;
3936 New_Ref : Node_Id;
3937 BIP_Call : Boolean := False;
3939 begin
3940 -- Don't do anything for deferred constants. All proper actions will
3941 -- be expanded during the full declaration.
3943 if No (Expr) and Constant_Present (N) then
3944 return;
3945 end if;
3947 -- Make shared memory routines for shared passive variable
3949 if Is_Shared_Passive (Def_Id) then
3950 Make_Shared_Var_Procs (N);
3951 end if;
3953 -- If tasks being declared, make sure we have an activation chain
3954 -- defined for the tasks (has no effect if we already have one), and
3955 -- also that a Master variable is established and that the appropriate
3956 -- enclosing construct is established as a task master.
3958 if Has_Task (Typ) then
3959 Build_Activation_Chain_Entity (N);
3960 Build_Master_Entity (Def_Id);
3961 end if;
3963 -- Build a list controller for declarations of the form
3964 -- Obj : access Some_Type [:= Expression];
3966 if Ekind (Typ) = E_Anonymous_Access_Type
3967 and then Is_Controlled (Directly_Designated_Type (Typ))
3968 and then No (Associated_Final_Chain (Typ))
3969 then
3970 Build_Final_List (N, Typ);
3971 end if;
3973 -- Default initialization required, and no expression present
3975 if No (Expr) then
3977 -- Expand Initialize call for controlled objects. One may wonder why
3978 -- the Initialize Call is not done in the regular Init procedure
3979 -- attached to the record type. That's because the init procedure is
3980 -- recursively called on each component, including _Parent, thus the
3981 -- Init call for a controlled object would generate not only one
3982 -- Initialize call as it is required but one for each ancestor of
3983 -- its type. This processing is suppressed if No_Initialization set.
3985 if not Controlled_Type (Typ)
3986 or else No_Initialization (N)
3987 then
3988 null;
3990 elsif not Abort_Allowed
3991 or else not Comes_From_Source (N)
3992 then
3993 Insert_Actions_After (N,
3994 Make_Init_Call (
3995 Ref => New_Occurrence_Of (Def_Id, Loc),
3996 Typ => Base_Type (Typ),
3997 Flist_Ref => Find_Final_List (Def_Id),
3998 With_Attach => Make_Integer_Literal (Loc, 1)));
4000 -- Abort allowed
4002 else
4003 -- We need to protect the initialize call
4005 -- begin
4006 -- Defer_Abort.all;
4007 -- Initialize (...);
4008 -- at end
4009 -- Undefer_Abort.all;
4010 -- end;
4012 -- ??? this won't protect the initialize call for controlled
4013 -- components which are part of the init proc, so this block
4014 -- should probably also contain the call to _init_proc but this
4015 -- requires some code reorganization...
4017 declare
4018 L : constant List_Id :=
4019 Make_Init_Call
4020 (Ref => New_Occurrence_Of (Def_Id, Loc),
4021 Typ => Base_Type (Typ),
4022 Flist_Ref => Find_Final_List (Def_Id),
4023 With_Attach => Make_Integer_Literal (Loc, 1));
4025 Blk : constant Node_Id :=
4026 Make_Block_Statement (Loc,
4027 Handled_Statement_Sequence =>
4028 Make_Handled_Sequence_Of_Statements (Loc, L));
4030 begin
4031 Prepend_To (L, Build_Runtime_Call (Loc, RE_Abort_Defer));
4032 Set_At_End_Proc (Handled_Statement_Sequence (Blk),
4033 New_Occurrence_Of (RTE (RE_Abort_Undefer_Direct), Loc));
4034 Insert_Actions_After (N, New_List (Blk));
4035 Expand_At_End_Handler
4036 (Handled_Statement_Sequence (Blk), Entity (Identifier (Blk)));
4037 end;
4038 end if;
4040 -- Call type initialization procedure if there is one. We build the
4041 -- call and put it immediately after the object declaration, so that
4042 -- it will be expanded in the usual manner. Note that this will
4043 -- result in proper handling of defaulted discriminants. The call
4044 -- to the Init_Proc is suppressed if No_Initialization is set.
4046 if Has_Non_Null_Base_Init_Proc (Typ)
4047 and then not No_Initialization (N)
4048 and then not Is_Value_Type (Typ)
4049 then
4050 -- The call to the initialization procedure does NOT freeze the
4051 -- object being initialized. This is because the call is not a
4052 -- source level call. This works fine, because the only possible
4053 -- statements depending on freeze status that can appear after the
4054 -- _Init call are rep clauses which can safely appear after actual
4055 -- references to the object.
4057 Id_Ref := New_Reference_To (Def_Id, Loc);
4058 Set_Must_Not_Freeze (Id_Ref);
4059 Set_Assignment_OK (Id_Ref);
4061 declare
4062 Init_Expr : constant Node_Id :=
4063 Static_Initialization (Base_Init_Proc (Typ));
4064 begin
4065 if Present (Init_Expr) then
4066 Set_Expression
4067 (N, New_Copy_Tree (Init_Expr, New_Scope => Current_Scope));
4068 return;
4069 else
4070 Initialization_Warning (Id_Ref);
4072 Insert_Actions_After (N,
4073 Build_Initialization_Call (Loc, Id_Ref, Typ));
4074 end if;
4075 end;
4077 -- If simple initialization is required, then set an appropriate
4078 -- simple initialization expression in place. This special
4079 -- initialization is required even though No_Init_Flag is present,
4080 -- but is not needed if there was an explicit initialization.
4082 -- An internally generated temporary needs no initialization because
4083 -- it will be assigned subsequently. In particular, there is no point
4084 -- in applying Initialize_Scalars to such a temporary.
4086 elsif Needs_Simple_Initialization (Typ)
4087 and then not Is_Internal (Def_Id)
4088 and then not Has_Init_Expression (N)
4089 then
4090 Set_No_Initialization (N, False);
4091 Set_Expression (N, Get_Simple_Init_Val (Typ, Loc, Esize (Def_Id)));
4092 Analyze_And_Resolve (Expression (N), Typ);
4093 end if;
4095 -- Generate attribute for Persistent_BSS if needed
4097 if Persistent_BSS_Mode
4098 and then Comes_From_Source (N)
4099 and then Is_Potentially_Persistent_Type (Typ)
4100 and then not Has_Init_Expression (N)
4101 and then Is_Library_Level_Entity (Def_Id)
4102 then
4103 declare
4104 Prag : Node_Id;
4105 begin
4106 Prag :=
4107 Make_Linker_Section_Pragma
4108 (Def_Id, Sloc (N), ".persistent.bss");
4109 Insert_After (N, Prag);
4110 Analyze (Prag);
4111 end;
4112 end if;
4114 -- If access type, then we know it is null if not initialized
4116 if Is_Access_Type (Typ) then
4117 Set_Is_Known_Null (Def_Id);
4118 end if;
4120 -- Explicit initialization present
4122 else
4123 -- Obtain actual expression from qualified expression
4125 if Nkind (Expr) = N_Qualified_Expression then
4126 Expr_Q := Expression (Expr);
4127 else
4128 Expr_Q := Expr;
4129 end if;
4131 -- When we have the appropriate type of aggregate in the expression
4132 -- (it has been determined during analysis of the aggregate by
4133 -- setting the delay flag), let's perform in place assignment and
4134 -- thus avoid creating a temporary.
4136 if Is_Delayed_Aggregate (Expr_Q) then
4137 Convert_Aggr_In_Object_Decl (N);
4139 else
4140 -- Ada 2005 (AI-318-02): If the initialization expression is a
4141 -- call to a build-in-place function, then access to the declared
4142 -- object must be passed to the function. Currently we limit such
4143 -- functions to those with constrained limited result subtypes,
4144 -- but eventually we plan to expand the allowed forms of functions
4145 -- that are treated as build-in-place.
4147 if Ada_Version >= Ada_05
4148 and then Is_Build_In_Place_Function_Call (Expr_Q)
4149 then
4150 Make_Build_In_Place_Call_In_Object_Declaration (N, Expr_Q);
4151 BIP_Call := True;
4152 end if;
4154 -- In most cases, we must check that the initial value meets any
4155 -- constraint imposed by the declared type. However, there is one
4156 -- very important exception to this rule. If the entity has an
4157 -- unconstrained nominal subtype, then it acquired its constraints
4158 -- from the expression in the first place, and not only does this
4159 -- mean that the constraint check is not needed, but an attempt to
4160 -- perform the constraint check can cause order order of
4161 -- elaboration problems.
4163 if not Is_Constr_Subt_For_U_Nominal (Typ) then
4165 -- If this is an allocator for an aggregate that has been
4166 -- allocated in place, delay checks until assignments are
4167 -- made, because the discriminants are not initialized.
4169 if Nkind (Expr) = N_Allocator
4170 and then No_Initialization (Expr)
4171 then
4172 null;
4173 else
4174 Apply_Constraint_Check (Expr, Typ);
4175 end if;
4176 end if;
4178 -- Ada 2005 (AI-251): Rewrite the expression that initializes a
4179 -- class-wide object to ensure that we copy the full object.
4181 -- Replace
4182 -- CW : I'Class := Obj;
4183 -- by
4184 -- CW__1 : I'Class := I'Class (Base_Address (Obj'Address));
4185 -- CW : I'Class renames Displace (CW__1, I'Tag);
4187 if Is_Interface (Typ)
4188 and then Is_Class_Wide_Type (Etype (Expr))
4189 and then Comes_From_Source (Def_Id)
4190 then
4191 declare
4192 Decl_1 : Node_Id;
4193 Decl_2 : Node_Id;
4195 begin
4196 Decl_1 :=
4197 Make_Object_Declaration (Loc,
4198 Defining_Identifier =>
4199 Make_Defining_Identifier (Loc,
4200 New_Internal_Name ('D')),
4202 Object_Definition =>
4203 Make_Attribute_Reference (Loc,
4204 Prefix =>
4205 New_Occurrence_Of
4206 (Root_Type (Etype (Def_Id)), Loc),
4207 Attribute_Name => Name_Class),
4209 Expression =>
4210 Unchecked_Convert_To
4211 (Class_Wide_Type (Root_Type (Etype (Def_Id))),
4212 Make_Explicit_Dereference (Loc,
4213 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
4214 Make_Function_Call (Loc,
4215 Name =>
4216 New_Reference_To (RTE (RE_Base_Address),
4217 Loc),
4218 Parameter_Associations => New_List (
4219 Make_Attribute_Reference (Loc,
4220 Prefix => Relocate_Node (Expr),
4221 Attribute_Name => Name_Address)))))));
4223 Insert_Action (N, Decl_1);
4225 Decl_2 :=
4226 Make_Object_Renaming_Declaration (Loc,
4227 Defining_Identifier =>
4228 Make_Defining_Identifier (Loc,
4229 New_Internal_Name ('D')),
4231 Subtype_Mark =>
4232 Make_Attribute_Reference (Loc,
4233 Prefix =>
4234 New_Occurrence_Of
4235 (Root_Type (Etype (Def_Id)), Loc),
4236 Attribute_Name => Name_Class),
4238 Name =>
4239 Unchecked_Convert_To (
4240 Class_Wide_Type (Root_Type (Etype (Def_Id))),
4241 Make_Explicit_Dereference (Loc,
4242 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
4243 Make_Function_Call (Loc,
4244 Name =>
4245 New_Reference_To (RTE (RE_Displace), Loc),
4247 Parameter_Associations => New_List (
4248 Make_Attribute_Reference (Loc,
4249 Prefix =>
4250 New_Reference_To
4251 (Defining_Identifier (Decl_1), Loc),
4252 Attribute_Name => Name_Address),
4254 Unchecked_Convert_To (RTE (RE_Tag),
4255 New_Reference_To
4256 (Node
4257 (First_Elmt
4258 (Access_Disp_Table
4259 (Root_Type (Typ)))),
4260 Loc))))))));
4262 Rewrite (N, Decl_2);
4263 Analyze (N);
4265 -- Replace internal identifier of Decl_2 by the identifier
4266 -- found in the sources. We also have to exchange entities
4267 -- containing their defining identifiers to ensure the
4268 -- correct replacement of the object declaration by this
4269 -- object renaming declaration (because such definings
4270 -- identifier have been previously added by Enter_Name to
4271 -- the current scope). We must preserve the homonym chain
4272 -- of the source entity as well.
4274 Set_Chars (Defining_Identifier (N), Chars (Def_Id));
4275 Set_Homonym (Defining_Identifier (N), Homonym (Def_Id));
4276 Exchange_Entities (Defining_Identifier (N), Def_Id);
4278 return;
4279 end;
4280 end if;
4282 -- If the type is controlled and not limited then the target is
4283 -- adjusted after the copy and attached to the finalization list.
4284 -- However, no adjustment is done in the case where the object was
4285 -- initialized by a call to a function whose result is built in
4286 -- place, since no copy occurred. (We eventually plan to support
4287 -- in-place function results for some nonlimited types. ???)
4289 if Controlled_Type (Typ)
4290 and then not Is_Limited_Type (Typ)
4291 and then not BIP_Call
4292 then
4293 Insert_Actions_After (N,
4294 Make_Adjust_Call (
4295 Ref => New_Reference_To (Def_Id, Loc),
4296 Typ => Base_Type (Typ),
4297 Flist_Ref => Find_Final_List (Def_Id),
4298 With_Attach => Make_Integer_Literal (Loc, 1)));
4299 end if;
4301 -- For tagged types, when an init value is given, the tag has to
4302 -- be re-initialized separately in order to avoid the propagation
4303 -- of a wrong tag coming from a view conversion unless the type
4304 -- is class wide (in this case the tag comes from the init value).
4305 -- Suppress the tag assignment when VM_Target because VM tags are
4306 -- represented implicitly in objects. Ditto for types that are
4307 -- CPP_CLASS, and for initializations that are aggregates, because
4308 -- they have to have the right tag.
4310 if Is_Tagged_Type (Typ)
4311 and then not Is_Class_Wide_Type (Typ)
4312 and then not Is_CPP_Class (Typ)
4313 and then VM_Target = No_VM
4314 and then Nkind (Expr) /= N_Aggregate
4315 then
4316 -- The re-assignment of the tag has to be done even if the
4317 -- object is a constant.
4319 New_Ref :=
4320 Make_Selected_Component (Loc,
4321 Prefix => New_Reference_To (Def_Id, Loc),
4322 Selector_Name =>
4323 New_Reference_To (First_Tag_Component (Typ), Loc));
4325 Set_Assignment_OK (New_Ref);
4327 Insert_After (N,
4328 Make_Assignment_Statement (Loc,
4329 Name => New_Ref,
4330 Expression =>
4331 Unchecked_Convert_To (RTE (RE_Tag),
4332 New_Reference_To
4333 (Node
4334 (First_Elmt
4335 (Access_Disp_Table (Base_Type (Typ)))),
4336 Loc))));
4338 -- For discrete types, set the Is_Known_Valid flag if the
4339 -- initializing value is known to be valid.
4341 elsif Is_Discrete_Type (Typ) and then Expr_Known_Valid (Expr) then
4342 Set_Is_Known_Valid (Def_Id);
4344 elsif Is_Access_Type (Typ) then
4346 -- For access types set the Is_Known_Non_Null flag if the
4347 -- initializing value is known to be non-null. We can also set
4348 -- Can_Never_Be_Null if this is a constant.
4350 if Known_Non_Null (Expr) then
4351 Set_Is_Known_Non_Null (Def_Id, True);
4353 if Constant_Present (N) then
4354 Set_Can_Never_Be_Null (Def_Id);
4355 end if;
4356 end if;
4357 end if;
4359 -- If validity checking on copies, validate initial expression
4361 if Validity_Checks_On
4362 and then Validity_Check_Copies
4363 then
4364 Ensure_Valid (Expr);
4365 Set_Is_Known_Valid (Def_Id);
4366 end if;
4367 end if;
4369 -- Cases where the back end cannot handle the initialization directly
4370 -- In such cases, we expand an assignment that will be appropriately
4371 -- handled by Expand_N_Assignment_Statement.
4373 -- The exclusion of the unconstrained case is wrong, but for now it
4374 -- is too much trouble ???
4376 if (Is_Possibly_Unaligned_Slice (Expr)
4377 or else (Is_Possibly_Unaligned_Object (Expr)
4378 and then not Represented_As_Scalar (Etype (Expr))))
4380 -- The exclusion of the unconstrained case is wrong, but for now
4381 -- it is too much trouble ???
4383 and then not (Is_Array_Type (Etype (Expr))
4384 and then not Is_Constrained (Etype (Expr)))
4385 then
4386 declare
4387 Stat : constant Node_Id :=
4388 Make_Assignment_Statement (Loc,
4389 Name => New_Reference_To (Def_Id, Loc),
4390 Expression => Relocate_Node (Expr));
4391 begin
4392 Set_Expression (N, Empty);
4393 Set_No_Initialization (N);
4394 Set_Assignment_OK (Name (Stat));
4395 Set_No_Ctrl_Actions (Stat);
4396 Insert_After (N, Stat);
4397 Analyze (Stat);
4398 end;
4399 end if;
4400 end if;
4402 exception
4403 when RE_Not_Available =>
4404 return;
4405 end Expand_N_Object_Declaration;
4407 ---------------------------------
4408 -- Expand_N_Subtype_Indication --
4409 ---------------------------------
4411 -- Add a check on the range of the subtype. The static case is partially
4412 -- duplicated by Process_Range_Expr_In_Decl in Sem_Ch3, but we still need
4413 -- to check here for the static case in order to avoid generating
4414 -- extraneous expanded code. Also deal with validity checking.
4416 procedure Expand_N_Subtype_Indication (N : Node_Id) is
4417 Ran : constant Node_Id := Range_Expression (Constraint (N));
4418 Typ : constant Entity_Id := Entity (Subtype_Mark (N));
4420 begin
4421 if Nkind (Constraint (N)) = N_Range_Constraint then
4422 Validity_Check_Range (Range_Expression (Constraint (N)));
4423 end if;
4425 if Nkind (Parent (N)) = N_Constrained_Array_Definition
4426 or else
4427 Nkind (Parent (N)) = N_Slice
4428 then
4429 Apply_Range_Check (Ran, Typ);
4430 end if;
4431 end Expand_N_Subtype_Indication;
4433 ---------------------------
4434 -- Expand_N_Variant_Part --
4435 ---------------------------
4437 -- If the last variant does not contain the Others choice, replace it with
4438 -- an N_Others_Choice node since Gigi always wants an Others. Note that we
4439 -- do not bother to call Analyze on the modified variant part, since it's
4440 -- only effect would be to compute the Others_Discrete_Choices node
4441 -- laboriously, and of course we already know the list of choices that
4442 -- corresponds to the others choice (it's the list we are replacing!)
4444 procedure Expand_N_Variant_Part (N : Node_Id) is
4445 Last_Var : constant Node_Id := Last_Non_Pragma (Variants (N));
4446 Others_Node : Node_Id;
4447 begin
4448 if Nkind (First (Discrete_Choices (Last_Var))) /= N_Others_Choice then
4449 Others_Node := Make_Others_Choice (Sloc (Last_Var));
4450 Set_Others_Discrete_Choices
4451 (Others_Node, Discrete_Choices (Last_Var));
4452 Set_Discrete_Choices (Last_Var, New_List (Others_Node));
4453 end if;
4454 end Expand_N_Variant_Part;
4456 ---------------------------------
4457 -- Expand_Previous_Access_Type --
4458 ---------------------------------
4460 procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
4461 T : Entity_Id := First_Entity (Current_Scope);
4463 begin
4464 -- Find all access types declared in the current scope, whose
4465 -- designated type is Def_Id.
4467 while Present (T) loop
4468 if Is_Access_Type (T)
4469 and then Designated_Type (T) = Def_Id
4470 then
4471 Build_Master_Entity (Def_Id);
4472 Build_Master_Renaming (Parent (Def_Id), T);
4473 end if;
4475 Next_Entity (T);
4476 end loop;
4477 end Expand_Previous_Access_Type;
4479 ------------------------------
4480 -- Expand_Record_Controller --
4481 ------------------------------
4483 procedure Expand_Record_Controller (T : Entity_Id) is
4484 Def : Node_Id := Type_Definition (Parent (T));
4485 Comp_List : Node_Id;
4486 Comp_Decl : Node_Id;
4487 Loc : Source_Ptr;
4488 First_Comp : Node_Id;
4489 Controller_Type : Entity_Id;
4490 Ent : Entity_Id;
4492 begin
4493 if Nkind (Def) = N_Derived_Type_Definition then
4494 Def := Record_Extension_Part (Def);
4495 end if;
4497 if Null_Present (Def) then
4498 Set_Component_List (Def,
4499 Make_Component_List (Sloc (Def),
4500 Component_Items => Empty_List,
4501 Variant_Part => Empty,
4502 Null_Present => True));
4503 end if;
4505 Comp_List := Component_List (Def);
4507 if Null_Present (Comp_List)
4508 or else Is_Empty_List (Component_Items (Comp_List))
4509 then
4510 Loc := Sloc (Comp_List);
4511 else
4512 Loc := Sloc (First (Component_Items (Comp_List)));
4513 end if;
4515 if Is_Inherently_Limited_Type (T) then
4516 Controller_Type := RTE (RE_Limited_Record_Controller);
4517 else
4518 Controller_Type := RTE (RE_Record_Controller);
4519 end if;
4521 Ent := Make_Defining_Identifier (Loc, Name_uController);
4523 Comp_Decl :=
4524 Make_Component_Declaration (Loc,
4525 Defining_Identifier => Ent,
4526 Component_Definition =>
4527 Make_Component_Definition (Loc,
4528 Aliased_Present => False,
4529 Subtype_Indication => New_Reference_To (Controller_Type, Loc)));
4531 if Null_Present (Comp_List)
4532 or else Is_Empty_List (Component_Items (Comp_List))
4533 then
4534 Set_Component_Items (Comp_List, New_List (Comp_Decl));
4535 Set_Null_Present (Comp_List, False);
4537 else
4538 -- The controller cannot be placed before the _Parent field since
4539 -- gigi lays out field in order and _parent must be first to preserve
4540 -- the polymorphism of tagged types.
4542 First_Comp := First (Component_Items (Comp_List));
4544 if not Is_Tagged_Type (T) then
4545 Insert_Before (First_Comp, Comp_Decl);
4547 -- if T is a tagged type, place controller declaration after parent
4548 -- field and after eventual tags of interface types.
4550 else
4551 while Present (First_Comp)
4552 and then
4553 (Chars (Defining_Identifier (First_Comp)) = Name_uParent
4554 or else Is_Tag (Defining_Identifier (First_Comp))
4556 -- Ada 2005 (AI-251): The following condition covers secondary
4557 -- tags but also the adjacent component contanining the offset
4558 -- to the base of the object (component generated if the parent
4559 -- has discriminants ---see Add_Interface_Tag_Components). This
4560 -- is required to avoid the addition of the controller between
4561 -- the secondary tag and its adjacent component.
4563 or else Present
4564 (Related_Interface
4565 (Defining_Identifier (First_Comp))))
4566 loop
4567 Next (First_Comp);
4568 end loop;
4570 -- An empty tagged extension might consist only of the parent
4571 -- component. Otherwise insert the controller before the first
4572 -- component that is neither parent nor tag.
4574 if Present (First_Comp) then
4575 Insert_Before (First_Comp, Comp_Decl);
4576 else
4577 Append (Comp_Decl, Component_Items (Comp_List));
4578 end if;
4579 end if;
4580 end if;
4582 Push_Scope (T);
4583 Analyze (Comp_Decl);
4584 Set_Ekind (Ent, E_Component);
4585 Init_Component_Location (Ent);
4587 -- Move the _controller entity ahead in the list of internal entities
4588 -- of the enclosing record so that it is selected instead of a
4589 -- potentially inherited one.
4591 declare
4592 E : constant Entity_Id := Last_Entity (T);
4593 Comp : Entity_Id;
4595 begin
4596 pragma Assert (Chars (E) = Name_uController);
4598 Set_Next_Entity (E, First_Entity (T));
4599 Set_First_Entity (T, E);
4601 Comp := Next_Entity (E);
4602 while Next_Entity (Comp) /= E loop
4603 Next_Entity (Comp);
4604 end loop;
4606 Set_Next_Entity (Comp, Empty);
4607 Set_Last_Entity (T, Comp);
4608 end;
4610 End_Scope;
4612 exception
4613 when RE_Not_Available =>
4614 return;
4615 end Expand_Record_Controller;
4617 ------------------------
4618 -- Expand_Tagged_Root --
4619 ------------------------
4621 procedure Expand_Tagged_Root (T : Entity_Id) is
4622 Def : constant Node_Id := Type_Definition (Parent (T));
4623 Comp_List : Node_Id;
4624 Comp_Decl : Node_Id;
4625 Sloc_N : Source_Ptr;
4627 begin
4628 if Null_Present (Def) then
4629 Set_Component_List (Def,
4630 Make_Component_List (Sloc (Def),
4631 Component_Items => Empty_List,
4632 Variant_Part => Empty,
4633 Null_Present => True));
4634 end if;
4636 Comp_List := Component_List (Def);
4638 if Null_Present (Comp_List)
4639 or else Is_Empty_List (Component_Items (Comp_List))
4640 then
4641 Sloc_N := Sloc (Comp_List);
4642 else
4643 Sloc_N := Sloc (First (Component_Items (Comp_List)));
4644 end if;
4646 Comp_Decl :=
4647 Make_Component_Declaration (Sloc_N,
4648 Defining_Identifier => First_Tag_Component (T),
4649 Component_Definition =>
4650 Make_Component_Definition (Sloc_N,
4651 Aliased_Present => False,
4652 Subtype_Indication => New_Reference_To (RTE (RE_Tag), Sloc_N)));
4654 if Null_Present (Comp_List)
4655 or else Is_Empty_List (Component_Items (Comp_List))
4656 then
4657 Set_Component_Items (Comp_List, New_List (Comp_Decl));
4658 Set_Null_Present (Comp_List, False);
4660 else
4661 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
4662 end if;
4664 -- We don't Analyze the whole expansion because the tag component has
4665 -- already been analyzed previously. Here we just insure that the tree
4666 -- is coherent with the semantic decoration
4668 Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
4670 exception
4671 when RE_Not_Available =>
4672 return;
4673 end Expand_Tagged_Root;
4675 ----------------------
4676 -- Clean_Task_Names --
4677 ----------------------
4679 procedure Clean_Task_Names
4680 (Typ : Entity_Id;
4681 Proc_Id : Entity_Id)
4683 begin
4684 if Has_Task (Typ)
4685 and then not Restriction_Active (No_Implicit_Heap_Allocations)
4686 and then not Global_Discard_Names
4687 and then VM_Target = No_VM
4688 then
4689 Set_Uses_Sec_Stack (Proc_Id);
4690 end if;
4691 end Clean_Task_Names;
4693 -----------------------
4694 -- Freeze_Array_Type --
4695 -----------------------
4697 procedure Freeze_Array_Type (N : Node_Id) is
4698 Typ : constant Entity_Id := Entity (N);
4699 Base : constant Entity_Id := Base_Type (Typ);
4701 begin
4702 if not Is_Bit_Packed_Array (Typ) then
4704 -- If the component contains tasks, so does the array type. This may
4705 -- not be indicated in the array type because the component may have
4706 -- been a private type at the point of definition. Same if component
4707 -- type is controlled.
4709 Set_Has_Task (Base, Has_Task (Component_Type (Typ)));
4710 Set_Has_Controlled_Component (Base,
4711 Has_Controlled_Component (Component_Type (Typ))
4712 or else Is_Controlled (Component_Type (Typ)));
4714 if No (Init_Proc (Base)) then
4716 -- If this is an anonymous array created for a declaration with
4717 -- an initial value, its init_proc will never be called. The
4718 -- initial value itself may have been expanded into assignments,
4719 -- in which case the object declaration is carries the
4720 -- No_Initialization flag.
4722 if Is_Itype (Base)
4723 and then Nkind (Associated_Node_For_Itype (Base)) =
4724 N_Object_Declaration
4725 and then (Present (Expression (Associated_Node_For_Itype (Base)))
4726 or else
4727 No_Initialization (Associated_Node_For_Itype (Base)))
4728 then
4729 null;
4731 -- We do not need an init proc for string or wide [wide] string,
4732 -- since the only time these need initialization in normalize or
4733 -- initialize scalars mode, and these types are treated specially
4734 -- and do not need initialization procedures.
4736 elsif Root_Type (Base) = Standard_String
4737 or else Root_Type (Base) = Standard_Wide_String
4738 or else Root_Type (Base) = Standard_Wide_Wide_String
4739 then
4740 null;
4742 -- Otherwise we have to build an init proc for the subtype
4744 else
4745 Build_Array_Init_Proc (Base, N);
4746 end if;
4747 end if;
4749 if Typ = Base and then Has_Controlled_Component (Base) then
4750 Build_Controlling_Procs (Base);
4752 if not Is_Limited_Type (Component_Type (Typ))
4753 and then Number_Dimensions (Typ) = 1
4754 then
4755 Build_Slice_Assignment (Typ);
4756 end if;
4757 end if;
4759 -- For packed case, there is a default initialization, except if the
4760 -- component type is itself a packed structure with an initialization
4761 -- procedure.
4763 elsif Present (Init_Proc (Component_Type (Base)))
4764 and then No (Base_Init_Proc (Base))
4765 then
4766 Build_Array_Init_Proc (Base, N);
4767 end if;
4768 end Freeze_Array_Type;
4770 -----------------------------
4771 -- Freeze_Enumeration_Type --
4772 -----------------------------
4774 procedure Freeze_Enumeration_Type (N : Node_Id) is
4775 Typ : constant Entity_Id := Entity (N);
4776 Loc : constant Source_Ptr := Sloc (Typ);
4777 Ent : Entity_Id;
4778 Lst : List_Id;
4779 Num : Nat;
4780 Arr : Entity_Id;
4781 Fent : Entity_Id;
4782 Ityp : Entity_Id;
4783 Is_Contiguous : Boolean;
4784 Pos_Expr : Node_Id;
4785 Last_Repval : Uint;
4787 Func : Entity_Id;
4788 pragma Warnings (Off, Func);
4790 begin
4791 -- Various optimization are possible if the given representation is
4792 -- contiguous.
4794 Is_Contiguous := True;
4795 Ent := First_Literal (Typ);
4796 Last_Repval := Enumeration_Rep (Ent);
4797 Next_Literal (Ent);
4799 while Present (Ent) loop
4800 if Enumeration_Rep (Ent) - Last_Repval /= 1 then
4801 Is_Contiguous := False;
4802 exit;
4803 else
4804 Last_Repval := Enumeration_Rep (Ent);
4805 end if;
4807 Next_Literal (Ent);
4808 end loop;
4810 if Is_Contiguous then
4811 Set_Has_Contiguous_Rep (Typ);
4812 Ent := First_Literal (Typ);
4813 Num := 1;
4814 Lst := New_List (New_Reference_To (Ent, Sloc (Ent)));
4816 else
4817 -- Build list of literal references
4819 Lst := New_List;
4820 Num := 0;
4822 Ent := First_Literal (Typ);
4823 while Present (Ent) loop
4824 Append_To (Lst, New_Reference_To (Ent, Sloc (Ent)));
4825 Num := Num + 1;
4826 Next_Literal (Ent);
4827 end loop;
4828 end if;
4830 -- Now build an array declaration
4832 -- typA : array (Natural range 0 .. num - 1) of ctype :=
4833 -- (v, v, v, v, v, ....)
4835 -- where ctype is the corresponding integer type. If the representation
4836 -- is contiguous, we only keep the first literal, which provides the
4837 -- offset for Pos_To_Rep computations.
4839 Arr :=
4840 Make_Defining_Identifier (Loc,
4841 Chars => New_External_Name (Chars (Typ), 'A'));
4843 Append_Freeze_Action (Typ,
4844 Make_Object_Declaration (Loc,
4845 Defining_Identifier => Arr,
4846 Constant_Present => True,
4848 Object_Definition =>
4849 Make_Constrained_Array_Definition (Loc,
4850 Discrete_Subtype_Definitions => New_List (
4851 Make_Subtype_Indication (Loc,
4852 Subtype_Mark => New_Reference_To (Standard_Natural, Loc),
4853 Constraint =>
4854 Make_Range_Constraint (Loc,
4855 Range_Expression =>
4856 Make_Range (Loc,
4857 Low_Bound =>
4858 Make_Integer_Literal (Loc, 0),
4859 High_Bound =>
4860 Make_Integer_Literal (Loc, Num - 1))))),
4862 Component_Definition =>
4863 Make_Component_Definition (Loc,
4864 Aliased_Present => False,
4865 Subtype_Indication => New_Reference_To (Typ, Loc))),
4867 Expression =>
4868 Make_Aggregate (Loc,
4869 Expressions => Lst)));
4871 Set_Enum_Pos_To_Rep (Typ, Arr);
4873 -- Now we build the function that converts representation values to
4874 -- position values. This function has the form:
4876 -- function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
4877 -- begin
4878 -- case ityp!(A) is
4879 -- when enum-lit'Enum_Rep => return posval;
4880 -- when enum-lit'Enum_Rep => return posval;
4881 -- ...
4882 -- when others =>
4883 -- [raise Constraint_Error when F "invalid data"]
4884 -- return -1;
4885 -- end case;
4886 -- end;
4888 -- Note: the F parameter determines whether the others case (no valid
4889 -- representation) raises Constraint_Error or returns a unique value
4890 -- of minus one. The latter case is used, e.g. in 'Valid code.
4892 -- Note: the reason we use Enum_Rep values in the case here is to avoid
4893 -- the code generator making inappropriate assumptions about the range
4894 -- of the values in the case where the value is invalid. ityp is a
4895 -- signed or unsigned integer type of appropriate width.
4897 -- Note: if exceptions are not supported, then we suppress the raise
4898 -- and return -1 unconditionally (this is an erroneous program in any
4899 -- case and there is no obligation to raise Constraint_Error here!) We
4900 -- also do this if pragma Restrictions (No_Exceptions) is active.
4902 -- Is this right??? What about No_Exception_Propagation???
4904 -- Representations are signed
4906 if Enumeration_Rep (First_Literal (Typ)) < 0 then
4908 -- The underlying type is signed. Reset the Is_Unsigned_Type
4909 -- explicitly, because it might have been inherited from
4910 -- parent type.
4912 Set_Is_Unsigned_Type (Typ, False);
4914 if Esize (Typ) <= Standard_Integer_Size then
4915 Ityp := Standard_Integer;
4916 else
4917 Ityp := Universal_Integer;
4918 end if;
4920 -- Representations are unsigned
4922 else
4923 if Esize (Typ) <= Standard_Integer_Size then
4924 Ityp := RTE (RE_Unsigned);
4925 else
4926 Ityp := RTE (RE_Long_Long_Unsigned);
4927 end if;
4928 end if;
4930 -- The body of the function is a case statement. First collect case
4931 -- alternatives, or optimize the contiguous case.
4933 Lst := New_List;
4935 -- If representation is contiguous, Pos is computed by subtracting
4936 -- the representation of the first literal.
4938 if Is_Contiguous then
4939 Ent := First_Literal (Typ);
4941 if Enumeration_Rep (Ent) = Last_Repval then
4943 -- Another special case: for a single literal, Pos is zero
4945 Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
4947 else
4948 Pos_Expr :=
4949 Convert_To (Standard_Integer,
4950 Make_Op_Subtract (Loc,
4951 Left_Opnd =>
4952 Unchecked_Convert_To (Ityp,
4953 Make_Identifier (Loc, Name_uA)),
4954 Right_Opnd =>
4955 Make_Integer_Literal (Loc,
4956 Intval =>
4957 Enumeration_Rep (First_Literal (Typ)))));
4958 end if;
4960 Append_To (Lst,
4961 Make_Case_Statement_Alternative (Loc,
4962 Discrete_Choices => New_List (
4963 Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
4964 Low_Bound =>
4965 Make_Integer_Literal (Loc,
4966 Intval => Enumeration_Rep (Ent)),
4967 High_Bound =>
4968 Make_Integer_Literal (Loc, Intval => Last_Repval))),
4970 Statements => New_List (
4971 Make_Return_Statement (Loc,
4972 Expression => Pos_Expr))));
4974 else
4975 Ent := First_Literal (Typ);
4976 while Present (Ent) loop
4977 Append_To (Lst,
4978 Make_Case_Statement_Alternative (Loc,
4979 Discrete_Choices => New_List (
4980 Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
4981 Intval => Enumeration_Rep (Ent))),
4983 Statements => New_List (
4984 Make_Return_Statement (Loc,
4985 Expression =>
4986 Make_Integer_Literal (Loc,
4987 Intval => Enumeration_Pos (Ent))))));
4989 Next_Literal (Ent);
4990 end loop;
4991 end if;
4993 -- In normal mode, add the others clause with the test
4995 if not No_Exception_Handlers_Set then
4996 Append_To (Lst,
4997 Make_Case_Statement_Alternative (Loc,
4998 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
4999 Statements => New_List (
5000 Make_Raise_Constraint_Error (Loc,
5001 Condition => Make_Identifier (Loc, Name_uF),
5002 Reason => CE_Invalid_Data),
5003 Make_Return_Statement (Loc,
5004 Expression =>
5005 Make_Integer_Literal (Loc, -1)))));
5007 -- If either of the restrictions No_Exceptions_Handlers/Propagation is
5008 -- active then return -1 (we cannot usefully raise Constraint_Error in
5009 -- this case). See description above for further details.
5011 else
5012 Append_To (Lst,
5013 Make_Case_Statement_Alternative (Loc,
5014 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
5015 Statements => New_List (
5016 Make_Return_Statement (Loc,
5017 Expression =>
5018 Make_Integer_Literal (Loc, -1)))));
5019 end if;
5021 -- Now we can build the function body
5023 Fent :=
5024 Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
5026 Func :=
5027 Make_Subprogram_Body (Loc,
5028 Specification =>
5029 Make_Function_Specification (Loc,
5030 Defining_Unit_Name => Fent,
5031 Parameter_Specifications => New_List (
5032 Make_Parameter_Specification (Loc,
5033 Defining_Identifier =>
5034 Make_Defining_Identifier (Loc, Name_uA),
5035 Parameter_Type => New_Reference_To (Typ, Loc)),
5036 Make_Parameter_Specification (Loc,
5037 Defining_Identifier =>
5038 Make_Defining_Identifier (Loc, Name_uF),
5039 Parameter_Type => New_Reference_To (Standard_Boolean, Loc))),
5041 Result_Definition => New_Reference_To (Standard_Integer, Loc)),
5043 Declarations => Empty_List,
5045 Handled_Statement_Sequence =>
5046 Make_Handled_Sequence_Of_Statements (Loc,
5047 Statements => New_List (
5048 Make_Case_Statement (Loc,
5049 Expression =>
5050 Unchecked_Convert_To (Ityp,
5051 Make_Identifier (Loc, Name_uA)),
5052 Alternatives => Lst))));
5054 Set_TSS (Typ, Fent);
5055 Set_Is_Pure (Fent);
5057 if not Debug_Generated_Code then
5058 Set_Debug_Info_Off (Fent);
5059 end if;
5061 exception
5062 when RE_Not_Available =>
5063 return;
5064 end Freeze_Enumeration_Type;
5066 ------------------------
5067 -- Freeze_Record_Type --
5068 ------------------------
5070 procedure Freeze_Record_Type (N : Node_Id) is
5071 Comp : Entity_Id;
5072 Def_Id : constant Node_Id := Entity (N);
5073 Predef_List : List_Id;
5074 Type_Decl : constant Node_Id := Parent (Def_Id);
5076 Renamed_Eq : Node_Id := Empty;
5077 -- Could use some comments ???
5079 Wrapper_Decl_List : List_Id := No_List;
5080 Wrapper_Body_List : List_Id := No_List;
5081 Null_Proc_Decl_List : List_Id := No_List;
5083 begin
5084 -- Build discriminant checking functions if not a derived type (for
5085 -- derived types that are not tagged types, we always use the
5086 -- discriminant checking functions of the parent type). However, for
5087 -- untagged types the derivation may have taken place before the
5088 -- parent was frozen, so we copy explicitly the discriminant checking
5089 -- functions from the parent into the components of the derived type.
5091 if not Is_Derived_Type (Def_Id)
5092 or else Has_New_Non_Standard_Rep (Def_Id)
5093 or else Is_Tagged_Type (Def_Id)
5094 then
5095 Build_Discr_Checking_Funcs (Type_Decl);
5097 elsif Is_Derived_Type (Def_Id)
5098 and then not Is_Tagged_Type (Def_Id)
5100 -- If we have a derived Unchecked_Union, we do not inherit the
5101 -- discriminant checking functions from the parent type since the
5102 -- discriminants are non existent.
5104 and then not Is_Unchecked_Union (Def_Id)
5105 and then Has_Discriminants (Def_Id)
5106 then
5107 declare
5108 Old_Comp : Entity_Id;
5110 begin
5111 Old_Comp :=
5112 First_Component (Base_Type (Underlying_Type (Etype (Def_Id))));
5113 Comp := First_Component (Def_Id);
5114 while Present (Comp) loop
5115 if Ekind (Comp) = E_Component
5116 and then Chars (Comp) = Chars (Old_Comp)
5117 then
5118 Set_Discriminant_Checking_Func (Comp,
5119 Discriminant_Checking_Func (Old_Comp));
5120 end if;
5122 Next_Component (Old_Comp);
5123 Next_Component (Comp);
5124 end loop;
5125 end;
5126 end if;
5128 if Is_Derived_Type (Def_Id)
5129 and then Is_Limited_Type (Def_Id)
5130 and then Is_Tagged_Type (Def_Id)
5131 then
5132 Check_Stream_Attributes (Def_Id);
5133 end if;
5135 -- Update task and controlled component flags, because some of the
5136 -- component types may have been private at the point of the record
5137 -- declaration.
5139 Comp := First_Component (Def_Id);
5141 while Present (Comp) loop
5142 if Has_Task (Etype (Comp)) then
5143 Set_Has_Task (Def_Id);
5145 elsif Has_Controlled_Component (Etype (Comp))
5146 or else (Chars (Comp) /= Name_uParent
5147 and then Is_Controlled (Etype (Comp)))
5148 then
5149 Set_Has_Controlled_Component (Def_Id);
5150 end if;
5152 Next_Component (Comp);
5153 end loop;
5155 -- Creation of the Dispatch Table. Note that a Dispatch Table is built
5156 -- for regular tagged types as well as for Ada types deriving from a C++
5157 -- Class, but not for tagged types directly corresponding to C++ classes
5158 -- In the later case we assume that it is created in the C++ side and we
5159 -- just use it.
5161 if Is_Tagged_Type (Def_Id) then
5163 if Is_CPP_Class (Def_Id) then
5165 -- Because of the new C++ ABI compatibility we now allow the
5166 -- programmer to use the Ada tag (and in this case we must do
5167 -- the normal expansion of the tag)
5169 if Etype (First_Component (Def_Id)) = RTE (RE_Tag)
5170 and then Underlying_Type (Etype (Def_Id)) = Def_Id
5171 then
5172 Expand_Tagged_Root (Def_Id);
5173 end if;
5175 Set_All_DT_Position (Def_Id);
5176 Set_Default_Constructor (Def_Id);
5178 -- With CPP_Class types Make_DT does a minimum decoration of the
5179 -- Access_Disp_Table list.
5181 if VM_Target = No_VM then
5182 Append_Freeze_Actions (Def_Id, Make_DT (Def_Id));
5183 end if;
5185 else
5186 if not Static_Dispatch_Tables then
5188 -- Usually inherited primitives are not delayed but the first
5189 -- Ada extension of a CPP_Class is an exception since the
5190 -- address of the inherited subprogram has to be inserted in
5191 -- the new Ada Dispatch Table and this is a freezing action.
5193 -- Similarly, if this is an inherited operation whose parent is
5194 -- not frozen yet, it is not in the DT of the parent, and we
5195 -- generate an explicit freeze node for the inherited operation
5196 -- so that it is properly inserted in the DT of the current
5197 -- type.
5199 declare
5200 Elmt : Elmt_Id := First_Elmt (Primitive_Operations (Def_Id));
5201 Subp : Entity_Id;
5203 begin
5204 while Present (Elmt) loop
5205 Subp := Node (Elmt);
5207 if Present (Alias (Subp)) then
5208 if Is_CPP_Class (Etype (Def_Id)) then
5209 Set_Has_Delayed_Freeze (Subp);
5211 elsif Has_Delayed_Freeze (Alias (Subp))
5212 and then not Is_Frozen (Alias (Subp))
5213 then
5214 Set_Is_Frozen (Subp, False);
5215 Set_Has_Delayed_Freeze (Subp);
5216 end if;
5217 end if;
5219 Next_Elmt (Elmt);
5220 end loop;
5221 end;
5222 end if;
5224 if Underlying_Type (Etype (Def_Id)) = Def_Id then
5225 Expand_Tagged_Root (Def_Id);
5226 end if;
5228 -- Unfreeze momentarily the type to add the predefined primitives
5229 -- operations. The reason we unfreeze is so that these predefined
5230 -- operations will indeed end up as primitive operations (which
5231 -- must be before the freeze point).
5233 Set_Is_Frozen (Def_Id, False);
5235 -- Do not add the spec of the predefined primitives if we are
5236 -- compiling under restriction No_Dispatching_Calls
5238 if not Restriction_Active (No_Dispatching_Calls) then
5239 Make_Predefined_Primitive_Specs
5240 (Def_Id, Predef_List, Renamed_Eq);
5241 Insert_List_Before_And_Analyze (N, Predef_List);
5242 end if;
5244 -- Ada 2005 (AI-391): For a nonabstract null extension, create
5245 -- wrapper functions for each nonoverridden inherited function
5246 -- with a controlling result of the type. The wrapper for such
5247 -- a function returns an extension aggregate that invokes the
5248 -- the parent function.
5250 if Ada_Version >= Ada_05
5251 and then not Is_Abstract_Type (Def_Id)
5252 and then Is_Null_Extension (Def_Id)
5253 then
5254 Make_Controlling_Function_Wrappers
5255 (Def_Id, Wrapper_Decl_List, Wrapper_Body_List);
5256 Insert_List_Before_And_Analyze (N, Wrapper_Decl_List);
5257 end if;
5259 -- Ada 2005 (AI-251): For a nonabstract type extension, build
5260 -- null procedure declarations for each set of homographic null
5261 -- procedures that are inherited from interface types but not
5262 -- overridden. This is done to ensure that the dispatch table
5263 -- entry associated with such null primitives are properly filled.
5265 if Ada_Version >= Ada_05
5266 and then Etype (Def_Id) /= Def_Id
5267 and then not Is_Abstract_Type (Def_Id)
5268 then
5269 Make_Null_Procedure_Specs (Def_Id, Null_Proc_Decl_List);
5270 Insert_Actions (N, Null_Proc_Decl_List);
5271 end if;
5273 Set_Is_Frozen (Def_Id);
5274 Set_All_DT_Position (Def_Id);
5276 -- Add the controlled component before the freezing actions
5277 -- referenced in those actions.
5279 if Has_New_Controlled_Component (Def_Id) then
5280 Expand_Record_Controller (Def_Id);
5281 end if;
5283 -- Build the dispatch table. Suppress its creation when VM_Target
5284 -- because the dispatching mechanism is handled internally by the
5285 -- VMs.
5287 if VM_Target = No_VM then
5288 Append_Freeze_Actions (Def_Id, Make_DT (Def_Id));
5289 end if;
5291 -- Make sure that the primitives Initialize, Adjust and Finalize
5292 -- are Frozen before other TSS subprograms. We don't want them
5293 -- Frozen inside.
5295 if Is_Controlled (Def_Id) then
5296 if not Is_Limited_Type (Def_Id) then
5297 Append_Freeze_Actions (Def_Id,
5298 Freeze_Entity
5299 (Find_Prim_Op (Def_Id, Name_Adjust), Sloc (Def_Id)));
5300 end if;
5302 Append_Freeze_Actions (Def_Id,
5303 Freeze_Entity
5304 (Find_Prim_Op (Def_Id, Name_Initialize), Sloc (Def_Id)));
5306 Append_Freeze_Actions (Def_Id,
5307 Freeze_Entity
5308 (Find_Prim_Op (Def_Id, Name_Finalize), Sloc (Def_Id)));
5309 end if;
5311 -- Freeze rest of primitive operations. There is no need to handle
5312 -- the predefined primitives if we are compiling under restriction
5313 -- No_Dispatching_Calls
5315 if not Restriction_Active (No_Dispatching_Calls) then
5316 Append_Freeze_Actions
5317 (Def_Id, Predefined_Primitive_Freeze (Def_Id));
5318 end if;
5319 end if;
5321 -- In the non-tagged case, an equality function is provided only for
5322 -- variant records (that are not unchecked unions).
5324 elsif Has_Discriminants (Def_Id)
5325 and then not Is_Limited_Type (Def_Id)
5326 then
5327 declare
5328 Comps : constant Node_Id :=
5329 Component_List (Type_Definition (Type_Decl));
5331 begin
5332 if Present (Comps)
5333 and then Present (Variant_Part (Comps))
5334 then
5335 Build_Variant_Record_Equality (Def_Id);
5336 end if;
5337 end;
5338 end if;
5340 -- Before building the record initialization procedure, if we are
5341 -- dealing with a concurrent record value type, then we must go through
5342 -- the discriminants, exchanging discriminals between the concurrent
5343 -- type and the concurrent record value type. See the section "Handling
5344 -- of Discriminants" in the Einfo spec for details.
5346 if Is_Concurrent_Record_Type (Def_Id)
5347 and then Has_Discriminants (Def_Id)
5348 then
5349 declare
5350 Ctyp : constant Entity_Id :=
5351 Corresponding_Concurrent_Type (Def_Id);
5352 Conc_Discr : Entity_Id;
5353 Rec_Discr : Entity_Id;
5354 Temp : Entity_Id;
5356 begin
5357 Conc_Discr := First_Discriminant (Ctyp);
5358 Rec_Discr := First_Discriminant (Def_Id);
5360 while Present (Conc_Discr) loop
5361 Temp := Discriminal (Conc_Discr);
5362 Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
5363 Set_Discriminal (Rec_Discr, Temp);
5365 Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
5366 Set_Discriminal_Link (Discriminal (Rec_Discr), Rec_Discr);
5368 Next_Discriminant (Conc_Discr);
5369 Next_Discriminant (Rec_Discr);
5370 end loop;
5371 end;
5372 end if;
5374 if Has_Controlled_Component (Def_Id) then
5375 if No (Controller_Component (Def_Id)) then
5376 Expand_Record_Controller (Def_Id);
5377 end if;
5379 Build_Controlling_Procs (Def_Id);
5380 end if;
5382 Adjust_Discriminants (Def_Id);
5384 if VM_Target = No_VM or else not Is_Interface (Def_Id) then
5386 -- Do not need init for interfaces on e.g. CIL since they're
5387 -- abstract. Helps operation of peverify (the PE Verify tool).
5389 Build_Record_Init_Proc (Type_Decl, Def_Id);
5390 end if;
5392 -- For tagged type, build bodies of primitive operations. Note that we
5393 -- do this after building the record initialization experiment, since
5394 -- the primitive operations may need the initialization routine
5396 if Is_Tagged_Type (Def_Id) then
5398 -- Do not add the body of the predefined primitives if we are
5399 -- compiling under restriction No_Dispatching_Calls
5401 if not Restriction_Active (No_Dispatching_Calls) then
5402 Predef_List := Predefined_Primitive_Bodies (Def_Id, Renamed_Eq);
5403 Append_Freeze_Actions (Def_Id, Predef_List);
5404 end if;
5406 -- Ada 2005 (AI-391): If any wrappers were created for nonoverridden
5407 -- inherited functions, then add their bodies to the freeze actions.
5409 if Present (Wrapper_Body_List) then
5410 Append_Freeze_Actions (Def_Id, Wrapper_Body_List);
5411 end if;
5413 -- Populate the two auxiliary tables used for dispatching
5414 -- asynchronous, conditional and timed selects for synchronized
5415 -- types that implement a limited interface.
5417 if Ada_Version >= Ada_05
5418 and then not Restriction_Active (No_Dispatching_Calls)
5419 and then Is_Concurrent_Record_Type (Def_Id)
5420 and then Has_Abstract_Interfaces (Def_Id)
5421 then
5422 Append_Freeze_Actions (Def_Id,
5423 Make_Select_Specific_Data_Table (Def_Id));
5424 end if;
5425 end if;
5426 end Freeze_Record_Type;
5428 ------------------------------
5429 -- Freeze_Stream_Operations --
5430 ------------------------------
5432 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
5433 Names : constant array (1 .. 4) of TSS_Name_Type :=
5434 (TSS_Stream_Input,
5435 TSS_Stream_Output,
5436 TSS_Stream_Read,
5437 TSS_Stream_Write);
5438 Stream_Op : Entity_Id;
5440 begin
5441 -- Primitive operations of tagged types are frozen when the dispatch
5442 -- table is constructed.
5444 if not Comes_From_Source (Typ)
5445 or else Is_Tagged_Type (Typ)
5446 then
5447 return;
5448 end if;
5450 for J in Names'Range loop
5451 Stream_Op := TSS (Typ, Names (J));
5453 if Present (Stream_Op)
5454 and then Is_Subprogram (Stream_Op)
5455 and then Nkind (Unit_Declaration_Node (Stream_Op)) =
5456 N_Subprogram_Declaration
5457 and then not Is_Frozen (Stream_Op)
5458 then
5459 Append_Freeze_Actions
5460 (Typ, Freeze_Entity (Stream_Op, Sloc (N)));
5461 end if;
5462 end loop;
5463 end Freeze_Stream_Operations;
5465 -----------------
5466 -- Freeze_Type --
5467 -----------------
5469 -- Full type declarations are expanded at the point at which the type is
5470 -- frozen. The formal N is the Freeze_Node for the type. Any statements or
5471 -- declarations generated by the freezing (e.g. the procedure generated
5472 -- for initialization) are chained in the Actions field list of the freeze
5473 -- node using Append_Freeze_Actions.
5475 function Freeze_Type (N : Node_Id) return Boolean is
5476 Def_Id : constant Entity_Id := Entity (N);
5477 RACW_Seen : Boolean := False;
5478 Result : Boolean := False;
5480 begin
5481 -- Process associated access types needing special processing
5483 if Present (Access_Types_To_Process (N)) then
5484 declare
5485 E : Elmt_Id := First_Elmt (Access_Types_To_Process (N));
5486 begin
5487 while Present (E) loop
5489 if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
5490 Validate_RACW_Primitives (Node (E));
5491 RACW_Seen := True;
5492 end if;
5494 E := Next_Elmt (E);
5495 end loop;
5496 end;
5498 if RACW_Seen then
5500 -- If there are RACWs designating this type, make stubs now
5502 Remote_Types_Tagged_Full_View_Encountered (Def_Id);
5503 end if;
5504 end if;
5506 -- Freeze processing for record types
5508 if Is_Record_Type (Def_Id) then
5509 if Ekind (Def_Id) = E_Record_Type then
5510 Freeze_Record_Type (N);
5512 -- The subtype may have been declared before the type was frozen. If
5513 -- the type has controlled components it is necessary to create the
5514 -- entity for the controller explicitly because it did not exist at
5515 -- the point of the subtype declaration. Only the entity is needed,
5516 -- the back-end will obtain the layout from the type. This is only
5517 -- necessary if this is constrained subtype whose component list is
5518 -- not shared with the base type.
5520 elsif Ekind (Def_Id) = E_Record_Subtype
5521 and then Has_Discriminants (Def_Id)
5522 and then Last_Entity (Def_Id) /= Last_Entity (Base_Type (Def_Id))
5523 and then Present (Controller_Component (Def_Id))
5524 then
5525 declare
5526 Old_C : constant Entity_Id := Controller_Component (Def_Id);
5527 New_C : Entity_Id;
5529 begin
5530 if Scope (Old_C) = Base_Type (Def_Id) then
5532 -- The entity is the one in the parent. Create new one
5534 New_C := New_Copy (Old_C);
5535 Set_Parent (New_C, Parent (Old_C));
5536 Push_Scope (Def_Id);
5537 Enter_Name (New_C);
5538 End_Scope;
5539 end if;
5540 end;
5542 if Is_Itype (Def_Id)
5543 and then Is_Record_Type (Underlying_Type (Scope (Def_Id)))
5544 then
5545 -- The freeze node is only used to introduce the controller,
5546 -- the back-end has no use for it for a discriminated
5547 -- component.
5549 Set_Freeze_Node (Def_Id, Empty);
5550 Set_Has_Delayed_Freeze (Def_Id, False);
5551 Result := True;
5552 end if;
5554 -- Similar process if the controller of the subtype is not present
5555 -- but the parent has it. This can happen with constrained
5556 -- record components where the subtype is an itype.
5558 elsif Ekind (Def_Id) = E_Record_Subtype
5559 and then Is_Itype (Def_Id)
5560 and then No (Controller_Component (Def_Id))
5561 and then Present (Controller_Component (Etype (Def_Id)))
5562 then
5563 declare
5564 Old_C : constant Entity_Id :=
5565 Controller_Component (Etype (Def_Id));
5566 New_C : constant Entity_Id := New_Copy (Old_C);
5568 begin
5569 Set_Next_Entity (New_C, First_Entity (Def_Id));
5570 Set_First_Entity (Def_Id, New_C);
5572 -- The freeze node is only used to introduce the controller,
5573 -- the back-end has no use for it for a discriminated
5574 -- component.
5576 Set_Freeze_Node (Def_Id, Empty);
5577 Set_Has_Delayed_Freeze (Def_Id, False);
5578 Result := True;
5579 end;
5580 end if;
5582 -- Freeze processing for array types
5584 elsif Is_Array_Type (Def_Id) then
5585 Freeze_Array_Type (N);
5587 -- Freeze processing for access types
5589 -- For pool-specific access types, find out the pool object used for
5590 -- this type, needs actual expansion of it in some cases. Here are the
5591 -- different cases :
5593 -- 1. Rep Clause "for Def_Id'Storage_Size use 0;"
5594 -- ---> don't use any storage pool
5596 -- 2. Rep Clause : for Def_Id'Storage_Size use Expr.
5597 -- Expand:
5598 -- Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
5600 -- 3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
5601 -- ---> Storage Pool is the specified one
5603 -- See GNAT Pool packages in the Run-Time for more details
5605 elsif Ekind (Def_Id) = E_Access_Type
5606 or else Ekind (Def_Id) = E_General_Access_Type
5607 then
5608 declare
5609 Loc : constant Source_Ptr := Sloc (N);
5610 Desig_Type : constant Entity_Id := Designated_Type (Def_Id);
5611 Pool_Object : Entity_Id;
5612 Siz_Exp : Node_Id;
5614 Freeze_Action_Typ : Entity_Id;
5616 begin
5617 if Has_Storage_Size_Clause (Def_Id) then
5618 Siz_Exp := Expression (Parent (Storage_Size_Variable (Def_Id)));
5619 else
5620 Siz_Exp := Empty;
5621 end if;
5623 -- Case 1
5625 -- Rep Clause "for Def_Id'Storage_Size use 0;"
5626 -- ---> don't use any storage pool
5628 if Has_Storage_Size_Clause (Def_Id)
5629 and then Compile_Time_Known_Value (Siz_Exp)
5630 and then Expr_Value (Siz_Exp) = 0
5631 then
5632 null;
5634 -- Case 2
5636 -- Rep Clause : for Def_Id'Storage_Size use Expr.
5637 -- ---> Expand:
5638 -- Def_Id__Pool : Stack_Bounded_Pool
5639 -- (Expr, DT'Size, DT'Alignment);
5641 elsif Has_Storage_Size_Clause (Def_Id) then
5642 declare
5643 DT_Size : Node_Id;
5644 DT_Align : Node_Id;
5646 begin
5647 -- For unconstrained composite types we give a size of zero
5648 -- so that the pool knows that it needs a special algorithm
5649 -- for variable size object allocation.
5651 if Is_Composite_Type (Desig_Type)
5652 and then not Is_Constrained (Desig_Type)
5653 then
5654 DT_Size :=
5655 Make_Integer_Literal (Loc, 0);
5657 DT_Align :=
5658 Make_Integer_Literal (Loc, Maximum_Alignment);
5660 else
5661 DT_Size :=
5662 Make_Attribute_Reference (Loc,
5663 Prefix => New_Reference_To (Desig_Type, Loc),
5664 Attribute_Name => Name_Max_Size_In_Storage_Elements);
5666 DT_Align :=
5667 Make_Attribute_Reference (Loc,
5668 Prefix => New_Reference_To (Desig_Type, Loc),
5669 Attribute_Name => Name_Alignment);
5670 end if;
5672 Pool_Object :=
5673 Make_Defining_Identifier (Loc,
5674 Chars => New_External_Name (Chars (Def_Id), 'P'));
5676 -- We put the code associated with the pools in the entity
5677 -- that has the later freeze node, usually the access type
5678 -- but it can also be the designated_type; because the pool
5679 -- code requires both those types to be frozen
5681 if Is_Frozen (Desig_Type)
5682 and then (No (Freeze_Node (Desig_Type))
5683 or else Analyzed (Freeze_Node (Desig_Type)))
5684 then
5685 Freeze_Action_Typ := Def_Id;
5687 -- A Taft amendment type cannot get the freeze actions
5688 -- since the full view is not there.
5690 elsif Is_Incomplete_Or_Private_Type (Desig_Type)
5691 and then No (Full_View (Desig_Type))
5692 then
5693 Freeze_Action_Typ := Def_Id;
5695 else
5696 Freeze_Action_Typ := Desig_Type;
5697 end if;
5699 Append_Freeze_Action (Freeze_Action_Typ,
5700 Make_Object_Declaration (Loc,
5701 Defining_Identifier => Pool_Object,
5702 Object_Definition =>
5703 Make_Subtype_Indication (Loc,
5704 Subtype_Mark =>
5705 New_Reference_To
5706 (RTE (RE_Stack_Bounded_Pool), Loc),
5708 Constraint =>
5709 Make_Index_Or_Discriminant_Constraint (Loc,
5710 Constraints => New_List (
5712 -- First discriminant is the Pool Size
5714 New_Reference_To (
5715 Storage_Size_Variable (Def_Id), Loc),
5717 -- Second discriminant is the element size
5719 DT_Size,
5721 -- Third discriminant is the alignment
5723 DT_Align)))));
5724 end;
5726 Set_Associated_Storage_Pool (Def_Id, Pool_Object);
5728 -- Case 3
5730 -- Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
5731 -- ---> Storage Pool is the specified one
5733 elsif Present (Associated_Storage_Pool (Def_Id)) then
5735 -- Nothing to do the associated storage pool has been attached
5736 -- when analyzing the rep. clause
5738 null;
5739 end if;
5741 -- For access-to-controlled types (including class-wide types and
5742 -- Taft-amendment types which potentially have controlled
5743 -- components), expand the list controller object that will store
5744 -- the dynamically allocated objects. Do not do this
5745 -- transformation for expander-generated access types, but do it
5746 -- for types that are the full view of types derived from other
5747 -- private types. Also suppress the list controller in the case
5748 -- of a designated type with convention Java, since this is used
5749 -- when binding to Java API specs, where there's no equivalent of
5750 -- a finalization list and we don't want to pull in the
5751 -- finalization support if not needed.
5753 if not Comes_From_Source (Def_Id)
5754 and then not Has_Private_Declaration (Def_Id)
5755 then
5756 null;
5758 elsif (Controlled_Type (Desig_Type)
5759 and then Convention (Desig_Type) /= Convention_Java
5760 and then Convention (Desig_Type) /= Convention_CIL)
5761 or else
5762 (Is_Incomplete_Or_Private_Type (Desig_Type)
5763 and then No (Full_View (Desig_Type))
5765 -- An exception is made for types defined in the run-time
5766 -- because Ada.Tags.Tag itself is such a type and cannot
5767 -- afford this unnecessary overhead that would generates a
5768 -- loop in the expansion scheme...
5770 and then not In_Runtime (Def_Id)
5772 -- Another exception is if Restrictions (No_Finalization)
5773 -- is active, since then we know nothing is controlled.
5775 and then not Restriction_Active (No_Finalization))
5777 -- If the designated type is not frozen yet, its controlled
5778 -- status must be retrieved explicitly.
5780 or else (Is_Array_Type (Desig_Type)
5781 and then not Is_Frozen (Desig_Type)
5782 and then Controlled_Type (Component_Type (Desig_Type)))
5784 -- The designated type has controlled anonymous access
5785 -- discriminants.
5787 or else Has_Controlled_Coextensions (Desig_Type)
5788 then
5789 Set_Associated_Final_Chain (Def_Id,
5790 Make_Defining_Identifier (Loc,
5791 New_External_Name (Chars (Def_Id), 'L')));
5793 Append_Freeze_Action (Def_Id,
5794 Make_Object_Declaration (Loc,
5795 Defining_Identifier => Associated_Final_Chain (Def_Id),
5796 Object_Definition =>
5797 New_Reference_To (RTE (RE_List_Controller), Loc)));
5798 end if;
5799 end;
5801 -- Freeze processing for enumeration types
5803 elsif Ekind (Def_Id) = E_Enumeration_Type then
5805 -- We only have something to do if we have a non-standard
5806 -- representation (i.e. at least one literal whose pos value
5807 -- is not the same as its representation)
5809 if Has_Non_Standard_Rep (Def_Id) then
5810 Freeze_Enumeration_Type (N);
5811 end if;
5813 -- Private types that are completed by a derivation from a private
5814 -- type have an internally generated full view, that needs to be
5815 -- frozen. This must be done explicitly because the two views share
5816 -- the freeze node, and the underlying full view is not visible when
5817 -- the freeze node is analyzed.
5819 elsif Is_Private_Type (Def_Id)
5820 and then Is_Derived_Type (Def_Id)
5821 and then Present (Full_View (Def_Id))
5822 and then Is_Itype (Full_View (Def_Id))
5823 and then Has_Private_Declaration (Full_View (Def_Id))
5824 and then Freeze_Node (Full_View (Def_Id)) = N
5825 then
5826 Set_Entity (N, Full_View (Def_Id));
5827 Result := Freeze_Type (N);
5828 Set_Entity (N, Def_Id);
5830 -- All other types require no expander action. There are such cases
5831 -- (e.g. task types and protected types). In such cases, the freeze
5832 -- nodes are there for use by Gigi.
5834 end if;
5836 Freeze_Stream_Operations (N, Def_Id);
5837 return Result;
5839 exception
5840 when RE_Not_Available =>
5841 return False;
5842 end Freeze_Type;
5844 -------------------------
5845 -- Get_Simple_Init_Val --
5846 -------------------------
5848 function Get_Simple_Init_Val
5849 (T : Entity_Id;
5850 Loc : Source_Ptr;
5851 Size : Uint := No_Uint) return Node_Id
5853 Val : Node_Id;
5854 Result : Node_Id;
5855 Val_RE : RE_Id;
5857 Size_To_Use : Uint;
5858 -- This is the size to be used for computation of the appropriate
5859 -- initial value for the Normalize_Scalars and Initialize_Scalars case.
5861 Lo_Bound : Uint;
5862 Hi_Bound : Uint;
5863 -- These are the values computed by the procedure Check_Subtype_Bounds
5865 procedure Check_Subtype_Bounds;
5866 -- This procedure examines the subtype T, and its ancestor subtypes and
5867 -- derived types to determine the best known information about the
5868 -- bounds of the subtype. After the call Lo_Bound is set either to
5869 -- No_Uint if no information can be determined, or to a value which
5870 -- represents a known low bound, i.e. a valid value of the subtype can
5871 -- not be less than this value. Hi_Bound is similarly set to a known
5872 -- high bound (valid value cannot be greater than this).
5874 --------------------------
5875 -- Check_Subtype_Bounds --
5876 --------------------------
5878 procedure Check_Subtype_Bounds is
5879 ST1 : Entity_Id;
5880 ST2 : Entity_Id;
5881 Lo : Node_Id;
5882 Hi : Node_Id;
5883 Loval : Uint;
5884 Hival : Uint;
5886 begin
5887 Lo_Bound := No_Uint;
5888 Hi_Bound := No_Uint;
5890 -- Loop to climb ancestor subtypes and derived types
5892 ST1 := T;
5893 loop
5894 if not Is_Discrete_Type (ST1) then
5895 return;
5896 end if;
5898 Lo := Type_Low_Bound (ST1);
5899 Hi := Type_High_Bound (ST1);
5901 if Compile_Time_Known_Value (Lo) then
5902 Loval := Expr_Value (Lo);
5904 if Lo_Bound = No_Uint or else Lo_Bound < Loval then
5905 Lo_Bound := Loval;
5906 end if;
5907 end if;
5909 if Compile_Time_Known_Value (Hi) then
5910 Hival := Expr_Value (Hi);
5912 if Hi_Bound = No_Uint or else Hi_Bound > Hival then
5913 Hi_Bound := Hival;
5914 end if;
5915 end if;
5917 ST2 := Ancestor_Subtype (ST1);
5919 if No (ST2) then
5920 ST2 := Etype (ST1);
5921 end if;
5923 exit when ST1 = ST2;
5924 ST1 := ST2;
5925 end loop;
5926 end Check_Subtype_Bounds;
5928 -- Start of processing for Get_Simple_Init_Val
5930 begin
5931 -- For a private type, we should always have an underlying type
5932 -- (because this was already checked in Needs_Simple_Initialization).
5933 -- What we do is to get the value for the underlying type and then do
5934 -- an Unchecked_Convert to the private type.
5936 if Is_Private_Type (T) then
5937 Val := Get_Simple_Init_Val (Underlying_Type (T), Loc, Size);
5939 -- A special case, if the underlying value is null, then qualify it
5940 -- with the underlying type, so that the null is properly typed
5941 -- Similarly, if it is an aggregate it must be qualified, because an
5942 -- unchecked conversion does not provide a context for it.
5944 if Nkind (Val) = N_Null
5945 or else Nkind (Val) = N_Aggregate
5946 then
5947 Val :=
5948 Make_Qualified_Expression (Loc,
5949 Subtype_Mark =>
5950 New_Occurrence_Of (Underlying_Type (T), Loc),
5951 Expression => Val);
5952 end if;
5954 Result := Unchecked_Convert_To (T, Val);
5956 -- Don't truncate result (important for Initialize/Normalize_Scalars)
5958 if Nkind (Result) = N_Unchecked_Type_Conversion
5959 and then Is_Scalar_Type (Underlying_Type (T))
5960 then
5961 Set_No_Truncation (Result);
5962 end if;
5964 return Result;
5966 -- For scalars, we must have normalize/initialize scalars case
5968 elsif Is_Scalar_Type (T) then
5969 pragma Assert (Init_Or_Norm_Scalars);
5971 -- Compute size of object. If it is given by the caller, we can use
5972 -- it directly, otherwise we use Esize (T) as an estimate. As far as
5973 -- we know this covers all cases correctly.
5975 if Size = No_Uint or else Size <= Uint_0 then
5976 Size_To_Use := UI_Max (Uint_1, Esize (T));
5977 else
5978 Size_To_Use := Size;
5979 end if;
5981 -- Maximum size to use is 64 bits, since we will create values
5982 -- of type Unsigned_64 and the range must fit this type.
5984 if Size_To_Use /= No_Uint and then Size_To_Use > Uint_64 then
5985 Size_To_Use := Uint_64;
5986 end if;
5988 -- Check known bounds of subtype
5990 Check_Subtype_Bounds;
5992 -- Processing for Normalize_Scalars case
5994 if Normalize_Scalars then
5996 -- If zero is invalid, it is a convenient value to use that is
5997 -- for sure an appropriate invalid value in all situations.
5999 if Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
6000 Val := Make_Integer_Literal (Loc, 0);
6002 -- Cases where all one bits is the appropriate invalid value
6004 -- For modular types, all 1 bits is either invalid or valid. If
6005 -- it is valid, then there is nothing that can be done since there
6006 -- are no invalid values (we ruled out zero already).
6008 -- For signed integer types that have no negative values, either
6009 -- there is room for negative values, or there is not. If there
6010 -- is, then all 1 bits may be interpreted as minus one, which is
6011 -- certainly invalid. Alternatively it is treated as the largest
6012 -- positive value, in which case the observation for modular types
6013 -- still applies.
6015 -- For float types, all 1-bits is a NaN (not a number), which is
6016 -- certainly an appropriately invalid value.
6018 elsif Is_Unsigned_Type (T)
6019 or else Is_Floating_Point_Type (T)
6020 or else Is_Enumeration_Type (T)
6021 then
6022 Val := Make_Integer_Literal (Loc, 2 ** Size_To_Use - 1);
6024 -- Resolve as Unsigned_64, because the largest number we
6025 -- can generate is out of range of universal integer.
6027 Analyze_And_Resolve (Val, RTE (RE_Unsigned_64));
6029 -- Case of signed types
6031 else
6032 declare
6033 Signed_Size : constant Uint :=
6034 UI_Min (Uint_63, Size_To_Use - 1);
6036 begin
6037 -- Normally we like to use the most negative number. The
6038 -- one exception is when this number is in the known
6039 -- subtype range and the largest positive number is not in
6040 -- the known subtype range.
6042 -- For this exceptional case, use largest positive value
6044 if Lo_Bound /= No_Uint and then Hi_Bound /= No_Uint
6045 and then Lo_Bound <= (-(2 ** Signed_Size))
6046 and then Hi_Bound < 2 ** Signed_Size
6047 then
6048 Val := Make_Integer_Literal (Loc, 2 ** Signed_Size - 1);
6050 -- Normal case of largest negative value
6052 else
6053 Val := Make_Integer_Literal (Loc, -(2 ** Signed_Size));
6054 end if;
6055 end;
6056 end if;
6058 -- Here for Initialize_Scalars case
6060 else
6061 -- For float types, use float values from System.Scalar_Values
6063 if Is_Floating_Point_Type (T) then
6064 if Root_Type (T) = Standard_Short_Float then
6065 Val_RE := RE_IS_Isf;
6066 elsif Root_Type (T) = Standard_Float then
6067 Val_RE := RE_IS_Ifl;
6068 elsif Root_Type (T) = Standard_Long_Float then
6069 Val_RE := RE_IS_Ilf;
6070 else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
6071 Val_RE := RE_IS_Ill;
6072 end if;
6074 -- If zero is invalid, use zero values from System.Scalar_Values
6076 elsif Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
6077 if Size_To_Use <= 8 then
6078 Val_RE := RE_IS_Iz1;
6079 elsif Size_To_Use <= 16 then
6080 Val_RE := RE_IS_Iz2;
6081 elsif Size_To_Use <= 32 then
6082 Val_RE := RE_IS_Iz4;
6083 else
6084 Val_RE := RE_IS_Iz8;
6085 end if;
6087 -- For unsigned, use unsigned values from System.Scalar_Values
6089 elsif Is_Unsigned_Type (T) then
6090 if Size_To_Use <= 8 then
6091 Val_RE := RE_IS_Iu1;
6092 elsif Size_To_Use <= 16 then
6093 Val_RE := RE_IS_Iu2;
6094 elsif Size_To_Use <= 32 then
6095 Val_RE := RE_IS_Iu4;
6096 else
6097 Val_RE := RE_IS_Iu8;
6098 end if;
6100 -- For signed, use signed values from System.Scalar_Values
6102 else
6103 if Size_To_Use <= 8 then
6104 Val_RE := RE_IS_Is1;
6105 elsif Size_To_Use <= 16 then
6106 Val_RE := RE_IS_Is2;
6107 elsif Size_To_Use <= 32 then
6108 Val_RE := RE_IS_Is4;
6109 else
6110 Val_RE := RE_IS_Is8;
6111 end if;
6112 end if;
6114 Val := New_Occurrence_Of (RTE (Val_RE), Loc);
6115 end if;
6117 -- The final expression is obtained by doing an unchecked conversion
6118 -- of this result to the base type of the required subtype. We use
6119 -- the base type to avoid the unchecked conversion from chopping
6120 -- bits, and then we set Kill_Range_Check to preserve the "bad"
6121 -- value.
6123 Result := Unchecked_Convert_To (Base_Type (T), Val);
6125 -- Ensure result is not truncated, since we want the "bad" bits
6126 -- and also kill range check on result.
6128 if Nkind (Result) = N_Unchecked_Type_Conversion then
6129 Set_No_Truncation (Result);
6130 Set_Kill_Range_Check (Result, True);
6131 end if;
6133 return Result;
6135 -- String or Wide_[Wide]_String (must have Initialize_Scalars set)
6137 elsif Root_Type (T) = Standard_String
6138 or else
6139 Root_Type (T) = Standard_Wide_String
6140 or else
6141 Root_Type (T) = Standard_Wide_Wide_String
6142 then
6143 pragma Assert (Init_Or_Norm_Scalars);
6145 return
6146 Make_Aggregate (Loc,
6147 Component_Associations => New_List (
6148 Make_Component_Association (Loc,
6149 Choices => New_List (
6150 Make_Others_Choice (Loc)),
6151 Expression =>
6152 Get_Simple_Init_Val
6153 (Component_Type (T), Loc, Esize (Root_Type (T))))));
6155 -- Access type is initialized to null
6157 elsif Is_Access_Type (T) then
6158 return
6159 Make_Null (Loc);
6161 -- No other possibilities should arise, since we should only be
6162 -- calling Get_Simple_Init_Val if Needs_Simple_Initialization
6163 -- returned True, indicating one of the above cases held.
6165 else
6166 raise Program_Error;
6167 end if;
6169 exception
6170 when RE_Not_Available =>
6171 return Empty;
6172 end Get_Simple_Init_Val;
6174 ------------------------------
6175 -- Has_New_Non_Standard_Rep --
6176 ------------------------------
6178 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
6179 begin
6180 if not Is_Derived_Type (T) then
6181 return Has_Non_Standard_Rep (T)
6182 or else Has_Non_Standard_Rep (Root_Type (T));
6184 -- If Has_Non_Standard_Rep is not set on the derived type, the
6185 -- representation is fully inherited.
6187 elsif not Has_Non_Standard_Rep (T) then
6188 return False;
6190 else
6191 return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
6193 -- May need a more precise check here: the First_Rep_Item may
6194 -- be a stream attribute, which does not affect the representation
6195 -- of the type ???
6196 end if;
6197 end Has_New_Non_Standard_Rep;
6199 ----------------
6200 -- In_Runtime --
6201 ----------------
6203 function In_Runtime (E : Entity_Id) return Boolean is
6204 S1 : Entity_Id;
6206 begin
6207 S1 := Scope (E);
6208 while Scope (S1) /= Standard_Standard loop
6209 S1 := Scope (S1);
6210 end loop;
6212 return Chars (S1) = Name_System or else Chars (S1) = Name_Ada;
6213 end In_Runtime;
6215 ----------------------------
6216 -- Initialization_Warning --
6217 ----------------------------
6219 procedure Initialization_Warning (E : Entity_Id) is
6220 Warning_Needed : Boolean;
6222 begin
6223 Warning_Needed := False;
6225 if Ekind (Current_Scope) = E_Package
6226 and then Static_Elaboration_Desired (Current_Scope)
6227 then
6228 if Is_Type (E) then
6229 if Is_Record_Type (E) then
6230 if Has_Discriminants (E)
6231 or else Is_Limited_Type (E)
6232 or else Has_Non_Standard_Rep (E)
6233 then
6234 Warning_Needed := True;
6236 else
6237 -- Verify that at least one component has an initializtion
6238 -- expression. No need for a warning on a type if all its
6239 -- components have no initialization.
6241 declare
6242 Comp : Entity_Id;
6244 begin
6245 Comp := First_Component (E);
6246 while Present (Comp) loop
6247 if Ekind (Comp) = E_Discriminant
6248 or else
6249 (Nkind (Parent (Comp)) = N_Component_Declaration
6250 and then Present (Expression (Parent (Comp))))
6251 then
6252 Warning_Needed := True;
6253 exit;
6254 end if;
6256 Next_Component (Comp);
6257 end loop;
6258 end;
6259 end if;
6261 if Warning_Needed then
6262 Error_Msg_N
6263 ("Objects of the type cannot be initialized " &
6264 "statically by default?",
6265 Parent (E));
6266 end if;
6267 end if;
6269 else
6270 Error_Msg_N ("Object cannot be initialized statically?", E);
6271 end if;
6272 end if;
6273 end Initialization_Warning;
6275 ------------------
6276 -- Init_Formals --
6277 ------------------
6279 function Init_Formals (Typ : Entity_Id) return List_Id is
6280 Loc : constant Source_Ptr := Sloc (Typ);
6281 Formals : List_Id;
6283 begin
6284 -- First parameter is always _Init : in out typ. Note that we need
6285 -- this to be in/out because in the case of the task record value,
6286 -- there are default record fields (_Priority, _Size, -Task_Info)
6287 -- that may be referenced in the generated initialization routine.
6289 Formals := New_List (
6290 Make_Parameter_Specification (Loc,
6291 Defining_Identifier =>
6292 Make_Defining_Identifier (Loc, Name_uInit),
6293 In_Present => True,
6294 Out_Present => True,
6295 Parameter_Type => New_Reference_To (Typ, Loc)));
6297 -- For task record value, or type that contains tasks, add two more
6298 -- formals, _Master : Master_Id and _Chain : in out Activation_Chain
6299 -- We also add these parameters for the task record type case.
6301 if Has_Task (Typ)
6302 or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
6303 then
6304 Append_To (Formals,
6305 Make_Parameter_Specification (Loc,
6306 Defining_Identifier =>
6307 Make_Defining_Identifier (Loc, Name_uMaster),
6308 Parameter_Type => New_Reference_To (RTE (RE_Master_Id), Loc)));
6310 Append_To (Formals,
6311 Make_Parameter_Specification (Loc,
6312 Defining_Identifier =>
6313 Make_Defining_Identifier (Loc, Name_uChain),
6314 In_Present => True,
6315 Out_Present => True,
6316 Parameter_Type =>
6317 New_Reference_To (RTE (RE_Activation_Chain), Loc)));
6319 Append_To (Formals,
6320 Make_Parameter_Specification (Loc,
6321 Defining_Identifier =>
6322 Make_Defining_Identifier (Loc, Name_uTask_Name),
6323 In_Present => True,
6324 Parameter_Type =>
6325 New_Reference_To (Standard_String, Loc)));
6326 end if;
6328 return Formals;
6330 exception
6331 when RE_Not_Available =>
6332 return Empty_List;
6333 end Init_Formals;
6335 -------------------------
6336 -- Init_Secondary_Tags --
6337 -------------------------
6339 procedure Init_Secondary_Tags
6340 (Typ : Entity_Id;
6341 Target : Node_Id;
6342 Stmts_List : List_Id)
6344 Loc : constant Source_Ptr := Sloc (Target);
6345 ADT : Elmt_Id;
6346 Full_Typ : Entity_Id;
6347 AI_Tag_Comp : Entity_Id;
6349 Is_Synch_Typ : Boolean := False;
6350 -- In case of non concurrent-record-types each parent-type has the
6351 -- tags associated with the interface types that are not implemented
6352 -- by the ancestors; concurrent-record-types have their whole list of
6353 -- interface tags (and this case requires some special management).
6355 procedure Initialize_Tag
6356 (Typ : Entity_Id;
6357 Iface : Entity_Id;
6358 Tag_Comp : in out Entity_Id;
6359 Iface_Tag : Node_Id);
6360 -- Initialize the tag of the secondary dispatch table of Typ associated
6361 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
6363 procedure Init_Secondary_Tags_Internal (Typ : Entity_Id);
6364 -- Internal subprogram used to recursively climb to the root type.
6365 -- We assume that all the primitives of the imported C++ class are
6366 -- defined in the C side.
6368 --------------------
6369 -- Initialize_Tag --
6370 --------------------
6372 procedure Initialize_Tag
6373 (Typ : Entity_Id;
6374 Iface : Entity_Id;
6375 Tag_Comp : in out Entity_Id;
6376 Iface_Tag : Node_Id)
6378 Prev_E : Entity_Id;
6380 begin
6381 -- If we are compiling under the CPP full ABI compatibility mode and
6382 -- the ancestor is a CPP_Pragma tagged type then we generate code to
6383 -- inherit the contents of the dispatch table directly from the
6384 -- ancestor.
6386 if Is_CPP_Class (Etype (Typ)) then
6387 Append_To (Stmts_List,
6388 Build_Inherit_Prims (Loc,
6389 Old_Tag_Node =>
6390 Make_Selected_Component (Loc,
6391 Prefix => New_Copy_Tree (Target),
6392 Selector_Name => New_Reference_To (Tag_Comp, Loc)),
6393 New_Tag_Node =>
6394 New_Reference_To (Iface_Tag, Loc),
6395 Num_Prims =>
6396 UI_To_Int
6397 (DT_Entry_Count (First_Tag_Component (Iface)))));
6398 end if;
6400 -- Initialize the pointer to the secondary DT associated with the
6401 -- interface.
6403 Append_To (Stmts_List,
6404 Make_Assignment_Statement (Loc,
6405 Name =>
6406 Make_Selected_Component (Loc,
6407 Prefix => New_Copy_Tree (Target),
6408 Selector_Name => New_Reference_To (Tag_Comp, Loc)),
6409 Expression =>
6410 New_Reference_To (Iface_Tag, Loc)));
6412 -- If the ancestor is CPP_Class, nothing else to do here
6414 if Is_CPP_Class (Etype (Typ)) then
6415 null;
6417 -- Otherwise, comment required ???
6419 else
6420 -- Issue error if Set_Offset_To_Top is not available in a
6421 -- configurable run-time environment.
6423 if not RTE_Available (RE_Set_Offset_To_Top) then
6424 Error_Msg_CRT ("abstract interface types", Typ);
6425 return;
6426 end if;
6428 -- We generate a different call when the parent of the type has
6429 -- discriminants.
6431 if Typ /= Etype (Typ)
6432 and then Has_Discriminants (Etype (Typ))
6433 then
6434 pragma Assert
6435 (Present (DT_Offset_To_Top_Func (Tag_Comp)));
6437 -- Generate:
6438 -- Set_Offset_To_Top
6439 -- (This => Init,
6440 -- Interface_T => Iface'Tag,
6441 -- Is_Constant => False,
6442 -- Offset_Value => n,
6443 -- Offset_Func => Fn'Address)
6445 Append_To (Stmts_List,
6446 Make_Procedure_Call_Statement (Loc,
6447 Name => New_Reference_To
6448 (RTE (RE_Set_Offset_To_Top), Loc),
6449 Parameter_Associations => New_List (
6450 Make_Attribute_Reference (Loc,
6451 Prefix => New_Copy_Tree (Target),
6452 Attribute_Name => Name_Address),
6454 Unchecked_Convert_To (RTE (RE_Tag),
6455 New_Reference_To
6456 (Node (First_Elmt (Access_Disp_Table (Iface))),
6457 Loc)),
6459 New_Occurrence_Of (Standard_False, Loc),
6461 Unchecked_Convert_To
6462 (RTE (RE_Storage_Offset),
6463 Make_Attribute_Reference (Loc,
6464 Prefix =>
6465 Make_Selected_Component (Loc,
6466 Prefix => New_Copy_Tree (Target),
6467 Selector_Name =>
6468 New_Reference_To (Tag_Comp, Loc)),
6469 Attribute_Name => Name_Position)),
6471 Unchecked_Convert_To (RTE (RE_Offset_To_Top_Function_Ptr),
6472 Make_Attribute_Reference (Loc,
6473 Prefix => New_Reference_To
6474 (DT_Offset_To_Top_Func (Tag_Comp), Loc),
6475 Attribute_Name => Name_Address)))));
6477 -- In this case the next component stores the value of the
6478 -- offset to the top.
6480 Prev_E := Tag_Comp;
6481 Next_Entity (Tag_Comp);
6482 pragma Assert (Present (Tag_Comp));
6484 Append_To (Stmts_List,
6485 Make_Assignment_Statement (Loc,
6486 Name =>
6487 Make_Selected_Component (Loc,
6488 Prefix => New_Copy_Tree (Target),
6489 Selector_Name => New_Reference_To (Tag_Comp, Loc)),
6490 Expression =>
6491 Make_Attribute_Reference (Loc,
6492 Prefix =>
6493 Make_Selected_Component (Loc,
6494 Prefix => New_Copy_Tree (Target),
6495 Selector_Name =>
6496 New_Reference_To (Prev_E, Loc)),
6497 Attribute_Name => Name_Position)));
6499 -- Normal case: No discriminants in the parent type
6501 else
6502 -- Generate:
6503 -- Set_Offset_To_Top
6504 -- (This => Init,
6505 -- Interface_T => Iface'Tag,
6506 -- Is_Constant => True,
6507 -- Offset_Value => n,
6508 -- Offset_Func => null);
6510 Append_To (Stmts_List,
6511 Make_Procedure_Call_Statement (Loc,
6512 Name => New_Reference_To
6513 (RTE (RE_Set_Offset_To_Top), Loc),
6514 Parameter_Associations => New_List (
6515 Make_Attribute_Reference (Loc,
6516 Prefix => New_Copy_Tree (Target),
6517 Attribute_Name => Name_Address),
6519 Unchecked_Convert_To (RTE (RE_Tag),
6520 New_Reference_To
6521 (Node (First_Elmt
6522 (Access_Disp_Table (Iface))),
6523 Loc)),
6525 New_Occurrence_Of (Standard_True, Loc),
6527 Unchecked_Convert_To
6528 (RTE (RE_Storage_Offset),
6529 Make_Attribute_Reference (Loc,
6530 Prefix =>
6531 Make_Selected_Component (Loc,
6532 Prefix => New_Copy_Tree (Target),
6533 Selector_Name =>
6534 New_Reference_To (Tag_Comp, Loc)),
6535 Attribute_Name => Name_Position)),
6537 Make_Null (Loc))));
6538 end if;
6539 end if;
6540 end Initialize_Tag;
6542 ----------------------------------
6543 -- Init_Secondary_Tags_Internal --
6544 ----------------------------------
6546 procedure Init_Secondary_Tags_Internal (Typ : Entity_Id) is
6547 AI_Elmt : Elmt_Id;
6549 begin
6550 -- Climb to the ancestor (if any) handling synchronized interface
6551 -- derivations and private types
6553 if Is_Concurrent_Record_Type (Typ) then
6554 declare
6555 Iface_List : constant List_Id := Abstract_Interface_List (Typ);
6557 begin
6558 if Is_Non_Empty_List (Iface_List) then
6559 Init_Secondary_Tags_Internal (Etype (First (Iface_List)));
6560 end if;
6561 end;
6563 elsif Present (Full_View (Etype (Typ))) then
6564 if Full_View (Etype (Typ)) /= Typ then
6565 Init_Secondary_Tags_Internal (Full_View (Etype (Typ)));
6566 end if;
6568 elsif Etype (Typ) /= Typ then
6569 Init_Secondary_Tags_Internal (Etype (Typ));
6570 end if;
6572 if Is_Interface (Typ) then
6573 -- Generate:
6574 -- Set_Offset_To_Top
6575 -- (This => Init,
6576 -- Interface_T => Iface'Tag,
6577 -- Is_Constant => True,
6578 -- Offset_Value => 0,
6579 -- Offset_Func => null)
6581 Append_To (Stmts_List,
6582 Make_Procedure_Call_Statement (Loc,
6583 Name => New_Reference_To (RTE (RE_Set_Offset_To_Top), Loc),
6584 Parameter_Associations => New_List (
6585 Make_Attribute_Reference (Loc,
6586 Prefix => New_Copy_Tree (Target),
6587 Attribute_Name => Name_Address),
6588 Unchecked_Convert_To (RTE (RE_Tag),
6589 New_Reference_To
6590 (Node (First_Elmt (Access_Disp_Table (Typ))),
6591 Loc)),
6592 New_Occurrence_Of (Standard_True, Loc),
6593 Make_Integer_Literal (Loc, Uint_0),
6594 Make_Null (Loc))));
6595 end if;
6597 if Present (Abstract_Interfaces (Typ))
6598 and then not Is_Empty_Elmt_List (Abstract_Interfaces (Typ))
6599 then
6600 if not Is_Synch_Typ then
6601 AI_Tag_Comp := Next_Tag_Component (First_Tag_Component (Typ));
6602 pragma Assert (Present (AI_Tag_Comp));
6603 end if;
6605 AI_Elmt := First_Elmt (Abstract_Interfaces (Typ));
6606 while Present (AI_Elmt) loop
6607 pragma Assert (Present (Node (ADT)));
6609 Initialize_Tag
6610 (Typ => Typ,
6611 Iface => Node (AI_Elmt),
6612 Tag_Comp => AI_Tag_Comp,
6613 Iface_Tag => Node (ADT));
6615 Next_Elmt (ADT);
6616 AI_Tag_Comp := Next_Tag_Component (AI_Tag_Comp);
6617 Next_Elmt (AI_Elmt);
6618 end loop;
6619 end if;
6620 end Init_Secondary_Tags_Internal;
6622 -- Start of processing for Init_Secondary_Tags
6624 begin
6625 -- Skip the first _Tag, which is the main tag of the tagged type.
6626 -- Following tags correspond with abstract interfaces.
6628 ADT := Next_Elmt (First_Elmt (Access_Disp_Table (Typ)));
6630 -- Handle private types
6632 if Present (Full_View (Typ)) then
6633 Full_Typ := Full_View (Typ);
6634 else
6635 Full_Typ := Typ;
6636 end if;
6638 if Is_Concurrent_Record_Type (Typ) then
6639 Is_Synch_Typ := True;
6640 AI_Tag_Comp := Next_Tag_Component (First_Tag_Component (Typ));
6641 end if;
6643 Init_Secondary_Tags_Internal (Full_Typ);
6644 end Init_Secondary_Tags;
6646 ----------------------------------------
6647 -- Make_Controlling_Function_Wrappers --
6648 ----------------------------------------
6650 procedure Make_Controlling_Function_Wrappers
6651 (Tag_Typ : Entity_Id;
6652 Decl_List : out List_Id;
6653 Body_List : out List_Id)
6655 Loc : constant Source_Ptr := Sloc (Tag_Typ);
6656 Prim_Elmt : Elmt_Id;
6657 Subp : Entity_Id;
6658 Actual_List : List_Id;
6659 Formal_List : List_Id;
6660 Formal : Entity_Id;
6661 Par_Formal : Entity_Id;
6662 Formal_Node : Node_Id;
6663 Func_Spec : Node_Id;
6664 Func_Decl : Node_Id;
6665 Func_Body : Node_Id;
6666 Return_Stmt : Node_Id;
6668 begin
6669 Decl_List := New_List;
6670 Body_List := New_List;
6672 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
6674 while Present (Prim_Elmt) loop
6675 Subp := Node (Prim_Elmt);
6677 -- If a primitive function with a controlling result of the type has
6678 -- not been overridden by the user, then we must create a wrapper
6679 -- function here that effectively overrides it and invokes the
6680 -- (non-abstract) parent function. This can only occur for a null
6681 -- extension. Note that functions with anonymous controlling access
6682 -- results don't qualify and must be overridden. We also exclude
6683 -- Input attributes, since each type will have its own version of
6684 -- Input constructed by the expander. The test for Comes_From_Source
6685 -- is needed to distinguish inherited operations from renamings
6686 -- (which also have Alias set).
6687 -- The function may be abstract, or require_Overriding may be set
6688 -- for it, because tests for null extensions may already have reset
6689 -- the Is_Abstract_Subprogram_Flag.
6691 if (Is_Abstract_Subprogram (Subp)
6692 or else Requires_Overriding (Subp))
6693 and then Present (Alias (Subp))
6694 and then not Is_Abstract_Subprogram (Alias (Subp))
6695 and then not Comes_From_Source (Subp)
6696 and then Ekind (Subp) = E_Function
6697 and then Has_Controlling_Result (Subp)
6698 and then not Is_Access_Type (Etype (Subp))
6699 and then not Is_TSS (Subp, TSS_Stream_Input)
6700 then
6701 Formal_List := No_List;
6702 Formal := First_Formal (Subp);
6704 if Present (Formal) then
6705 Formal_List := New_List;
6707 while Present (Formal) loop
6708 Append
6709 (Make_Parameter_Specification
6710 (Loc,
6711 Defining_Identifier =>
6712 Make_Defining_Identifier (Sloc (Formal),
6713 Chars => Chars (Formal)),
6714 In_Present => In_Present (Parent (Formal)),
6715 Out_Present => Out_Present (Parent (Formal)),
6716 Parameter_Type =>
6717 New_Reference_To (Etype (Formal), Loc),
6718 Expression =>
6719 New_Copy_Tree (Expression (Parent (Formal)))),
6720 Formal_List);
6722 Next_Formal (Formal);
6723 end loop;
6724 end if;
6726 Func_Spec :=
6727 Make_Function_Specification (Loc,
6728 Defining_Unit_Name =>
6729 Make_Defining_Identifier (Loc, Chars (Subp)),
6730 Parameter_Specifications =>
6731 Formal_List,
6732 Result_Definition =>
6733 New_Reference_To (Etype (Subp), Loc));
6735 Func_Decl := Make_Subprogram_Declaration (Loc, Func_Spec);
6736 Append_To (Decl_List, Func_Decl);
6738 -- Build a wrapper body that calls the parent function. The body
6739 -- contains a single return statement that returns an extension
6740 -- aggregate whose ancestor part is a call to the parent function,
6741 -- passing the formals as actuals (with any controlling arguments
6742 -- converted to the types of the corresponding formals of the
6743 -- parent function, which might be anonymous access types), and
6744 -- having a null extension.
6746 Formal := First_Formal (Subp);
6747 Par_Formal := First_Formal (Alias (Subp));
6748 Formal_Node := First (Formal_List);
6750 if Present (Formal) then
6751 Actual_List := New_List;
6752 else
6753 Actual_List := No_List;
6754 end if;
6756 while Present (Formal) loop
6757 if Is_Controlling_Formal (Formal) then
6758 Append_To (Actual_List,
6759 Make_Type_Conversion (Loc,
6760 Subtype_Mark =>
6761 New_Occurrence_Of (Etype (Par_Formal), Loc),
6762 Expression =>
6763 New_Reference_To
6764 (Defining_Identifier (Formal_Node), Loc)));
6765 else
6766 Append_To
6767 (Actual_List,
6768 New_Reference_To
6769 (Defining_Identifier (Formal_Node), Loc));
6770 end if;
6772 Next_Formal (Formal);
6773 Next_Formal (Par_Formal);
6774 Next (Formal_Node);
6775 end loop;
6777 Return_Stmt :=
6778 Make_Return_Statement (Loc,
6779 Expression =>
6780 Make_Extension_Aggregate (Loc,
6781 Ancestor_Part =>
6782 Make_Function_Call (Loc,
6783 Name => New_Reference_To (Alias (Subp), Loc),
6784 Parameter_Associations => Actual_List),
6785 Null_Record_Present => True));
6787 Func_Body :=
6788 Make_Subprogram_Body (Loc,
6789 Specification => New_Copy_Tree (Func_Spec),
6790 Declarations => Empty_List,
6791 Handled_Statement_Sequence =>
6792 Make_Handled_Sequence_Of_Statements (Loc,
6793 Statements => New_List (Return_Stmt)));
6795 Set_Defining_Unit_Name
6796 (Specification (Func_Body),
6797 Make_Defining_Identifier (Loc, Chars (Subp)));
6799 Append_To (Body_List, Func_Body);
6801 -- Replace the inherited function with the wrapper function
6802 -- in the primitive operations list.
6804 Override_Dispatching_Operation
6805 (Tag_Typ, Subp, New_Op => Defining_Unit_Name (Func_Spec));
6806 end if;
6808 Next_Elmt (Prim_Elmt);
6809 end loop;
6810 end Make_Controlling_Function_Wrappers;
6812 ------------------
6813 -- Make_Eq_Case --
6814 ------------------
6816 -- <Make_Eq_if shared components>
6817 -- case X.D1 is
6818 -- when V1 => <Make_Eq_Case> on subcomponents
6819 -- ...
6820 -- when Vn => <Make_Eq_Case> on subcomponents
6821 -- end case;
6823 function Make_Eq_Case
6824 (E : Entity_Id;
6825 CL : Node_Id;
6826 Discr : Entity_Id := Empty) return List_Id
6828 Loc : constant Source_Ptr := Sloc (E);
6829 Result : constant List_Id := New_List;
6830 Variant : Node_Id;
6831 Alt_List : List_Id;
6833 begin
6834 Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
6836 if No (Variant_Part (CL)) then
6837 return Result;
6838 end if;
6840 Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
6842 if No (Variant) then
6843 return Result;
6844 end if;
6846 Alt_List := New_List;
6848 while Present (Variant) loop
6849 Append_To (Alt_List,
6850 Make_Case_Statement_Alternative (Loc,
6851 Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
6852 Statements => Make_Eq_Case (E, Component_List (Variant))));
6854 Next_Non_Pragma (Variant);
6855 end loop;
6857 -- If we have an Unchecked_Union, use one of the parameters that
6858 -- captures the discriminants.
6860 if Is_Unchecked_Union (E) then
6861 Append_To (Result,
6862 Make_Case_Statement (Loc,
6863 Expression => New_Reference_To (Discr, Loc),
6864 Alternatives => Alt_List));
6866 else
6867 Append_To (Result,
6868 Make_Case_Statement (Loc,
6869 Expression =>
6870 Make_Selected_Component (Loc,
6871 Prefix => Make_Identifier (Loc, Name_X),
6872 Selector_Name => New_Copy (Name (Variant_Part (CL)))),
6873 Alternatives => Alt_List));
6874 end if;
6876 return Result;
6877 end Make_Eq_Case;
6879 ----------------
6880 -- Make_Eq_If --
6881 ----------------
6883 -- Generates:
6885 -- if
6886 -- X.C1 /= Y.C1
6887 -- or else
6888 -- X.C2 /= Y.C2
6889 -- ...
6890 -- then
6891 -- return False;
6892 -- end if;
6894 -- or a null statement if the list L is empty
6896 function Make_Eq_If
6897 (E : Entity_Id;
6898 L : List_Id) return Node_Id
6900 Loc : constant Source_Ptr := Sloc (E);
6901 C : Node_Id;
6902 Field_Name : Name_Id;
6903 Cond : Node_Id;
6905 begin
6906 if No (L) then
6907 return Make_Null_Statement (Loc);
6909 else
6910 Cond := Empty;
6912 C := First_Non_Pragma (L);
6913 while Present (C) loop
6914 Field_Name := Chars (Defining_Identifier (C));
6916 -- The tags must not be compared: they are not part of the value.
6917 -- Ditto for the controller component, if present.
6919 -- Note also that in the following, we use Make_Identifier for
6920 -- the component names. Use of New_Reference_To to identify the
6921 -- components would be incorrect because the wrong entities for
6922 -- discriminants could be picked up in the private type case.
6924 if Field_Name /= Name_uTag
6925 and then
6926 Field_Name /= Name_uController
6927 then
6928 Evolve_Or_Else (Cond,
6929 Make_Op_Ne (Loc,
6930 Left_Opnd =>
6931 Make_Selected_Component (Loc,
6932 Prefix => Make_Identifier (Loc, Name_X),
6933 Selector_Name =>
6934 Make_Identifier (Loc, Field_Name)),
6936 Right_Opnd =>
6937 Make_Selected_Component (Loc,
6938 Prefix => Make_Identifier (Loc, Name_Y),
6939 Selector_Name =>
6940 Make_Identifier (Loc, Field_Name))));
6941 end if;
6943 Next_Non_Pragma (C);
6944 end loop;
6946 if No (Cond) then
6947 return Make_Null_Statement (Loc);
6949 else
6950 return
6951 Make_Implicit_If_Statement (E,
6952 Condition => Cond,
6953 Then_Statements => New_List (
6954 Make_Return_Statement (Loc,
6955 Expression => New_Occurrence_Of (Standard_False, Loc))));
6956 end if;
6957 end if;
6958 end Make_Eq_If;
6960 -------------------------------
6961 -- Make_Null_Procedure_Specs --
6962 -------------------------------
6964 procedure Make_Null_Procedure_Specs
6965 (Tag_Typ : Entity_Id;
6966 Decl_List : out List_Id)
6968 Loc : constant Source_Ptr := Sloc (Tag_Typ);
6969 Formal : Entity_Id;
6970 Formal_List : List_Id;
6971 Parent_Subp : Entity_Id;
6972 Prim_Elmt : Elmt_Id;
6973 Proc_Spec : Node_Id;
6974 Proc_Decl : Node_Id;
6975 Subp : Entity_Id;
6977 function Is_Null_Interface_Primitive (E : Entity_Id) return Boolean;
6978 -- Returns True if E is a null procedure that is an interface primitive
6980 ---------------------------------
6981 -- Is_Null_Interface_Primitive --
6982 ---------------------------------
6984 function Is_Null_Interface_Primitive (E : Entity_Id) return Boolean is
6985 begin
6986 return Comes_From_Source (E)
6987 and then Is_Dispatching_Operation (E)
6988 and then Ekind (E) = E_Procedure
6989 and then Null_Present (Parent (E))
6990 and then Is_Interface (Find_Dispatching_Type (E));
6991 end Is_Null_Interface_Primitive;
6993 -- Start of processing for Make_Null_Procedure_Specs
6995 begin
6996 Decl_List := New_List;
6997 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
6998 while Present (Prim_Elmt) loop
6999 Subp := Node (Prim_Elmt);
7001 -- If a null procedure inherited from an interface has not been
7002 -- overridden, then we build a null procedure declaration to
7003 -- override the inherited procedure.
7005 Parent_Subp := Alias (Subp);
7007 if Present (Parent_Subp)
7008 and then Is_Null_Interface_Primitive (Parent_Subp)
7009 then
7010 Formal_List := No_List;
7011 Formal := First_Formal (Subp);
7013 if Present (Formal) then
7014 Formal_List := New_List;
7016 while Present (Formal) loop
7017 Append
7018 (Make_Parameter_Specification (Loc,
7019 Defining_Identifier =>
7020 Make_Defining_Identifier (Sloc (Formal),
7021 Chars => Chars (Formal)),
7022 In_Present => In_Present (Parent (Formal)),
7023 Out_Present => Out_Present (Parent (Formal)),
7024 Parameter_Type =>
7025 New_Reference_To (Etype (Formal), Loc),
7026 Expression =>
7027 New_Copy_Tree (Expression (Parent (Formal)))),
7028 Formal_List);
7030 Next_Formal (Formal);
7031 end loop;
7032 end if;
7034 Proc_Spec :=
7035 Make_Procedure_Specification (Loc,
7036 Defining_Unit_Name =>
7037 Make_Defining_Identifier (Loc, Chars (Subp)),
7038 Parameter_Specifications => Formal_List);
7039 Set_Null_Present (Proc_Spec);
7041 Proc_Decl := Make_Subprogram_Declaration (Loc, Proc_Spec);
7042 Append_To (Decl_List, Proc_Decl);
7043 Analyze (Proc_Decl);
7044 end if;
7046 Next_Elmt (Prim_Elmt);
7047 end loop;
7048 end Make_Null_Procedure_Specs;
7050 -------------------------------------
7051 -- Make_Predefined_Primitive_Specs --
7052 -------------------------------------
7054 procedure Make_Predefined_Primitive_Specs
7055 (Tag_Typ : Entity_Id;
7056 Predef_List : out List_Id;
7057 Renamed_Eq : out Node_Id)
7059 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7060 Res : constant List_Id := New_List;
7061 Prim : Elmt_Id;
7062 Eq_Needed : Boolean;
7063 Eq_Spec : Node_Id;
7064 Eq_Name : Name_Id := Name_Op_Eq;
7066 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
7067 -- Returns true if Prim is a renaming of an unresolved predefined
7068 -- equality operation.
7070 -------------------------------
7071 -- Is_Predefined_Eq_Renaming --
7072 -------------------------------
7074 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
7075 begin
7076 return Chars (Prim) /= Name_Op_Eq
7077 and then Present (Alias (Prim))
7078 and then Comes_From_Source (Prim)
7079 and then Is_Intrinsic_Subprogram (Alias (Prim))
7080 and then Chars (Alias (Prim)) = Name_Op_Eq;
7081 end Is_Predefined_Eq_Renaming;
7083 -- Start of processing for Make_Predefined_Primitive_Specs
7085 begin
7086 Renamed_Eq := Empty;
7088 -- Spec of _Size
7090 Append_To (Res, Predef_Spec_Or_Body (Loc,
7091 Tag_Typ => Tag_Typ,
7092 Name => Name_uSize,
7093 Profile => New_List (
7094 Make_Parameter_Specification (Loc,
7095 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7096 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7098 Ret_Type => Standard_Long_Long_Integer));
7100 -- Spec of _Alignment
7102 Append_To (Res, Predef_Spec_Or_Body (Loc,
7103 Tag_Typ => Tag_Typ,
7104 Name => Name_uAlignment,
7105 Profile => New_List (
7106 Make_Parameter_Specification (Loc,
7107 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7108 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7110 Ret_Type => Standard_Integer));
7112 -- Specs for dispatching stream attributes
7114 declare
7115 Stream_Op_TSS_Names :
7116 constant array (Integer range <>) of TSS_Name_Type :=
7117 (TSS_Stream_Read,
7118 TSS_Stream_Write,
7119 TSS_Stream_Input,
7120 TSS_Stream_Output);
7121 begin
7122 for Op in Stream_Op_TSS_Names'Range loop
7123 if Stream_Operation_OK (Tag_Typ, Stream_Op_TSS_Names (Op)) then
7124 Append_To (Res,
7125 Predef_Stream_Attr_Spec (Loc, Tag_Typ,
7126 Stream_Op_TSS_Names (Op)));
7127 end if;
7128 end loop;
7129 end;
7131 -- Spec of "=" if expanded if the type is not limited and if a
7132 -- user defined "=" was not already declared for the non-full
7133 -- view of a private extension
7135 if not Is_Limited_Type (Tag_Typ) then
7136 Eq_Needed := True;
7138 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
7139 while Present (Prim) loop
7141 -- If a primitive is encountered that renames the predefined
7142 -- equality operator before reaching any explicit equality
7143 -- primitive, then we still need to create a predefined
7144 -- equality function, because calls to it can occur via
7145 -- the renaming. A new name is created for the equality
7146 -- to avoid conflicting with any user-defined equality.
7147 -- (Note that this doesn't account for renamings of
7148 -- equality nested within subpackages???)
7150 if Is_Predefined_Eq_Renaming (Node (Prim)) then
7151 Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
7153 elsif Chars (Node (Prim)) = Name_Op_Eq
7154 and then (No (Alias (Node (Prim)))
7155 or else Nkind (Unit_Declaration_Node (Node (Prim))) =
7156 N_Subprogram_Renaming_Declaration)
7157 and then Etype (First_Formal (Node (Prim))) =
7158 Etype (Next_Formal (First_Formal (Node (Prim))))
7159 and then Base_Type (Etype (Node (Prim))) = Standard_Boolean
7161 then
7162 Eq_Needed := False;
7163 exit;
7165 -- If the parent equality is abstract, the inherited equality is
7166 -- abstract as well, and no body can be created for for it.
7168 elsif Chars (Node (Prim)) = Name_Op_Eq
7169 and then Present (Alias (Node (Prim)))
7170 and then Is_Abstract_Subprogram (Alias (Node (Prim)))
7171 then
7172 Eq_Needed := False;
7173 exit;
7174 end if;
7176 Next_Elmt (Prim);
7177 end loop;
7179 -- If a renaming of predefined equality was found but there was no
7180 -- user-defined equality (so Eq_Needed is still true), then set the
7181 -- name back to Name_Op_Eq. But in the case where a user-defined
7182 -- equality was located after such a renaming, then the predefined
7183 -- equality function is still needed, so Eq_Needed must be set back
7184 -- to True.
7186 if Eq_Name /= Name_Op_Eq then
7187 if Eq_Needed then
7188 Eq_Name := Name_Op_Eq;
7189 else
7190 Eq_Needed := True;
7191 end if;
7192 end if;
7194 if Eq_Needed then
7195 Eq_Spec := Predef_Spec_Or_Body (Loc,
7196 Tag_Typ => Tag_Typ,
7197 Name => Eq_Name,
7198 Profile => New_List (
7199 Make_Parameter_Specification (Loc,
7200 Defining_Identifier =>
7201 Make_Defining_Identifier (Loc, Name_X),
7202 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
7203 Make_Parameter_Specification (Loc,
7204 Defining_Identifier =>
7205 Make_Defining_Identifier (Loc, Name_Y),
7206 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7207 Ret_Type => Standard_Boolean);
7208 Append_To (Res, Eq_Spec);
7210 if Eq_Name /= Name_Op_Eq then
7211 Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
7213 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
7214 while Present (Prim) loop
7216 -- Any renamings of equality that appeared before an
7217 -- overriding equality must be updated to refer to the
7218 -- entity for the predefined equality, otherwise calls via
7219 -- the renaming would get incorrectly resolved to call the
7220 -- user-defined equality function.
7222 if Is_Predefined_Eq_Renaming (Node (Prim)) then
7223 Set_Alias (Node (Prim), Renamed_Eq);
7225 -- Exit upon encountering a user-defined equality
7227 elsif Chars (Node (Prim)) = Name_Op_Eq
7228 and then No (Alias (Node (Prim)))
7229 then
7230 exit;
7231 end if;
7233 Next_Elmt (Prim);
7234 end loop;
7235 end if;
7236 end if;
7238 -- Spec for dispatching assignment
7240 Append_To (Res, Predef_Spec_Or_Body (Loc,
7241 Tag_Typ => Tag_Typ,
7242 Name => Name_uAssign,
7243 Profile => New_List (
7244 Make_Parameter_Specification (Loc,
7245 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7246 Out_Present => True,
7247 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
7249 Make_Parameter_Specification (Loc,
7250 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
7251 Parameter_Type => New_Reference_To (Tag_Typ, Loc)))));
7252 end if;
7254 -- Ada 2005: Generate declarations for the following primitive
7255 -- operations for limited interfaces and synchronized types that
7256 -- implement a limited interface.
7258 -- disp_asynchronous_select
7259 -- disp_conditional_select
7260 -- disp_get_prim_op_kind
7261 -- disp_get_task_id
7262 -- disp_timed_select
7264 -- These operations cannot be implemented on VM targets, so we simply
7265 -- disable their generation in this case. We also disable generation
7266 -- of these bodies if No_Dispatching_Calls is active.
7268 if Ada_Version >= Ada_05
7269 and then VM_Target = No_VM
7270 and then
7271 ((Is_Interface (Tag_Typ) and then Is_Limited_Record (Tag_Typ))
7272 or else (Is_Concurrent_Record_Type (Tag_Typ)
7273 and then Has_Abstract_Interfaces (Tag_Typ)))
7274 then
7275 Append_To (Res,
7276 Make_Subprogram_Declaration (Loc,
7277 Specification =>
7278 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
7280 Append_To (Res,
7281 Make_Subprogram_Declaration (Loc,
7282 Specification =>
7283 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
7285 Append_To (Res,
7286 Make_Subprogram_Declaration (Loc,
7287 Specification =>
7288 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
7290 Append_To (Res,
7291 Make_Subprogram_Declaration (Loc,
7292 Specification =>
7293 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
7295 Append_To (Res,
7296 Make_Subprogram_Declaration (Loc,
7297 Specification =>
7298 Make_Disp_Timed_Select_Spec (Tag_Typ)));
7299 end if;
7301 -- Specs for finalization actions that may be required in case a future
7302 -- extension contain a controlled element. We generate those only for
7303 -- root tagged types where they will get dummy bodies or when the type
7304 -- has controlled components and their body must be generated. It is
7305 -- also impossible to provide those for tagged types defined within
7306 -- s-finimp since it would involve circularity problems
7308 if In_Finalization_Root (Tag_Typ) then
7309 null;
7311 -- We also skip these if finalization is not available
7313 elsif Restriction_Active (No_Finalization) then
7314 null;
7316 elsif Etype (Tag_Typ) = Tag_Typ
7317 or else Controlled_Type (Tag_Typ)
7319 -- Ada 2005 (AI-251): We must also generate these subprograms if
7320 -- the immediate ancestor is an interface to ensure the correct
7321 -- initialization of its dispatch table.
7323 or else (not Is_Interface (Tag_Typ)
7324 and then
7325 Is_Interface (Etype (Tag_Typ)))
7326 then
7327 if not Is_Limited_Type (Tag_Typ) then
7328 Append_To (Res,
7329 Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
7330 end if;
7332 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
7333 end if;
7335 Predef_List := Res;
7336 end Make_Predefined_Primitive_Specs;
7338 ---------------------------------
7339 -- Needs_Simple_Initialization --
7340 ---------------------------------
7342 function Needs_Simple_Initialization (T : Entity_Id) return Boolean is
7343 begin
7344 -- Check for private type, in which case test applies to the underlying
7345 -- type of the private type.
7347 if Is_Private_Type (T) then
7348 declare
7349 RT : constant Entity_Id := Underlying_Type (T);
7351 begin
7352 if Present (RT) then
7353 return Needs_Simple_Initialization (RT);
7354 else
7355 return False;
7356 end if;
7357 end;
7359 -- Cases needing simple initialization are access types, and, if pragma
7360 -- Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
7361 -- types.
7363 elsif Is_Access_Type (T)
7364 or else (Init_Or_Norm_Scalars and then (Is_Scalar_Type (T)))
7365 then
7366 return True;
7368 -- If Initialize/Normalize_Scalars is in effect, string objects also
7369 -- need initialization, unless they are created in the course of
7370 -- expanding an aggregate (since in the latter case they will be
7371 -- filled with appropriate initializing values before they are used).
7373 elsif Init_Or_Norm_Scalars
7374 and then
7375 (Root_Type (T) = Standard_String
7376 or else Root_Type (T) = Standard_Wide_String
7377 or else Root_Type (T) = Standard_Wide_Wide_String)
7378 and then
7379 (not Is_Itype (T)
7380 or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
7381 then
7382 return True;
7384 else
7385 return False;
7386 end if;
7387 end Needs_Simple_Initialization;
7389 ----------------------
7390 -- Predef_Deep_Spec --
7391 ----------------------
7393 function Predef_Deep_Spec
7394 (Loc : Source_Ptr;
7395 Tag_Typ : Entity_Id;
7396 Name : TSS_Name_Type;
7397 For_Body : Boolean := False) return Node_Id
7399 Prof : List_Id;
7400 Type_B : Entity_Id;
7402 begin
7403 if Name = TSS_Deep_Finalize then
7404 Prof := New_List;
7405 Type_B := Standard_Boolean;
7407 else
7408 Prof := New_List (
7409 Make_Parameter_Specification (Loc,
7410 Defining_Identifier => Make_Defining_Identifier (Loc, Name_L),
7411 In_Present => True,
7412 Out_Present => True,
7413 Parameter_Type =>
7414 New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
7415 Type_B := Standard_Short_Short_Integer;
7416 end if;
7418 Append_To (Prof,
7419 Make_Parameter_Specification (Loc,
7420 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
7421 In_Present => True,
7422 Out_Present => True,
7423 Parameter_Type => New_Reference_To (Tag_Typ, Loc)));
7425 Append_To (Prof,
7426 Make_Parameter_Specification (Loc,
7427 Defining_Identifier => Make_Defining_Identifier (Loc, Name_B),
7428 Parameter_Type => New_Reference_To (Type_B, Loc)));
7430 return Predef_Spec_Or_Body (Loc,
7431 Name => Make_TSS_Name (Tag_Typ, Name),
7432 Tag_Typ => Tag_Typ,
7433 Profile => Prof,
7434 For_Body => For_Body);
7436 exception
7437 when RE_Not_Available =>
7438 return Empty;
7439 end Predef_Deep_Spec;
7441 -------------------------
7442 -- Predef_Spec_Or_Body --
7443 -------------------------
7445 function Predef_Spec_Or_Body
7446 (Loc : Source_Ptr;
7447 Tag_Typ : Entity_Id;
7448 Name : Name_Id;
7449 Profile : List_Id;
7450 Ret_Type : Entity_Id := Empty;
7451 For_Body : Boolean := False) return Node_Id
7453 Id : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
7454 Spec : Node_Id;
7456 begin
7457 Set_Is_Public (Id, Is_Public (Tag_Typ));
7459 -- The internal flag is set to mark these declarations because they have
7460 -- specific properties. First, they are primitives even if they are not
7461 -- defined in the type scope (the freezing point is not necessarily in
7462 -- the same scope). Second, the predefined equality can be overridden by
7463 -- a user-defined equality, no body will be generated in this case.
7465 Set_Is_Internal (Id);
7467 if not Debug_Generated_Code then
7468 Set_Debug_Info_Off (Id);
7469 end if;
7471 if No (Ret_Type) then
7472 Spec :=
7473 Make_Procedure_Specification (Loc,
7474 Defining_Unit_Name => Id,
7475 Parameter_Specifications => Profile);
7476 else
7477 Spec :=
7478 Make_Function_Specification (Loc,
7479 Defining_Unit_Name => Id,
7480 Parameter_Specifications => Profile,
7481 Result_Definition =>
7482 New_Reference_To (Ret_Type, Loc));
7483 end if;
7485 -- If body case, return empty subprogram body. Note that this is ill-
7486 -- formed, because there is not even a null statement, and certainly not
7487 -- a return in the function case. The caller is expected to do surgery
7488 -- on the body to add the appropriate stuff.
7490 if For_Body then
7491 return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
7493 -- For the case of Input/Output attributes applied to an abstract type,
7494 -- generate abstract specifications. These will never be called, but we
7495 -- need the slots allocated in the dispatching table so that attributes
7496 -- typ'Class'Input and typ'Class'Output will work properly.
7498 elsif (Is_TSS (Name, TSS_Stream_Input)
7499 or else
7500 Is_TSS (Name, TSS_Stream_Output))
7501 and then Is_Abstract_Type (Tag_Typ)
7502 then
7503 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
7505 -- Normal spec case, where we return a subprogram declaration
7507 else
7508 return Make_Subprogram_Declaration (Loc, Spec);
7509 end if;
7510 end Predef_Spec_Or_Body;
7512 -----------------------------
7513 -- Predef_Stream_Attr_Spec --
7514 -----------------------------
7516 function Predef_Stream_Attr_Spec
7517 (Loc : Source_Ptr;
7518 Tag_Typ : Entity_Id;
7519 Name : TSS_Name_Type;
7520 For_Body : Boolean := False) return Node_Id
7522 Ret_Type : Entity_Id;
7524 begin
7525 if Name = TSS_Stream_Input then
7526 Ret_Type := Tag_Typ;
7527 else
7528 Ret_Type := Empty;
7529 end if;
7531 return Predef_Spec_Or_Body (Loc,
7532 Name => Make_TSS_Name (Tag_Typ, Name),
7533 Tag_Typ => Tag_Typ,
7534 Profile => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
7535 Ret_Type => Ret_Type,
7536 For_Body => For_Body);
7537 end Predef_Stream_Attr_Spec;
7539 ---------------------------------
7540 -- Predefined_Primitive_Bodies --
7541 ---------------------------------
7543 function Predefined_Primitive_Bodies
7544 (Tag_Typ : Entity_Id;
7545 Renamed_Eq : Node_Id) return List_Id
7547 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7548 Res : constant List_Id := New_List;
7549 Decl : Node_Id;
7550 Prim : Elmt_Id;
7551 Eq_Needed : Boolean;
7552 Eq_Name : Name_Id;
7553 Ent : Entity_Id;
7555 begin
7556 -- See if we have a predefined "=" operator
7558 if Present (Renamed_Eq) then
7559 Eq_Needed := True;
7560 Eq_Name := Chars (Renamed_Eq);
7562 else
7563 Eq_Needed := False;
7564 Eq_Name := No_Name;
7566 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
7567 while Present (Prim) loop
7568 if Chars (Node (Prim)) = Name_Op_Eq
7569 and then Is_Internal (Node (Prim))
7570 then
7571 Eq_Needed := True;
7572 Eq_Name := Name_Op_Eq;
7573 end if;
7575 Next_Elmt (Prim);
7576 end loop;
7577 end if;
7579 -- Body of _Alignment
7581 Decl := Predef_Spec_Or_Body (Loc,
7582 Tag_Typ => Tag_Typ,
7583 Name => Name_uAlignment,
7584 Profile => New_List (
7585 Make_Parameter_Specification (Loc,
7586 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7587 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7589 Ret_Type => Standard_Integer,
7590 For_Body => True);
7592 Set_Handled_Statement_Sequence (Decl,
7593 Make_Handled_Sequence_Of_Statements (Loc, New_List (
7594 Make_Return_Statement (Loc,
7595 Expression =>
7596 Make_Attribute_Reference (Loc,
7597 Prefix => Make_Identifier (Loc, Name_X),
7598 Attribute_Name => Name_Alignment)))));
7600 Append_To (Res, Decl);
7602 -- Body of _Size
7604 Decl := Predef_Spec_Or_Body (Loc,
7605 Tag_Typ => Tag_Typ,
7606 Name => Name_uSize,
7607 Profile => New_List (
7608 Make_Parameter_Specification (Loc,
7609 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7610 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7612 Ret_Type => Standard_Long_Long_Integer,
7613 For_Body => True);
7615 Set_Handled_Statement_Sequence (Decl,
7616 Make_Handled_Sequence_Of_Statements (Loc, New_List (
7617 Make_Return_Statement (Loc,
7618 Expression =>
7619 Make_Attribute_Reference (Loc,
7620 Prefix => Make_Identifier (Loc, Name_X),
7621 Attribute_Name => Name_Size)))));
7623 Append_To (Res, Decl);
7625 -- Bodies for Dispatching stream IO routines. We need these only for
7626 -- non-limited types (in the limited case there is no dispatching).
7627 -- We also skip them if dispatching or finalization are not available.
7629 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Read)
7630 and then No (TSS (Tag_Typ, TSS_Stream_Read))
7631 then
7632 Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
7633 Append_To (Res, Decl);
7634 end if;
7636 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Write)
7637 and then No (TSS (Tag_Typ, TSS_Stream_Write))
7638 then
7639 Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
7640 Append_To (Res, Decl);
7641 end if;
7643 -- Skip bodies of _Input and _Output for the abstract case, since the
7644 -- corresponding specs are abstract (see Predef_Spec_Or_Body).
7646 if not Is_Abstract_Type (Tag_Typ) then
7647 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Input)
7648 and then No (TSS (Tag_Typ, TSS_Stream_Input))
7649 then
7650 Build_Record_Or_Elementary_Input_Function
7651 (Loc, Tag_Typ, Decl, Ent);
7652 Append_To (Res, Decl);
7653 end if;
7655 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Output)
7656 and then No (TSS (Tag_Typ, TSS_Stream_Output))
7657 then
7658 Build_Record_Or_Elementary_Output_Procedure
7659 (Loc, Tag_Typ, Decl, Ent);
7660 Append_To (Res, Decl);
7661 end if;
7662 end if;
7664 -- Ada 2005: Generate bodies for the following primitive operations for
7665 -- limited interfaces and synchronized types that implement a limited
7666 -- interface.
7668 -- disp_asynchronous_select
7669 -- disp_conditional_select
7670 -- disp_get_prim_op_kind
7671 -- disp_get_task_id
7672 -- disp_timed_select
7674 -- The interface versions will have null bodies
7676 -- These operations cannot be implemented on VM targets, so we simply
7677 -- disable their generation in this case. We also disable generation
7678 -- of these bodies if No_Dispatching_Calls is active.
7680 if Ada_Version >= Ada_05
7681 and then VM_Target = No_VM
7682 and then not Restriction_Active (No_Dispatching_Calls)
7683 and then
7684 ((Is_Interface (Tag_Typ) and then Is_Limited_Record (Tag_Typ))
7685 or else (Is_Concurrent_Record_Type (Tag_Typ)
7686 and then Has_Abstract_Interfaces (Tag_Typ)))
7687 then
7688 Append_To (Res, Make_Disp_Asynchronous_Select_Body (Tag_Typ));
7689 Append_To (Res, Make_Disp_Conditional_Select_Body (Tag_Typ));
7690 Append_To (Res, Make_Disp_Get_Prim_Op_Kind_Body (Tag_Typ));
7691 Append_To (Res, Make_Disp_Get_Task_Id_Body (Tag_Typ));
7692 Append_To (Res, Make_Disp_Timed_Select_Body (Tag_Typ));
7693 end if;
7695 if not Is_Limited_Type (Tag_Typ) then
7697 -- Body for equality
7699 if Eq_Needed then
7700 Decl :=
7701 Predef_Spec_Or_Body (Loc,
7702 Tag_Typ => Tag_Typ,
7703 Name => Eq_Name,
7704 Profile => New_List (
7705 Make_Parameter_Specification (Loc,
7706 Defining_Identifier =>
7707 Make_Defining_Identifier (Loc, Name_X),
7708 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
7710 Make_Parameter_Specification (Loc,
7711 Defining_Identifier =>
7712 Make_Defining_Identifier (Loc, Name_Y),
7713 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7715 Ret_Type => Standard_Boolean,
7716 For_Body => True);
7718 declare
7719 Def : constant Node_Id := Parent (Tag_Typ);
7720 Stmts : constant List_Id := New_List;
7721 Variant_Case : Boolean := Has_Discriminants (Tag_Typ);
7722 Comps : Node_Id := Empty;
7723 Typ_Def : Node_Id := Type_Definition (Def);
7725 begin
7726 if Variant_Case then
7727 if Nkind (Typ_Def) = N_Derived_Type_Definition then
7728 Typ_Def := Record_Extension_Part (Typ_Def);
7729 end if;
7731 if Present (Typ_Def) then
7732 Comps := Component_List (Typ_Def);
7733 end if;
7735 Variant_Case := Present (Comps)
7736 and then Present (Variant_Part (Comps));
7737 end if;
7739 if Variant_Case then
7740 Append_To (Stmts,
7741 Make_Eq_If (Tag_Typ, Discriminant_Specifications (Def)));
7742 Append_List_To (Stmts, Make_Eq_Case (Tag_Typ, Comps));
7743 Append_To (Stmts,
7744 Make_Return_Statement (Loc,
7745 Expression => New_Reference_To (Standard_True, Loc)));
7747 else
7748 Append_To (Stmts,
7749 Make_Return_Statement (Loc,
7750 Expression =>
7751 Expand_Record_Equality (Tag_Typ,
7752 Typ => Tag_Typ,
7753 Lhs => Make_Identifier (Loc, Name_X),
7754 Rhs => Make_Identifier (Loc, Name_Y),
7755 Bodies => Declarations (Decl))));
7756 end if;
7758 Set_Handled_Statement_Sequence (Decl,
7759 Make_Handled_Sequence_Of_Statements (Loc, Stmts));
7760 end;
7761 Append_To (Res, Decl);
7762 end if;
7764 -- Body for dispatching assignment
7766 Decl :=
7767 Predef_Spec_Or_Body (Loc,
7768 Tag_Typ => Tag_Typ,
7769 Name => Name_uAssign,
7770 Profile => New_List (
7771 Make_Parameter_Specification (Loc,
7772 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
7773 Out_Present => True,
7774 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
7776 Make_Parameter_Specification (Loc,
7777 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
7778 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
7779 For_Body => True);
7781 Set_Handled_Statement_Sequence (Decl,
7782 Make_Handled_Sequence_Of_Statements (Loc, New_List (
7783 Make_Assignment_Statement (Loc,
7784 Name => Make_Identifier (Loc, Name_X),
7785 Expression => Make_Identifier (Loc, Name_Y)))));
7787 Append_To (Res, Decl);
7788 end if;
7790 -- Generate dummy bodies for finalization actions of types that have
7791 -- no controlled components.
7793 -- Skip this processing if we are in the finalization routine in the
7794 -- runtime itself, otherwise we get hopelessly circularly confused!
7796 if In_Finalization_Root (Tag_Typ) then
7797 null;
7799 -- Skip this if finalization is not available
7801 elsif Restriction_Active (No_Finalization) then
7802 null;
7804 elsif (Etype (Tag_Typ) = Tag_Typ
7805 or else Is_Controlled (Tag_Typ)
7807 -- Ada 2005 (AI-251): We must also generate these subprograms
7808 -- if the immediate ancestor of Tag_Typ is an interface to
7809 -- ensure the correct initialization of its dispatch table.
7811 or else (not Is_Interface (Tag_Typ)
7812 and then
7813 Is_Interface (Etype (Tag_Typ))))
7814 and then not Has_Controlled_Component (Tag_Typ)
7815 then
7816 if not Is_Limited_Type (Tag_Typ) then
7817 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
7819 if Is_Controlled (Tag_Typ) then
7820 Set_Handled_Statement_Sequence (Decl,
7821 Make_Handled_Sequence_Of_Statements (Loc,
7822 Make_Adjust_Call (
7823 Ref => Make_Identifier (Loc, Name_V),
7824 Typ => Tag_Typ,
7825 Flist_Ref => Make_Identifier (Loc, Name_L),
7826 With_Attach => Make_Identifier (Loc, Name_B))));
7828 else
7829 Set_Handled_Statement_Sequence (Decl,
7830 Make_Handled_Sequence_Of_Statements (Loc, New_List (
7831 Make_Null_Statement (Loc))));
7832 end if;
7834 Append_To (Res, Decl);
7835 end if;
7837 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
7839 if Is_Controlled (Tag_Typ) then
7840 Set_Handled_Statement_Sequence (Decl,
7841 Make_Handled_Sequence_Of_Statements (Loc,
7842 Make_Final_Call (
7843 Ref => Make_Identifier (Loc, Name_V),
7844 Typ => Tag_Typ,
7845 With_Detach => Make_Identifier (Loc, Name_B))));
7847 else
7848 Set_Handled_Statement_Sequence (Decl,
7849 Make_Handled_Sequence_Of_Statements (Loc, New_List (
7850 Make_Null_Statement (Loc))));
7851 end if;
7853 Append_To (Res, Decl);
7854 end if;
7856 return Res;
7857 end Predefined_Primitive_Bodies;
7859 ---------------------------------
7860 -- Predefined_Primitive_Freeze --
7861 ---------------------------------
7863 function Predefined_Primitive_Freeze
7864 (Tag_Typ : Entity_Id) return List_Id
7866 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7867 Res : constant List_Id := New_List;
7868 Prim : Elmt_Id;
7869 Frnodes : List_Id;
7871 begin
7872 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
7873 while Present (Prim) loop
7874 if Is_Predefined_Dispatching_Operation (Node (Prim)) then
7875 Frnodes := Freeze_Entity (Node (Prim), Loc);
7877 if Present (Frnodes) then
7878 Append_List_To (Res, Frnodes);
7879 end if;
7880 end if;
7882 Next_Elmt (Prim);
7883 end loop;
7885 return Res;
7886 end Predefined_Primitive_Freeze;
7888 -------------------------
7889 -- Stream_Operation_OK --
7890 -------------------------
7892 function Stream_Operation_OK
7893 (Typ : Entity_Id;
7894 Operation : TSS_Name_Type) return Boolean
7896 Has_Inheritable_Stream_Attribute : Boolean := False;
7898 begin
7899 if Is_Limited_Type (Typ)
7900 and then Is_Tagged_Type (Typ)
7901 and then Is_Derived_Type (Typ)
7902 then
7903 -- Special case of a limited type extension: a default implementation
7904 -- of the stream attributes Read and Write exists if the attribute
7905 -- has been specified for an ancestor type.
7907 Has_Inheritable_Stream_Attribute :=
7908 Present (Find_Inherited_TSS (Base_Type (Etype (Typ)), Operation));
7909 end if;
7911 return
7912 not (Is_Limited_Type (Typ)
7913 and then not Has_Inheritable_Stream_Attribute)
7914 and then not Has_Unknown_Discriminants (Typ)
7915 and then not (Is_Interface (Typ)
7916 and then (Is_Task_Interface (Typ)
7917 or else Is_Protected_Interface (Typ)
7918 or else Is_Synchronized_Interface (Typ)))
7919 and then not Restriction_Active (No_Streams)
7920 and then not Restriction_Active (No_Dispatch)
7921 and then not No_Run_Time_Mode
7922 and then RTE_Available (RE_Tag)
7923 and then RTE_Available (RE_Root_Stream_Type);
7924 end Stream_Operation_OK;
7925 end Exp_Ch3;