* gcc.dg/vect/vect-22.c: Require vect_float.
[official-gcc.git] / gcc / ada / exp_ch3.adb
blob4b829214bf759884803553efb9ae29232a616159
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-2005 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_Ch4; use Exp_Ch4;
33 with Exp_Ch7; use Exp_Ch7;
34 with Exp_Ch9; use Exp_Ch9;
35 with Exp_Ch11; use Exp_Ch11;
36 with Exp_Disp; use Exp_Disp;
37 with Exp_Dist; use Exp_Dist;
38 with Exp_Smem; use Exp_Smem;
39 with Exp_Strm; use Exp_Strm;
40 with Exp_Tss; use Exp_Tss;
41 with Exp_Util; use Exp_Util;
42 with Freeze; use Freeze;
43 with Hostparm; use Hostparm;
44 with Nlists; use Nlists;
45 with Nmake; use Nmake;
46 with Opt; use Opt;
47 with Restrict; use Restrict;
48 with Rident; use Rident;
49 with Rtsfind; use Rtsfind;
50 with Sem; use Sem;
51 with Sem_Attr; use Sem_Attr;
52 with Sem_Ch3; use Sem_Ch3;
53 with Sem_Ch8; use Sem_Ch8;
54 with Sem_Eval; use Sem_Eval;
55 with Sem_Mech; use Sem_Mech;
56 with Sem_Res; use Sem_Res;
57 with Sem_Util; use Sem_Util;
58 with Sinfo; use Sinfo;
59 with Stand; use Stand;
60 with Snames; use Snames;
61 with Tbuild; use Tbuild;
62 with Ttypes; use Ttypes;
63 with Validsw; use Validsw;
65 package body Exp_Ch3 is
67 -----------------------
68 -- Local Subprograms --
69 -----------------------
71 procedure Adjust_Discriminants (Rtype : Entity_Id);
72 -- This is used when freezing a record type. It attempts to construct
73 -- more restrictive subtypes for discriminants so that the max size of
74 -- the record can be calculated more accurately. See the body of this
75 -- procedure for details.
77 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id);
78 -- Build initialization procedure for given array type. Nod is a node
79 -- used for attachment of any actions required in its construction.
80 -- It also supplies the source location used for the procedure.
82 procedure Build_Class_Wide_Master (T : Entity_Id);
83 -- for access to class-wide limited types we must build a task master
84 -- because some subsequent extension may add a task component. To avoid
85 -- bringing in the tasking run-time whenever an access-to-class-wide
86 -- limited type is used, we use the soft-link mechanism and add a level
87 -- of indirection to calls to routines that manipulate Master_Ids.
89 function Build_Discriminant_Formals
90 (Rec_Id : Entity_Id;
91 Use_Dl : Boolean) return List_Id;
92 -- This function uses the discriminants of a type to build a list of
93 -- formal parameters, used in the following function. If the flag Use_Dl
94 -- is set, the list is built using the already defined discriminals
95 -- of the type. Otherwise new identifiers are created, with the source
96 -- names of the discriminants.
98 procedure Build_Master_Renaming (N : Node_Id; T : Entity_Id);
99 -- If the designated type of an access type is a task type or contains
100 -- tasks, we make sure that a _Master variable is declared in the current
101 -- scope, and then declare a renaming for it:
103 -- atypeM : Master_Id renames _Master;
105 -- where atyp is the name of the access type. This declaration is
106 -- used when an allocator for the access type is expanded. The node N
107 -- is the full declaration of the designated type that contains tasks.
108 -- The renaming declaration is inserted before N, and after the Master
109 -- declaration.
111 procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id);
112 -- Build record initialization procedure. N is the type declaration
113 -- node, and Pe is the corresponding entity for the record type.
115 procedure Build_Slice_Assignment (Typ : Entity_Id);
116 -- Build assignment procedure for one-dimensional arrays of controlled
117 -- types. Other array and slice assignments are expanded in-line, but
118 -- the code expansion for controlled components (when control actions
119 -- are active) can lead to very large blocks that GCC3 handles poorly.
121 procedure Build_Variant_Record_Equality (Typ : Entity_Id);
122 -- Create An Equality function for the non-tagged variant record 'Typ'
123 -- and attach it to the TSS list
125 procedure Check_Stream_Attributes (Typ : Entity_Id);
126 -- Check that if a limited extension has a parent with user-defined
127 -- stream attributes, and does not itself have user-definer
128 -- stream-attributes, then any limited component of the extension also
129 -- has the corresponding user-defined stream attributes.
131 procedure Expand_Tagged_Root (T : Entity_Id);
132 -- Add a field _Tag at the beginning of the record. This field carries
133 -- the value of the access to the Dispatch table. This procedure is only
134 -- called on root (non CPP_Class) types, the _Tag field being inherited
135 -- by the descendants.
137 procedure Expand_Record_Controller (T : Entity_Id);
138 -- T must be a record type that Has_Controlled_Component. Add a field
139 -- _controller of type Record_Controller or Limited_Record_Controller
140 -- in the record T.
142 procedure Freeze_Array_Type (N : Node_Id);
143 -- Freeze an array type. Deals with building the initialization procedure,
144 -- creating the packed array type for a packed array and also with the
145 -- creation of the controlling procedures for the controlled case. The
146 -- argument N is the N_Freeze_Entity node for the type.
148 procedure Freeze_Enumeration_Type (N : Node_Id);
149 -- Freeze enumeration type with non-standard representation. Builds the
150 -- array and function needed to convert between enumeration pos and
151 -- enumeration representation values. N is the N_Freeze_Entity node
152 -- for the type.
154 procedure Freeze_Record_Type (N : Node_Id);
155 -- Freeze record type. Builds all necessary discriminant checking
156 -- and other ancillary functions, and builds dispatch tables where
157 -- needed. The argument N is the N_Freeze_Entity node. This processing
158 -- applies only to E_Record_Type entities, not to class wide types,
159 -- record subtypes, or private types.
161 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id);
162 -- Treat user-defined stream operations as renaming_as_body if the
163 -- subprogram they rename is not frozen when the type is frozen.
165 function Init_Formals (Typ : Entity_Id) return List_Id;
166 -- This function builds the list of formals for an initialization routine.
167 -- The first formal is always _Init with the given type. For task value
168 -- record types and types containing tasks, three additional formals are
169 -- added:
171 -- _Master : Master_Id
172 -- _Chain : in out Activation_Chain
173 -- _Task_Name : String
175 -- The caller must append additional entries for discriminants if required.
177 function In_Runtime (E : Entity_Id) return Boolean;
178 -- Check if E is defined in the RTL (in a child of Ada or System). Used
179 -- to avoid to bring in the overhead of _Input, _Output for tagged types.
181 function Make_Eq_Case
182 (E : Entity_Id;
183 CL : Node_Id;
184 Discr : Entity_Id := Empty) return List_Id;
185 -- Building block for variant record equality. Defined to share the
186 -- code between the tagged and non-tagged case. Given a Component_List
187 -- node CL, it generates an 'if' followed by a 'case' statement that
188 -- compares all components of local temporaries named X and Y (that
189 -- are declared as formals at some upper level). E provides the Sloc to be
190 -- used for the generated code. Discr is used as the case statement switch
191 -- in the case of Unchecked_Union equality.
193 function Make_Eq_If
194 (E : Entity_Id;
195 L : List_Id) return Node_Id;
196 -- Building block for variant record equality. Defined to share the
197 -- code between the tagged and non-tagged case. Given the list of
198 -- components (or discriminants) L, it generates a return statement
199 -- that compares all components of local temporaries named X and Y
200 -- (that are declared as formals at some upper level). E provides the Sloc
201 -- to be used for the generated code.
203 procedure Make_Predefined_Primitive_Specs
204 (Tag_Typ : Entity_Id;
205 Predef_List : out List_Id;
206 Renamed_Eq : out Node_Id);
207 -- Create a list with the specs of the predefined primitive operations.
208 -- The following entries are present for all tagged types, and provide
209 -- the results of the corresponding attribute applied to the object.
210 -- Dispatching is required in general, since the result of the attribute
211 -- will vary with the actual object subtype.
213 -- _alignment provides result of 'Alignment attribute
214 -- _size provides result of 'Size attribute
215 -- typSR provides result of 'Read attribute
216 -- typSW provides result of 'Write attribute
217 -- typSI provides result of 'Input attribute
218 -- typSO provides result of 'Output attribute
220 -- The following entries are additionally present for non-limited
221 -- tagged types, and implement additional dispatching operations
222 -- for predefined operations:
224 -- _equality implements "=" operator
225 -- _assign implements assignment operation
226 -- typDF implements deep finalization
227 -- typDA implements deep adust
229 -- The latter two are empty procedures unless the type contains some
230 -- controlled components that require finalization actions (the deep
231 -- in the name refers to the fact that the action applies to components).
233 -- The list is returned in Predef_List. The Parameter Renamed_Eq
234 -- either returns the value Empty, or else the defining unit name
235 -- for the predefined equality function in the case where the type
236 -- has a primitive operation that is a renaming of predefined equality
237 -- (but only if there is also an overriding user-defined equality
238 -- function). The returned Renamed_Eq will be passed to the
239 -- corresponding parameter of Predefined_Primitive_Bodies.
241 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean;
242 -- returns True if there are representation clauses for type T that
243 -- are not inherited. If the result is false, the init_proc and the
244 -- discriminant_checking functions of the parent can be reused by
245 -- a derived type.
247 function Predef_Spec_Or_Body
248 (Loc : Source_Ptr;
249 Tag_Typ : Entity_Id;
250 Name : Name_Id;
251 Profile : List_Id;
252 Ret_Type : Entity_Id := Empty;
253 For_Body : Boolean := False) return Node_Id;
254 -- This function generates the appropriate expansion for a predefined
255 -- primitive operation specified by its name, parameter profile and
256 -- return type (Empty means this is a procedure). If For_Body is false,
257 -- then the returned node is a subprogram declaration. If For_Body is
258 -- true, then the returned node is a empty subprogram body containing
259 -- no declarations and no statements.
261 function Predef_Stream_Attr_Spec
262 (Loc : Source_Ptr;
263 Tag_Typ : Entity_Id;
264 Name : TSS_Name_Type;
265 For_Body : Boolean := False) return Node_Id;
266 -- Specialized version of Predef_Spec_Or_Body that apply to read, write,
267 -- input and output attribute whose specs are constructed in Exp_Strm.
269 function Predef_Deep_Spec
270 (Loc : Source_Ptr;
271 Tag_Typ : Entity_Id;
272 Name : TSS_Name_Type;
273 For_Body : Boolean := False) return Node_Id;
274 -- Specialized version of Predef_Spec_Or_Body that apply to _deep_adjust
275 -- and _deep_finalize
277 function Predefined_Primitive_Bodies
278 (Tag_Typ : Entity_Id;
279 Renamed_Eq : Node_Id) return List_Id;
280 -- Create the bodies of the predefined primitives that are described in
281 -- Predefined_Primitive_Specs. When not empty, Renamed_Eq must denote
282 -- the defining unit name of the type's predefined equality as returned
283 -- by Make_Predefined_Primitive_Specs.
285 function Predefined_Primitive_Freeze (Tag_Typ : Entity_Id) return List_Id;
286 -- Freeze entities of all predefined primitive operations. This is needed
287 -- because the bodies of these operations do not normally do any freezeing.
289 function Stream_Operation_OK
290 (Typ : Entity_Id;
291 Operation : TSS_Name_Type) return Boolean;
292 -- Check whether the named stream operation must be emitted for a given
293 -- type. The rules for inheritance of stream attributes by type extensions
294 -- are enforced by this function. Furthermore, various restrictions prevent
295 -- the generation of these operations, as a useful optimization or for
296 -- certification purposes.
298 --------------------------
299 -- Adjust_Discriminants --
300 --------------------------
302 -- This procedure attempts to define subtypes for discriminants that
303 -- are more restrictive than those declared. Such a replacement is
304 -- possible if we can demonstrate that values outside the restricted
305 -- range would cause constraint errors in any case. The advantage of
306 -- restricting the discriminant types in this way is tha the maximum
307 -- size of the variant record can be calculated more conservatively.
309 -- An example of a situation in which we can perform this type of
310 -- restriction is the following:
312 -- subtype B is range 1 .. 10;
313 -- type Q is array (B range <>) of Integer;
315 -- type V (N : Natural) is record
316 -- C : Q (1 .. N);
317 -- end record;
319 -- In this situation, we can restrict the upper bound of N to 10, since
320 -- any larger value would cause a constraint error in any case.
322 -- There are many situations in which such restriction is possible, but
323 -- for now, we just look for cases like the above, where the component
324 -- in question is a one dimensional array whose upper bound is one of
325 -- the record discriminants. Also the component must not be part of
326 -- any variant part, since then the component does not always exist.
328 procedure Adjust_Discriminants (Rtype : Entity_Id) is
329 Loc : constant Source_Ptr := Sloc (Rtype);
330 Comp : Entity_Id;
331 Ctyp : Entity_Id;
332 Ityp : Entity_Id;
333 Lo : Node_Id;
334 Hi : Node_Id;
335 P : Node_Id;
336 Loval : Uint;
337 Discr : Entity_Id;
338 Dtyp : Entity_Id;
339 Dhi : Node_Id;
340 Dhiv : Uint;
341 Ahi : Node_Id;
342 Ahiv : Uint;
343 Tnn : Entity_Id;
345 begin
346 Comp := First_Component (Rtype);
347 while Present (Comp) loop
349 -- If our parent is a variant, quit, we do not look at components
350 -- that are in variant parts, because they may not always exist.
352 P := Parent (Comp); -- component declaration
353 P := Parent (P); -- component list
355 exit when Nkind (Parent (P)) = N_Variant;
357 -- We are looking for a one dimensional array type
359 Ctyp := Etype (Comp);
361 if not Is_Array_Type (Ctyp)
362 or else Number_Dimensions (Ctyp) > 1
363 then
364 goto Continue;
365 end if;
367 -- The lower bound must be constant, and the upper bound is a
368 -- discriminant (which is a discriminant of the current record).
370 Ityp := Etype (First_Index (Ctyp));
371 Lo := Type_Low_Bound (Ityp);
372 Hi := Type_High_Bound (Ityp);
374 if not Compile_Time_Known_Value (Lo)
375 or else Nkind (Hi) /= N_Identifier
376 or else No (Entity (Hi))
377 or else Ekind (Entity (Hi)) /= E_Discriminant
378 then
379 goto Continue;
380 end if;
382 -- We have an array with appropriate bounds
384 Loval := Expr_Value (Lo);
385 Discr := Entity (Hi);
386 Dtyp := Etype (Discr);
388 -- See if the discriminant has a known upper bound
390 Dhi := Type_High_Bound (Dtyp);
392 if not Compile_Time_Known_Value (Dhi) then
393 goto Continue;
394 end if;
396 Dhiv := Expr_Value (Dhi);
398 -- See if base type of component array has known upper bound
400 Ahi := Type_High_Bound (Etype (First_Index (Base_Type (Ctyp))));
402 if not Compile_Time_Known_Value (Ahi) then
403 goto Continue;
404 end if;
406 Ahiv := Expr_Value (Ahi);
408 -- The condition for doing the restriction is that the high bound
409 -- of the discriminant is greater than the low bound of the array,
410 -- and is also greater than the high bound of the base type index.
412 if Dhiv > Loval and then Dhiv > Ahiv then
414 -- We can reset the upper bound of the discriminant type to
415 -- whichever is larger, the low bound of the component, or
416 -- the high bound of the base type array index.
418 -- We build a subtype that is declared as
420 -- subtype Tnn is discr_type range discr_type'First .. max;
422 -- And insert this declaration into the tree. The type of the
423 -- discriminant is then reset to this more restricted subtype.
425 Tnn := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
427 Insert_Action (Declaration_Node (Rtype),
428 Make_Subtype_Declaration (Loc,
429 Defining_Identifier => Tnn,
430 Subtype_Indication =>
431 Make_Subtype_Indication (Loc,
432 Subtype_Mark => New_Occurrence_Of (Dtyp, Loc),
433 Constraint =>
434 Make_Range_Constraint (Loc,
435 Range_Expression =>
436 Make_Range (Loc,
437 Low_Bound =>
438 Make_Attribute_Reference (Loc,
439 Attribute_Name => Name_First,
440 Prefix => New_Occurrence_Of (Dtyp, Loc)),
441 High_Bound =>
442 Make_Integer_Literal (Loc,
443 Intval => UI_Max (Loval, Ahiv)))))));
445 Set_Etype (Discr, Tnn);
446 end if;
448 <<Continue>>
449 Next_Component (Comp);
450 end loop;
451 end Adjust_Discriminants;
453 ---------------------------
454 -- Build_Array_Init_Proc --
455 ---------------------------
457 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id) is
458 Loc : constant Source_Ptr := Sloc (Nod);
459 Comp_Type : constant Entity_Id := Component_Type (A_Type);
460 Index_List : List_Id;
461 Proc_Id : Entity_Id;
462 Body_Stmts : List_Id;
464 function Init_Component return List_Id;
465 -- Create one statement to initialize one array component, designated
466 -- by a full set of indices.
468 function Init_One_Dimension (N : Int) return List_Id;
469 -- Create loop to initialize one dimension of the array. The single
470 -- statement in the loop body initializes the inner dimensions if any,
471 -- or else the single component. Note that this procedure is called
472 -- recursively, with N being the dimension to be initialized. A call
473 -- with N greater than the number of dimensions simply generates the
474 -- component initialization, terminating the recursion.
476 --------------------
477 -- Init_Component --
478 --------------------
480 function Init_Component return List_Id is
481 Comp : Node_Id;
483 begin
484 Comp :=
485 Make_Indexed_Component (Loc,
486 Prefix => Make_Identifier (Loc, Name_uInit),
487 Expressions => Index_List);
489 if Needs_Simple_Initialization (Comp_Type) then
490 Set_Assignment_OK (Comp);
491 return New_List (
492 Make_Assignment_Statement (Loc,
493 Name => Comp,
494 Expression =>
495 Get_Simple_Init_Val
496 (Comp_Type, Loc, Component_Size (A_Type))));
498 else
499 return
500 Build_Initialization_Call (Loc, Comp, Comp_Type, True, A_Type);
501 end if;
502 end Init_Component;
504 ------------------------
505 -- Init_One_Dimension --
506 ------------------------
508 function Init_One_Dimension (N : Int) return List_Id is
509 Index : Entity_Id;
511 begin
512 -- If the component does not need initializing, then there is nothing
513 -- to do here, so we return a null body. This occurs when generating
514 -- the dummy Init_Proc needed for Initialize_Scalars processing.
516 if not Has_Non_Null_Base_Init_Proc (Comp_Type)
517 and then not Needs_Simple_Initialization (Comp_Type)
518 and then not Has_Task (Comp_Type)
519 then
520 return New_List (Make_Null_Statement (Loc));
522 -- If all dimensions dealt with, we simply initialize the component
524 elsif N > Number_Dimensions (A_Type) then
525 return Init_Component;
527 -- Here we generate the required loop
529 else
530 Index :=
531 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
533 Append (New_Reference_To (Index, Loc), Index_List);
535 return New_List (
536 Make_Implicit_Loop_Statement (Nod,
537 Identifier => Empty,
538 Iteration_Scheme =>
539 Make_Iteration_Scheme (Loc,
540 Loop_Parameter_Specification =>
541 Make_Loop_Parameter_Specification (Loc,
542 Defining_Identifier => Index,
543 Discrete_Subtype_Definition =>
544 Make_Attribute_Reference (Loc,
545 Prefix => Make_Identifier (Loc, Name_uInit),
546 Attribute_Name => Name_Range,
547 Expressions => New_List (
548 Make_Integer_Literal (Loc, N))))),
549 Statements => Init_One_Dimension (N + 1)));
550 end if;
551 end Init_One_Dimension;
553 -- Start of processing for Build_Array_Init_Proc
555 begin
556 if Suppress_Init_Proc (A_Type) then
557 return;
558 end if;
560 Index_List := New_List;
562 -- We need an initialization procedure if any of the following is true:
564 -- 1. The component type has an initialization procedure
565 -- 2. The component type needs simple initialization
566 -- 3. Tasks are present
567 -- 4. The type is marked as a publc entity
569 -- The reason for the public entity test is to deal properly with the
570 -- Initialize_Scalars pragma. This pragma can be set in the client and
571 -- not in the declaring package, this means the client will make a call
572 -- to the initialization procedure (because one of conditions 1-3 must
573 -- apply in this case), and we must generate a procedure (even if it is
574 -- null) to satisfy the call in this case.
576 -- Exception: do not build an array init_proc for a type whose root
577 -- type is Standard.String or Standard.Wide_[Wide_]String, since there
578 -- is no place to put the code, and in any case we handle initialization
579 -- of such types (in the Initialize_Scalars case, that's the only time
580 -- the issue arises) in a special manner anyway which does not need an
581 -- init_proc.
583 if Has_Non_Null_Base_Init_Proc (Comp_Type)
584 or else Needs_Simple_Initialization (Comp_Type)
585 or else Has_Task (Comp_Type)
586 or else (not Restriction_Active (No_Initialize_Scalars)
587 and then Is_Public (A_Type)
588 and then Root_Type (A_Type) /= Standard_String
589 and then Root_Type (A_Type) /= Standard_Wide_String
590 and then Root_Type (A_Type) /= Standard_Wide_Wide_String)
591 then
592 Proc_Id :=
593 Make_Defining_Identifier (Loc, Make_Init_Proc_Name (A_Type));
595 Body_Stmts := Init_One_Dimension (1);
597 Discard_Node (
598 Make_Subprogram_Body (Loc,
599 Specification =>
600 Make_Procedure_Specification (Loc,
601 Defining_Unit_Name => Proc_Id,
602 Parameter_Specifications => Init_Formals (A_Type)),
603 Declarations => New_List,
604 Handled_Statement_Sequence =>
605 Make_Handled_Sequence_Of_Statements (Loc,
606 Statements => Body_Stmts)));
608 Set_Ekind (Proc_Id, E_Procedure);
609 Set_Is_Public (Proc_Id, Is_Public (A_Type));
610 Set_Is_Internal (Proc_Id);
611 Set_Has_Completion (Proc_Id);
613 if not Debug_Generated_Code then
614 Set_Debug_Info_Off (Proc_Id);
615 end if;
617 -- Set inlined unless controlled stuff or tasks around, in which
618 -- case we do not want to inline, because nested stuff may cause
619 -- difficulties in interunit inlining, and furthermore there is
620 -- in any case no point in inlining such complex init procs.
622 if not Has_Task (Proc_Id)
623 and then not Controlled_Type (Proc_Id)
624 then
625 Set_Is_Inlined (Proc_Id);
626 end if;
628 -- Associate Init_Proc with type, and determine if the procedure
629 -- is null (happens because of the Initialize_Scalars pragma case,
630 -- where we have to generate a null procedure in case it is called
631 -- by a client with Initialize_Scalars set). Such procedures have
632 -- to be generated, but do not have to be called, so we mark them
633 -- as null to suppress the call.
635 Set_Init_Proc (A_Type, Proc_Id);
637 if List_Length (Body_Stmts) = 1
638 and then Nkind (First (Body_Stmts)) = N_Null_Statement
639 then
640 Set_Is_Null_Init_Proc (Proc_Id);
641 end if;
642 end if;
643 end Build_Array_Init_Proc;
645 -----------------------------
646 -- Build_Class_Wide_Master --
647 -----------------------------
649 procedure Build_Class_Wide_Master (T : Entity_Id) is
650 Loc : constant Source_Ptr := Sloc (T);
651 M_Id : Entity_Id;
652 Decl : Node_Id;
653 P : Node_Id;
655 begin
656 -- Nothing to do if there is no task hierarchy
658 if Restriction_Active (No_Task_Hierarchy) then
659 return;
660 end if;
662 -- Nothing to do if we already built a master entity for this scope
664 if not Has_Master_Entity (Scope (T)) then
666 -- first build the master entity
667 -- _Master : constant Master_Id := Current_Master.all;
668 -- and insert it just before the current declaration
670 Decl :=
671 Make_Object_Declaration (Loc,
672 Defining_Identifier =>
673 Make_Defining_Identifier (Loc, Name_uMaster),
674 Constant_Present => True,
675 Object_Definition => New_Reference_To (Standard_Integer, Loc),
676 Expression =>
677 Make_Explicit_Dereference (Loc,
678 New_Reference_To (RTE (RE_Current_Master), Loc)));
680 P := Parent (T);
681 Insert_Before (P, Decl);
682 Analyze (Decl);
683 Set_Has_Master_Entity (Scope (T));
685 -- Now mark the containing scope as a task master
687 while Nkind (P) /= N_Compilation_Unit loop
688 P := Parent (P);
690 -- If we fall off the top, we are at the outer level, and the
691 -- environment task is our effective master, so nothing to mark.
693 if Nkind (P) = N_Task_Body
694 or else Nkind (P) = N_Block_Statement
695 or else Nkind (P) = N_Subprogram_Body
696 then
697 Set_Is_Task_Master (P, True);
698 exit;
699 end if;
700 end loop;
701 end if;
703 -- Now define the renaming of the master_id
705 M_Id :=
706 Make_Defining_Identifier (Loc,
707 New_External_Name (Chars (T), 'M'));
709 Decl :=
710 Make_Object_Renaming_Declaration (Loc,
711 Defining_Identifier => M_Id,
712 Subtype_Mark => New_Reference_To (Standard_Integer, Loc),
713 Name => Make_Identifier (Loc, Name_uMaster));
714 Insert_Before (Parent (T), Decl);
715 Analyze (Decl);
717 Set_Master_Id (T, M_Id);
719 exception
720 when RE_Not_Available =>
721 return;
722 end Build_Class_Wide_Master;
724 --------------------------------
725 -- Build_Discr_Checking_Funcs --
726 --------------------------------
728 procedure Build_Discr_Checking_Funcs (N : Node_Id) is
729 Rec_Id : Entity_Id;
730 Loc : Source_Ptr;
731 Enclosing_Func_Id : Entity_Id;
732 Sequence : Nat := 1;
733 Type_Def : Node_Id;
734 V : Node_Id;
736 function Build_Case_Statement
737 (Case_Id : Entity_Id;
738 Variant : Node_Id) return Node_Id;
739 -- Build a case statement containing only two alternatives. The
740 -- first alternative corresponds exactly to the discrete choices
741 -- given on the variant with contains the components that we are
742 -- generating the checks for. If the discriminant is one of these
743 -- return False. The second alternative is an OTHERS choice that
744 -- will return True indicating the discriminant did not match.
746 function Build_Dcheck_Function
747 (Case_Id : Entity_Id;
748 Variant : Node_Id) return Entity_Id;
749 -- Build the discriminant checking function for a given variant
751 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id);
752 -- Builds the discriminant checking function for each variant of the
753 -- given variant part of the record type.
755 --------------------------
756 -- Build_Case_Statement --
757 --------------------------
759 function Build_Case_Statement
760 (Case_Id : Entity_Id;
761 Variant : Node_Id) return Node_Id
763 Alt_List : constant List_Id := New_List;
764 Actuals_List : List_Id;
765 Case_Node : Node_Id;
766 Case_Alt_Node : Node_Id;
767 Choice : Node_Id;
768 Choice_List : List_Id;
769 D : Entity_Id;
770 Return_Node : Node_Id;
772 begin
773 Case_Node := New_Node (N_Case_Statement, Loc);
775 -- Replace the discriminant which controls the variant, with the
776 -- name of the formal of the checking function.
778 Set_Expression (Case_Node,
779 Make_Identifier (Loc, Chars (Case_Id)));
781 Choice := First (Discrete_Choices (Variant));
783 if Nkind (Choice) = N_Others_Choice then
784 Choice_List := New_Copy_List (Others_Discrete_Choices (Choice));
785 else
786 Choice_List := New_Copy_List (Discrete_Choices (Variant));
787 end if;
789 if not Is_Empty_List (Choice_List) then
790 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
791 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
793 -- In case this is a nested variant, we need to return the result
794 -- of the discriminant checking function for the immediately
795 -- enclosing variant.
797 if Present (Enclosing_Func_Id) then
798 Actuals_List := New_List;
800 D := First_Discriminant (Rec_Id);
801 while Present (D) loop
802 Append (Make_Identifier (Loc, Chars (D)), Actuals_List);
803 Next_Discriminant (D);
804 end loop;
806 Return_Node :=
807 Make_Return_Statement (Loc,
808 Expression =>
809 Make_Function_Call (Loc,
810 Name =>
811 New_Reference_To (Enclosing_Func_Id, Loc),
812 Parameter_Associations =>
813 Actuals_List));
815 else
816 Return_Node :=
817 Make_Return_Statement (Loc,
818 Expression =>
819 New_Reference_To (Standard_False, Loc));
820 end if;
822 Set_Statements (Case_Alt_Node, New_List (Return_Node));
823 Append (Case_Alt_Node, Alt_List);
824 end if;
826 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
827 Choice_List := New_List (New_Node (N_Others_Choice, Loc));
828 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
830 Return_Node :=
831 Make_Return_Statement (Loc,
832 Expression =>
833 New_Reference_To (Standard_True, Loc));
835 Set_Statements (Case_Alt_Node, New_List (Return_Node));
836 Append (Case_Alt_Node, Alt_List);
838 Set_Alternatives (Case_Node, Alt_List);
839 return Case_Node;
840 end Build_Case_Statement;
842 ---------------------------
843 -- Build_Dcheck_Function --
844 ---------------------------
846 function Build_Dcheck_Function
847 (Case_Id : Entity_Id;
848 Variant : Node_Id) return Entity_Id
850 Body_Node : Node_Id;
851 Func_Id : Entity_Id;
852 Parameter_List : List_Id;
853 Spec_Node : Node_Id;
855 begin
856 Body_Node := New_Node (N_Subprogram_Body, Loc);
857 Sequence := Sequence + 1;
859 Func_Id :=
860 Make_Defining_Identifier (Loc,
861 Chars => New_External_Name (Chars (Rec_Id), 'D', Sequence));
863 Spec_Node := New_Node (N_Function_Specification, Loc);
864 Set_Defining_Unit_Name (Spec_Node, Func_Id);
866 Parameter_List := Build_Discriminant_Formals (Rec_Id, False);
868 Set_Parameter_Specifications (Spec_Node, Parameter_List);
869 Set_Result_Definition (Spec_Node,
870 New_Reference_To (Standard_Boolean, Loc));
871 Set_Specification (Body_Node, Spec_Node);
872 Set_Declarations (Body_Node, New_List);
874 Set_Handled_Statement_Sequence (Body_Node,
875 Make_Handled_Sequence_Of_Statements (Loc,
876 Statements => New_List (
877 Build_Case_Statement (Case_Id, Variant))));
879 Set_Ekind (Func_Id, E_Function);
880 Set_Mechanism (Func_Id, Default_Mechanism);
881 Set_Is_Inlined (Func_Id, True);
882 Set_Is_Pure (Func_Id, True);
883 Set_Is_Public (Func_Id, Is_Public (Rec_Id));
884 Set_Is_Internal (Func_Id, True);
886 if not Debug_Generated_Code then
887 Set_Debug_Info_Off (Func_Id);
888 end if;
890 Analyze (Body_Node);
892 Append_Freeze_Action (Rec_Id, Body_Node);
893 Set_Dcheck_Function (Variant, Func_Id);
894 return Func_Id;
895 end Build_Dcheck_Function;
897 ----------------------------
898 -- Build_Dcheck_Functions --
899 ----------------------------
901 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id) is
902 Component_List_Node : Node_Id;
903 Decl : Entity_Id;
904 Discr_Name : Entity_Id;
905 Func_Id : Entity_Id;
906 Variant : Node_Id;
907 Saved_Enclosing_Func_Id : Entity_Id;
909 begin
910 -- Build the discriminant checking function for each variant, label
911 -- all components of that variant with the function's name.
913 Discr_Name := Entity (Name (Variant_Part_Node));
914 Variant := First_Non_Pragma (Variants (Variant_Part_Node));
916 while Present (Variant) loop
917 Func_Id := Build_Dcheck_Function (Discr_Name, Variant);
918 Component_List_Node := Component_List (Variant);
920 if not Null_Present (Component_List_Node) then
921 Decl :=
922 First_Non_Pragma (Component_Items (Component_List_Node));
924 while Present (Decl) loop
925 Set_Discriminant_Checking_Func
926 (Defining_Identifier (Decl), Func_Id);
928 Next_Non_Pragma (Decl);
929 end loop;
931 if Present (Variant_Part (Component_List_Node)) then
932 Saved_Enclosing_Func_Id := Enclosing_Func_Id;
933 Enclosing_Func_Id := Func_Id;
934 Build_Dcheck_Functions (Variant_Part (Component_List_Node));
935 Enclosing_Func_Id := Saved_Enclosing_Func_Id;
936 end if;
937 end if;
939 Next_Non_Pragma (Variant);
940 end loop;
941 end Build_Dcheck_Functions;
943 -- Start of processing for Build_Discr_Checking_Funcs
945 begin
946 -- Only build if not done already
948 if not Discr_Check_Funcs_Built (N) then
949 Type_Def := Type_Definition (N);
951 if Nkind (Type_Def) = N_Record_Definition then
952 if No (Component_List (Type_Def)) then -- null record.
953 return;
954 else
955 V := Variant_Part (Component_List (Type_Def));
956 end if;
958 else pragma Assert (Nkind (Type_Def) = N_Derived_Type_Definition);
959 if No (Component_List (Record_Extension_Part (Type_Def))) then
960 return;
961 else
962 V := Variant_Part
963 (Component_List (Record_Extension_Part (Type_Def)));
964 end if;
965 end if;
967 Rec_Id := Defining_Identifier (N);
969 if Present (V) and then not Is_Unchecked_Union (Rec_Id) then
970 Loc := Sloc (N);
971 Enclosing_Func_Id := Empty;
972 Build_Dcheck_Functions (V);
973 end if;
975 Set_Discr_Check_Funcs_Built (N);
976 end if;
977 end Build_Discr_Checking_Funcs;
979 --------------------------------
980 -- Build_Discriminant_Formals --
981 --------------------------------
983 function Build_Discriminant_Formals
984 (Rec_Id : Entity_Id;
985 Use_Dl : Boolean) return List_Id
987 Loc : Source_Ptr := Sloc (Rec_Id);
988 Parameter_List : constant List_Id := New_List;
989 D : Entity_Id;
990 Formal : Entity_Id;
991 Param_Spec_Node : Node_Id;
993 begin
994 if Has_Discriminants (Rec_Id) then
995 D := First_Discriminant (Rec_Id);
996 while Present (D) loop
997 Loc := Sloc (D);
999 if Use_Dl then
1000 Formal := Discriminal (D);
1001 else
1002 Formal := Make_Defining_Identifier (Loc, Chars (D));
1003 end if;
1005 Param_Spec_Node :=
1006 Make_Parameter_Specification (Loc,
1007 Defining_Identifier => Formal,
1008 Parameter_Type =>
1009 New_Reference_To (Etype (D), Loc));
1010 Append (Param_Spec_Node, Parameter_List);
1011 Next_Discriminant (D);
1012 end loop;
1013 end if;
1015 return Parameter_List;
1016 end Build_Discriminant_Formals;
1018 -------------------------------
1019 -- Build_Initialization_Call --
1020 -------------------------------
1022 -- References to a discriminant inside the record type declaration
1023 -- can appear either in the subtype_indication to constrain a
1024 -- record or an array, or as part of a larger expression given for
1025 -- the initial value of a component. In both of these cases N appears
1026 -- in the record initialization procedure and needs to be replaced by
1027 -- the formal parameter of the initialization procedure which
1028 -- corresponds to that discriminant.
1030 -- In the example below, references to discriminants D1 and D2 in proc_1
1031 -- are replaced by references to formals with the same name
1032 -- (discriminals)
1034 -- A similar replacement is done for calls to any record
1035 -- initialization procedure for any components that are themselves
1036 -- of a record type.
1038 -- type R (D1, D2 : Integer) is record
1039 -- X : Integer := F * D1;
1040 -- Y : Integer := F * D2;
1041 -- end record;
1043 -- procedure proc_1 (Out_2 : out R; D1 : Integer; D2 : Integer) is
1044 -- begin
1045 -- Out_2.D1 := D1;
1046 -- Out_2.D2 := D2;
1047 -- Out_2.X := F * D1;
1048 -- Out_2.Y := F * D2;
1049 -- end;
1051 function Build_Initialization_Call
1052 (Loc : Source_Ptr;
1053 Id_Ref : Node_Id;
1054 Typ : Entity_Id;
1055 In_Init_Proc : Boolean := False;
1056 Enclos_Type : Entity_Id := Empty;
1057 Discr_Map : Elist_Id := New_Elmt_List;
1058 With_Default_Init : Boolean := False) return List_Id
1060 First_Arg : Node_Id;
1061 Args : List_Id;
1062 Decls : List_Id;
1063 Decl : Node_Id;
1064 Discr : Entity_Id;
1065 Arg : Node_Id;
1066 Proc : constant Entity_Id := Base_Init_Proc (Typ);
1067 Init_Type : constant Entity_Id := Etype (First_Formal (Proc));
1068 Full_Init_Type : constant Entity_Id := Underlying_Type (Init_Type);
1069 Res : constant List_Id := New_List;
1070 Full_Type : Entity_Id := Typ;
1071 Controller_Typ : Entity_Id;
1073 begin
1074 -- Nothing to do if the Init_Proc is null, unless Initialize_Scalars
1075 -- is active (in which case we make the call anyway, since in the
1076 -- actual compiled client it may be non null).
1078 if Is_Null_Init_Proc (Proc) and then not Init_Or_Norm_Scalars then
1079 return Empty_List;
1080 end if;
1082 -- Go to full view if private type. In the case of successive
1083 -- private derivations, this can require more than one step.
1085 while Is_Private_Type (Full_Type)
1086 and then Present (Full_View (Full_Type))
1087 loop
1088 Full_Type := Full_View (Full_Type);
1089 end loop;
1091 -- If Typ is derived, the procedure is the initialization procedure for
1092 -- the root type. Wrap the argument in an conversion to make it type
1093 -- honest. Actually it isn't quite type honest, because there can be
1094 -- conflicts of views in the private type case. That is why we set
1095 -- Conversion_OK in the conversion node.
1096 if (Is_Record_Type (Typ)
1097 or else Is_Array_Type (Typ)
1098 or else Is_Private_Type (Typ))
1099 and then Init_Type /= Base_Type (Typ)
1100 then
1101 First_Arg := OK_Convert_To (Etype (Init_Type), Id_Ref);
1102 Set_Etype (First_Arg, Init_Type);
1104 else
1105 First_Arg := Id_Ref;
1106 end if;
1108 Args := New_List (Convert_Concurrent (First_Arg, Typ));
1110 -- In the tasks case, add _Master as the value of the _Master parameter
1111 -- and _Chain as the value of the _Chain parameter. At the outer level,
1112 -- these will be variables holding the corresponding values obtained
1113 -- from GNARL. At inner levels, they will be the parameters passed down
1114 -- through the outer routines.
1116 if Has_Task (Full_Type) then
1117 if Restriction_Active (No_Task_Hierarchy) then
1119 -- See comments in System.Tasking.Initialization.Init_RTS
1120 -- for the value 3 (should be rtsfindable constant ???)
1122 Append_To (Args, Make_Integer_Literal (Loc, 3));
1123 else
1124 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1125 end if;
1127 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1129 -- Ada 2005 (AI-287): In case of default initialized components
1130 -- with tasks, we generate a null string actual parameter.
1131 -- This is just a workaround that must be improved later???
1133 if With_Default_Init then
1134 Append_To (Args,
1135 Make_String_Literal (Loc,
1136 Strval => ""));
1138 else
1139 Decls := Build_Task_Image_Decls (Loc, Id_Ref, Enclos_Type);
1140 Decl := Last (Decls);
1142 Append_To (Args,
1143 New_Occurrence_Of (Defining_Identifier (Decl), Loc));
1144 Append_List (Decls, Res);
1145 end if;
1147 else
1148 Decls := No_List;
1149 Decl := Empty;
1150 end if;
1152 -- Add discriminant values if discriminants are present
1154 if Has_Discriminants (Full_Init_Type) then
1155 Discr := First_Discriminant (Full_Init_Type);
1157 while Present (Discr) loop
1159 -- If this is a discriminated concurrent type, the init_proc
1160 -- for the corresponding record is being called. Use that
1161 -- type directly to find the discriminant value, to handle
1162 -- properly intervening renamed discriminants.
1164 declare
1165 T : Entity_Id := Full_Type;
1167 begin
1168 if Is_Protected_Type (T) then
1169 T := Corresponding_Record_Type (T);
1171 elsif Is_Private_Type (T)
1172 and then Present (Underlying_Full_View (T))
1173 and then Is_Protected_Type (Underlying_Full_View (T))
1174 then
1175 T := Corresponding_Record_Type (Underlying_Full_View (T));
1176 end if;
1178 Arg :=
1179 Get_Discriminant_Value (
1180 Discr,
1182 Discriminant_Constraint (Full_Type));
1183 end;
1185 if In_Init_Proc then
1187 -- Replace any possible references to the discriminant in the
1188 -- call to the record initialization procedure with references
1189 -- to the appropriate formal parameter.
1191 if Nkind (Arg) = N_Identifier
1192 and then Ekind (Entity (Arg)) = E_Discriminant
1193 then
1194 Arg := New_Reference_To (Discriminal (Entity (Arg)), Loc);
1196 -- Case of access discriminants. We replace the reference
1197 -- to the type by a reference to the actual object
1199 elsif Nkind (Arg) = N_Attribute_Reference
1200 and then Is_Access_Type (Etype (Arg))
1201 and then Is_Entity_Name (Prefix (Arg))
1202 and then Is_Type (Entity (Prefix (Arg)))
1203 then
1204 Arg :=
1205 Make_Attribute_Reference (Loc,
1206 Prefix => New_Copy (Prefix (Id_Ref)),
1207 Attribute_Name => Name_Unrestricted_Access);
1209 -- Otherwise make a copy of the default expression. Note
1210 -- that we use the current Sloc for this, because we do not
1211 -- want the call to appear to be at the declaration point.
1212 -- Within the expression, replace discriminants with their
1213 -- discriminals.
1215 else
1216 Arg :=
1217 New_Copy_Tree (Arg, Map => Discr_Map, New_Sloc => Loc);
1218 end if;
1220 else
1221 if Is_Constrained (Full_Type) then
1222 Arg := Duplicate_Subexpr_No_Checks (Arg);
1223 else
1224 -- The constraints come from the discriminant default
1225 -- exps, they must be reevaluated, so we use New_Copy_Tree
1226 -- but we ensure the proper Sloc (for any embedded calls).
1228 Arg := New_Copy_Tree (Arg, New_Sloc => Loc);
1229 end if;
1230 end if;
1232 -- Ada 2005 (AI-287) In case of default initialized components,
1233 -- we need to generate the corresponding selected component node
1234 -- to access the discriminant value. In other cases this is not
1235 -- required because we are inside the init proc and we use the
1236 -- corresponding formal.
1238 if With_Default_Init
1239 and then Nkind (Id_Ref) = N_Selected_Component
1240 then
1241 Append_To (Args,
1242 Make_Selected_Component (Loc,
1243 Prefix => New_Copy_Tree (Prefix (Id_Ref)),
1244 Selector_Name => Arg));
1245 else
1246 Append_To (Args, Arg);
1247 end if;
1249 Next_Discriminant (Discr);
1250 end loop;
1251 end if;
1253 -- If this is a call to initialize the parent component of a derived
1254 -- tagged type, indicate that the tag should not be set in the parent.
1256 if Is_Tagged_Type (Full_Init_Type)
1257 and then not Is_CPP_Class (Full_Init_Type)
1258 and then Nkind (Id_Ref) = N_Selected_Component
1259 and then Chars (Selector_Name (Id_Ref)) = Name_uParent
1260 then
1261 Append_To (Args, New_Occurrence_Of (Standard_False, Loc));
1262 end if;
1264 Append_To (Res,
1265 Make_Procedure_Call_Statement (Loc,
1266 Name => New_Occurrence_Of (Proc, Loc),
1267 Parameter_Associations => Args));
1269 if Controlled_Type (Typ)
1270 and then Nkind (Id_Ref) = N_Selected_Component
1271 then
1272 if Chars (Selector_Name (Id_Ref)) /= Name_uParent then
1273 Append_List_To (Res,
1274 Make_Init_Call (
1275 Ref => New_Copy_Tree (First_Arg),
1276 Typ => Typ,
1277 Flist_Ref =>
1278 Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1279 With_Attach => Make_Integer_Literal (Loc, 1)));
1281 -- If the enclosing type is an extension with new controlled
1282 -- components, it has his own record controller. If the parent
1283 -- also had a record controller, attach it to the new one.
1284 -- Build_Init_Statements relies on the fact that in this specific
1285 -- case the last statement of the result is the attach call to
1286 -- the controller. If this is changed, it must be synchronized.
1288 elsif Present (Enclos_Type)
1289 and then Has_New_Controlled_Component (Enclos_Type)
1290 and then Has_Controlled_Component (Typ)
1291 then
1292 if Is_Return_By_Reference_Type (Typ) then
1293 Controller_Typ := RTE (RE_Limited_Record_Controller);
1294 else
1295 Controller_Typ := RTE (RE_Record_Controller);
1296 end if;
1298 Append_List_To (Res,
1299 Make_Init_Call (
1300 Ref =>
1301 Make_Selected_Component (Loc,
1302 Prefix => New_Copy_Tree (First_Arg),
1303 Selector_Name => Make_Identifier (Loc, Name_uController)),
1304 Typ => Controller_Typ,
1305 Flist_Ref => Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1306 With_Attach => Make_Integer_Literal (Loc, 1)));
1307 end if;
1308 end if;
1310 return Res;
1312 exception
1313 when RE_Not_Available =>
1314 return Empty_List;
1315 end Build_Initialization_Call;
1317 ---------------------------
1318 -- Build_Master_Renaming --
1319 ---------------------------
1321 procedure Build_Master_Renaming (N : Node_Id; T : Entity_Id) is
1322 Loc : constant Source_Ptr := Sloc (N);
1323 M_Id : Entity_Id;
1324 Decl : Node_Id;
1326 begin
1327 -- Nothing to do if there is no task hierarchy
1329 if Restriction_Active (No_Task_Hierarchy) then
1330 return;
1331 end if;
1333 M_Id :=
1334 Make_Defining_Identifier (Loc,
1335 New_External_Name (Chars (T), 'M'));
1337 Decl :=
1338 Make_Object_Renaming_Declaration (Loc,
1339 Defining_Identifier => M_Id,
1340 Subtype_Mark => New_Reference_To (RTE (RE_Master_Id), Loc),
1341 Name => Make_Identifier (Loc, Name_uMaster));
1342 Insert_Before (N, Decl);
1343 Analyze (Decl);
1345 Set_Master_Id (T, M_Id);
1347 exception
1348 when RE_Not_Available =>
1349 return;
1350 end Build_Master_Renaming;
1352 ----------------------------
1353 -- Build_Record_Init_Proc --
1354 ----------------------------
1356 procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id) is
1357 Loc : Source_Ptr := Sloc (N);
1358 Discr_Map : constant Elist_Id := New_Elmt_List;
1359 Proc_Id : Entity_Id;
1360 Rec_Type : Entity_Id;
1361 Set_Tag : Entity_Id := Empty;
1363 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id;
1364 -- Build a assignment statement node which assigns to record
1365 -- component its default expression if defined. The left hand side
1366 -- of the assignment is marked Assignment_OK so that initialization
1367 -- of limited private records works correctly, Return also the
1368 -- adjustment call for controlled objects
1370 procedure Build_Discriminant_Assignments (Statement_List : List_Id);
1371 -- If the record has discriminants, adds assignment statements to
1372 -- statement list to initialize the discriminant values from the
1373 -- arguments of the initialization procedure.
1375 function Build_Init_Statements (Comp_List : Node_Id) return List_Id;
1376 -- Build a list representing a sequence of statements which initialize
1377 -- components of the given component list. This may involve building
1378 -- case statements for the variant parts.
1380 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id;
1381 -- Given a non-tagged type-derivation that declares discriminants,
1382 -- such as
1384 -- type R (R1, R2 : Integer) is record ... end record;
1386 -- type D (D1 : Integer) is new R (1, D1);
1388 -- we make the _init_proc of D be
1390 -- procedure _init_proc(X : D; D1 : Integer) is
1391 -- begin
1392 -- _init_proc( R(X), 1, D1);
1393 -- end _init_proc;
1395 -- This function builds the call statement in this _init_proc.
1397 procedure Build_Init_Procedure;
1398 -- Build the tree corresponding to the procedure specification and body
1399 -- of the initialization procedure (by calling all the preceding
1400 -- auxiliary routines), and install it as the _init TSS.
1402 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id);
1403 -- Add range checks to components of disciminated records. S is a
1404 -- subtype indication of a record component. Check_List is a list
1405 -- to which the check actions are appended.
1407 function Component_Needs_Simple_Initialization
1408 (T : Entity_Id) return Boolean;
1409 -- Determines if a component needs simple initialization, given its type
1410 -- T. This is the same as Needs_Simple_Initialization except for the
1411 -- following difference: the types Tag, Interface_Tag, and Vtable_Ptr
1412 -- which are access types which would normally require simple
1413 -- initialization to null, do not require initialization as components,
1414 -- since they are explicitly initialized by other means.
1416 procedure Constrain_Array
1417 (SI : Node_Id;
1418 Check_List : List_Id);
1419 -- Called from Build_Record_Checks.
1420 -- Apply a list of index constraints to an unconstrained array type.
1421 -- The first parameter is the entity for the resulting subtype.
1422 -- Check_List is a list to which the check actions are appended.
1424 procedure Constrain_Index
1425 (Index : Node_Id;
1426 S : Node_Id;
1427 Check_List : List_Id);
1428 -- Called from Build_Record_Checks.
1429 -- Process an index constraint in a constrained array declaration.
1430 -- The constraint can be a subtype name, or a range with or without
1431 -- an explicit subtype mark. The index is the corresponding index of the
1432 -- unconstrained array. S is the range expression. Check_List is a list
1433 -- to which the check actions are appended.
1435 function Parent_Subtype_Renaming_Discrims return Boolean;
1436 -- Returns True for base types N that rename discriminants, else False
1438 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean;
1439 -- Determines whether a record initialization procedure needs to be
1440 -- generated for the given record type.
1442 ----------------------
1443 -- Build_Assignment --
1444 ----------------------
1446 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id is
1447 Exp : Node_Id := N;
1448 Lhs : Node_Id;
1449 Typ : constant Entity_Id := Underlying_Type (Etype (Id));
1450 Kind : Node_Kind := Nkind (N);
1451 Res : List_Id;
1453 begin
1454 Loc := Sloc (N);
1455 Lhs :=
1456 Make_Selected_Component (Loc,
1457 Prefix => Make_Identifier (Loc, Name_uInit),
1458 Selector_Name => New_Occurrence_Of (Id, Loc));
1459 Set_Assignment_OK (Lhs);
1461 -- Case of an access attribute applied to the current instance.
1462 -- Replace the reference to the type by a reference to the actual
1463 -- object. (Note that this handles the case of the top level of
1464 -- the expression being given by such an attribute, but does not
1465 -- cover uses nested within an initial value expression. Nested
1466 -- uses are unlikely to occur in practice, but are theoretically
1467 -- possible. It is not clear how to handle them without fully
1468 -- traversing the expression. ???
1470 if Kind = N_Attribute_Reference
1471 and then (Attribute_Name (N) = Name_Unchecked_Access
1472 or else
1473 Attribute_Name (N) = Name_Unrestricted_Access)
1474 and then Is_Entity_Name (Prefix (N))
1475 and then Is_Type (Entity (Prefix (N)))
1476 and then Entity (Prefix (N)) = Rec_Type
1477 then
1478 Exp :=
1479 Make_Attribute_Reference (Loc,
1480 Prefix => Make_Identifier (Loc, Name_uInit),
1481 Attribute_Name => Name_Unrestricted_Access);
1482 end if;
1484 -- Ada 2005 (AI-231): Add the run-time check if required
1486 if Ada_Version >= Ada_05
1487 and then Can_Never_Be_Null (Etype (Id)) -- Lhs
1488 then
1489 if Nkind (Exp) = N_Null then
1490 return New_List (
1491 Make_Raise_Constraint_Error (Sloc (Exp),
1492 Reason => CE_Null_Not_Allowed));
1494 elsif Present (Etype (Exp))
1495 and then not Can_Never_Be_Null (Etype (Exp))
1496 then
1497 Install_Null_Excluding_Check (Exp);
1498 end if;
1499 end if;
1501 -- Take a copy of Exp to ensure that later copies of this
1502 -- component_declaration in derived types see the original tree,
1503 -- not a node rewritten during expansion of the init_proc.
1505 Exp := New_Copy_Tree (Exp);
1507 Res := New_List (
1508 Make_Assignment_Statement (Loc,
1509 Name => Lhs,
1510 Expression => Exp));
1512 Set_No_Ctrl_Actions (First (Res));
1514 -- Adjust the tag if tagged (because of possible view conversions).
1515 -- Suppress the tag adjustment when Java_VM because JVM tags are
1516 -- represented implicitly in objects.
1518 if Is_Tagged_Type (Typ) and then not Java_VM then
1519 Append_To (Res,
1520 Make_Assignment_Statement (Loc,
1521 Name =>
1522 Make_Selected_Component (Loc,
1523 Prefix => New_Copy_Tree (Lhs),
1524 Selector_Name =>
1525 New_Reference_To (First_Tag_Component (Typ), Loc)),
1527 Expression =>
1528 Unchecked_Convert_To (RTE (RE_Tag),
1529 New_Reference_To
1530 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc))));
1531 end if;
1533 -- Adjust the component if controlled except if it is an
1534 -- aggregate that will be expanded inline
1536 if Kind = N_Qualified_Expression then
1537 Kind := Nkind (Expression (N));
1538 end if;
1540 if Controlled_Type (Typ)
1541 and then not (Kind = N_Aggregate or else Kind = N_Extension_Aggregate)
1542 then
1543 Append_List_To (Res,
1544 Make_Adjust_Call (
1545 Ref => New_Copy_Tree (Lhs),
1546 Typ => Etype (Id),
1547 Flist_Ref =>
1548 Find_Final_List (Etype (Id), New_Copy_Tree (Lhs)),
1549 With_Attach => Make_Integer_Literal (Loc, 1)));
1550 end if;
1552 return Res;
1554 exception
1555 when RE_Not_Available =>
1556 return Empty_List;
1557 end Build_Assignment;
1559 ------------------------------------
1560 -- Build_Discriminant_Assignments --
1561 ------------------------------------
1563 procedure Build_Discriminant_Assignments (Statement_List : List_Id) is
1564 D : Entity_Id;
1565 Is_Tagged : constant Boolean := Is_Tagged_Type (Rec_Type);
1567 begin
1568 if Has_Discriminants (Rec_Type)
1569 and then not Is_Unchecked_Union (Rec_Type)
1570 then
1571 D := First_Discriminant (Rec_Type);
1573 while Present (D) loop
1574 -- Don't generate the assignment for discriminants in derived
1575 -- tagged types if the discriminant is a renaming of some
1576 -- ancestor discriminant. This initialization will be done
1577 -- when initializing the _parent field of the derived record.
1579 if Is_Tagged and then
1580 Present (Corresponding_Discriminant (D))
1581 then
1582 null;
1584 else
1585 Loc := Sloc (D);
1586 Append_List_To (Statement_List,
1587 Build_Assignment (D,
1588 New_Reference_To (Discriminal (D), Loc)));
1589 end if;
1591 Next_Discriminant (D);
1592 end loop;
1593 end if;
1594 end Build_Discriminant_Assignments;
1596 --------------------------
1597 -- Build_Init_Call_Thru --
1598 --------------------------
1600 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id is
1601 Parent_Proc : constant Entity_Id :=
1602 Base_Init_Proc (Etype (Rec_Type));
1604 Parent_Type : constant Entity_Id :=
1605 Etype (First_Formal (Parent_Proc));
1607 Uparent_Type : constant Entity_Id :=
1608 Underlying_Type (Parent_Type);
1610 First_Discr_Param : Node_Id;
1612 Parent_Discr : Entity_Id;
1613 First_Arg : Node_Id;
1614 Args : List_Id;
1615 Arg : Node_Id;
1616 Res : List_Id;
1618 begin
1619 -- First argument (_Init) is the object to be initialized.
1620 -- ??? not sure where to get a reasonable Loc for First_Arg
1622 First_Arg :=
1623 OK_Convert_To (Parent_Type,
1624 New_Reference_To (Defining_Identifier (First (Parameters)), Loc));
1626 Set_Etype (First_Arg, Parent_Type);
1628 Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
1630 -- In the tasks case,
1631 -- add _Master as the value of the _Master parameter
1632 -- add _Chain as the value of the _Chain parameter.
1633 -- add _Task_Name as the value of the _Task_Name parameter.
1634 -- At the outer level, these will be variables holding the
1635 -- corresponding values obtained from GNARL or the expander.
1637 -- At inner levels, they will be the parameters passed down through
1638 -- the outer routines.
1640 First_Discr_Param := Next (First (Parameters));
1642 if Has_Task (Rec_Type) then
1643 if Restriction_Active (No_Task_Hierarchy) then
1645 -- See comments in System.Tasking.Initialization.Init_RTS
1646 -- for the value 3.
1648 Append_To (Args, Make_Integer_Literal (Loc, 3));
1649 else
1650 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1651 end if;
1653 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1654 Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
1655 First_Discr_Param := Next (Next (Next (First_Discr_Param)));
1656 end if;
1658 -- Append discriminant values
1660 if Has_Discriminants (Uparent_Type) then
1661 pragma Assert (not Is_Tagged_Type (Uparent_Type));
1663 Parent_Discr := First_Discriminant (Uparent_Type);
1664 while Present (Parent_Discr) loop
1666 -- Get the initial value for this discriminant
1667 -- ??? needs to be cleaned up to use parent_Discr_Constr
1668 -- directly.
1670 declare
1671 Discr_Value : Elmt_Id :=
1672 First_Elmt
1673 (Stored_Constraint (Rec_Type));
1675 Discr : Entity_Id :=
1676 First_Stored_Discriminant (Uparent_Type);
1677 begin
1678 while Original_Record_Component (Parent_Discr) /= Discr loop
1679 Next_Stored_Discriminant (Discr);
1680 Next_Elmt (Discr_Value);
1681 end loop;
1683 Arg := Node (Discr_Value);
1684 end;
1686 -- Append it to the list
1688 if Nkind (Arg) = N_Identifier
1689 and then Ekind (Entity (Arg)) = E_Discriminant
1690 then
1691 Append_To (Args,
1692 New_Reference_To (Discriminal (Entity (Arg)), Loc));
1694 -- Case of access discriminants. We replace the reference
1695 -- to the type by a reference to the actual object
1697 -- ??? why is this code deleted without comment
1699 -- elsif Nkind (Arg) = N_Attribute_Reference
1700 -- and then Is_Entity_Name (Prefix (Arg))
1701 -- and then Is_Type (Entity (Prefix (Arg)))
1702 -- then
1703 -- Append_To (Args,
1704 -- Make_Attribute_Reference (Loc,
1705 -- Prefix => New_Copy (Prefix (Id_Ref)),
1706 -- Attribute_Name => Name_Unrestricted_Access));
1708 else
1709 Append_To (Args, New_Copy (Arg));
1710 end if;
1712 Next_Discriminant (Parent_Discr);
1713 end loop;
1714 end if;
1716 Res :=
1717 New_List (
1718 Make_Procedure_Call_Statement (Loc,
1719 Name => New_Occurrence_Of (Parent_Proc, Loc),
1720 Parameter_Associations => Args));
1722 return Res;
1723 end Build_Init_Call_Thru;
1725 --------------------------
1726 -- Build_Init_Procedure --
1727 --------------------------
1729 procedure Build_Init_Procedure is
1730 Body_Node : Node_Id;
1731 Handled_Stmt_Node : Node_Id;
1732 Parameters : List_Id;
1733 Proc_Spec_Node : Node_Id;
1734 Body_Stmts : List_Id;
1735 Record_Extension_Node : Node_Id;
1736 Init_Tag : Node_Id;
1738 procedure Init_Secondary_Tags (Typ : Entity_Id);
1739 -- Ada 2005 (AI-251): Initialize the tags of all the secondary
1740 -- tables associated with abstract interface types
1742 -------------------------
1743 -- Init_Secondary_Tags --
1744 -------------------------
1746 procedure Init_Secondary_Tags (Typ : Entity_Id) is
1747 ADT : Elmt_Id;
1749 procedure Init_Secondary_Tags_Internal (Typ : Entity_Id);
1750 -- Internal subprogram used to recursively climb to the root type
1752 ----------------------------------
1753 -- Init_Secondary_Tags_Internal --
1754 ----------------------------------
1756 procedure Init_Secondary_Tags_Internal (Typ : Entity_Id) is
1757 E : Entity_Id;
1758 Aux_N : Node_Id;
1760 begin
1761 if not Is_Interface (Typ)
1762 and then Etype (Typ) /= Typ
1763 then
1764 Init_Secondary_Tags_Internal (Etype (Typ));
1765 end if;
1767 if Present (Abstract_Interfaces (Typ))
1768 and then not Is_Empty_Elmt_List (Abstract_Interfaces (Typ))
1769 then
1770 E := First_Entity (Typ);
1771 while Present (E) loop
1772 if Is_Tag (E)
1773 and then Chars (E) /= Name_uTag
1774 then
1775 Aux_N := Node (ADT);
1776 pragma Assert (Present (Aux_N));
1778 -- Initialize the pointer to the secondary DT
1779 -- associated with the interface
1781 Append_To (Body_Stmts,
1782 Make_Assignment_Statement (Loc,
1783 Name =>
1784 Make_Selected_Component (Loc,
1785 Prefix => Make_Identifier (Loc, Name_uInit),
1786 Selector_Name =>
1787 New_Reference_To (E, Loc)),
1788 Expression =>
1789 New_Reference_To (Aux_N, Loc)));
1791 -- Generate:
1792 -- Set_Offset_To_Top (DT_Ptr, n);
1794 Append_To (Body_Stmts,
1795 Make_Procedure_Call_Statement (Loc,
1796 Name => New_Reference_To
1797 (RTE (RE_Set_Offset_To_Top), Loc),
1798 Parameter_Associations => New_List (
1799 Unchecked_Convert_To (RTE (RE_Tag),
1800 New_Reference_To (Aux_N, Loc)),
1801 Unchecked_Convert_To (RTE (RE_Storage_Offset),
1802 Make_Attribute_Reference (Loc,
1803 Prefix =>
1804 Make_Selected_Component (Loc,
1805 Prefix => Make_Identifier (Loc,
1806 Name_uInit),
1807 Selector_Name => New_Reference_To
1808 (E, Loc)),
1809 Attribute_Name => Name_Position)))));
1811 Next_Elmt (ADT);
1812 end if;
1814 Next_Entity (E);
1815 end loop;
1816 end if;
1817 end Init_Secondary_Tags_Internal;
1819 -- Start of processing for Init_Secondary_Tags
1821 begin
1822 -- Skip the first _Tag, which is the main tag of the
1823 -- tagged type. Following tags correspond with abstract
1824 -- interfaces.
1826 ADT := Next_Elmt (First_Elmt (Access_Disp_Table (Typ)));
1827 Init_Secondary_Tags_Internal (Typ);
1828 end Init_Secondary_Tags;
1830 -- Start of processing for Build_Init_Procedure
1832 begin
1833 Body_Stmts := New_List;
1834 Body_Node := New_Node (N_Subprogram_Body, Loc);
1836 Proc_Id :=
1837 Make_Defining_Identifier (Loc,
1838 Chars => Make_Init_Proc_Name (Rec_Type));
1839 Set_Ekind (Proc_Id, E_Procedure);
1841 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
1842 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
1844 Parameters := Init_Formals (Rec_Type);
1845 Append_List_To (Parameters,
1846 Build_Discriminant_Formals (Rec_Type, True));
1848 -- For tagged types, we add a flag to indicate whether the routine
1849 -- is called to initialize a parent component in the init_proc of
1850 -- a type extension. If the flag is false, we do not set the tag
1851 -- because it has been set already in the extension.
1853 if Is_Tagged_Type (Rec_Type)
1854 and then not Is_CPP_Class (Rec_Type)
1855 then
1856 Set_Tag :=
1857 Make_Defining_Identifier (Loc, New_Internal_Name ('P'));
1859 Append_To (Parameters,
1860 Make_Parameter_Specification (Loc,
1861 Defining_Identifier => Set_Tag,
1862 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
1863 Expression => New_Occurrence_Of (Standard_True, Loc)));
1864 end if;
1866 Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
1867 Set_Specification (Body_Node, Proc_Spec_Node);
1868 Set_Declarations (Body_Node, New_List);
1870 if Parent_Subtype_Renaming_Discrims then
1872 -- N is a Derived_Type_Definition that renames the parameters
1873 -- of the ancestor type. We init it by expanding our discrims
1874 -- and call the ancestor _init_proc with a type-converted object
1876 Append_List_To (Body_Stmts,
1877 Build_Init_Call_Thru (Parameters));
1879 elsif Nkind (Type_Definition (N)) = N_Record_Definition then
1880 Build_Discriminant_Assignments (Body_Stmts);
1882 if not Null_Present (Type_Definition (N)) then
1883 Append_List_To (Body_Stmts,
1884 Build_Init_Statements (
1885 Component_List (Type_Definition (N))));
1886 end if;
1888 else
1889 -- N is a Derived_Type_Definition with a possible non-empty
1890 -- extension. The initialization of a type extension consists
1891 -- in the initialization of the components in the extension.
1893 Build_Discriminant_Assignments (Body_Stmts);
1895 Record_Extension_Node :=
1896 Record_Extension_Part (Type_Definition (N));
1898 if not Null_Present (Record_Extension_Node) then
1899 declare
1900 Stmts : constant List_Id :=
1901 Build_Init_Statements (
1902 Component_List (Record_Extension_Node));
1904 begin
1905 -- The parent field must be initialized first because
1906 -- the offset of the new discriminants may depend on it
1908 Prepend_To (Body_Stmts, Remove_Head (Stmts));
1909 Append_List_To (Body_Stmts, Stmts);
1910 end;
1911 end if;
1912 end if;
1914 -- Add here the assignment to instantiate the Tag
1916 -- The assignement corresponds to the code:
1918 -- _Init._Tag := Typ'Tag;
1920 -- Suppress the tag assignment when Java_VM because JVM tags are
1921 -- represented implicitly in objects.
1923 if Is_Tagged_Type (Rec_Type)
1924 and then not Is_CPP_Class (Rec_Type)
1925 and then not Java_VM
1926 then
1927 Init_Tag :=
1928 Make_Assignment_Statement (Loc,
1929 Name =>
1930 Make_Selected_Component (Loc,
1931 Prefix => Make_Identifier (Loc, Name_uInit),
1932 Selector_Name =>
1933 New_Reference_To (First_Tag_Component (Rec_Type), Loc)),
1935 Expression =>
1936 New_Reference_To
1937 (Node (First_Elmt (Access_Disp_Table (Rec_Type))), Loc));
1939 -- The tag must be inserted before the assignments to other
1940 -- components, because the initial value of the component may
1941 -- depend ot the tag (eg. through a dispatching operation on
1942 -- an access to the current type). The tag assignment is not done
1943 -- when initializing the parent component of a type extension,
1944 -- because in that case the tag is set in the extension.
1945 -- Extensions of imported C++ classes add a final complication,
1946 -- because we cannot inhibit tag setting in the constructor for
1947 -- the parent. In that case we insert the tag initialization
1948 -- after the calls to initialize the parent.
1950 Init_Tag :=
1951 Make_If_Statement (Loc,
1952 Condition => New_Occurrence_Of (Set_Tag, Loc),
1953 Then_Statements => New_List (Init_Tag));
1955 if not Is_CPP_Class (Etype (Rec_Type)) then
1956 Prepend_To (Body_Stmts, Init_Tag);
1958 -- Ada 2005 (AI-251): Initialization of all the tags
1959 -- corresponding with abstract interfaces
1961 if Ada_Version >= Ada_05
1962 and then not Is_Interface (Rec_Type)
1963 then
1964 Init_Secondary_Tags (Rec_Type);
1965 end if;
1967 else
1968 declare
1969 Nod : Node_Id := First (Body_Stmts);
1971 begin
1972 -- We assume the first init_proc call is for the parent
1974 while Present (Next (Nod))
1975 and then (Nkind (Nod) /= N_Procedure_Call_Statement
1976 or else not Is_Init_Proc (Name (Nod)))
1977 loop
1978 Nod := Next (Nod);
1979 end loop;
1981 Insert_After (Nod, Init_Tag);
1982 end;
1983 end if;
1984 end if;
1986 Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
1987 Set_Statements (Handled_Stmt_Node, Body_Stmts);
1988 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
1989 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
1991 if not Debug_Generated_Code then
1992 Set_Debug_Info_Off (Proc_Id);
1993 end if;
1995 -- Associate Init_Proc with type, and determine if the procedure
1996 -- is null (happens because of the Initialize_Scalars pragma case,
1997 -- where we have to generate a null procedure in case it is called
1998 -- by a client with Initialize_Scalars set). Such procedures have
1999 -- to be generated, but do not have to be called, so we mark them
2000 -- as null to suppress the call.
2002 Set_Init_Proc (Rec_Type, Proc_Id);
2004 if List_Length (Body_Stmts) = 1
2005 and then Nkind (First (Body_Stmts)) = N_Null_Statement
2006 then
2007 Set_Is_Null_Init_Proc (Proc_Id);
2008 end if;
2009 end Build_Init_Procedure;
2011 ---------------------------
2012 -- Build_Init_Statements --
2013 ---------------------------
2015 function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
2016 Check_List : constant List_Id := New_List;
2017 Alt_List : List_Id;
2018 Statement_List : List_Id;
2019 Stmts : List_Id;
2021 Per_Object_Constraint_Components : Boolean;
2023 Decl : Node_Id;
2024 Variant : Node_Id;
2026 Id : Entity_Id;
2027 Typ : Entity_Id;
2029 function Has_Access_Constraint (E : Entity_Id) return Boolean;
2030 -- Components with access discriminants that depend on the current
2031 -- instance must be initialized after all other components.
2033 ---------------------------
2034 -- Has_Access_Constraint --
2035 ---------------------------
2037 function Has_Access_Constraint (E : Entity_Id) return Boolean is
2038 Disc : Entity_Id;
2039 T : constant Entity_Id := Etype (E);
2041 begin
2042 if Has_Per_Object_Constraint (E)
2043 and then Has_Discriminants (T)
2044 then
2045 Disc := First_Discriminant (T);
2046 while Present (Disc) loop
2047 if Is_Access_Type (Etype (Disc)) then
2048 return True;
2049 end if;
2051 Next_Discriminant (Disc);
2052 end loop;
2054 return False;
2055 else
2056 return False;
2057 end if;
2058 end Has_Access_Constraint;
2060 -- Start of processing for Build_Init_Statements
2062 begin
2063 if Null_Present (Comp_List) then
2064 return New_List (Make_Null_Statement (Loc));
2065 end if;
2067 Statement_List := New_List;
2069 -- Loop through components, skipping pragmas, in 2 steps. The first
2070 -- step deals with regular components. The second step deals with
2071 -- components have per object constraints, and no explicit initia-
2072 -- lization.
2074 Per_Object_Constraint_Components := False;
2076 -- First step : regular components
2078 Decl := First_Non_Pragma (Component_Items (Comp_List));
2079 while Present (Decl) loop
2080 Loc := Sloc (Decl);
2081 Build_Record_Checks
2082 (Subtype_Indication (Component_Definition (Decl)), Check_List);
2084 Id := Defining_Identifier (Decl);
2085 Typ := Etype (Id);
2087 if Has_Access_Constraint (Id)
2088 and then No (Expression (Decl))
2089 then
2090 -- Skip processing for now and ask for a second pass
2092 Per_Object_Constraint_Components := True;
2094 else
2095 -- Case of explicit initialization
2097 if Present (Expression (Decl)) then
2098 Stmts := Build_Assignment (Id, Expression (Decl));
2100 -- Case of composite component with its own Init_Proc
2102 elsif Has_Non_Null_Base_Init_Proc (Typ) then
2103 Stmts :=
2104 Build_Initialization_Call
2105 (Loc,
2106 Make_Selected_Component (Loc,
2107 Prefix => Make_Identifier (Loc, Name_uInit),
2108 Selector_Name => New_Occurrence_Of (Id, Loc)),
2109 Typ,
2110 True,
2111 Rec_Type,
2112 Discr_Map => Discr_Map);
2114 -- Case of component needing simple initialization
2116 elsif Component_Needs_Simple_Initialization (Typ) then
2117 Stmts :=
2118 Build_Assignment
2119 (Id, Get_Simple_Init_Val (Typ, Loc, Esize (Id)));
2121 -- Nothing needed for this case
2123 else
2124 Stmts := No_List;
2125 end if;
2127 if Present (Check_List) then
2128 Append_List_To (Statement_List, Check_List);
2129 end if;
2131 if Present (Stmts) then
2133 -- Add the initialization of the record controller before
2134 -- the _Parent field is attached to it when the attachment
2135 -- can occur. It does not work to simply initialize the
2136 -- controller first: it must be initialized after the parent
2137 -- if the parent holds discriminants that can be used
2138 -- to compute the offset of the controller. We assume here
2139 -- that the last statement of the initialization call is the
2140 -- attachement of the parent (see Build_Initialization_Call)
2142 if Chars (Id) = Name_uController
2143 and then Rec_Type /= Etype (Rec_Type)
2144 and then Has_Controlled_Component (Etype (Rec_Type))
2145 and then Has_New_Controlled_Component (Rec_Type)
2146 then
2147 Insert_List_Before (Last (Statement_List), Stmts);
2148 else
2149 Append_List_To (Statement_List, Stmts);
2150 end if;
2151 end if;
2152 end if;
2154 Next_Non_Pragma (Decl);
2155 end loop;
2157 if Per_Object_Constraint_Components then
2159 -- Second pass: components with per-object constraints
2161 Decl := First_Non_Pragma (Component_Items (Comp_List));
2163 while Present (Decl) loop
2164 Loc := Sloc (Decl);
2165 Id := Defining_Identifier (Decl);
2166 Typ := Etype (Id);
2168 if Has_Access_Constraint (Id)
2169 and then No (Expression (Decl))
2170 then
2171 if Has_Non_Null_Base_Init_Proc (Typ) then
2172 Append_List_To (Statement_List,
2173 Build_Initialization_Call (Loc,
2174 Make_Selected_Component (Loc,
2175 Prefix => Make_Identifier (Loc, Name_uInit),
2176 Selector_Name => New_Occurrence_Of (Id, Loc)),
2177 Typ, True, Rec_Type, Discr_Map => Discr_Map));
2179 elsif Component_Needs_Simple_Initialization (Typ) then
2180 Append_List_To (Statement_List,
2181 Build_Assignment
2182 (Id, Get_Simple_Init_Val (Typ, Loc, Esize (Id))));
2183 end if;
2184 end if;
2186 Next_Non_Pragma (Decl);
2187 end loop;
2188 end if;
2190 -- Process the variant part
2192 if Present (Variant_Part (Comp_List)) then
2193 Alt_List := New_List;
2194 Variant := First_Non_Pragma (Variants (Variant_Part (Comp_List)));
2196 while Present (Variant) loop
2197 Loc := Sloc (Variant);
2198 Append_To (Alt_List,
2199 Make_Case_Statement_Alternative (Loc,
2200 Discrete_Choices =>
2201 New_Copy_List (Discrete_Choices (Variant)),
2202 Statements =>
2203 Build_Init_Statements (Component_List (Variant))));
2205 Next_Non_Pragma (Variant);
2206 end loop;
2208 -- The expression of the case statement which is a reference
2209 -- to one of the discriminants is replaced by the appropriate
2210 -- formal parameter of the initialization procedure.
2212 Append_To (Statement_List,
2213 Make_Case_Statement (Loc,
2214 Expression =>
2215 New_Reference_To (Discriminal (
2216 Entity (Name (Variant_Part (Comp_List)))), Loc),
2217 Alternatives => Alt_List));
2218 end if;
2220 -- For a task record type, add the task create call and calls
2221 -- to bind any interrupt (signal) entries.
2223 if Is_Task_Record_Type (Rec_Type) then
2225 -- In the case of the restricted run time the ATCB has already
2226 -- been preallocated.
2228 if Restricted_Profile then
2229 Append_To (Statement_List,
2230 Make_Assignment_Statement (Loc,
2231 Name => Make_Selected_Component (Loc,
2232 Prefix => Make_Identifier (Loc, Name_uInit),
2233 Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
2234 Expression => Make_Attribute_Reference (Loc,
2235 Prefix =>
2236 Make_Selected_Component (Loc,
2237 Prefix => Make_Identifier (Loc, Name_uInit),
2238 Selector_Name =>
2239 Make_Identifier (Loc, Name_uATCB)),
2240 Attribute_Name => Name_Unchecked_Access)));
2241 end if;
2243 Append_To (Statement_List, Make_Task_Create_Call (Rec_Type));
2245 declare
2246 Task_Type : constant Entity_Id :=
2247 Corresponding_Concurrent_Type (Rec_Type);
2248 Task_Decl : constant Node_Id := Parent (Task_Type);
2249 Task_Def : constant Node_Id := Task_Definition (Task_Decl);
2250 Vis_Decl : Node_Id;
2251 Ent : Entity_Id;
2253 begin
2254 if Present (Task_Def) then
2255 Vis_Decl := First (Visible_Declarations (Task_Def));
2256 while Present (Vis_Decl) loop
2257 Loc := Sloc (Vis_Decl);
2259 if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
2260 if Get_Attribute_Id (Chars (Vis_Decl)) =
2261 Attribute_Address
2262 then
2263 Ent := Entity (Name (Vis_Decl));
2265 if Ekind (Ent) = E_Entry then
2266 Append_To (Statement_List,
2267 Make_Procedure_Call_Statement (Loc,
2268 Name => New_Reference_To (
2269 RTE (RE_Bind_Interrupt_To_Entry), Loc),
2270 Parameter_Associations => New_List (
2271 Make_Selected_Component (Loc,
2272 Prefix =>
2273 Make_Identifier (Loc, Name_uInit),
2274 Selector_Name =>
2275 Make_Identifier (Loc, Name_uTask_Id)),
2276 Entry_Index_Expression (
2277 Loc, Ent, Empty, Task_Type),
2278 Expression (Vis_Decl))));
2279 end if;
2280 end if;
2281 end if;
2283 Next (Vis_Decl);
2284 end loop;
2285 end if;
2286 end;
2287 end if;
2289 -- For a protected type, add statements generated by
2290 -- Make_Initialize_Protection.
2292 if Is_Protected_Record_Type (Rec_Type) then
2293 Append_List_To (Statement_List,
2294 Make_Initialize_Protection (Rec_Type));
2295 end if;
2297 -- If no initializations when generated for component declarations
2298 -- corresponding to this Statement_List, append a null statement
2299 -- to the Statement_List to make it a valid Ada tree.
2301 if Is_Empty_List (Statement_List) then
2302 Append (New_Node (N_Null_Statement, Loc), Statement_List);
2303 end if;
2305 return Statement_List;
2307 exception
2308 when RE_Not_Available =>
2309 return Empty_List;
2310 end Build_Init_Statements;
2312 -------------------------
2313 -- Build_Record_Checks --
2314 -------------------------
2316 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
2317 Subtype_Mark_Id : Entity_Id;
2319 begin
2320 if Nkind (S) = N_Subtype_Indication then
2321 Find_Type (Subtype_Mark (S));
2322 Subtype_Mark_Id := Entity (Subtype_Mark (S));
2324 -- Remaining processing depends on type
2326 case Ekind (Subtype_Mark_Id) is
2328 when Array_Kind =>
2329 Constrain_Array (S, Check_List);
2331 when others =>
2332 null;
2333 end case;
2334 end if;
2335 end Build_Record_Checks;
2337 -------------------------------------------
2338 -- Component_Needs_Simple_Initialization --
2339 -------------------------------------------
2341 function Component_Needs_Simple_Initialization
2342 (T : Entity_Id) return Boolean
2344 begin
2345 return
2346 Needs_Simple_Initialization (T)
2347 and then not Is_RTE (T, RE_Tag)
2348 and then not Is_RTE (T, RE_Vtable_Ptr)
2349 and then not Is_RTE (T, RE_Interface_Tag); -- Ada 2005 (AI-251)
2350 end Component_Needs_Simple_Initialization;
2352 ---------------------
2353 -- Constrain_Array --
2354 ---------------------
2356 procedure Constrain_Array
2357 (SI : Node_Id;
2358 Check_List : List_Id)
2360 C : constant Node_Id := Constraint (SI);
2361 Number_Of_Constraints : Nat := 0;
2362 Index : Node_Id;
2363 S, T : Entity_Id;
2365 begin
2366 T := Entity (Subtype_Mark (SI));
2368 if Ekind (T) in Access_Kind then
2369 T := Designated_Type (T);
2370 end if;
2372 S := First (Constraints (C));
2374 while Present (S) loop
2375 Number_Of_Constraints := Number_Of_Constraints + 1;
2376 Next (S);
2377 end loop;
2379 -- In either case, the index constraint must provide a discrete
2380 -- range for each index of the array type and the type of each
2381 -- discrete range must be the same as that of the corresponding
2382 -- index. (RM 3.6.1)
2384 S := First (Constraints (C));
2385 Index := First_Index (T);
2386 Analyze (Index);
2388 -- Apply constraints to each index type
2390 for J in 1 .. Number_Of_Constraints loop
2391 Constrain_Index (Index, S, Check_List);
2392 Next (Index);
2393 Next (S);
2394 end loop;
2396 end Constrain_Array;
2398 ---------------------
2399 -- Constrain_Index --
2400 ---------------------
2402 procedure Constrain_Index
2403 (Index : Node_Id;
2404 S : Node_Id;
2405 Check_List : List_Id)
2407 T : constant Entity_Id := Etype (Index);
2409 begin
2410 if Nkind (S) = N_Range then
2411 Process_Range_Expr_In_Decl (S, T, Check_List);
2412 end if;
2413 end Constrain_Index;
2415 --------------------------------------
2416 -- Parent_Subtype_Renaming_Discrims --
2417 --------------------------------------
2419 function Parent_Subtype_Renaming_Discrims return Boolean is
2420 De : Entity_Id;
2421 Dp : Entity_Id;
2423 begin
2424 if Base_Type (Pe) /= Pe then
2425 return False;
2426 end if;
2428 if Etype (Pe) = Pe
2429 or else not Has_Discriminants (Pe)
2430 or else Is_Constrained (Pe)
2431 or else Is_Tagged_Type (Pe)
2432 then
2433 return False;
2434 end if;
2436 -- If there are no explicit stored discriminants we have inherited
2437 -- the root type discriminants so far, so no renamings occurred.
2439 if First_Discriminant (Pe) = First_Stored_Discriminant (Pe) then
2440 return False;
2441 end if;
2443 -- Check if we have done some trivial renaming of the parent
2444 -- discriminants, i.e. someting like
2446 -- type DT (X1,X2: int) is new PT (X1,X2);
2448 De := First_Discriminant (Pe);
2449 Dp := First_Discriminant (Etype (Pe));
2451 while Present (De) loop
2452 pragma Assert (Present (Dp));
2454 if Corresponding_Discriminant (De) /= Dp then
2455 return True;
2456 end if;
2458 Next_Discriminant (De);
2459 Next_Discriminant (Dp);
2460 end loop;
2462 return Present (Dp);
2463 end Parent_Subtype_Renaming_Discrims;
2465 ------------------------
2466 -- Requires_Init_Proc --
2467 ------------------------
2469 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
2470 Comp_Decl : Node_Id;
2471 Id : Entity_Id;
2472 Typ : Entity_Id;
2474 begin
2475 -- Definitely do not need one if specifically suppressed
2477 if Suppress_Init_Proc (Rec_Id) then
2478 return False;
2479 end if;
2481 -- Otherwise we need to generate an initialization procedure if
2482 -- Is_CPP_Class is False and at least one of the following applies:
2484 -- 1. Discriminants are present, since they need to be initialized
2485 -- with the appropriate discriminant constraint expressions.
2486 -- However, the discriminant of an unchecked union does not
2487 -- count, since the discriminant is not present.
2489 -- 2. The type is a tagged type, since the implicit Tag component
2490 -- needs to be initialized with a pointer to the dispatch table.
2492 -- 3. The type contains tasks
2494 -- 4. One or more components has an initial value
2496 -- 5. One or more components is for a type which itself requires
2497 -- an initialization procedure.
2499 -- 6. One or more components is a type that requires simple
2500 -- initialization (see Needs_Simple_Initialization), except
2501 -- that types Tag and Interface_Tag are excluded, since fields
2502 -- of these types are initialized by other means.
2504 -- 7. The type is the record type built for a task type (since at
2505 -- the very least, Create_Task must be called)
2507 -- 8. The type is the record type built for a protected type (since
2508 -- at least Initialize_Protection must be called)
2510 -- 9. The type is marked as a public entity. The reason we add this
2511 -- case (even if none of the above apply) is to properly handle
2512 -- Initialize_Scalars. If a package is compiled without an IS
2513 -- pragma, and the client is compiled with an IS pragma, then
2514 -- the client will think an initialization procedure is present
2515 -- and call it, when in fact no such procedure is required, but
2516 -- since the call is generated, there had better be a routine
2517 -- at the other end of the call, even if it does nothing!)
2519 -- Note: the reason we exclude the CPP_Class case is ???
2521 if Is_CPP_Class (Rec_Id) then
2522 return False;
2524 elsif not Restriction_Active (No_Initialize_Scalars)
2525 and then Is_Public (Rec_Id)
2526 then
2527 return True;
2529 elsif (Has_Discriminants (Rec_Id)
2530 and then not Is_Unchecked_Union (Rec_Id))
2531 or else Is_Tagged_Type (Rec_Id)
2532 or else Is_Concurrent_Record_Type (Rec_Id)
2533 or else Has_Task (Rec_Id)
2534 then
2535 return True;
2536 end if;
2538 Id := First_Component (Rec_Id);
2540 while Present (Id) loop
2541 Comp_Decl := Parent (Id);
2542 Typ := Etype (Id);
2544 if Present (Expression (Comp_Decl))
2545 or else Has_Non_Null_Base_Init_Proc (Typ)
2546 or else Component_Needs_Simple_Initialization (Typ)
2547 then
2548 return True;
2549 end if;
2551 Next_Component (Id);
2552 end loop;
2554 return False;
2555 end Requires_Init_Proc;
2557 -- Start of processing for Build_Record_Init_Proc
2559 begin
2560 Rec_Type := Defining_Identifier (N);
2562 -- This may be full declaration of a private type, in which case
2563 -- the visible entity is a record, and the private entity has been
2564 -- exchanged with it in the private part of the current package.
2565 -- The initialization procedure is built for the record type, which
2566 -- is retrievable from the private entity.
2568 if Is_Incomplete_Or_Private_Type (Rec_Type) then
2569 Rec_Type := Underlying_Type (Rec_Type);
2570 end if;
2572 -- If there are discriminants, build the discriminant map to replace
2573 -- discriminants by their discriminals in complex bound expressions.
2574 -- These only arise for the corresponding records of protected types.
2576 if Is_Concurrent_Record_Type (Rec_Type)
2577 and then Has_Discriminants (Rec_Type)
2578 then
2579 declare
2580 Disc : Entity_Id;
2582 begin
2583 Disc := First_Discriminant (Rec_Type);
2585 while Present (Disc) loop
2586 Append_Elmt (Disc, Discr_Map);
2587 Append_Elmt (Discriminal (Disc), Discr_Map);
2588 Next_Discriminant (Disc);
2589 end loop;
2590 end;
2591 end if;
2593 -- Derived types that have no type extension can use the initialization
2594 -- procedure of their parent and do not need a procedure of their own.
2595 -- This is only correct if there are no representation clauses for the
2596 -- type or its parent, and if the parent has in fact been frozen so
2597 -- that its initialization procedure exists.
2599 if Is_Derived_Type (Rec_Type)
2600 and then not Is_Tagged_Type (Rec_Type)
2601 and then not Is_Unchecked_Union (Rec_Type)
2602 and then not Has_New_Non_Standard_Rep (Rec_Type)
2603 and then not Parent_Subtype_Renaming_Discrims
2604 and then Has_Non_Null_Base_Init_Proc (Etype (Rec_Type))
2605 then
2606 Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
2608 -- Otherwise if we need an initialization procedure, then build one,
2609 -- mark it as public and inlinable and as having a completion.
2611 elsif Requires_Init_Proc (Rec_Type)
2612 or else Is_Unchecked_Union (Rec_Type)
2613 then
2614 Build_Init_Procedure;
2615 Set_Is_Public (Proc_Id, Is_Public (Pe));
2617 -- The initialization of protected records is not worth inlining.
2618 -- In addition, when compiled for another unit for inlining purposes,
2619 -- it may make reference to entities that have not been elaborated
2620 -- yet. The initialization of controlled records contains a nested
2621 -- clean-up procedure that makes it impractical to inline as well,
2622 -- and leads to undefined symbols if inlined in a different unit.
2623 -- Similar considerations apply to task types.
2625 if not Is_Concurrent_Type (Rec_Type)
2626 and then not Has_Task (Rec_Type)
2627 and then not Controlled_Type (Rec_Type)
2628 then
2629 Set_Is_Inlined (Proc_Id);
2630 end if;
2632 Set_Is_Internal (Proc_Id);
2633 Set_Has_Completion (Proc_Id);
2635 if not Debug_Generated_Code then
2636 Set_Debug_Info_Off (Proc_Id);
2637 end if;
2638 end if;
2639 end Build_Record_Init_Proc;
2641 ----------------------------
2642 -- Build_Slice_Assignment --
2643 ----------------------------
2645 -- Generates the following subprogram:
2647 -- procedure Assign
2648 -- (Source, Target : Array_Type,
2649 -- Left_Lo, Left_Hi, Right_Lo, Right_Hi : Index;
2650 -- Rev : Boolean)
2651 -- is
2652 -- Li1 : Index;
2653 -- Ri1 : Index;
2655 -- begin
2656 -- if Rev then
2657 -- Li1 := Left_Hi;
2658 -- Ri1 := Right_Hi;
2659 -- else
2660 -- Li1 := Left_Lo;
2661 -- Ri1 := Right_Lo;
2662 -- end if;
2664 -- loop
2665 -- if Rev then
2666 -- exit when Li1 < Left_Lo;
2667 -- else
2668 -- exit when Li1 > Left_Hi;
2669 -- end if;
2671 -- Target (Li1) := Source (Ri1);
2673 -- if Rev then
2674 -- Li1 := Index'pred (Li1);
2675 -- Ri1 := Index'pred (Ri1);
2676 -- else
2677 -- Li1 := Index'succ (Li1);
2678 -- Ri1 := Index'succ (Ri1);
2679 -- end if;
2680 -- end loop;
2681 -- end Assign;
2683 procedure Build_Slice_Assignment (Typ : Entity_Id) is
2684 Loc : constant Source_Ptr := Sloc (Typ);
2685 Index : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
2687 -- Build formal parameters of procedure
2689 Larray : constant Entity_Id :=
2690 Make_Defining_Identifier
2691 (Loc, Chars => New_Internal_Name ('A'));
2692 Rarray : constant Entity_Id :=
2693 Make_Defining_Identifier
2694 (Loc, Chars => New_Internal_Name ('R'));
2695 Left_Lo : constant Entity_Id :=
2696 Make_Defining_Identifier
2697 (Loc, Chars => New_Internal_Name ('L'));
2698 Left_Hi : constant Entity_Id :=
2699 Make_Defining_Identifier
2700 (Loc, Chars => New_Internal_Name ('L'));
2701 Right_Lo : constant Entity_Id :=
2702 Make_Defining_Identifier
2703 (Loc, Chars => New_Internal_Name ('R'));
2704 Right_Hi : constant Entity_Id :=
2705 Make_Defining_Identifier
2706 (Loc, Chars => New_Internal_Name ('R'));
2707 Rev : constant Entity_Id :=
2708 Make_Defining_Identifier
2709 (Loc, Chars => New_Internal_Name ('D'));
2710 Proc_Name : constant Entity_Id :=
2711 Make_Defining_Identifier (Loc,
2712 Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
2714 Lnn : constant Entity_Id :=
2715 Make_Defining_Identifier (Loc, New_Internal_Name ('L'));
2716 Rnn : constant Entity_Id :=
2717 Make_Defining_Identifier (Loc, New_Internal_Name ('R'));
2718 -- Subscripts for left and right sides
2720 Decls : List_Id;
2721 Loops : Node_Id;
2722 Stats : List_Id;
2724 begin
2725 -- Build declarations for indices
2727 Decls := New_List;
2729 Append_To (Decls,
2730 Make_Object_Declaration (Loc,
2731 Defining_Identifier => Lnn,
2732 Object_Definition =>
2733 New_Occurrence_Of (Index, Loc)));
2735 Append_To (Decls,
2736 Make_Object_Declaration (Loc,
2737 Defining_Identifier => Rnn,
2738 Object_Definition =>
2739 New_Occurrence_Of (Index, Loc)));
2741 Stats := New_List;
2743 -- Build initializations for indices
2745 declare
2746 F_Init : constant List_Id := New_List;
2747 B_Init : constant List_Id := New_List;
2749 begin
2750 Append_To (F_Init,
2751 Make_Assignment_Statement (Loc,
2752 Name => New_Occurrence_Of (Lnn, Loc),
2753 Expression => New_Occurrence_Of (Left_Lo, Loc)));
2755 Append_To (F_Init,
2756 Make_Assignment_Statement (Loc,
2757 Name => New_Occurrence_Of (Rnn, Loc),
2758 Expression => New_Occurrence_Of (Right_Lo, Loc)));
2760 Append_To (B_Init,
2761 Make_Assignment_Statement (Loc,
2762 Name => New_Occurrence_Of (Lnn, Loc),
2763 Expression => New_Occurrence_Of (Left_Hi, Loc)));
2765 Append_To (B_Init,
2766 Make_Assignment_Statement (Loc,
2767 Name => New_Occurrence_Of (Rnn, Loc),
2768 Expression => New_Occurrence_Of (Right_Hi, Loc)));
2770 Append_To (Stats,
2771 Make_If_Statement (Loc,
2772 Condition => New_Occurrence_Of (Rev, Loc),
2773 Then_Statements => B_Init,
2774 Else_Statements => F_Init));
2775 end;
2777 -- Now construct the assignment statement
2779 Loops :=
2780 Make_Loop_Statement (Loc,
2781 Statements => New_List (
2782 Make_Assignment_Statement (Loc,
2783 Name =>
2784 Make_Indexed_Component (Loc,
2785 Prefix => New_Occurrence_Of (Larray, Loc),
2786 Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
2787 Expression =>
2788 Make_Indexed_Component (Loc,
2789 Prefix => New_Occurrence_Of (Rarray, Loc),
2790 Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
2791 End_Label => Empty);
2793 -- Build exit condition
2795 declare
2796 F_Ass : constant List_Id := New_List;
2797 B_Ass : constant List_Id := New_List;
2799 begin
2800 Append_To (F_Ass,
2801 Make_Exit_Statement (Loc,
2802 Condition =>
2803 Make_Op_Gt (Loc,
2804 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
2805 Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
2807 Append_To (B_Ass,
2808 Make_Exit_Statement (Loc,
2809 Condition =>
2810 Make_Op_Lt (Loc,
2811 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
2812 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
2814 Prepend_To (Statements (Loops),
2815 Make_If_Statement (Loc,
2816 Condition => New_Occurrence_Of (Rev, Loc),
2817 Then_Statements => B_Ass,
2818 Else_Statements => F_Ass));
2819 end;
2821 -- Build the increment/decrement statements
2823 declare
2824 F_Ass : constant List_Id := New_List;
2825 B_Ass : constant List_Id := New_List;
2827 begin
2828 Append_To (F_Ass,
2829 Make_Assignment_Statement (Loc,
2830 Name => New_Occurrence_Of (Lnn, Loc),
2831 Expression =>
2832 Make_Attribute_Reference (Loc,
2833 Prefix =>
2834 New_Occurrence_Of (Index, Loc),
2835 Attribute_Name => Name_Succ,
2836 Expressions => New_List (
2837 New_Occurrence_Of (Lnn, Loc)))));
2839 Append_To (F_Ass,
2840 Make_Assignment_Statement (Loc,
2841 Name => New_Occurrence_Of (Rnn, Loc),
2842 Expression =>
2843 Make_Attribute_Reference (Loc,
2844 Prefix =>
2845 New_Occurrence_Of (Index, Loc),
2846 Attribute_Name => Name_Succ,
2847 Expressions => New_List (
2848 New_Occurrence_Of (Rnn, Loc)))));
2850 Append_To (B_Ass,
2851 Make_Assignment_Statement (Loc,
2852 Name => New_Occurrence_Of (Lnn, Loc),
2853 Expression =>
2854 Make_Attribute_Reference (Loc,
2855 Prefix =>
2856 New_Occurrence_Of (Index, Loc),
2857 Attribute_Name => Name_Pred,
2858 Expressions => New_List (
2859 New_Occurrence_Of (Lnn, Loc)))));
2861 Append_To (B_Ass,
2862 Make_Assignment_Statement (Loc,
2863 Name => New_Occurrence_Of (Rnn, Loc),
2864 Expression =>
2865 Make_Attribute_Reference (Loc,
2866 Prefix =>
2867 New_Occurrence_Of (Index, Loc),
2868 Attribute_Name => Name_Pred,
2869 Expressions => New_List (
2870 New_Occurrence_Of (Rnn, Loc)))));
2872 Append_To (Statements (Loops),
2873 Make_If_Statement (Loc,
2874 Condition => New_Occurrence_Of (Rev, Loc),
2875 Then_Statements => B_Ass,
2876 Else_Statements => F_Ass));
2877 end;
2879 Append_To (Stats, Loops);
2881 declare
2882 Spec : Node_Id;
2883 Formals : List_Id := New_List;
2885 begin
2886 Formals := New_List (
2887 Make_Parameter_Specification (Loc,
2888 Defining_Identifier => Larray,
2889 Out_Present => True,
2890 Parameter_Type =>
2891 New_Reference_To (Base_Type (Typ), Loc)),
2893 Make_Parameter_Specification (Loc,
2894 Defining_Identifier => Rarray,
2895 Parameter_Type =>
2896 New_Reference_To (Base_Type (Typ), Loc)),
2898 Make_Parameter_Specification (Loc,
2899 Defining_Identifier => Left_Lo,
2900 Parameter_Type =>
2901 New_Reference_To (Index, Loc)),
2903 Make_Parameter_Specification (Loc,
2904 Defining_Identifier => Left_Hi,
2905 Parameter_Type =>
2906 New_Reference_To (Index, Loc)),
2908 Make_Parameter_Specification (Loc,
2909 Defining_Identifier => Right_Lo,
2910 Parameter_Type =>
2911 New_Reference_To (Index, Loc)),
2913 Make_Parameter_Specification (Loc,
2914 Defining_Identifier => Right_Hi,
2915 Parameter_Type =>
2916 New_Reference_To (Index, Loc)));
2918 Append_To (Formals,
2919 Make_Parameter_Specification (Loc,
2920 Defining_Identifier => Rev,
2921 Parameter_Type =>
2922 New_Reference_To (Standard_Boolean, Loc)));
2924 Spec :=
2925 Make_Procedure_Specification (Loc,
2926 Defining_Unit_Name => Proc_Name,
2927 Parameter_Specifications => Formals);
2929 Discard_Node (
2930 Make_Subprogram_Body (Loc,
2931 Specification => Spec,
2932 Declarations => Decls,
2933 Handled_Statement_Sequence =>
2934 Make_Handled_Sequence_Of_Statements (Loc,
2935 Statements => Stats)));
2936 end;
2938 Set_TSS (Typ, Proc_Name);
2939 Set_Is_Pure (Proc_Name);
2940 end Build_Slice_Assignment;
2942 ------------------------------------
2943 -- Build_Variant_Record_Equality --
2944 ------------------------------------
2946 -- Generates:
2948 -- function _Equality (X, Y : T) return Boolean is
2949 -- begin
2950 -- -- Compare discriminants
2952 -- if False or else X.D1 /= Y.D1 or else X.D2 /= Y.D2 then
2953 -- return False;
2954 -- end if;
2956 -- -- Compare components
2958 -- if False or else X.C1 /= Y.C1 or else X.C2 /= Y.C2 then
2959 -- return False;
2960 -- end if;
2962 -- -- Compare variant part
2964 -- case X.D1 is
2965 -- when V1 =>
2966 -- if False or else X.C2 /= Y.C2 or else X.C3 /= Y.C3 then
2967 -- return False;
2968 -- end if;
2969 -- ...
2970 -- when Vn =>
2971 -- if False or else X.Cn /= Y.Cn then
2972 -- return False;
2973 -- end if;
2974 -- end case;
2975 -- return True;
2976 -- end _Equality;
2978 procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
2979 Loc : constant Source_Ptr := Sloc (Typ);
2981 F : constant Entity_Id :=
2982 Make_Defining_Identifier (Loc,
2983 Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
2985 X : constant Entity_Id :=
2986 Make_Defining_Identifier (Loc,
2987 Chars => Name_X);
2989 Y : constant Entity_Id :=
2990 Make_Defining_Identifier (Loc,
2991 Chars => Name_Y);
2993 Def : constant Node_Id := Parent (Typ);
2994 Comps : constant Node_Id := Component_List (Type_Definition (Def));
2995 Stmts : constant List_Id := New_List;
2996 Pspecs : constant List_Id := New_List;
2998 begin
2999 -- Derived Unchecked_Union types no longer inherit the equality function
3000 -- of their parent.
3002 if Is_Derived_Type (Typ)
3003 and then not Is_Unchecked_Union (Typ)
3004 and then not Has_New_Non_Standard_Rep (Typ)
3005 then
3006 declare
3007 Parent_Eq : constant Entity_Id :=
3008 TSS (Root_Type (Typ), TSS_Composite_Equality);
3010 begin
3011 if Present (Parent_Eq) then
3012 Copy_TSS (Parent_Eq, Typ);
3013 return;
3014 end if;
3015 end;
3016 end if;
3018 Discard_Node (
3019 Make_Subprogram_Body (Loc,
3020 Specification =>
3021 Make_Function_Specification (Loc,
3022 Defining_Unit_Name => F,
3023 Parameter_Specifications => Pspecs,
3024 Result_Definition => New_Reference_To (Standard_Boolean, Loc)),
3025 Declarations => New_List,
3026 Handled_Statement_Sequence =>
3027 Make_Handled_Sequence_Of_Statements (Loc,
3028 Statements => Stmts)));
3030 Append_To (Pspecs,
3031 Make_Parameter_Specification (Loc,
3032 Defining_Identifier => X,
3033 Parameter_Type => New_Reference_To (Typ, Loc)));
3035 Append_To (Pspecs,
3036 Make_Parameter_Specification (Loc,
3037 Defining_Identifier => Y,
3038 Parameter_Type => New_Reference_To (Typ, Loc)));
3040 -- Unchecked_Unions require additional machinery to support equality.
3041 -- Two extra parameters (A and B) are added to the equality function
3042 -- parameter list in order to capture the inferred values of the
3043 -- discriminants in later calls.
3045 if Is_Unchecked_Union (Typ) then
3046 declare
3047 Discr_Type : constant Node_Id := Etype (First_Discriminant (Typ));
3049 A : constant Node_Id :=
3050 Make_Defining_Identifier (Loc,
3051 Chars => Name_A);
3053 B : constant Node_Id :=
3054 Make_Defining_Identifier (Loc,
3055 Chars => Name_B);
3057 begin
3058 -- Add A and B to the parameter list
3060 Append_To (Pspecs,
3061 Make_Parameter_Specification (Loc,
3062 Defining_Identifier => A,
3063 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
3065 Append_To (Pspecs,
3066 Make_Parameter_Specification (Loc,
3067 Defining_Identifier => B,
3068 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
3070 -- Generate the following header code to compare the inferred
3071 -- discriminants:
3073 -- if a /= b then
3074 -- return False;
3075 -- end if;
3077 Append_To (Stmts,
3078 Make_If_Statement (Loc,
3079 Condition =>
3080 Make_Op_Ne (Loc,
3081 Left_Opnd => New_Reference_To (A, Loc),
3082 Right_Opnd => New_Reference_To (B, Loc)),
3083 Then_Statements => New_List (
3084 Make_Return_Statement (Loc,
3085 Expression => New_Occurrence_Of (Standard_False, Loc)))));
3087 -- Generate component-by-component comparison. Note that we must
3088 -- propagate one of the inferred discriminant formals to act as
3089 -- the case statement switch.
3091 Append_List_To (Stmts,
3092 Make_Eq_Case (Typ, Comps, A));
3094 end;
3096 -- Normal case (not unchecked union)
3098 else
3099 Append_To (Stmts,
3100 Make_Eq_If (Typ,
3101 Discriminant_Specifications (Def)));
3103 Append_List_To (Stmts,
3104 Make_Eq_Case (Typ, Comps));
3105 end if;
3107 Append_To (Stmts,
3108 Make_Return_Statement (Loc,
3109 Expression => New_Reference_To (Standard_True, Loc)));
3111 Set_TSS (Typ, F);
3112 Set_Is_Pure (F);
3114 if not Debug_Generated_Code then
3115 Set_Debug_Info_Off (F);
3116 end if;
3117 end Build_Variant_Record_Equality;
3119 -----------------------------
3120 -- Check_Stream_Attributes --
3121 -----------------------------
3123 procedure Check_Stream_Attributes (Typ : Entity_Id) is
3124 Comp : Entity_Id;
3125 Par_Read : constant Boolean :=
3126 Stream_Attribute_Available (Typ, TSS_Stream_Read)
3127 and then not Has_Specified_Stream_Read (Typ);
3128 Par_Write : constant Boolean :=
3129 Stream_Attribute_Available (Typ, TSS_Stream_Write)
3130 and then not Has_Specified_Stream_Write (Typ);
3132 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type);
3133 -- Check that Comp has a user-specified Nam stream attribute
3135 ----------------
3136 -- Check_Attr --
3137 ----------------
3139 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type) is
3140 begin
3141 if not Stream_Attribute_Available (Etype (Comp), TSS_Nam) then
3142 Error_Msg_Name_1 := Nam;
3143 Error_Msg_N
3144 ("|component& in limited extension must have% attribute", Comp);
3145 end if;
3146 end Check_Attr;
3148 -- Start of processing for Check_Stream_Attributes
3150 begin
3151 if Par_Read or else Par_Write then
3152 Comp := First_Component (Typ);
3153 while Present (Comp) loop
3154 if Comes_From_Source (Comp)
3155 and then Original_Record_Component (Comp) = Comp
3156 and then Is_Limited_Type (Etype (Comp))
3157 then
3158 if Par_Read then
3159 Check_Attr (Name_Read, TSS_Stream_Read);
3160 end if;
3162 if Par_Write then
3163 Check_Attr (Name_Write, TSS_Stream_Write);
3164 end if;
3165 end if;
3167 Next_Component (Comp);
3168 end loop;
3169 end if;
3170 end Check_Stream_Attributes;
3172 -----------------------------
3173 -- Expand_Record_Extension --
3174 -----------------------------
3176 -- Add a field _parent at the beginning of the record extension. This is
3177 -- used to implement inheritance. Here are some examples of expansion:
3179 -- 1. no discriminants
3180 -- type T2 is new T1 with null record;
3181 -- gives
3182 -- type T2 is new T1 with record
3183 -- _Parent : T1;
3184 -- end record;
3186 -- 2. renamed discriminants
3187 -- type T2 (B, C : Int) is new T1 (A => B) with record
3188 -- _Parent : T1 (A => B);
3189 -- D : Int;
3190 -- end;
3192 -- 3. inherited discriminants
3193 -- type T2 is new T1 with record -- discriminant A inherited
3194 -- _Parent : T1 (A);
3195 -- D : Int;
3196 -- end;
3198 procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
3199 Indic : constant Node_Id := Subtype_Indication (Def);
3200 Loc : constant Source_Ptr := Sloc (Def);
3201 Rec_Ext_Part : Node_Id := Record_Extension_Part (Def);
3202 Par_Subtype : Entity_Id;
3203 Comp_List : Node_Id;
3204 Comp_Decl : Node_Id;
3205 Parent_N : Node_Id;
3206 D : Entity_Id;
3207 List_Constr : constant List_Id := New_List;
3209 begin
3210 -- Expand_Record_Extension is called directly from the semantics, so
3211 -- we must check to see whether expansion is active before proceeding
3213 if not Expander_Active then
3214 return;
3215 end if;
3217 -- This may be a derivation of an untagged private type whose full
3218 -- view is tagged, in which case the Derived_Type_Definition has no
3219 -- extension part. Build an empty one now.
3221 if No (Rec_Ext_Part) then
3222 Rec_Ext_Part :=
3223 Make_Record_Definition (Loc,
3224 End_Label => Empty,
3225 Component_List => Empty,
3226 Null_Present => True);
3228 Set_Record_Extension_Part (Def, Rec_Ext_Part);
3229 Mark_Rewrite_Insertion (Rec_Ext_Part);
3230 end if;
3232 Comp_List := Component_List (Rec_Ext_Part);
3234 Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
3236 -- If the derived type inherits its discriminants the type of the
3237 -- _parent field must be constrained by the inherited discriminants
3239 if Has_Discriminants (T)
3240 and then Nkind (Indic) /= N_Subtype_Indication
3241 and then not Is_Constrained (Entity (Indic))
3242 then
3243 D := First_Discriminant (T);
3244 while Present (D) loop
3245 Append_To (List_Constr, New_Occurrence_Of (D, Loc));
3246 Next_Discriminant (D);
3247 end loop;
3249 Par_Subtype :=
3250 Process_Subtype (
3251 Make_Subtype_Indication (Loc,
3252 Subtype_Mark => New_Reference_To (Entity (Indic), Loc),
3253 Constraint =>
3254 Make_Index_Or_Discriminant_Constraint (Loc,
3255 Constraints => List_Constr)),
3256 Def);
3258 -- Otherwise the original subtype_indication is just what is needed
3260 else
3261 Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
3262 end if;
3264 Set_Parent_Subtype (T, Par_Subtype);
3266 Comp_Decl :=
3267 Make_Component_Declaration (Loc,
3268 Defining_Identifier => Parent_N,
3269 Component_Definition =>
3270 Make_Component_Definition (Loc,
3271 Aliased_Present => False,
3272 Subtype_Indication => New_Reference_To (Par_Subtype, Loc)));
3274 if Null_Present (Rec_Ext_Part) then
3275 Set_Component_List (Rec_Ext_Part,
3276 Make_Component_List (Loc,
3277 Component_Items => New_List (Comp_Decl),
3278 Variant_Part => Empty,
3279 Null_Present => False));
3280 Set_Null_Present (Rec_Ext_Part, False);
3282 elsif Null_Present (Comp_List)
3283 or else Is_Empty_List (Component_Items (Comp_List))
3284 then
3285 Set_Component_Items (Comp_List, New_List (Comp_Decl));
3286 Set_Null_Present (Comp_List, False);
3288 else
3289 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
3290 end if;
3292 Analyze (Comp_Decl);
3293 end Expand_Record_Extension;
3295 ------------------------------------
3296 -- Expand_N_Full_Type_Declaration --
3297 ------------------------------------
3299 procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
3300 Def_Id : constant Entity_Id := Defining_Identifier (N);
3301 B_Id : constant Entity_Id := Base_Type (Def_Id);
3302 Par_Id : Entity_Id;
3303 FN : Node_Id;
3305 begin
3306 if Is_Access_Type (Def_Id) then
3308 -- Anonymous access types are created for the components of the
3309 -- record parameter for an entry declaration. No master is created
3310 -- for such a type.
3312 if Has_Task (Designated_Type (Def_Id))
3313 and then Comes_From_Source (N)
3314 then
3315 Build_Master_Entity (Def_Id);
3316 Build_Master_Renaming (Parent (Def_Id), Def_Id);
3318 -- Create a class-wide master because a Master_Id must be generated
3319 -- for access-to-limited-class-wide types, whose root may be extended
3320 -- with task components.
3322 elsif Is_Class_Wide_Type (Designated_Type (Def_Id))
3323 and then Is_Limited_Type (Designated_Type (Def_Id))
3324 and then Tasking_Allowed
3326 -- Don't create a class-wide master for types whose convention is
3327 -- Java since these types cannot embed Ada tasks anyway. Note that
3328 -- the following test cannot catch the following case:
3330 -- package java.lang.Object is
3331 -- type Typ is tagged limited private;
3332 -- type Ref is access all Typ'Class;
3333 -- private
3334 -- type Typ is tagged limited ...;
3335 -- pragma Convention (Typ, Java)
3336 -- end;
3338 -- Because the convention appears after we have done the
3339 -- processing for type Ref.
3341 and then Convention (Designated_Type (Def_Id)) /= Convention_Java
3342 then
3343 Build_Class_Wide_Master (Def_Id);
3345 elsif Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
3346 Expand_Access_Protected_Subprogram_Type (N);
3347 end if;
3349 elsif Has_Task (Def_Id) then
3350 Expand_Previous_Access_Type (Def_Id);
3351 end if;
3353 Par_Id := Etype (B_Id);
3355 -- The parent type is private then we need to inherit
3356 -- any TSS operations from the full view.
3358 if Ekind (Par_Id) in Private_Kind
3359 and then Present (Full_View (Par_Id))
3360 then
3361 Par_Id := Base_Type (Full_View (Par_Id));
3362 end if;
3364 if Nkind (Type_Definition (Original_Node (N)))
3365 = N_Derived_Type_Definition
3366 and then not Is_Tagged_Type (Def_Id)
3367 and then Present (Freeze_Node (Par_Id))
3368 and then Present (TSS_Elist (Freeze_Node (Par_Id)))
3369 then
3370 Ensure_Freeze_Node (B_Id);
3371 FN := Freeze_Node (B_Id);
3373 if No (TSS_Elist (FN)) then
3374 Set_TSS_Elist (FN, New_Elmt_List);
3375 end if;
3377 declare
3378 T_E : constant Elist_Id := TSS_Elist (FN);
3379 Elmt : Elmt_Id;
3381 begin
3382 Elmt := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
3384 while Present (Elmt) loop
3385 if Chars (Node (Elmt)) /= Name_uInit then
3386 Append_Elmt (Node (Elmt), T_E);
3387 end if;
3389 Next_Elmt (Elmt);
3390 end loop;
3392 -- If the derived type itself is private with a full view, then
3393 -- associate the full view with the inherited TSS_Elist as well.
3395 if Ekind (B_Id) in Private_Kind
3396 and then Present (Full_View (B_Id))
3397 then
3398 Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
3399 Set_TSS_Elist
3400 (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
3401 end if;
3402 end;
3403 end if;
3404 end Expand_N_Full_Type_Declaration;
3406 ---------------------------------
3407 -- Expand_N_Object_Declaration --
3408 ---------------------------------
3410 -- First we do special processing for objects of a tagged type where this
3411 -- is the point at which the type is frozen. The creation of the dispatch
3412 -- table and the initialization procedure have to be deferred to this
3413 -- point, since we reference previously declared primitive subprograms.
3415 -- For all types, we call an initialization procedure if there is one
3417 procedure Expand_N_Object_Declaration (N : Node_Id) is
3418 Def_Id : constant Entity_Id := Defining_Identifier (N);
3419 Typ : constant Entity_Id := Etype (Def_Id);
3420 Loc : constant Source_Ptr := Sloc (N);
3421 Expr : constant Node_Id := Expression (N);
3422 New_Ref : Node_Id;
3423 Id_Ref : Node_Id;
3424 Expr_Q : Node_Id;
3426 begin
3427 -- Don't do anything for deferred constants. All proper actions will
3428 -- be expanded during the full declaration.
3430 if No (Expr) and Constant_Present (N) then
3431 return;
3432 end if;
3434 -- Make shared memory routines for shared passive variable
3436 if Is_Shared_Passive (Def_Id) then
3437 Make_Shared_Var_Procs (N);
3438 end if;
3440 -- If tasks being declared, make sure we have an activation chain
3441 -- defined for the tasks (has no effect if we already have one), and
3442 -- also that a Master variable is established and that the appropriate
3443 -- enclosing construct is established as a task master.
3445 if Has_Task (Typ) then
3446 Build_Activation_Chain_Entity (N);
3447 Build_Master_Entity (Def_Id);
3448 end if;
3450 -- Default initialization required, and no expression present
3452 if No (Expr) then
3454 -- Expand Initialize call for controlled objects. One may wonder why
3455 -- the Initialize Call is not done in the regular Init procedure
3456 -- attached to the record type. That's because the init procedure is
3457 -- recursively called on each component, including _Parent, thus the
3458 -- Init call for a controlled object would generate not only one
3459 -- Initialize call as it is required but one for each ancestor of
3460 -- its type. This processing is suppressed if No_Initialization set.
3462 if not Controlled_Type (Typ)
3463 or else No_Initialization (N)
3464 then
3465 null;
3467 elsif not Abort_Allowed
3468 or else not Comes_From_Source (N)
3469 then
3470 Insert_Actions_After (N,
3471 Make_Init_Call (
3472 Ref => New_Occurrence_Of (Def_Id, Loc),
3473 Typ => Base_Type (Typ),
3474 Flist_Ref => Find_Final_List (Def_Id),
3475 With_Attach => Make_Integer_Literal (Loc, 1)));
3477 -- Abort allowed
3479 else
3480 -- We need to protect the initialize call
3482 -- begin
3483 -- Defer_Abort.all;
3484 -- Initialize (...);
3485 -- at end
3486 -- Undefer_Abort.all;
3487 -- end;
3489 -- ??? this won't protect the initialize call for controlled
3490 -- components which are part of the init proc, so this block
3491 -- should probably also contain the call to _init_proc but this
3492 -- requires some code reorganization...
3494 declare
3495 L : constant List_Id :=
3496 Make_Init_Call (
3497 Ref => New_Occurrence_Of (Def_Id, Loc),
3498 Typ => Base_Type (Typ),
3499 Flist_Ref => Find_Final_List (Def_Id),
3500 With_Attach => Make_Integer_Literal (Loc, 1));
3502 Blk : constant Node_Id :=
3503 Make_Block_Statement (Loc,
3504 Handled_Statement_Sequence =>
3505 Make_Handled_Sequence_Of_Statements (Loc, L));
3507 begin
3508 Prepend_To (L, Build_Runtime_Call (Loc, RE_Abort_Defer));
3509 Set_At_End_Proc (Handled_Statement_Sequence (Blk),
3510 New_Occurrence_Of (RTE (RE_Abort_Undefer_Direct), Loc));
3511 Insert_Actions_After (N, New_List (Blk));
3512 Expand_At_End_Handler
3513 (Handled_Statement_Sequence (Blk), Entity (Identifier (Blk)));
3514 end;
3515 end if;
3517 -- Call type initialization procedure if there is one. We build the
3518 -- call and put it immediately after the object declaration, so that
3519 -- it will be expanded in the usual manner. Note that this will
3520 -- result in proper handling of defaulted discriminants. The call
3521 -- to the Init_Proc is suppressed if No_Initialization is set.
3523 if Has_Non_Null_Base_Init_Proc (Typ)
3524 and then not No_Initialization (N)
3525 then
3526 -- The call to the initialization procedure does NOT freeze
3527 -- the object being initialized. This is because the call is
3528 -- not a source level call. This works fine, because the only
3529 -- possible statements depending on freeze status that can
3530 -- appear after the _Init call are rep clauses which can
3531 -- safely appear after actual references to the object.
3533 Id_Ref := New_Reference_To (Def_Id, Loc);
3534 Set_Must_Not_Freeze (Id_Ref);
3535 Set_Assignment_OK (Id_Ref);
3537 Insert_Actions_After (N,
3538 Build_Initialization_Call (Loc, Id_Ref, Typ));
3540 -- If simple initialization is required, then set an appropriate
3541 -- simple initialization expression in place. This special
3542 -- initialization is required even though No_Init_Flag is present.
3544 -- An internally generated temporary needs no initialization because
3545 -- it will be assigned subsequently. In particular, there is no
3546 -- point in applying Initialize_Scalars to such a temporary.
3548 elsif Needs_Simple_Initialization (Typ)
3549 and then not Is_Internal (Def_Id)
3550 then
3551 Set_No_Initialization (N, False);
3552 Set_Expression (N, Get_Simple_Init_Val (Typ, Loc, Esize (Def_Id)));
3553 Analyze_And_Resolve (Expression (N), Typ);
3554 end if;
3556 -- Generate attribute for Persistent_BSS if needed
3558 declare
3559 Prag : Node_Id;
3560 begin
3561 if Persistent_BSS_Mode
3562 and then Comes_From_Source (N)
3563 and then Is_Potentially_Persistent_Type (Typ)
3564 and then Is_Library_Level_Entity (Def_Id)
3565 then
3566 Prag :=
3567 Make_Linker_Section_Pragma
3568 (Def_Id, Sloc (N), ".persistent.bss");
3569 Insert_After (N, Prag);
3570 Analyze (Prag);
3571 end if;
3572 end;
3574 -- Explicit initialization present
3576 else
3577 -- Obtain actual expression from qualified expression
3579 if Nkind (Expr) = N_Qualified_Expression then
3580 Expr_Q := Expression (Expr);
3581 else
3582 Expr_Q := Expr;
3583 end if;
3585 -- When we have the appropriate type of aggregate in the
3586 -- expression (it has been determined during analysis of the
3587 -- aggregate by setting the delay flag), let's perform in
3588 -- place assignment and thus avoid creating a temporary.
3590 if Is_Delayed_Aggregate (Expr_Q) then
3591 Convert_Aggr_In_Object_Decl (N);
3593 else
3594 -- In most cases, we must check that the initial value meets
3595 -- any constraint imposed by the declared type. However, there
3596 -- is one very important exception to this rule. If the entity
3597 -- has an unconstrained nominal subtype, then it acquired its
3598 -- constraints from the expression in the first place, and not
3599 -- only does this mean that the constraint check is not needed,
3600 -- but an attempt to perform the constraint check can
3601 -- cause order of elaboration problems.
3603 if not Is_Constr_Subt_For_U_Nominal (Typ) then
3605 -- If this is an allocator for an aggregate that has been
3606 -- allocated in place, delay checks until assignments are
3607 -- made, because the discriminants are not initialized.
3609 if Nkind (Expr) = N_Allocator
3610 and then No_Initialization (Expr)
3611 then
3612 null;
3613 else
3614 Apply_Constraint_Check (Expr, Typ);
3615 end if;
3616 end if;
3618 -- If the type is controlled we attach the object to the final
3619 -- list and adjust the target after the copy. This
3621 if Controlled_Type (Typ) then
3622 declare
3623 Flist : Node_Id;
3624 F : Entity_Id;
3626 begin
3627 -- Attach the result to a dummy final list which will never
3628 -- be finalized if Delay_Finalize_Attachis set. It is
3629 -- important to attach to a dummy final list rather than
3630 -- not attaching at all in order to reset the pointers
3631 -- coming from the initial value. Equivalent code exists
3632 -- in the sec-stack case in Exp_Ch4.Expand_N_Allocator.
3634 if Delay_Finalize_Attach (N) then
3635 F :=
3636 Make_Defining_Identifier (Loc, New_Internal_Name ('F'));
3637 Insert_Action (N,
3638 Make_Object_Declaration (Loc,
3639 Defining_Identifier => F,
3640 Object_Definition =>
3641 New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
3643 Flist := New_Reference_To (F, Loc);
3645 else
3646 Flist := Find_Final_List (Def_Id);
3647 end if;
3649 Insert_Actions_After (N,
3650 Make_Adjust_Call (
3651 Ref => New_Reference_To (Def_Id, Loc),
3652 Typ => Base_Type (Typ),
3653 Flist_Ref => Flist,
3654 With_Attach => Make_Integer_Literal (Loc, 1)));
3655 end;
3656 end if;
3658 -- For tagged types, when an init value is given, the tag has to
3659 -- be re-initialized separately in order to avoid the propagation
3660 -- of a wrong tag coming from a view conversion unless the type
3661 -- is class wide (in this case the tag comes from the init
3662 -- value). Suppress the tag assignment when Java_VM because JVM
3663 -- tags are represented implicitly in objects. Ditto for types
3664 -- that are CPP_CLASS, and for initializations that are
3665 -- aggregates, because they have to have the right tag.
3667 if Is_Tagged_Type (Typ)
3668 and then not Is_Class_Wide_Type (Typ)
3669 and then not Is_CPP_Class (Typ)
3670 and then not Java_VM
3671 and then Nkind (Expr) /= N_Aggregate
3672 then
3673 -- The re-assignment of the tag has to be done even if
3674 -- the object is a constant
3676 New_Ref :=
3677 Make_Selected_Component (Loc,
3678 Prefix => New_Reference_To (Def_Id, Loc),
3679 Selector_Name =>
3680 New_Reference_To (First_Tag_Component (Typ), Loc));
3682 Set_Assignment_OK (New_Ref);
3684 Insert_After (N,
3685 Make_Assignment_Statement (Loc,
3686 Name => New_Ref,
3687 Expression =>
3688 Unchecked_Convert_To (RTE (RE_Tag),
3689 New_Reference_To
3690 (Node
3691 (First_Elmt
3692 (Access_Disp_Table (Base_Type (Typ)))),
3693 Loc))));
3695 -- For discrete types, set the Is_Known_Valid flag if the
3696 -- initializing value is known to be valid.
3698 elsif Is_Discrete_Type (Typ)
3699 and then Expr_Known_Valid (Expr)
3700 then
3701 Set_Is_Known_Valid (Def_Id);
3703 elsif Is_Access_Type (Typ) then
3705 -- For access types set the Is_Known_Non_Null flag if the
3706 -- initializing value is known to be non-null. We can also set
3707 -- Can_Never_Be_Null if this is a constant.
3709 if Known_Non_Null (Expr) then
3710 Set_Is_Known_Non_Null (Def_Id);
3712 if Constant_Present (N) then
3713 Set_Can_Never_Be_Null (Def_Id);
3714 end if;
3715 end if;
3716 end if;
3718 -- If validity checking on copies, validate initial expression
3720 if Validity_Checks_On
3721 and then Validity_Check_Copies
3722 then
3723 Ensure_Valid (Expr);
3724 Set_Is_Known_Valid (Def_Id);
3725 end if;
3726 end if;
3728 -- Cases where the back end cannot handle the initialization
3729 -- directly. In such cases, we expand an assignment that will
3730 -- be appropriately handled by Expand_N_Assignment_Statement.
3732 -- The exclusion of the unconstrained case is wrong, but for
3733 -- now it is too much trouble ???
3735 if (Is_Possibly_Unaligned_Slice (Expr)
3736 or else (Is_Possibly_Unaligned_Object (Expr)
3737 and then not Represented_As_Scalar (Etype (Expr))))
3739 -- The exclusion of the unconstrained case is wrong, but for
3740 -- now it is too much trouble ???
3742 and then not (Is_Array_Type (Etype (Expr))
3743 and then not Is_Constrained (Etype (Expr)))
3744 then
3745 declare
3746 Stat : constant Node_Id :=
3747 Make_Assignment_Statement (Loc,
3748 Name => New_Reference_To (Def_Id, Loc),
3749 Expression => Relocate_Node (Expr));
3750 begin
3751 Set_Expression (N, Empty);
3752 Set_No_Initialization (N);
3753 Set_Assignment_OK (Name (Stat));
3754 Set_No_Ctrl_Actions (Stat);
3755 Insert_After (N, Stat);
3756 Analyze (Stat);
3757 end;
3758 end if;
3759 end if;
3761 -- For array type, check for size too large
3762 -- We really need this for record types too???
3764 if Is_Array_Type (Typ) then
3765 Apply_Array_Size_Check (N, Typ);
3766 end if;
3768 exception
3769 when RE_Not_Available =>
3770 return;
3771 end Expand_N_Object_Declaration;
3773 ---------------------------------
3774 -- Expand_N_Subtype_Indication --
3775 ---------------------------------
3777 -- Add a check on the range of the subtype. The static case is partially
3778 -- duplicated by Process_Range_Expr_In_Decl in Sem_Ch3, but we still need
3779 -- to check here for the static case in order to avoid generating
3780 -- extraneous expanded code.
3782 procedure Expand_N_Subtype_Indication (N : Node_Id) is
3783 Ran : constant Node_Id := Range_Expression (Constraint (N));
3784 Typ : constant Entity_Id := Entity (Subtype_Mark (N));
3786 begin
3787 if Nkind (Parent (N)) = N_Constrained_Array_Definition or else
3788 Nkind (Parent (N)) = N_Slice
3789 then
3790 Resolve (Ran, Typ);
3791 Apply_Range_Check (Ran, Typ);
3792 end if;
3793 end Expand_N_Subtype_Indication;
3795 ---------------------------
3796 -- Expand_N_Variant_Part --
3797 ---------------------------
3799 -- If the last variant does not contain the Others choice, replace it with
3800 -- an N_Others_Choice node since Gigi always wants an Others. Note that we
3801 -- do not bother to call Analyze on the modified variant part, since it's
3802 -- only effect would be to compute the contents of the
3803 -- Others_Discrete_Choices node laboriously, and of course we already know
3804 -- the list of choices that corresponds to the others choice (it's the
3805 -- list we are replacing!)
3807 procedure Expand_N_Variant_Part (N : Node_Id) is
3808 Last_Var : constant Node_Id := Last_Non_Pragma (Variants (N));
3809 Others_Node : Node_Id;
3810 begin
3811 if Nkind (First (Discrete_Choices (Last_Var))) /= N_Others_Choice then
3812 Others_Node := Make_Others_Choice (Sloc (Last_Var));
3813 Set_Others_Discrete_Choices
3814 (Others_Node, Discrete_Choices (Last_Var));
3815 Set_Discrete_Choices (Last_Var, New_List (Others_Node));
3816 end if;
3817 end Expand_N_Variant_Part;
3819 ---------------------------------
3820 -- Expand_Previous_Access_Type --
3821 ---------------------------------
3823 procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
3824 T : Entity_Id := First_Entity (Current_Scope);
3826 begin
3827 -- Find all access types declared in the current scope, whose
3828 -- designated type is Def_Id.
3830 while Present (T) loop
3831 if Is_Access_Type (T)
3832 and then Designated_Type (T) = Def_Id
3833 then
3834 Build_Master_Entity (Def_Id);
3835 Build_Master_Renaming (Parent (Def_Id), T);
3836 end if;
3838 Next_Entity (T);
3839 end loop;
3840 end Expand_Previous_Access_Type;
3842 ------------------------------
3843 -- Expand_Record_Controller --
3844 ------------------------------
3846 procedure Expand_Record_Controller (T : Entity_Id) is
3847 Def : Node_Id := Type_Definition (Parent (T));
3848 Comp_List : Node_Id;
3849 Comp_Decl : Node_Id;
3850 Loc : Source_Ptr;
3851 First_Comp : Node_Id;
3852 Controller_Type : Entity_Id;
3853 Ent : Entity_Id;
3855 begin
3856 if Nkind (Def) = N_Derived_Type_Definition then
3857 Def := Record_Extension_Part (Def);
3858 end if;
3860 if Null_Present (Def) then
3861 Set_Component_List (Def,
3862 Make_Component_List (Sloc (Def),
3863 Component_Items => Empty_List,
3864 Variant_Part => Empty,
3865 Null_Present => True));
3866 end if;
3868 Comp_List := Component_List (Def);
3870 if Null_Present (Comp_List)
3871 or else Is_Empty_List (Component_Items (Comp_List))
3872 then
3873 Loc := Sloc (Comp_List);
3874 else
3875 Loc := Sloc (First (Component_Items (Comp_List)));
3876 end if;
3878 if Is_Return_By_Reference_Type (T) then
3879 Controller_Type := RTE (RE_Limited_Record_Controller);
3880 else
3881 Controller_Type := RTE (RE_Record_Controller);
3882 end if;
3884 Ent := Make_Defining_Identifier (Loc, Name_uController);
3886 Comp_Decl :=
3887 Make_Component_Declaration (Loc,
3888 Defining_Identifier => Ent,
3889 Component_Definition =>
3890 Make_Component_Definition (Loc,
3891 Aliased_Present => False,
3892 Subtype_Indication => New_Reference_To (Controller_Type, Loc)));
3894 if Null_Present (Comp_List)
3895 or else Is_Empty_List (Component_Items (Comp_List))
3896 then
3897 Set_Component_Items (Comp_List, New_List (Comp_Decl));
3898 Set_Null_Present (Comp_List, False);
3900 else
3901 -- The controller cannot be placed before the _Parent field since
3902 -- gigi lays out field in order and _parent must be first to
3903 -- preserve the polymorphism of tagged types.
3905 First_Comp := First (Component_Items (Comp_List));
3907 if Chars (Defining_Identifier (First_Comp)) /= Name_uParent
3908 and then Chars (Defining_Identifier (First_Comp)) /= Name_uTag
3909 then
3910 Insert_Before (First_Comp, Comp_Decl);
3911 else
3912 Insert_After (First_Comp, Comp_Decl);
3913 end if;
3914 end if;
3916 New_Scope (T);
3917 Analyze (Comp_Decl);
3918 Set_Ekind (Ent, E_Component);
3919 Init_Component_Location (Ent);
3921 -- Move the _controller entity ahead in the list of internal entities
3922 -- of the enclosing record so that it is selected instead of a
3923 -- potentially inherited one.
3925 declare
3926 E : constant Entity_Id := Last_Entity (T);
3927 Comp : Entity_Id;
3929 begin
3930 pragma Assert (Chars (E) = Name_uController);
3932 Set_Next_Entity (E, First_Entity (T));
3933 Set_First_Entity (T, E);
3935 Comp := Next_Entity (E);
3936 while Next_Entity (Comp) /= E loop
3937 Next_Entity (Comp);
3938 end loop;
3940 Set_Next_Entity (Comp, Empty);
3941 Set_Last_Entity (T, Comp);
3942 end;
3944 End_Scope;
3946 exception
3947 when RE_Not_Available =>
3948 return;
3949 end Expand_Record_Controller;
3951 ------------------------
3952 -- Expand_Tagged_Root --
3953 ------------------------
3955 procedure Expand_Tagged_Root (T : Entity_Id) is
3956 Def : constant Node_Id := Type_Definition (Parent (T));
3957 Comp_List : Node_Id;
3958 Comp_Decl : Node_Id;
3959 Sloc_N : Source_Ptr;
3961 begin
3962 if Null_Present (Def) then
3963 Set_Component_List (Def,
3964 Make_Component_List (Sloc (Def),
3965 Component_Items => Empty_List,
3966 Variant_Part => Empty,
3967 Null_Present => True));
3968 end if;
3970 Comp_List := Component_List (Def);
3972 if Null_Present (Comp_List)
3973 or else Is_Empty_List (Component_Items (Comp_List))
3974 then
3975 Sloc_N := Sloc (Comp_List);
3976 else
3977 Sloc_N := Sloc (First (Component_Items (Comp_List)));
3978 end if;
3980 Comp_Decl :=
3981 Make_Component_Declaration (Sloc_N,
3982 Defining_Identifier => First_Tag_Component (T),
3983 Component_Definition =>
3984 Make_Component_Definition (Sloc_N,
3985 Aliased_Present => False,
3986 Subtype_Indication => New_Reference_To (RTE (RE_Tag), Sloc_N)));
3988 if Null_Present (Comp_List)
3989 or else Is_Empty_List (Component_Items (Comp_List))
3990 then
3991 Set_Component_Items (Comp_List, New_List (Comp_Decl));
3992 Set_Null_Present (Comp_List, False);
3994 else
3995 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
3996 end if;
3998 -- We don't Analyze the whole expansion because the tag component has
3999 -- already been analyzed previously. Here we just insure that the tree
4000 -- is coherent with the semantic decoration
4002 Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
4004 exception
4005 when RE_Not_Available =>
4006 return;
4007 end Expand_Tagged_Root;
4009 -----------------------
4010 -- Freeze_Array_Type --
4011 -----------------------
4013 procedure Freeze_Array_Type (N : Node_Id) is
4014 Typ : constant Entity_Id := Entity (N);
4015 Base : constant Entity_Id := Base_Type (Typ);
4017 begin
4018 if not Is_Bit_Packed_Array (Typ) then
4020 -- If the component contains tasks, so does the array type. This may
4021 -- not be indicated in the array type because the component may have
4022 -- been a private type at the point of definition. Same if component
4023 -- type is controlled.
4025 Set_Has_Task (Base, Has_Task (Component_Type (Typ)));
4026 Set_Has_Controlled_Component (Base,
4027 Has_Controlled_Component (Component_Type (Typ))
4028 or else Is_Controlled (Component_Type (Typ)));
4030 if No (Init_Proc (Base)) then
4032 -- If this is an anonymous array created for a declaration with
4033 -- an initial value, its init_proc will never be called. The
4034 -- initial value itself may have been expanded into assign-
4035 -- ments, in which case the object declaration is carries the
4036 -- No_Initialization flag.
4038 if Is_Itype (Base)
4039 and then Nkind (Associated_Node_For_Itype (Base)) =
4040 N_Object_Declaration
4041 and then (Present (Expression (Associated_Node_For_Itype (Base)))
4042 or else
4043 No_Initialization (Associated_Node_For_Itype (Base)))
4044 then
4045 null;
4047 -- We do not need an init proc for string or wide [wide] string,
4048 -- since the only time these need initialization in normalize or
4049 -- initialize scalars mode, and these types are treated specially
4050 -- and do not need initialization procedures.
4052 elsif Root_Type (Base) = Standard_String
4053 or else Root_Type (Base) = Standard_Wide_String
4054 or else Root_Type (Base) = Standard_Wide_Wide_String
4055 then
4056 null;
4058 -- Otherwise we have to build an init proc for the subtype
4060 else
4061 Build_Array_Init_Proc (Base, N);
4062 end if;
4063 end if;
4065 if Typ = Base and then Has_Controlled_Component (Base) then
4066 Build_Controlling_Procs (Base);
4068 if not Is_Limited_Type (Component_Type (Typ))
4069 and then Number_Dimensions (Typ) = 1
4070 then
4071 Build_Slice_Assignment (Typ);
4072 end if;
4073 end if;
4075 -- For packed case, there is a default initialization, except if the
4076 -- component type is itself a packed structure with an initialization
4077 -- procedure.
4079 elsif Present (Init_Proc (Component_Type (Base)))
4080 and then No (Base_Init_Proc (Base))
4081 then
4082 Build_Array_Init_Proc (Base, N);
4083 end if;
4084 end Freeze_Array_Type;
4086 -----------------------------
4087 -- Freeze_Enumeration_Type --
4088 -----------------------------
4090 procedure Freeze_Enumeration_Type (N : Node_Id) is
4091 Typ : constant Entity_Id := Entity (N);
4092 Loc : constant Source_Ptr := Sloc (Typ);
4093 Ent : Entity_Id;
4094 Lst : List_Id;
4095 Num : Nat;
4096 Arr : Entity_Id;
4097 Fent : Entity_Id;
4098 Ityp : Entity_Id;
4099 Is_Contiguous : Boolean;
4100 Pos_Expr : Node_Id;
4101 Last_Repval : Uint;
4103 Func : Entity_Id;
4104 pragma Warnings (Off, Func);
4106 begin
4107 -- Various optimization are possible if the given representation is
4108 -- contiguous.
4110 Is_Contiguous := True;
4111 Ent := First_Literal (Typ);
4112 Last_Repval := Enumeration_Rep (Ent);
4113 Next_Literal (Ent);
4115 while Present (Ent) loop
4116 if Enumeration_Rep (Ent) - Last_Repval /= 1 then
4117 Is_Contiguous := False;
4118 exit;
4119 else
4120 Last_Repval := Enumeration_Rep (Ent);
4121 end if;
4123 Next_Literal (Ent);
4124 end loop;
4126 if Is_Contiguous then
4127 Set_Has_Contiguous_Rep (Typ);
4128 Ent := First_Literal (Typ);
4129 Num := 1;
4130 Lst := New_List (New_Reference_To (Ent, Sloc (Ent)));
4132 else
4133 -- Build list of literal references
4135 Lst := New_List;
4136 Num := 0;
4138 Ent := First_Literal (Typ);
4139 while Present (Ent) loop
4140 Append_To (Lst, New_Reference_To (Ent, Sloc (Ent)));
4141 Num := Num + 1;
4142 Next_Literal (Ent);
4143 end loop;
4144 end if;
4146 -- Now build an array declaration
4148 -- typA : array (Natural range 0 .. num - 1) of ctype :=
4149 -- (v, v, v, v, v, ....)
4151 -- where ctype is the corresponding integer type. If the representation
4152 -- is contiguous, we only keep the first literal, which provides the
4153 -- offset for Pos_To_Rep computations.
4155 Arr :=
4156 Make_Defining_Identifier (Loc,
4157 Chars => New_External_Name (Chars (Typ), 'A'));
4159 Append_Freeze_Action (Typ,
4160 Make_Object_Declaration (Loc,
4161 Defining_Identifier => Arr,
4162 Constant_Present => True,
4164 Object_Definition =>
4165 Make_Constrained_Array_Definition (Loc,
4166 Discrete_Subtype_Definitions => New_List (
4167 Make_Subtype_Indication (Loc,
4168 Subtype_Mark => New_Reference_To (Standard_Natural, Loc),
4169 Constraint =>
4170 Make_Range_Constraint (Loc,
4171 Range_Expression =>
4172 Make_Range (Loc,
4173 Low_Bound =>
4174 Make_Integer_Literal (Loc, 0),
4175 High_Bound =>
4176 Make_Integer_Literal (Loc, Num - 1))))),
4178 Component_Definition =>
4179 Make_Component_Definition (Loc,
4180 Aliased_Present => False,
4181 Subtype_Indication => New_Reference_To (Typ, Loc))),
4183 Expression =>
4184 Make_Aggregate (Loc,
4185 Expressions => Lst)));
4187 Set_Enum_Pos_To_Rep (Typ, Arr);
4189 -- Now we build the function that converts representation values to
4190 -- position values. This function has the form:
4192 -- function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
4193 -- begin
4194 -- case ityp!(A) is
4195 -- when enum-lit'Enum_Rep => return posval;
4196 -- when enum-lit'Enum_Rep => return posval;
4197 -- ...
4198 -- when others =>
4199 -- [raise Constraint_Error when F "invalid data"]
4200 -- return -1;
4201 -- end case;
4202 -- end;
4204 -- Note: the F parameter determines whether the others case (no valid
4205 -- representation) raises Constraint_Error or returns a unique value
4206 -- of minus one. The latter case is used, e.g. in 'Valid code.
4208 -- Note: the reason we use Enum_Rep values in the case here is to avoid
4209 -- the code generator making inappropriate assumptions about the range
4210 -- of the values in the case where the value is invalid. ityp is a
4211 -- signed or unsigned integer type of appropriate width.
4213 -- Note: if exceptions are not supported, then we suppress the raise
4214 -- and return -1 unconditionally (this is an erroneous program in any
4215 -- case and there is no obligation to raise Constraint_Error here!) We
4216 -- also do this if pragma Restrictions (No_Exceptions) is active.
4218 -- Representations are signed
4220 if Enumeration_Rep (First_Literal (Typ)) < 0 then
4222 -- The underlying type is signed. Reset the Is_Unsigned_Type
4223 -- explicitly, because it might have been inherited from
4224 -- parent type.
4226 Set_Is_Unsigned_Type (Typ, False);
4228 if Esize (Typ) <= Standard_Integer_Size then
4229 Ityp := Standard_Integer;
4230 else
4231 Ityp := Universal_Integer;
4232 end if;
4234 -- Representations are unsigned
4236 else
4237 if Esize (Typ) <= Standard_Integer_Size then
4238 Ityp := RTE (RE_Unsigned);
4239 else
4240 Ityp := RTE (RE_Long_Long_Unsigned);
4241 end if;
4242 end if;
4244 -- The body of the function is a case statement. First collect case
4245 -- alternatives, or optimize the contiguous case.
4247 Lst := New_List;
4249 -- If representation is contiguous, Pos is computed by subtracting
4250 -- the representation of the first literal.
4252 if Is_Contiguous then
4253 Ent := First_Literal (Typ);
4255 if Enumeration_Rep (Ent) = Last_Repval then
4257 -- Another special case: for a single literal, Pos is zero
4259 Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
4261 else
4262 Pos_Expr :=
4263 Convert_To (Standard_Integer,
4264 Make_Op_Subtract (Loc,
4265 Left_Opnd =>
4266 Unchecked_Convert_To (Ityp,
4267 Make_Identifier (Loc, Name_uA)),
4268 Right_Opnd =>
4269 Make_Integer_Literal (Loc,
4270 Intval =>
4271 Enumeration_Rep (First_Literal (Typ)))));
4272 end if;
4274 Append_To (Lst,
4275 Make_Case_Statement_Alternative (Loc,
4276 Discrete_Choices => New_List (
4277 Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
4278 Low_Bound =>
4279 Make_Integer_Literal (Loc,
4280 Intval => Enumeration_Rep (Ent)),
4281 High_Bound =>
4282 Make_Integer_Literal (Loc, Intval => Last_Repval))),
4284 Statements => New_List (
4285 Make_Return_Statement (Loc,
4286 Expression => Pos_Expr))));
4288 else
4289 Ent := First_Literal (Typ);
4291 while Present (Ent) loop
4292 Append_To (Lst,
4293 Make_Case_Statement_Alternative (Loc,
4294 Discrete_Choices => New_List (
4295 Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
4296 Intval => Enumeration_Rep (Ent))),
4298 Statements => New_List (
4299 Make_Return_Statement (Loc,
4300 Expression =>
4301 Make_Integer_Literal (Loc,
4302 Intval => Enumeration_Pos (Ent))))));
4304 Next_Literal (Ent);
4305 end loop;
4306 end if;
4308 -- In normal mode, add the others clause with the test
4310 if not Restriction_Active (No_Exception_Handlers) then
4311 Append_To (Lst,
4312 Make_Case_Statement_Alternative (Loc,
4313 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
4314 Statements => New_List (
4315 Make_Raise_Constraint_Error (Loc,
4316 Condition => Make_Identifier (Loc, Name_uF),
4317 Reason => CE_Invalid_Data),
4318 Make_Return_Statement (Loc,
4319 Expression =>
4320 Make_Integer_Literal (Loc, -1)))));
4322 -- If Restriction (No_Exceptions_Handlers) is active then we always
4323 -- return -1 (since we cannot usefully raise Constraint_Error in
4324 -- this case). See description above for further details.
4326 else
4327 Append_To (Lst,
4328 Make_Case_Statement_Alternative (Loc,
4329 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
4330 Statements => New_List (
4331 Make_Return_Statement (Loc,
4332 Expression =>
4333 Make_Integer_Literal (Loc, -1)))));
4334 end if;
4336 -- Now we can build the function body
4338 Fent :=
4339 Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
4341 Func :=
4342 Make_Subprogram_Body (Loc,
4343 Specification =>
4344 Make_Function_Specification (Loc,
4345 Defining_Unit_Name => Fent,
4346 Parameter_Specifications => New_List (
4347 Make_Parameter_Specification (Loc,
4348 Defining_Identifier =>
4349 Make_Defining_Identifier (Loc, Name_uA),
4350 Parameter_Type => New_Reference_To (Typ, Loc)),
4351 Make_Parameter_Specification (Loc,
4352 Defining_Identifier =>
4353 Make_Defining_Identifier (Loc, Name_uF),
4354 Parameter_Type => New_Reference_To (Standard_Boolean, Loc))),
4356 Result_Definition => New_Reference_To (Standard_Integer, Loc)),
4358 Declarations => Empty_List,
4360 Handled_Statement_Sequence =>
4361 Make_Handled_Sequence_Of_Statements (Loc,
4362 Statements => New_List (
4363 Make_Case_Statement (Loc,
4364 Expression =>
4365 Unchecked_Convert_To (Ityp,
4366 Make_Identifier (Loc, Name_uA)),
4367 Alternatives => Lst))));
4369 Set_TSS (Typ, Fent);
4370 Set_Is_Pure (Fent);
4372 if not Debug_Generated_Code then
4373 Set_Debug_Info_Off (Fent);
4374 end if;
4376 exception
4377 when RE_Not_Available =>
4378 return;
4379 end Freeze_Enumeration_Type;
4381 ------------------------
4382 -- Freeze_Record_Type --
4383 ------------------------
4385 procedure Freeze_Record_Type (N : Node_Id) is
4386 Comp : Entity_Id;
4387 Def_Id : constant Node_Id := Entity (N);
4388 Predef_List : List_Id;
4389 Type_Decl : constant Node_Id := Parent (Def_Id);
4391 Renamed_Eq : Node_Id := Empty;
4392 -- Could use some comments ???
4394 begin
4395 -- Build discriminant checking functions if not a derived type (for
4396 -- derived types that are not tagged types, we always use the
4397 -- discriminant checking functions of the parent type). However, for
4398 -- untagged types the derivation may have taken place before the
4399 -- parent was frozen, so we copy explicitly the discriminant checking
4400 -- functions from the parent into the components of the derived type.
4402 if not Is_Derived_Type (Def_Id)
4403 or else Has_New_Non_Standard_Rep (Def_Id)
4404 or else Is_Tagged_Type (Def_Id)
4405 then
4406 Build_Discr_Checking_Funcs (Type_Decl);
4408 elsif Is_Derived_Type (Def_Id)
4409 and then not Is_Tagged_Type (Def_Id)
4411 -- If we have a derived Unchecked_Union, we do not inherit the
4412 -- discriminant checking functions from the parent type since the
4413 -- discriminants are non existent.
4415 and then not Is_Unchecked_Union (Def_Id)
4416 and then Has_Discriminants (Def_Id)
4417 then
4418 declare
4419 Old_Comp : Entity_Id;
4421 begin
4422 Old_Comp :=
4423 First_Component (Base_Type (Underlying_Type (Etype (Def_Id))));
4424 Comp := First_Component (Def_Id);
4425 while Present (Comp) loop
4426 if Ekind (Comp) = E_Component
4427 and then Chars (Comp) = Chars (Old_Comp)
4428 then
4429 Set_Discriminant_Checking_Func (Comp,
4430 Discriminant_Checking_Func (Old_Comp));
4431 end if;
4433 Next_Component (Old_Comp);
4434 Next_Component (Comp);
4435 end loop;
4436 end;
4437 end if;
4439 if Is_Derived_Type (Def_Id)
4440 and then Is_Limited_Type (Def_Id)
4441 and then Is_Tagged_Type (Def_Id)
4442 then
4443 Check_Stream_Attributes (Def_Id);
4444 end if;
4446 -- Update task and controlled component flags, because some of the
4447 -- component types may have been private at the point of the record
4448 -- declaration.
4450 Comp := First_Component (Def_Id);
4452 while Present (Comp) loop
4453 if Has_Task (Etype (Comp)) then
4454 Set_Has_Task (Def_Id);
4456 elsif Has_Controlled_Component (Etype (Comp))
4457 or else (Chars (Comp) /= Name_uParent
4458 and then Is_Controlled (Etype (Comp)))
4459 then
4460 Set_Has_Controlled_Component (Def_Id);
4461 end if;
4463 Next_Component (Comp);
4464 end loop;
4466 -- Creation of the Dispatch Table. Note that a Dispatch Table is
4467 -- created for regular tagged types as well as for Ada types deriving
4468 -- from a C++ Class, but not for tagged types directly corresponding to
4469 -- the C++ classes. In the later case we assume that the Vtable is
4470 -- created in the C++ side and we just use it.
4472 if Is_Tagged_Type (Def_Id) then
4474 if Is_CPP_Class (Def_Id) then
4475 Set_All_DT_Position (Def_Id);
4476 Set_Default_Constructor (Def_Id);
4478 else
4479 -- Usually inherited primitives are not delayed but the first Ada
4480 -- extension of a CPP_Class is an exception since the address of
4481 -- the inherited subprogram has to be inserted in the new Ada
4482 -- Dispatch Table and this is a freezing action (usually the
4483 -- inherited primitive address is inserted in the DT by
4484 -- Inherit_DT)
4486 -- Similarly, if this is an inherited operation whose parent is
4487 -- not frozen yet, it is not in the DT of the parent, and we
4488 -- generate an explicit freeze node for the inherited operation,
4489 -- so that it is properly inserted in the DT of the current type.
4491 declare
4492 Elmt : Elmt_Id := First_Elmt (Primitive_Operations (Def_Id));
4493 Subp : Entity_Id;
4495 begin
4496 while Present (Elmt) loop
4497 Subp := Node (Elmt);
4499 if Present (Alias (Subp)) then
4500 if Is_CPP_Class (Etype (Def_Id)) then
4501 Set_Has_Delayed_Freeze (Subp);
4503 elsif Has_Delayed_Freeze (Alias (Subp))
4504 and then not Is_Frozen (Alias (Subp))
4505 then
4506 Set_Is_Frozen (Subp, False);
4507 Set_Has_Delayed_Freeze (Subp);
4508 end if;
4509 end if;
4511 Next_Elmt (Elmt);
4512 end loop;
4513 end;
4515 if Underlying_Type (Etype (Def_Id)) = Def_Id then
4516 Expand_Tagged_Root (Def_Id);
4517 end if;
4519 -- Unfreeze momentarily the type to add the predefined primitives
4520 -- operations. The reason we unfreeze is so that these predefined
4521 -- operations will indeed end up as primitive operations (which
4522 -- must be before the freeze point).
4524 Set_Is_Frozen (Def_Id, False);
4525 Make_Predefined_Primitive_Specs
4526 (Def_Id, Predef_List, Renamed_Eq);
4527 Insert_List_Before_And_Analyze (N, Predef_List);
4529 Set_Is_Frozen (Def_Id, True);
4530 Set_All_DT_Position (Def_Id);
4532 -- Add the controlled component before the freezing actions
4533 -- referenced in those actions.
4535 if Has_New_Controlled_Component (Def_Id) then
4536 Expand_Record_Controller (Def_Id);
4537 end if;
4539 -- Suppress creation of a dispatch table when Java_VM because the
4540 -- dispatching mechanism is handled internally by the JVM.
4542 if not Java_VM then
4544 -- Ada 2005 (AI-251): Build the secondary dispatch tables
4546 declare
4547 ADT : Elist_Id := Access_Disp_Table (Def_Id);
4549 procedure Add_Secondary_Tables (Typ : Entity_Id);
4550 -- Comment required ???
4552 --------------------------
4553 -- Add_Secondary_Tables --
4554 --------------------------
4556 procedure Add_Secondary_Tables (Typ : Entity_Id) is
4557 E : Entity_Id;
4558 Result : List_Id;
4560 begin
4561 if Etype (Typ) /= Typ then
4562 Add_Secondary_Tables (Etype (Typ));
4563 end if;
4565 if Present (Abstract_Interfaces (Typ))
4566 and then not Is_Empty_Elmt_List
4567 (Abstract_Interfaces (Typ))
4568 then
4569 E := First_Entity (Typ);
4570 while Present (E) loop
4571 if Is_Tag (E) and then Chars (E) /= Name_uTag then
4572 Make_Abstract_Interface_DT
4573 (AI_Tag => E,
4574 Acc_Disp_Tables => ADT,
4575 Result => Result);
4577 Append_Freeze_Actions (Def_Id, Result);
4578 end if;
4580 Next_Entity (E);
4581 end loop;
4582 end if;
4583 end Add_Secondary_Tables;
4585 -- Start of processing to build secondary dispatch tables
4587 begin
4588 Add_Secondary_Tables (Def_Id);
4589 Set_Access_Disp_Table (Def_Id, ADT);
4590 Append_Freeze_Actions (Def_Id, Make_DT (Def_Id));
4591 end;
4592 end if;
4594 -- Make sure that the primitives Initialize, Adjust and Finalize
4595 -- are Frozen before other TSS subprograms. We don't want them
4596 -- Frozen inside.
4598 if Is_Controlled (Def_Id) then
4599 if not Is_Limited_Type (Def_Id) then
4600 Append_Freeze_Actions (Def_Id,
4601 Freeze_Entity
4602 (Find_Prim_Op (Def_Id, Name_Adjust), Sloc (Def_Id)));
4603 end if;
4605 Append_Freeze_Actions (Def_Id,
4606 Freeze_Entity
4607 (Find_Prim_Op (Def_Id, Name_Initialize), Sloc (Def_Id)));
4609 Append_Freeze_Actions (Def_Id,
4610 Freeze_Entity
4611 (Find_Prim_Op (Def_Id, Name_Finalize), Sloc (Def_Id)));
4612 end if;
4614 -- Freeze rest of primitive operations
4616 Append_Freeze_Actions
4617 (Def_Id, Predefined_Primitive_Freeze (Def_Id));
4618 Append_Freeze_Actions
4619 (Def_Id, Init_Predefined_Interface_Primitives (Def_Id));
4620 end if;
4622 -- In the non-tagged case, an equality function is provided only for
4623 -- variant records (that are not unchecked unions).
4625 elsif Has_Discriminants (Def_Id)
4626 and then not Is_Limited_Type (Def_Id)
4627 then
4628 declare
4629 Comps : constant Node_Id :=
4630 Component_List (Type_Definition (Type_Decl));
4632 begin
4633 if Present (Comps)
4634 and then Present (Variant_Part (Comps))
4635 then
4636 Build_Variant_Record_Equality (Def_Id);
4637 end if;
4638 end;
4639 end if;
4641 -- Before building the record initialization procedure, if we are
4642 -- dealing with a concurrent record value type, then we must go through
4643 -- the discriminants, exchanging discriminals between the concurrent
4644 -- type and the concurrent record value type. See the section "Handling
4645 -- of Discriminants" in the Einfo spec for details.
4647 if Is_Concurrent_Record_Type (Def_Id)
4648 and then Has_Discriminants (Def_Id)
4649 then
4650 declare
4651 Ctyp : constant Entity_Id :=
4652 Corresponding_Concurrent_Type (Def_Id);
4653 Conc_Discr : Entity_Id;
4654 Rec_Discr : Entity_Id;
4655 Temp : Entity_Id;
4657 begin
4658 Conc_Discr := First_Discriminant (Ctyp);
4659 Rec_Discr := First_Discriminant (Def_Id);
4661 while Present (Conc_Discr) loop
4662 Temp := Discriminal (Conc_Discr);
4663 Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
4664 Set_Discriminal (Rec_Discr, Temp);
4666 Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
4667 Set_Discriminal_Link (Discriminal (Rec_Discr), Rec_Discr);
4669 Next_Discriminant (Conc_Discr);
4670 Next_Discriminant (Rec_Discr);
4671 end loop;
4672 end;
4673 end if;
4675 if Has_Controlled_Component (Def_Id) then
4676 if No (Controller_Component (Def_Id)) then
4677 Expand_Record_Controller (Def_Id);
4678 end if;
4680 Build_Controlling_Procs (Def_Id);
4681 end if;
4683 Adjust_Discriminants (Def_Id);
4684 Build_Record_Init_Proc (Type_Decl, Def_Id);
4686 -- For tagged type, build bodies of primitive operations. Note that we
4687 -- do this after building the record initialization experiment, since
4688 -- the primitive operations may need the initialization routine
4690 if Is_Tagged_Type (Def_Id) then
4691 Predef_List := Predefined_Primitive_Bodies (Def_Id, Renamed_Eq);
4692 Append_Freeze_Actions (Def_Id, Predef_List);
4694 -- Populate the two auxiliary tables used for dispatching
4695 -- asynchronous, conditional and timed selects for tagged
4696 -- types that implement a limited interface.
4698 if Ada_Version >= Ada_05
4699 and then not Is_Interface (Def_Id)
4700 and then not Is_Abstract (Def_Id)
4701 and then not Is_Controlled (Def_Id)
4702 and then Implements_Limited_Interface (Def_Id)
4703 then
4704 Append_Freeze_Actions (Def_Id, Make_Disp_Select_Tables (Def_Id));
4705 end if;
4706 end if;
4707 end Freeze_Record_Type;
4709 ------------------------------
4710 -- Freeze_Stream_Operations --
4711 ------------------------------
4713 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
4714 Names : constant array (1 .. 4) of TSS_Name_Type :=
4715 (TSS_Stream_Input,
4716 TSS_Stream_Output,
4717 TSS_Stream_Read,
4718 TSS_Stream_Write);
4719 Stream_Op : Entity_Id;
4721 begin
4722 -- Primitive operations of tagged types are frozen when the dispatch
4723 -- table is constructed.
4725 if not Comes_From_Source (Typ)
4726 or else Is_Tagged_Type (Typ)
4727 then
4728 return;
4729 end if;
4731 for J in Names'Range loop
4732 Stream_Op := TSS (Typ, Names (J));
4734 if Present (Stream_Op)
4735 and then Is_Subprogram (Stream_Op)
4736 and then Nkind (Unit_Declaration_Node (Stream_Op)) =
4737 N_Subprogram_Declaration
4738 and then not Is_Frozen (Stream_Op)
4739 then
4740 Append_Freeze_Actions
4741 (Typ, Freeze_Entity (Stream_Op, Sloc (N)));
4742 end if;
4743 end loop;
4744 end Freeze_Stream_Operations;
4746 -----------------
4747 -- Freeze_Type --
4748 -----------------
4750 -- Full type declarations are expanded at the point at which the type is
4751 -- frozen. The formal N is the Freeze_Node for the type. Any statements or
4752 -- declarations generated by the freezing (e.g. the procedure generated
4753 -- for initialization) are chained in the Actions field list of the freeze
4754 -- node using Append_Freeze_Actions.
4756 function Freeze_Type (N : Node_Id) return Boolean is
4757 Def_Id : constant Entity_Id := Entity (N);
4758 RACW_Seen : Boolean := False;
4759 Result : Boolean := False;
4761 begin
4762 -- Process associated access types needing special processing
4764 if Present (Access_Types_To_Process (N)) then
4765 declare
4766 E : Elmt_Id := First_Elmt (Access_Types_To_Process (N));
4767 begin
4768 while Present (E) loop
4770 if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
4771 RACW_Seen := True;
4772 end if;
4774 E := Next_Elmt (E);
4775 end loop;
4776 end;
4778 if RACW_Seen then
4780 -- If there are RACWs designating this type, make stubs now
4782 Remote_Types_Tagged_Full_View_Encountered (Def_Id);
4783 end if;
4784 end if;
4786 -- Freeze processing for record types
4788 if Is_Record_Type (Def_Id) then
4789 if Ekind (Def_Id) = E_Record_Type then
4790 Freeze_Record_Type (N);
4792 -- The subtype may have been declared before the type was frozen. If
4793 -- the type has controlled components it is necessary to create the
4794 -- entity for the controller explicitly because it did not exist at
4795 -- the point of the subtype declaration. Only the entity is needed,
4796 -- the back-end will obtain the layout from the type. This is only
4797 -- necessary if this is constrained subtype whose component list is
4798 -- not shared with the base type.
4800 elsif Ekind (Def_Id) = E_Record_Subtype
4801 and then Has_Discriminants (Def_Id)
4802 and then Last_Entity (Def_Id) /= Last_Entity (Base_Type (Def_Id))
4803 and then Present (Controller_Component (Def_Id))
4804 then
4805 declare
4806 Old_C : constant Entity_Id := Controller_Component (Def_Id);
4807 New_C : Entity_Id;
4809 begin
4810 if Scope (Old_C) = Base_Type (Def_Id) then
4812 -- The entity is the one in the parent. Create new one
4814 New_C := New_Copy (Old_C);
4815 Set_Parent (New_C, Parent (Old_C));
4816 New_Scope (Def_Id);
4817 Enter_Name (New_C);
4818 End_Scope;
4819 end if;
4820 end;
4822 if Is_Itype (Def_Id)
4823 and then Is_Record_Type (Underlying_Type (Scope (Def_Id)))
4824 then
4825 -- The freeze node is only used to introduce the controller,
4826 -- the back-end has no use for it for a discriminated
4827 -- component.
4829 Set_Freeze_Node (Def_Id, Empty);
4830 Set_Has_Delayed_Freeze (Def_Id, False);
4831 Result := True;
4832 end if;
4834 -- Similar process if the controller of the subtype is not present
4835 -- but the parent has it. This can happen with constrained
4836 -- record components where the subtype is an itype.
4838 elsif Ekind (Def_Id) = E_Record_Subtype
4839 and then Is_Itype (Def_Id)
4840 and then No (Controller_Component (Def_Id))
4841 and then Present (Controller_Component (Etype (Def_Id)))
4842 then
4843 declare
4844 Old_C : constant Entity_Id :=
4845 Controller_Component (Etype (Def_Id));
4846 New_C : constant Entity_Id := New_Copy (Old_C);
4848 begin
4849 Set_Next_Entity (New_C, First_Entity (Def_Id));
4850 Set_First_Entity (Def_Id, New_C);
4852 -- The freeze node is only used to introduce the controller,
4853 -- the back-end has no use for it for a discriminated
4854 -- component.
4856 Set_Freeze_Node (Def_Id, Empty);
4857 Set_Has_Delayed_Freeze (Def_Id, False);
4858 Result := True;
4859 end;
4860 end if;
4862 -- Freeze processing for array types
4864 elsif Is_Array_Type (Def_Id) then
4865 Freeze_Array_Type (N);
4867 -- Freeze processing for access types
4869 -- For pool-specific access types, find out the pool object used for
4870 -- this type, needs actual expansion of it in some cases. Here are the
4871 -- different cases :
4873 -- 1. Rep Clause "for Def_Id'Storage_Size use 0;"
4874 -- ---> don't use any storage pool
4876 -- 2. Rep Clause : for Def_Id'Storage_Size use Expr.
4877 -- Expand:
4878 -- Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
4880 -- 3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
4881 -- ---> Storage Pool is the specified one
4883 -- See GNAT Pool packages in the Run-Time for more details
4885 elsif Ekind (Def_Id) = E_Access_Type
4886 or else Ekind (Def_Id) = E_General_Access_Type
4887 then
4888 declare
4889 Loc : constant Source_Ptr := Sloc (N);
4890 Desig_Type : constant Entity_Id := Designated_Type (Def_Id);
4891 Pool_Object : Entity_Id;
4892 Siz_Exp : Node_Id;
4894 Freeze_Action_Typ : Entity_Id;
4896 begin
4897 if Has_Storage_Size_Clause (Def_Id) then
4898 Siz_Exp := Expression (Parent (Storage_Size_Variable (Def_Id)));
4899 else
4900 Siz_Exp := Empty;
4901 end if;
4903 -- Case 1
4905 -- Rep Clause "for Def_Id'Storage_Size use 0;"
4906 -- ---> don't use any storage pool
4908 if Has_Storage_Size_Clause (Def_Id)
4909 and then Compile_Time_Known_Value (Siz_Exp)
4910 and then Expr_Value (Siz_Exp) = 0
4911 then
4912 null;
4914 -- Case 2
4916 -- Rep Clause : for Def_Id'Storage_Size use Expr.
4917 -- ---> Expand:
4918 -- Def_Id__Pool : Stack_Bounded_Pool
4919 -- (Expr, DT'Size, DT'Alignment);
4921 elsif Has_Storage_Size_Clause (Def_Id) then
4922 declare
4923 DT_Size : Node_Id;
4924 DT_Align : Node_Id;
4926 begin
4927 -- For unconstrained composite types we give a size of zero
4928 -- so that the pool knows that it needs a special algorithm
4929 -- for variable size object allocation.
4931 if Is_Composite_Type (Desig_Type)
4932 and then not Is_Constrained (Desig_Type)
4933 then
4934 DT_Size :=
4935 Make_Integer_Literal (Loc, 0);
4937 DT_Align :=
4938 Make_Integer_Literal (Loc, Maximum_Alignment);
4940 else
4941 DT_Size :=
4942 Make_Attribute_Reference (Loc,
4943 Prefix => New_Reference_To (Desig_Type, Loc),
4944 Attribute_Name => Name_Max_Size_In_Storage_Elements);
4946 DT_Align :=
4947 Make_Attribute_Reference (Loc,
4948 Prefix => New_Reference_To (Desig_Type, Loc),
4949 Attribute_Name => Name_Alignment);
4950 end if;
4952 Pool_Object :=
4953 Make_Defining_Identifier (Loc,
4954 Chars => New_External_Name (Chars (Def_Id), 'P'));
4956 -- We put the code associated with the pools in the entity
4957 -- that has the later freeze node, usually the acces type
4958 -- but it can also be the designated_type; because the pool
4959 -- code requires both those types to be frozen
4961 if Is_Frozen (Desig_Type)
4962 and then (not Present (Freeze_Node (Desig_Type))
4963 or else Analyzed (Freeze_Node (Desig_Type)))
4964 then
4965 Freeze_Action_Typ := Def_Id;
4967 -- A Taft amendment type cannot get the freeze actions
4968 -- since the full view is not there.
4970 elsif Is_Incomplete_Or_Private_Type (Desig_Type)
4971 and then No (Full_View (Desig_Type))
4972 then
4973 Freeze_Action_Typ := Def_Id;
4975 else
4976 Freeze_Action_Typ := Desig_Type;
4977 end if;
4979 Append_Freeze_Action (Freeze_Action_Typ,
4980 Make_Object_Declaration (Loc,
4981 Defining_Identifier => Pool_Object,
4982 Object_Definition =>
4983 Make_Subtype_Indication (Loc,
4984 Subtype_Mark =>
4985 New_Reference_To
4986 (RTE (RE_Stack_Bounded_Pool), Loc),
4988 Constraint =>
4989 Make_Index_Or_Discriminant_Constraint (Loc,
4990 Constraints => New_List (
4992 -- First discriminant is the Pool Size
4994 New_Reference_To (
4995 Storage_Size_Variable (Def_Id), Loc),
4997 -- Second discriminant is the element size
4999 DT_Size,
5001 -- Third discriminant is the alignment
5003 DT_Align)))));
5004 end;
5006 Set_Associated_Storage_Pool (Def_Id, Pool_Object);
5008 -- Case 3
5010 -- Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
5011 -- ---> Storage Pool is the specified one
5013 elsif Present (Associated_Storage_Pool (Def_Id)) then
5015 -- Nothing to do the associated storage pool has been attached
5016 -- when analyzing the rep. clause
5018 null;
5019 end if;
5021 -- For access-to-controlled types (including class-wide types and
5022 -- Taft-amendment types which potentially have controlled
5023 -- components), expand the list controller object that will store
5024 -- the dynamically allocated objects. Do not do this
5025 -- transformation for expander-generated access types, but do it
5026 -- for types that are the full view of types derived from other
5027 -- private types. Also suppress the list controller in the case
5028 -- of a designated type with convention Java, since this is used
5029 -- when binding to Java API specs, where there's no equivalent of
5030 -- a finalization list and we don't want to pull in the
5031 -- finalization support if not needed.
5033 if not Comes_From_Source (Def_Id)
5034 and then not Has_Private_Declaration (Def_Id)
5035 then
5036 null;
5038 elsif (Controlled_Type (Desig_Type)
5039 and then Convention (Desig_Type) /= Convention_Java)
5040 or else
5041 (Is_Incomplete_Or_Private_Type (Desig_Type)
5042 and then No (Full_View (Desig_Type))
5044 -- An exception is made for types defined in the run-time
5045 -- because Ada.Tags.Tag itself is such a type and cannot
5046 -- afford this unnecessary overhead that would generates a
5047 -- loop in the expansion scheme...
5049 and then not In_Runtime (Def_Id)
5051 -- Another exception is if Restrictions (No_Finalization)
5052 -- is active, since then we know nothing is controlled.
5054 and then not Restriction_Active (No_Finalization))
5056 -- If the designated type is not frozen yet, its controlled
5057 -- status must be retrieved explicitly.
5059 or else (Is_Array_Type (Desig_Type)
5060 and then not Is_Frozen (Desig_Type)
5061 and then Controlled_Type (Component_Type (Desig_Type)))
5062 then
5063 Set_Associated_Final_Chain (Def_Id,
5064 Make_Defining_Identifier (Loc,
5065 New_External_Name (Chars (Def_Id), 'L')));
5067 Append_Freeze_Action (Def_Id,
5068 Make_Object_Declaration (Loc,
5069 Defining_Identifier => Associated_Final_Chain (Def_Id),
5070 Object_Definition =>
5071 New_Reference_To (RTE (RE_List_Controller), Loc)));
5072 end if;
5073 end;
5075 -- Freeze processing for enumeration types
5077 elsif Ekind (Def_Id) = E_Enumeration_Type then
5079 -- We only have something to do if we have a non-standard
5080 -- representation (i.e. at least one literal whose pos value
5081 -- is not the same as its representation)
5083 if Has_Non_Standard_Rep (Def_Id) then
5084 Freeze_Enumeration_Type (N);
5085 end if;
5087 -- Private types that are completed by a derivation from a private
5088 -- type have an internally generated full view, that needs to be
5089 -- frozen. This must be done explicitly because the two views share
5090 -- the freeze node, and the underlying full view is not visible when
5091 -- the freeze node is analyzed.
5093 elsif Is_Private_Type (Def_Id)
5094 and then Is_Derived_Type (Def_Id)
5095 and then Present (Full_View (Def_Id))
5096 and then Is_Itype (Full_View (Def_Id))
5097 and then Has_Private_Declaration (Full_View (Def_Id))
5098 and then Freeze_Node (Full_View (Def_Id)) = N
5099 then
5100 Set_Entity (N, Full_View (Def_Id));
5101 Result := Freeze_Type (N);
5102 Set_Entity (N, Def_Id);
5104 -- All other types require no expander action. There are such cases
5105 -- (e.g. task types and protected types). In such cases, the freeze
5106 -- nodes are there for use by Gigi.
5108 end if;
5110 Freeze_Stream_Operations (N, Def_Id);
5111 return Result;
5113 exception
5114 when RE_Not_Available =>
5115 return False;
5116 end Freeze_Type;
5118 -------------------------
5119 -- Get_Simple_Init_Val --
5120 -------------------------
5122 function Get_Simple_Init_Val
5123 (T : Entity_Id;
5124 Loc : Source_Ptr;
5125 Size : Uint := No_Uint) return Node_Id
5127 Val : Node_Id;
5128 Result : Node_Id;
5129 Val_RE : RE_Id;
5131 Size_To_Use : Uint;
5132 -- This is the size to be used for computation of the appropriate
5133 -- initial value for the Normalize_Scalars and Initialize_Scalars case.
5135 Lo_Bound : Uint;
5136 Hi_Bound : Uint;
5137 -- These are the values computed by the procedure Check_Subtype_Bounds
5139 procedure Check_Subtype_Bounds;
5140 -- This procedure examines the subtype T, and its ancestor subtypes and
5141 -- derived types to determine the best known information about the
5142 -- bounds of the subtype. After the call Lo_Bound is set either to
5143 -- No_Uint if no information can be determined, or to a value which
5144 -- represents a known low bound, i.e. a valid value of the subtype can
5145 -- not be less than this value. Hi_Bound is similarly set to a known
5146 -- high bound (valid value cannot be greater than this).
5148 --------------------------
5149 -- Check_Subtype_Bounds --
5150 --------------------------
5152 procedure Check_Subtype_Bounds is
5153 ST1 : Entity_Id;
5154 ST2 : Entity_Id;
5155 Lo : Node_Id;
5156 Hi : Node_Id;
5157 Loval : Uint;
5158 Hival : Uint;
5160 begin
5161 Lo_Bound := No_Uint;
5162 Hi_Bound := No_Uint;
5164 -- Loop to climb ancestor subtypes and derived types
5166 ST1 := T;
5167 loop
5168 if not Is_Discrete_Type (ST1) then
5169 return;
5170 end if;
5172 Lo := Type_Low_Bound (ST1);
5173 Hi := Type_High_Bound (ST1);
5175 if Compile_Time_Known_Value (Lo) then
5176 Loval := Expr_Value (Lo);
5178 if Lo_Bound = No_Uint or else Lo_Bound < Loval then
5179 Lo_Bound := Loval;
5180 end if;
5181 end if;
5183 if Compile_Time_Known_Value (Hi) then
5184 Hival := Expr_Value (Hi);
5186 if Hi_Bound = No_Uint or else Hi_Bound > Hival then
5187 Hi_Bound := Hival;
5188 end if;
5189 end if;
5191 ST2 := Ancestor_Subtype (ST1);
5193 if No (ST2) then
5194 ST2 := Etype (ST1);
5195 end if;
5197 exit when ST1 = ST2;
5198 ST1 := ST2;
5199 end loop;
5200 end Check_Subtype_Bounds;
5202 -- Start of processing for Get_Simple_Init_Val
5204 begin
5205 -- For a private type, we should always have an underlying type
5206 -- (because this was already checked in Needs_Simple_Initialization).
5207 -- What we do is to get the value for the underlying type and then do
5208 -- an Unchecked_Convert to the private type.
5210 if Is_Private_Type (T) then
5211 Val := Get_Simple_Init_Val (Underlying_Type (T), Loc, Size);
5213 -- A special case, if the underlying value is null, then qualify it
5214 -- with the underlying type, so that the null is properly typed
5215 -- Similarly, if it is an aggregate it must be qualified, because an
5216 -- unchecked conversion does not provide a context for it.
5218 if Nkind (Val) = N_Null
5219 or else Nkind (Val) = N_Aggregate
5220 then
5221 Val :=
5222 Make_Qualified_Expression (Loc,
5223 Subtype_Mark =>
5224 New_Occurrence_Of (Underlying_Type (T), Loc),
5225 Expression => Val);
5226 end if;
5228 Result := Unchecked_Convert_To (T, Val);
5230 -- Don't truncate result (important for Initialize/Normalize_Scalars)
5232 if Nkind (Result) = N_Unchecked_Type_Conversion
5233 and then Is_Scalar_Type (Underlying_Type (T))
5234 then
5235 Set_No_Truncation (Result);
5236 end if;
5238 return Result;
5240 -- For scalars, we must have normalize/initialize scalars case
5242 elsif Is_Scalar_Type (T) then
5243 pragma Assert (Init_Or_Norm_Scalars);
5245 -- Compute size of object. If it is given by the caller, we can use
5246 -- it directly, otherwise we use Esize (T) as an estimate. As far as
5247 -- we know this covers all cases correctly.
5249 if Size = No_Uint or else Size <= Uint_0 then
5250 Size_To_Use := UI_Max (Uint_1, Esize (T));
5251 else
5252 Size_To_Use := Size;
5253 end if;
5255 -- Maximum size to use is 64 bits, since we will create values
5256 -- of type Unsigned_64 and the range must fit this type.
5258 if Size_To_Use /= No_Uint and then Size_To_Use > Uint_64 then
5259 Size_To_Use := Uint_64;
5260 end if;
5262 -- Check known bounds of subtype
5264 Check_Subtype_Bounds;
5266 -- Processing for Normalize_Scalars case
5268 if Normalize_Scalars then
5270 -- If zero is invalid, it is a convenient value to use that is
5271 -- for sure an appropriate invalid value in all situations.
5273 if Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
5274 Val := Make_Integer_Literal (Loc, 0);
5276 -- Cases where all one bits is the appropriate invalid value
5278 -- For modular types, all 1 bits is either invalid or valid. If
5279 -- it is valid, then there is nothing that can be done since there
5280 -- are no invalid values (we ruled out zero already).
5282 -- For signed integer types that have no negative values, either
5283 -- there is room for negative values, or there is not. If there
5284 -- is, then all 1 bits may be interpretecd as minus one, which is
5285 -- certainly invalid. Alternatively it is treated as the largest
5286 -- positive value, in which case the observation for modular types
5287 -- still applies.
5289 -- For float types, all 1-bits is a NaN (not a number), which is
5290 -- certainly an appropriately invalid value.
5292 elsif Is_Unsigned_Type (T)
5293 or else Is_Floating_Point_Type (T)
5294 or else Is_Enumeration_Type (T)
5295 then
5296 Val := Make_Integer_Literal (Loc, 2 ** Size_To_Use - 1);
5298 -- Resolve as Unsigned_64, because the largest number we
5299 -- can generate is out of range of universal integer.
5301 Analyze_And_Resolve (Val, RTE (RE_Unsigned_64));
5303 -- Case of signed types
5305 else
5306 declare
5307 Signed_Size : constant Uint :=
5308 UI_Min (Uint_63, Size_To_Use - 1);
5310 begin
5311 -- Normally we like to use the most negative number. The
5312 -- one exception is when this number is in the known
5313 -- subtype range and the largest positive number is not in
5314 -- the known subtype range.
5316 -- For this exceptional case, use largest positive value
5318 if Lo_Bound /= No_Uint and then Hi_Bound /= No_Uint
5319 and then Lo_Bound <= (-(2 ** Signed_Size))
5320 and then Hi_Bound < 2 ** Signed_Size
5321 then
5322 Val := Make_Integer_Literal (Loc, 2 ** Signed_Size - 1);
5324 -- Normal case of largest negative value
5326 else
5327 Val := Make_Integer_Literal (Loc, -(2 ** Signed_Size));
5328 end if;
5329 end;
5330 end if;
5332 -- Here for Initialize_Scalars case
5334 else
5335 -- For float types, use float values from System.Scalar_Values
5337 if Is_Floating_Point_Type (T) then
5338 if Root_Type (T) = Standard_Short_Float then
5339 Val_RE := RE_IS_Isf;
5340 elsif Root_Type (T) = Standard_Float then
5341 Val_RE := RE_IS_Ifl;
5342 elsif Root_Type (T) = Standard_Long_Float then
5343 Val_RE := RE_IS_Ilf;
5344 else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
5345 Val_RE := RE_IS_Ill;
5346 end if;
5348 -- If zero is invalid, use zero values from System.Scalar_Values
5350 elsif Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
5351 if Size_To_Use <= 8 then
5352 Val_RE := RE_IS_Iz1;
5353 elsif Size_To_Use <= 16 then
5354 Val_RE := RE_IS_Iz2;
5355 elsif Size_To_Use <= 32 then
5356 Val_RE := RE_IS_Iz4;
5357 else
5358 Val_RE := RE_IS_Iz8;
5359 end if;
5361 -- For unsigned, use unsigned values from System.Scalar_Values
5363 elsif Is_Unsigned_Type (T) then
5364 if Size_To_Use <= 8 then
5365 Val_RE := RE_IS_Iu1;
5366 elsif Size_To_Use <= 16 then
5367 Val_RE := RE_IS_Iu2;
5368 elsif Size_To_Use <= 32 then
5369 Val_RE := RE_IS_Iu4;
5370 else
5371 Val_RE := RE_IS_Iu8;
5372 end if;
5374 -- For signed, use signed values from System.Scalar_Values
5376 else
5377 if Size_To_Use <= 8 then
5378 Val_RE := RE_IS_Is1;
5379 elsif Size_To_Use <= 16 then
5380 Val_RE := RE_IS_Is2;
5381 elsif Size_To_Use <= 32 then
5382 Val_RE := RE_IS_Is4;
5383 else
5384 Val_RE := RE_IS_Is8;
5385 end if;
5386 end if;
5388 Val := New_Occurrence_Of (RTE (Val_RE), Loc);
5389 end if;
5391 -- The final expression is obtained by doing an unchecked conversion
5392 -- of this result to the base type of the required subtype. We use
5393 -- the base type to avoid the unchecked conversion from chopping
5394 -- bits, and then we set Kill_Range_Check to preserve the "bad"
5395 -- value.
5397 Result := Unchecked_Convert_To (Base_Type (T), Val);
5399 -- Ensure result is not truncated, since we want the "bad" bits
5400 -- and also kill range check on result.
5402 if Nkind (Result) = N_Unchecked_Type_Conversion then
5403 Set_No_Truncation (Result);
5404 Set_Kill_Range_Check (Result, True);
5405 end if;
5407 return Result;
5409 -- String or Wide_[Wide]_String (must have Initialize_Scalars set)
5411 elsif Root_Type (T) = Standard_String
5412 or else
5413 Root_Type (T) = Standard_Wide_String
5414 or else
5415 Root_Type (T) = Standard_Wide_Wide_String
5416 then
5417 pragma Assert (Init_Or_Norm_Scalars);
5419 return
5420 Make_Aggregate (Loc,
5421 Component_Associations => New_List (
5422 Make_Component_Association (Loc,
5423 Choices => New_List (
5424 Make_Others_Choice (Loc)),
5425 Expression =>
5426 Get_Simple_Init_Val
5427 (Component_Type (T), Loc, Esize (Root_Type (T))))));
5429 -- Access type is initialized to null
5431 elsif Is_Access_Type (T) then
5432 return
5433 Make_Null (Loc);
5435 -- No other possibilities should arise, since we should only be
5436 -- calling Get_Simple_Init_Val if Needs_Simple_Initialization
5437 -- returned True, indicating one of the above cases held.
5439 else
5440 raise Program_Error;
5441 end if;
5443 exception
5444 when RE_Not_Available =>
5445 return Empty;
5446 end Get_Simple_Init_Val;
5448 ------------------------------
5449 -- Has_New_Non_Standard_Rep --
5450 ------------------------------
5452 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
5453 begin
5454 if not Is_Derived_Type (T) then
5455 return Has_Non_Standard_Rep (T)
5456 or else Has_Non_Standard_Rep (Root_Type (T));
5458 -- If Has_Non_Standard_Rep is not set on the derived type, the
5459 -- representation is fully inherited.
5461 elsif not Has_Non_Standard_Rep (T) then
5462 return False;
5464 else
5465 return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
5467 -- May need a more precise check here: the First_Rep_Item may
5468 -- be a stream attribute, which does not affect the representation
5469 -- of the type ???
5470 end if;
5471 end Has_New_Non_Standard_Rep;
5473 ----------------
5474 -- In_Runtime --
5475 ----------------
5477 function In_Runtime (E : Entity_Id) return Boolean is
5478 S1 : Entity_Id := Scope (E);
5480 begin
5481 while Scope (S1) /= Standard_Standard loop
5482 S1 := Scope (S1);
5483 end loop;
5485 return Chars (S1) = Name_System or else Chars (S1) = Name_Ada;
5486 end In_Runtime;
5488 ------------------
5489 -- Init_Formals --
5490 ------------------
5492 function Init_Formals (Typ : Entity_Id) return List_Id is
5493 Loc : constant Source_Ptr := Sloc (Typ);
5494 Formals : List_Id;
5496 begin
5497 -- First parameter is always _Init : in out typ. Note that we need
5498 -- this to be in/out because in the case of the task record value,
5499 -- there are default record fields (_Priority, _Size, -Task_Info)
5500 -- that may be referenced in the generated initialization routine.
5502 Formals := New_List (
5503 Make_Parameter_Specification (Loc,
5504 Defining_Identifier =>
5505 Make_Defining_Identifier (Loc, Name_uInit),
5506 In_Present => True,
5507 Out_Present => True,
5508 Parameter_Type => New_Reference_To (Typ, Loc)));
5510 -- For task record value, or type that contains tasks, add two more
5511 -- formals, _Master : Master_Id and _Chain : in out Activation_Chain
5512 -- We also add these parameters for the task record type case.
5514 if Has_Task (Typ)
5515 or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
5516 then
5517 Append_To (Formals,
5518 Make_Parameter_Specification (Loc,
5519 Defining_Identifier =>
5520 Make_Defining_Identifier (Loc, Name_uMaster),
5521 Parameter_Type => New_Reference_To (RTE (RE_Master_Id), Loc)));
5523 Append_To (Formals,
5524 Make_Parameter_Specification (Loc,
5525 Defining_Identifier =>
5526 Make_Defining_Identifier (Loc, Name_uChain),
5527 In_Present => True,
5528 Out_Present => True,
5529 Parameter_Type =>
5530 New_Reference_To (RTE (RE_Activation_Chain), Loc)));
5532 Append_To (Formals,
5533 Make_Parameter_Specification (Loc,
5534 Defining_Identifier =>
5535 Make_Defining_Identifier (Loc, Name_uTask_Name),
5536 In_Present => True,
5537 Parameter_Type =>
5538 New_Reference_To (Standard_String, Loc)));
5539 end if;
5541 return Formals;
5543 exception
5544 when RE_Not_Available =>
5545 return Empty_List;
5546 end Init_Formals;
5548 ------------------
5549 -- Make_Eq_Case --
5550 ------------------
5552 -- <Make_Eq_if shared components>
5553 -- case X.D1 is
5554 -- when V1 => <Make_Eq_Case> on subcomponents
5555 -- ...
5556 -- when Vn => <Make_Eq_Case> on subcomponents
5557 -- end case;
5559 function Make_Eq_Case
5560 (E : Entity_Id;
5561 CL : Node_Id;
5562 Discr : Entity_Id := Empty) return List_Id
5564 Loc : constant Source_Ptr := Sloc (E);
5565 Result : constant List_Id := New_List;
5566 Variant : Node_Id;
5567 Alt_List : List_Id;
5569 begin
5570 Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
5572 if No (Variant_Part (CL)) then
5573 return Result;
5574 end if;
5576 Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
5578 if No (Variant) then
5579 return Result;
5580 end if;
5582 Alt_List := New_List;
5584 while Present (Variant) loop
5585 Append_To (Alt_List,
5586 Make_Case_Statement_Alternative (Loc,
5587 Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
5588 Statements => Make_Eq_Case (E, Component_List (Variant))));
5590 Next_Non_Pragma (Variant);
5591 end loop;
5593 -- If we have an Unchecked_Union, use one of the parameters that
5594 -- captures the discriminants.
5596 if Is_Unchecked_Union (E) then
5597 Append_To (Result,
5598 Make_Case_Statement (Loc,
5599 Expression => New_Reference_To (Discr, Loc),
5600 Alternatives => Alt_List));
5602 else
5603 Append_To (Result,
5604 Make_Case_Statement (Loc,
5605 Expression =>
5606 Make_Selected_Component (Loc,
5607 Prefix => Make_Identifier (Loc, Name_X),
5608 Selector_Name => New_Copy (Name (Variant_Part (CL)))),
5609 Alternatives => Alt_List));
5610 end if;
5612 return Result;
5613 end Make_Eq_Case;
5615 ----------------
5616 -- Make_Eq_If --
5617 ----------------
5619 -- Generates:
5621 -- if
5622 -- X.C1 /= Y.C1
5623 -- or else
5624 -- X.C2 /= Y.C2
5625 -- ...
5626 -- then
5627 -- return False;
5628 -- end if;
5630 -- or a null statement if the list L is empty
5632 function Make_Eq_If
5633 (E : Entity_Id;
5634 L : List_Id) return Node_Id
5636 Loc : constant Source_Ptr := Sloc (E);
5637 C : Node_Id;
5638 Field_Name : Name_Id;
5639 Cond : Node_Id;
5641 begin
5642 if No (L) then
5643 return Make_Null_Statement (Loc);
5645 else
5646 Cond := Empty;
5648 C := First_Non_Pragma (L);
5649 while Present (C) loop
5650 Field_Name := Chars (Defining_Identifier (C));
5652 -- The tags must not be compared they are not part of the value.
5653 -- Note also that in the following, we use Make_Identifier for
5654 -- the component names. Use of New_Reference_To to identify the
5655 -- components would be incorrect because the wrong entities for
5656 -- discriminants could be picked up in the private type case.
5658 if Field_Name /= Name_uTag then
5659 Evolve_Or_Else (Cond,
5660 Make_Op_Ne (Loc,
5661 Left_Opnd =>
5662 Make_Selected_Component (Loc,
5663 Prefix => Make_Identifier (Loc, Name_X),
5664 Selector_Name =>
5665 Make_Identifier (Loc, Field_Name)),
5667 Right_Opnd =>
5668 Make_Selected_Component (Loc,
5669 Prefix => Make_Identifier (Loc, Name_Y),
5670 Selector_Name =>
5671 Make_Identifier (Loc, Field_Name))));
5672 end if;
5674 Next_Non_Pragma (C);
5675 end loop;
5677 if No (Cond) then
5678 return Make_Null_Statement (Loc);
5680 else
5681 return
5682 Make_Implicit_If_Statement (E,
5683 Condition => Cond,
5684 Then_Statements => New_List (
5685 Make_Return_Statement (Loc,
5686 Expression => New_Occurrence_Of (Standard_False, Loc))));
5687 end if;
5688 end if;
5689 end Make_Eq_If;
5691 -------------------------------------
5692 -- Make_Predefined_Primitive_Specs --
5693 -------------------------------------
5695 procedure Make_Predefined_Primitive_Specs
5696 (Tag_Typ : Entity_Id;
5697 Predef_List : out List_Id;
5698 Renamed_Eq : out Node_Id)
5700 Loc : constant Source_Ptr := Sloc (Tag_Typ);
5701 Res : constant List_Id := New_List;
5702 Prim : Elmt_Id;
5703 Eq_Needed : Boolean;
5704 Eq_Spec : Node_Id;
5705 Eq_Name : Name_Id := Name_Op_Eq;
5707 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
5708 -- Returns true if Prim is a renaming of an unresolved predefined
5709 -- equality operation.
5711 -------------------------------
5712 -- Is_Predefined_Eq_Renaming --
5713 -------------------------------
5715 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
5716 begin
5717 return Chars (Prim) /= Name_Op_Eq
5718 and then Present (Alias (Prim))
5719 and then Comes_From_Source (Prim)
5720 and then Is_Intrinsic_Subprogram (Alias (Prim))
5721 and then Chars (Alias (Prim)) = Name_Op_Eq;
5722 end Is_Predefined_Eq_Renaming;
5724 -- Start of processing for Make_Predefined_Primitive_Specs
5726 begin
5727 Renamed_Eq := Empty;
5729 -- Spec of _Size
5731 Append_To (Res, Predef_Spec_Or_Body (Loc,
5732 Tag_Typ => Tag_Typ,
5733 Name => Name_uSize,
5734 Profile => New_List (
5735 Make_Parameter_Specification (Loc,
5736 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5737 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
5739 Ret_Type => Standard_Long_Long_Integer));
5741 -- Spec of _Alignment
5743 Append_To (Res, Predef_Spec_Or_Body (Loc,
5744 Tag_Typ => Tag_Typ,
5745 Name => Name_uAlignment,
5746 Profile => New_List (
5747 Make_Parameter_Specification (Loc,
5748 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5749 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
5751 Ret_Type => Standard_Integer));
5753 -- Specs for dispatching stream attributes
5755 declare
5756 Stream_Op_TSS_Names :
5757 constant array (Integer range <>) of TSS_Name_Type :=
5758 (TSS_Stream_Read,
5759 TSS_Stream_Write,
5760 TSS_Stream_Input,
5761 TSS_Stream_Output);
5762 begin
5763 for Op in Stream_Op_TSS_Names'Range loop
5764 if Stream_Operation_OK (Tag_Typ, Stream_Op_TSS_Names (Op)) then
5765 Append_To (Res,
5766 Predef_Stream_Attr_Spec (Loc, Tag_Typ,
5767 Stream_Op_TSS_Names (Op)));
5768 end if;
5769 end loop;
5770 end;
5772 -- Spec of "=" if expanded if the type is not limited and if a
5773 -- user defined "=" was not already declared for the non-full
5774 -- view of a private extension
5776 if not Is_Limited_Type (Tag_Typ) then
5777 Eq_Needed := True;
5779 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
5780 while Present (Prim) loop
5782 -- If a primitive is encountered that renames the predefined
5783 -- equality operator before reaching any explicit equality
5784 -- primitive, then we still need to create a predefined
5785 -- equality function, because calls to it can occur via
5786 -- the renaming. A new name is created for the equality
5787 -- to avoid conflicting with any user-defined equality.
5788 -- (Note that this doesn't account for renamings of
5789 -- equality nested within subpackages???)
5791 if Is_Predefined_Eq_Renaming (Node (Prim)) then
5792 Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
5794 elsif Chars (Node (Prim)) = Name_Op_Eq
5795 and then (No (Alias (Node (Prim)))
5796 or else Nkind (Unit_Declaration_Node (Node (Prim))) =
5797 N_Subprogram_Renaming_Declaration)
5798 and then Etype (First_Formal (Node (Prim))) =
5799 Etype (Next_Formal (First_Formal (Node (Prim))))
5800 and then Base_Type (Etype (Node (Prim))) = Standard_Boolean
5802 then
5803 Eq_Needed := False;
5804 exit;
5806 -- If the parent equality is abstract, the inherited equality is
5807 -- abstract as well, and no body can be created for for it.
5809 elsif Chars (Node (Prim)) = Name_Op_Eq
5810 and then Present (Alias (Node (Prim)))
5811 and then Is_Abstract (Alias (Node (Prim)))
5812 then
5813 Eq_Needed := False;
5814 exit;
5815 end if;
5817 Next_Elmt (Prim);
5818 end loop;
5820 -- If a renaming of predefined equality was found
5821 -- but there was no user-defined equality (so Eq_Needed
5822 -- is still true), then set the name back to Name_Op_Eq.
5823 -- But in the case where a user-defined equality was
5824 -- located after such a renaming, then the predefined
5825 -- equality function is still needed, so Eq_Needed must
5826 -- be set back to True.
5828 if Eq_Name /= Name_Op_Eq then
5829 if Eq_Needed then
5830 Eq_Name := Name_Op_Eq;
5831 else
5832 Eq_Needed := True;
5833 end if;
5834 end if;
5836 if Eq_Needed then
5837 Eq_Spec := Predef_Spec_Or_Body (Loc,
5838 Tag_Typ => Tag_Typ,
5839 Name => Eq_Name,
5840 Profile => New_List (
5841 Make_Parameter_Specification (Loc,
5842 Defining_Identifier =>
5843 Make_Defining_Identifier (Loc, Name_X),
5844 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
5845 Make_Parameter_Specification (Loc,
5846 Defining_Identifier =>
5847 Make_Defining_Identifier (Loc, Name_Y),
5848 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
5849 Ret_Type => Standard_Boolean);
5850 Append_To (Res, Eq_Spec);
5852 if Eq_Name /= Name_Op_Eq then
5853 Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
5855 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
5856 while Present (Prim) loop
5858 -- Any renamings of equality that appeared before an
5859 -- overriding equality must be updated to refer to
5860 -- the entity for the predefined equality, otherwise
5861 -- calls via the renaming would get incorrectly
5862 -- resolved to call the user-defined equality function.
5864 if Is_Predefined_Eq_Renaming (Node (Prim)) then
5865 Set_Alias (Node (Prim), Renamed_Eq);
5867 -- Exit upon encountering a user-defined equality
5869 elsif Chars (Node (Prim)) = Name_Op_Eq
5870 and then No (Alias (Node (Prim)))
5871 then
5872 exit;
5873 end if;
5875 Next_Elmt (Prim);
5876 end loop;
5877 end if;
5878 end if;
5880 -- Spec for dispatching assignment
5882 Append_To (Res, Predef_Spec_Or_Body (Loc,
5883 Tag_Typ => Tag_Typ,
5884 Name => Name_uAssign,
5885 Profile => New_List (
5886 Make_Parameter_Specification (Loc,
5887 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5888 Out_Present => True,
5889 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
5891 Make_Parameter_Specification (Loc,
5892 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
5893 Parameter_Type => New_Reference_To (Tag_Typ, Loc)))));
5894 end if;
5896 -- Generate the declarations for the following primitive operations:
5897 -- disp_asynchronous_select
5898 -- disp_conditional_select
5899 -- disp_get_prim_op_kind
5900 -- disp_timed_select
5901 -- for limited interfaces and tagged types that implement a limited
5902 -- interface.
5904 if Ada_Version >= Ada_05
5905 and then
5906 ((Is_Interface (Tag_Typ)
5907 and then Is_Limited_Record (Tag_Typ))
5908 or else
5909 (not Is_Abstract (Tag_Typ)
5910 and then not Is_Controlled (Tag_Typ)
5911 and then Implements_Limited_Interface (Tag_Typ)))
5912 then
5913 if Is_Interface (Tag_Typ) then
5914 Append_To (Res,
5915 Make_Abstract_Subprogram_Declaration (Loc,
5916 Specification =>
5917 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
5919 Append_To (Res,
5920 Make_Abstract_Subprogram_Declaration (Loc,
5921 Specification =>
5922 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
5924 Append_To (Res,
5925 Make_Abstract_Subprogram_Declaration (Loc,
5926 Specification =>
5927 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
5929 Append_To (Res,
5930 Make_Abstract_Subprogram_Declaration (Loc,
5931 Specification =>
5932 Make_Disp_Timed_Select_Spec (Tag_Typ)));
5934 else
5935 Append_To (Res,
5936 Make_Subprogram_Declaration (Loc,
5937 Specification =>
5938 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
5940 Append_To (Res,
5941 Make_Subprogram_Declaration (Loc,
5942 Specification =>
5943 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
5945 Append_To (Res,
5946 Make_Subprogram_Declaration (Loc,
5947 Specification =>
5948 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
5950 Append_To (Res,
5951 Make_Subprogram_Declaration (Loc,
5952 Specification =>
5953 Make_Disp_Timed_Select_Spec (Tag_Typ)));
5954 end if;
5955 end if;
5957 -- Specs for finalization actions that may be required in case a
5958 -- future extension contain a controlled element. We generate those
5959 -- only for root tagged types where they will get dummy bodies or
5960 -- when the type has controlled components and their body must be
5961 -- generated. It is also impossible to provide those for tagged
5962 -- types defined within s-finimp since it would involve circularity
5963 -- problems
5965 if In_Finalization_Root (Tag_Typ) then
5966 null;
5968 -- We also skip these if finalization is not available
5970 elsif Restriction_Active (No_Finalization) then
5971 null;
5973 elsif Etype (Tag_Typ) = Tag_Typ or else Controlled_Type (Tag_Typ) then
5974 if not Is_Limited_Type (Tag_Typ) then
5975 Append_To (Res,
5976 Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
5977 end if;
5979 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
5980 end if;
5982 Predef_List := Res;
5983 end Make_Predefined_Primitive_Specs;
5985 ---------------------------------
5986 -- Needs_Simple_Initialization --
5987 ---------------------------------
5989 function Needs_Simple_Initialization (T : Entity_Id) return Boolean is
5990 begin
5991 -- Check for private type, in which case test applies to the
5992 -- underlying type of the private type.
5994 if Is_Private_Type (T) then
5995 declare
5996 RT : constant Entity_Id := Underlying_Type (T);
5998 begin
5999 if Present (RT) then
6000 return Needs_Simple_Initialization (RT);
6001 else
6002 return False;
6003 end if;
6004 end;
6006 -- Cases needing simple initialization are access types, and, if pragma
6007 -- Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
6008 -- types.
6010 elsif Is_Access_Type (T)
6011 or else (Init_Or_Norm_Scalars and then (Is_Scalar_Type (T)))
6012 then
6013 return True;
6015 -- If Initialize/Normalize_Scalars is in effect, string objects also
6016 -- need initialization, unless they are created in the course of
6017 -- expanding an aggregate (since in the latter case they will be
6018 -- filled with appropriate initializing values before they are used).
6020 elsif Init_Or_Norm_Scalars
6021 and then
6022 (Root_Type (T) = Standard_String
6023 or else Root_Type (T) = Standard_Wide_String
6024 or else Root_Type (T) = Standard_Wide_Wide_String)
6025 and then
6026 (not Is_Itype (T)
6027 or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
6028 then
6029 return True;
6031 else
6032 return False;
6033 end if;
6034 end Needs_Simple_Initialization;
6036 ----------------------
6037 -- Predef_Deep_Spec --
6038 ----------------------
6040 function Predef_Deep_Spec
6041 (Loc : Source_Ptr;
6042 Tag_Typ : Entity_Id;
6043 Name : TSS_Name_Type;
6044 For_Body : Boolean := False) return Node_Id
6046 Prof : List_Id;
6047 Type_B : Entity_Id;
6049 begin
6050 if Name = TSS_Deep_Finalize then
6051 Prof := New_List;
6052 Type_B := Standard_Boolean;
6054 else
6055 Prof := New_List (
6056 Make_Parameter_Specification (Loc,
6057 Defining_Identifier => Make_Defining_Identifier (Loc, Name_L),
6058 In_Present => True,
6059 Out_Present => True,
6060 Parameter_Type =>
6061 New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
6062 Type_B := Standard_Short_Short_Integer;
6063 end if;
6065 Append_To (Prof,
6066 Make_Parameter_Specification (Loc,
6067 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
6068 In_Present => True,
6069 Out_Present => True,
6070 Parameter_Type => New_Reference_To (Tag_Typ, Loc)));
6072 Append_To (Prof,
6073 Make_Parameter_Specification (Loc,
6074 Defining_Identifier => Make_Defining_Identifier (Loc, Name_B),
6075 Parameter_Type => New_Reference_To (Type_B, Loc)));
6077 return Predef_Spec_Or_Body (Loc,
6078 Name => Make_TSS_Name (Tag_Typ, Name),
6079 Tag_Typ => Tag_Typ,
6080 Profile => Prof,
6081 For_Body => For_Body);
6083 exception
6084 when RE_Not_Available =>
6085 return Empty;
6086 end Predef_Deep_Spec;
6088 -------------------------
6089 -- Predef_Spec_Or_Body --
6090 -------------------------
6092 function Predef_Spec_Or_Body
6093 (Loc : Source_Ptr;
6094 Tag_Typ : Entity_Id;
6095 Name : Name_Id;
6096 Profile : List_Id;
6097 Ret_Type : Entity_Id := Empty;
6098 For_Body : Boolean := False) return Node_Id
6100 Id : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
6101 Spec : Node_Id;
6103 begin
6104 Set_Is_Public (Id, Is_Public (Tag_Typ));
6106 -- The internal flag is set to mark these declarations because
6107 -- they have specific properties. First they are primitives even
6108 -- if they are not defined in the type scope (the freezing point
6109 -- is not necessarily in the same scope), furthermore the
6110 -- predefined equality can be overridden by a user-defined
6111 -- equality, no body will be generated in this case.
6113 Set_Is_Internal (Id);
6115 if not Debug_Generated_Code then
6116 Set_Debug_Info_Off (Id);
6117 end if;
6119 if No (Ret_Type) then
6120 Spec :=
6121 Make_Procedure_Specification (Loc,
6122 Defining_Unit_Name => Id,
6123 Parameter_Specifications => Profile);
6124 else
6125 Spec :=
6126 Make_Function_Specification (Loc,
6127 Defining_Unit_Name => Id,
6128 Parameter_Specifications => Profile,
6129 Result_Definition =>
6130 New_Reference_To (Ret_Type, Loc));
6131 end if;
6133 -- If body case, return empty subprogram body. Note that this is
6134 -- ill-formed, because there is not even a null statement, and
6135 -- certainly not a return in the function case. The caller is
6136 -- expected to do surgery on the body to add the appropriate stuff.
6138 if For_Body then
6139 return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
6141 -- For the case of Input/Output attributes applied to an abstract type,
6142 -- generate abstract specifications. These will never be called,
6143 -- but we need the slots allocated in the dispatching table so
6144 -- that typ'Class'Input and typ'Class'Output will work properly.
6146 elsif (Is_TSS (Name, TSS_Stream_Input)
6147 or else
6148 Is_TSS (Name, TSS_Stream_Output))
6149 and then Is_Abstract (Tag_Typ)
6150 then
6151 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
6153 -- Normal spec case, where we return a subprogram declaration
6155 else
6156 return Make_Subprogram_Declaration (Loc, Spec);
6157 end if;
6158 end Predef_Spec_Or_Body;
6160 -----------------------------
6161 -- Predef_Stream_Attr_Spec --
6162 -----------------------------
6164 function Predef_Stream_Attr_Spec
6165 (Loc : Source_Ptr;
6166 Tag_Typ : Entity_Id;
6167 Name : TSS_Name_Type;
6168 For_Body : Boolean := False) return Node_Id
6170 Ret_Type : Entity_Id;
6172 begin
6173 if Name = TSS_Stream_Input then
6174 Ret_Type := Tag_Typ;
6175 else
6176 Ret_Type := Empty;
6177 end if;
6179 return Predef_Spec_Or_Body (Loc,
6180 Name => Make_TSS_Name (Tag_Typ, Name),
6181 Tag_Typ => Tag_Typ,
6182 Profile => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
6183 Ret_Type => Ret_Type,
6184 For_Body => For_Body);
6185 end Predef_Stream_Attr_Spec;
6187 ---------------------------------
6188 -- Predefined_Primitive_Bodies --
6189 ---------------------------------
6191 function Predefined_Primitive_Bodies
6192 (Tag_Typ : Entity_Id;
6193 Renamed_Eq : Node_Id) return List_Id
6195 Loc : constant Source_Ptr := Sloc (Tag_Typ);
6196 Res : constant List_Id := New_List;
6197 Decl : Node_Id;
6198 Prim : Elmt_Id;
6199 Eq_Needed : Boolean;
6200 Eq_Name : Name_Id;
6201 Ent : Entity_Id;
6203 begin
6204 -- See if we have a predefined "=" operator
6206 if Present (Renamed_Eq) then
6207 Eq_Needed := True;
6208 Eq_Name := Chars (Renamed_Eq);
6210 else
6211 Eq_Needed := False;
6212 Eq_Name := No_Name;
6214 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
6215 while Present (Prim) loop
6216 if Chars (Node (Prim)) = Name_Op_Eq
6217 and then Is_Internal (Node (Prim))
6218 then
6219 Eq_Needed := True;
6220 Eq_Name := Name_Op_Eq;
6221 end if;
6223 Next_Elmt (Prim);
6224 end loop;
6225 end if;
6227 -- Body of _Alignment
6229 Decl := Predef_Spec_Or_Body (Loc,
6230 Tag_Typ => Tag_Typ,
6231 Name => Name_uAlignment,
6232 Profile => New_List (
6233 Make_Parameter_Specification (Loc,
6234 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
6235 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
6237 Ret_Type => Standard_Integer,
6238 For_Body => True);
6240 Set_Handled_Statement_Sequence (Decl,
6241 Make_Handled_Sequence_Of_Statements (Loc, New_List (
6242 Make_Return_Statement (Loc,
6243 Expression =>
6244 Make_Attribute_Reference (Loc,
6245 Prefix => Make_Identifier (Loc, Name_X),
6246 Attribute_Name => Name_Alignment)))));
6248 Append_To (Res, Decl);
6250 -- Body of _Size
6252 Decl := Predef_Spec_Or_Body (Loc,
6253 Tag_Typ => Tag_Typ,
6254 Name => Name_uSize,
6255 Profile => New_List (
6256 Make_Parameter_Specification (Loc,
6257 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
6258 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
6260 Ret_Type => Standard_Long_Long_Integer,
6261 For_Body => True);
6263 Set_Handled_Statement_Sequence (Decl,
6264 Make_Handled_Sequence_Of_Statements (Loc, New_List (
6265 Make_Return_Statement (Loc,
6266 Expression =>
6267 Make_Attribute_Reference (Loc,
6268 Prefix => Make_Identifier (Loc, Name_X),
6269 Attribute_Name => Name_Size)))));
6271 Append_To (Res, Decl);
6273 -- Bodies for Dispatching stream IO routines. We need these only for
6274 -- non-limited types (in the limited case there is no dispatching).
6275 -- We also skip them if dispatching or finalization are not available.
6277 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Read)
6278 and then No (TSS (Tag_Typ, TSS_Stream_Read))
6279 then
6280 Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
6281 Append_To (Res, Decl);
6282 end if;
6284 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Write)
6285 and then No (TSS (Tag_Typ, TSS_Stream_Write))
6286 then
6287 Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
6288 Append_To (Res, Decl);
6289 end if;
6291 -- Skip bodies of _Input and _Output for the abstract case, since
6292 -- the corresponding specs are abstract (see Predef_Spec_Or_Body)
6294 if not Is_Abstract (Tag_Typ) then
6295 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Input)
6296 and then No (TSS (Tag_Typ, TSS_Stream_Input))
6297 then
6298 Build_Record_Or_Elementary_Input_Function
6299 (Loc, Tag_Typ, Decl, Ent);
6300 Append_To (Res, Decl);
6301 end if;
6303 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Output)
6304 and then No (TSS (Tag_Typ, TSS_Stream_Output))
6305 then
6306 Build_Record_Or_Elementary_Output_Procedure
6307 (Loc, Tag_Typ, Decl, Ent);
6308 Append_To (Res, Decl);
6309 end if;
6310 end if;
6312 -- Generate the bodies for the following primitive operations:
6313 -- disp_asynchronous_select
6314 -- disp_conditional_select
6315 -- disp_get_prim_op_kind
6316 -- disp_timed_select
6317 -- for tagged types that implement a limited interface.
6319 if Ada_Version >= Ada_05
6320 and then not Is_Interface (Tag_Typ)
6321 and then not Is_Abstract (Tag_Typ)
6322 and then not Is_Controlled (Tag_Typ)
6323 and then Implements_Limited_Interface (Tag_Typ)
6324 then
6325 Append_To (Res,
6326 Make_Disp_Asynchronous_Select_Body (Tag_Typ));
6327 Append_To (Res,
6328 Make_Disp_Conditional_Select_Body (Tag_Typ));
6329 Append_To (Res,
6330 Make_Disp_Get_Prim_Op_Kind_Body (Tag_Typ));
6331 Append_To (Res,
6332 Make_Disp_Timed_Select_Body (Tag_Typ));
6333 end if;
6335 if not Is_Limited_Type (Tag_Typ) then
6337 -- Body for equality
6339 if Eq_Needed then
6341 Decl := Predef_Spec_Or_Body (Loc,
6342 Tag_Typ => Tag_Typ,
6343 Name => Eq_Name,
6344 Profile => New_List (
6345 Make_Parameter_Specification (Loc,
6346 Defining_Identifier =>
6347 Make_Defining_Identifier (Loc, Name_X),
6348 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
6350 Make_Parameter_Specification (Loc,
6351 Defining_Identifier =>
6352 Make_Defining_Identifier (Loc, Name_Y),
6353 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
6355 Ret_Type => Standard_Boolean,
6356 For_Body => True);
6358 declare
6359 Def : constant Node_Id := Parent (Tag_Typ);
6360 Stmts : constant List_Id := New_List;
6361 Variant_Case : Boolean := Has_Discriminants (Tag_Typ);
6362 Comps : Node_Id := Empty;
6363 Typ_Def : Node_Id := Type_Definition (Def);
6365 begin
6366 if Variant_Case then
6367 if Nkind (Typ_Def) = N_Derived_Type_Definition then
6368 Typ_Def := Record_Extension_Part (Typ_Def);
6369 end if;
6371 if Present (Typ_Def) then
6372 Comps := Component_List (Typ_Def);
6373 end if;
6375 Variant_Case := Present (Comps)
6376 and then Present (Variant_Part (Comps));
6377 end if;
6379 if Variant_Case then
6380 Append_To (Stmts,
6381 Make_Eq_If (Tag_Typ, Discriminant_Specifications (Def)));
6382 Append_List_To (Stmts, Make_Eq_Case (Tag_Typ, Comps));
6383 Append_To (Stmts,
6384 Make_Return_Statement (Loc,
6385 Expression => New_Reference_To (Standard_True, Loc)));
6387 else
6388 Append_To (Stmts,
6389 Make_Return_Statement (Loc,
6390 Expression =>
6391 Expand_Record_Equality (Tag_Typ,
6392 Typ => Tag_Typ,
6393 Lhs => Make_Identifier (Loc, Name_X),
6394 Rhs => Make_Identifier (Loc, Name_Y),
6395 Bodies => Declarations (Decl))));
6396 end if;
6398 Set_Handled_Statement_Sequence (Decl,
6399 Make_Handled_Sequence_Of_Statements (Loc, Stmts));
6400 end;
6401 Append_To (Res, Decl);
6402 end if;
6404 -- Body for dispatching assignment
6406 Decl := Predef_Spec_Or_Body (Loc,
6407 Tag_Typ => Tag_Typ,
6408 Name => Name_uAssign,
6409 Profile => New_List (
6410 Make_Parameter_Specification (Loc,
6411 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
6412 Out_Present => True,
6413 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
6415 Make_Parameter_Specification (Loc,
6416 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
6417 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
6418 For_Body => True);
6420 Set_Handled_Statement_Sequence (Decl,
6421 Make_Handled_Sequence_Of_Statements (Loc, New_List (
6422 Make_Assignment_Statement (Loc,
6423 Name => Make_Identifier (Loc, Name_X),
6424 Expression => Make_Identifier (Loc, Name_Y)))));
6426 Append_To (Res, Decl);
6427 end if;
6429 -- Generate dummy bodies for finalization actions of types that have
6430 -- no controlled components.
6432 -- Skip this processing if we are in the finalization routine in the
6433 -- runtime itself, otherwise we get hopelessly circularly confused!
6435 if In_Finalization_Root (Tag_Typ) then
6436 null;
6438 -- Skip this if finalization is not available
6440 elsif Restriction_Active (No_Finalization) then
6441 null;
6443 elsif (Etype (Tag_Typ) = Tag_Typ or else Is_Controlled (Tag_Typ))
6444 and then not Has_Controlled_Component (Tag_Typ)
6445 then
6446 if not Is_Limited_Type (Tag_Typ) then
6447 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
6449 if Is_Controlled (Tag_Typ) then
6450 Set_Handled_Statement_Sequence (Decl,
6451 Make_Handled_Sequence_Of_Statements (Loc,
6452 Make_Adjust_Call (
6453 Ref => Make_Identifier (Loc, Name_V),
6454 Typ => Tag_Typ,
6455 Flist_Ref => Make_Identifier (Loc, Name_L),
6456 With_Attach => Make_Identifier (Loc, Name_B))));
6458 else
6459 Set_Handled_Statement_Sequence (Decl,
6460 Make_Handled_Sequence_Of_Statements (Loc, New_List (
6461 Make_Null_Statement (Loc))));
6462 end if;
6464 Append_To (Res, Decl);
6465 end if;
6467 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
6469 if Is_Controlled (Tag_Typ) then
6470 Set_Handled_Statement_Sequence (Decl,
6471 Make_Handled_Sequence_Of_Statements (Loc,
6472 Make_Final_Call (
6473 Ref => Make_Identifier (Loc, Name_V),
6474 Typ => Tag_Typ,
6475 With_Detach => Make_Identifier (Loc, Name_B))));
6477 else
6478 Set_Handled_Statement_Sequence (Decl,
6479 Make_Handled_Sequence_Of_Statements (Loc, New_List (
6480 Make_Null_Statement (Loc))));
6481 end if;
6483 Append_To (Res, Decl);
6484 end if;
6486 return Res;
6487 end Predefined_Primitive_Bodies;
6489 ---------------------------------
6490 -- Predefined_Primitive_Freeze --
6491 ---------------------------------
6493 function Predefined_Primitive_Freeze
6494 (Tag_Typ : Entity_Id) return List_Id
6496 Loc : constant Source_Ptr := Sloc (Tag_Typ);
6497 Res : constant List_Id := New_List;
6498 Prim : Elmt_Id;
6499 Frnodes : List_Id;
6501 begin
6502 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
6503 while Present (Prim) loop
6504 if Is_Internal (Node (Prim)) then
6505 Frnodes := Freeze_Entity (Node (Prim), Loc);
6507 if Present (Frnodes) then
6508 Append_List_To (Res, Frnodes);
6509 end if;
6510 end if;
6512 Next_Elmt (Prim);
6513 end loop;
6515 return Res;
6516 end Predefined_Primitive_Freeze;
6518 -------------------------
6519 -- Stream_Operation_OK --
6520 -------------------------
6522 function Stream_Operation_OK
6523 (Typ : Entity_Id;
6524 Operation : TSS_Name_Type) return Boolean
6526 Has_Inheritable_Stream_Attribute : Boolean := False;
6528 begin
6529 if Is_Limited_Type (Typ)
6530 and then Is_Tagged_Type (Typ)
6531 and then Is_Derived_Type (Typ)
6532 then
6533 -- Special case of a limited type extension: a default implementation
6534 -- of the stream attributes Read and Write exists if the attribute
6535 -- has been specified for an ancestor type.
6537 Has_Inheritable_Stream_Attribute :=
6538 Present (Find_Inherited_TSS (Base_Type (Etype (Typ)), Operation));
6539 end if;
6541 return
6542 not (Is_Limited_Type (Typ)
6543 and then not Has_Inheritable_Stream_Attribute)
6544 and then RTE_Available (RE_Tag)
6545 and then RTE_Available (RE_Root_Stream_Type)
6546 and then not Restriction_Active (No_Dispatch)
6547 and then not Restriction_Active (No_Streams);
6548 end Stream_Operation_OK;
6549 end Exp_Ch3;