* config/arm/arm.md (addsi3_cbranch_scratch): Correct constraints.
[official-gcc.git] / gcc / ada / exp_ch3.adb
blob52394d376c2c1cd5052071952445e45611e6dc34
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-2004 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, 59 Temple Place - Suite 330, Boston, --
20 -- MA 02111-1307, 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 Elists; use Elists;
31 with Errout; use Errout;
32 with Exp_Aggr; use Exp_Aggr;
33 with Exp_Ch4; use Exp_Ch4;
34 with Exp_Ch7; use Exp_Ch7;
35 with Exp_Ch9; use Exp_Ch9;
36 with Exp_Ch11; use Exp_Ch11;
37 with Exp_Disp; use Exp_Disp;
38 with Exp_Dist; use Exp_Dist;
39 with Exp_Smem; use Exp_Smem;
40 with Exp_Strm; use Exp_Strm;
41 with Exp_Tss; use Exp_Tss;
42 with Exp_Util; use Exp_Util;
43 with Freeze; use Freeze;
44 with Hostparm; use Hostparm;
45 with Nlists; use Nlists;
46 with Nmake; use Nmake;
47 with Opt; use Opt;
48 with Restrict; use Restrict;
49 with Rident; use Rident;
50 with Rtsfind; use Rtsfind;
51 with Sem; use Sem;
52 with Sem_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 Stringt; use Stringt;
61 with Snames; use Snames;
62 with Tbuild; use Tbuild;
63 with Ttypes; use Ttypes;
64 with Uintp; use Uintp;
65 with Validsw; use Validsw;
67 package body Exp_Ch3 is
69 -----------------------
70 -- Local Subprograms --
71 -----------------------
73 procedure Adjust_Discriminants (Rtype : Entity_Id);
74 -- This is used when freezing a record type. It attempts to construct
75 -- more restrictive subtypes for discriminants so that the max size of
76 -- the record can be calculated more accurately. See the body of this
77 -- procedure for details.
79 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id);
80 -- Build initialization procedure for given array type. Nod is a node
81 -- used for attachment of any actions required in its construction.
82 -- It also supplies the source location used for the procedure.
84 procedure Build_Class_Wide_Master (T : Entity_Id);
85 -- for access to class-wide limited types we must build a task master
86 -- because some subsequent extension may add a task component. To avoid
87 -- bringing in the tasking run-time whenever an access-to-class-wide
88 -- limited type is used, we use the soft-link mechanism and add a level
89 -- of indirection to calls to routines that manipulate Master_Ids.
91 function Build_Discriminant_Formals
92 (Rec_Id : Entity_Id;
93 Use_Dl : Boolean) return List_Id;
94 -- This function uses the discriminants of a type to build a list of
95 -- formal parameters, used in the following function. If the flag Use_Dl
96 -- is set, the list is built using the already defined discriminals
97 -- of the type. Otherwise new identifiers are created, with the source
98 -- names of the discriminants.
100 procedure Build_Master_Renaming (N : Node_Id; T : Entity_Id);
101 -- If the designated type of an access type is a task type or contains
102 -- tasks, we make sure that a _Master variable is declared in the current
103 -- scope, and then declare a renaming for it:
105 -- atypeM : Master_Id renames _Master;
107 -- where atyp is the name of the access type. This declaration is
108 -- used when an allocator for the access type is expanded. The node N
109 -- is the full declaration of the designated type that contains tasks.
110 -- The renaming declaration is inserted before N, and after the Master
111 -- declaration.
113 procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id);
114 -- Build record initialization procedure. N is the type declaration
115 -- node, and Pe is the corresponding entity for the record type.
117 procedure Build_Slice_Assignment (Typ : Entity_Id);
118 -- Build assignment procedure for one-dimensional arrays of controlled
119 -- types. Other array and slice assignments are expanded in-line, but
120 -- the code expansion for controlled components (when control actions
121 -- are active) can lead to very large blocks that GCC3 handles poorly.
123 procedure Build_Variant_Record_Equality (Typ : Entity_Id);
124 -- Create An Equality function for the non-tagged variant record 'Typ'
125 -- and attach it to the TSS list
127 procedure Check_Stream_Attributes (Typ : Entity_Id);
128 -- Check that if a limited extension has a parent with user-defined
129 -- stream attributes, any limited component of the extension also has
130 -- the corresponding user-defined stream attributes.
132 procedure Expand_Tagged_Root (T : Entity_Id);
133 -- Add a field _Tag at the beginning of the record. This field carries
134 -- the value of the access to the Dispatch table. This procedure is only
135 -- called on root (non CPP_Class) types, the _Tag field being inherited
136 -- by the descendants.
138 procedure Expand_Record_Controller (T : Entity_Id);
139 -- T must be a record type that Has_Controlled_Component. Add a field
140 -- _controller of type Record_Controller or Limited_Record_Controller
141 -- in the record T.
143 procedure Freeze_Array_Type (N : Node_Id);
144 -- Freeze an array type. Deals with building the initialization procedure,
145 -- creating the packed array type for a packed array and also with the
146 -- creation of the controlling procedures for the controlled case. The
147 -- argument N is the N_Freeze_Entity node for the type.
149 procedure Freeze_Enumeration_Type (N : Node_Id);
150 -- Freeze enumeration type with non-standard representation. Builds the
151 -- array and function needed to convert between enumeration pos and
152 -- enumeration representation values. N is the N_Freeze_Entity node
153 -- for the type.
155 procedure Freeze_Record_Type (N : Node_Id);
156 -- Freeze record type. Builds all necessary discriminant checking
157 -- and other ancillary functions, and builds dispatch tables where
158 -- needed. The argument N is the N_Freeze_Entity node. This processing
159 -- applies only to E_Record_Type entities, not to class wide types,
160 -- record subtypes, or private types.
162 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id);
163 -- Treat user-defined stream operations as renaming_as_body if the
164 -- subprogram they rename is not frozen when the type is frozen.
166 function Init_Formals (Typ : Entity_Id) return List_Id;
167 -- This function builds the list of formals for an initialization routine.
168 -- The first formal is always _Init with the given type. For task value
169 -- record types and types containing tasks, three additional formals are
170 -- added:
172 -- _Master : Master_Id
173 -- _Chain : in out Activation_Chain
174 -- _Task_Name : String
176 -- The caller must append additional entries for discriminants if required.
178 function In_Runtime (E : Entity_Id) return Boolean;
179 -- Check if E is defined in the RTL (in a child of Ada or System). Used
180 -- to avoid to bring in the overhead of _Input, _Output for tagged types.
182 function Make_Eq_Case
183 (E : Entity_Id;
184 CL : Node_Id;
185 Discr : Entity_Id := Empty) return List_Id;
186 -- Building block for variant record equality. Defined to share the
187 -- code between the tagged and non-tagged case. Given a Component_List
188 -- node CL, it generates an 'if' followed by a 'case' statement that
189 -- compares all components of local temporaries named X and Y (that
190 -- are declared as formals at some upper level). E provides the Sloc to be
191 -- used for the generated code. Discr is used as the case statement switch
192 -- in the case of Unchecked_Union equality.
194 function Make_Eq_If
195 (E : Entity_Id;
196 L : List_Id) return Node_Id;
197 -- Building block for variant record equality. Defined to share the
198 -- code between the tagged and non-tagged case. Given the list of
199 -- components (or discriminants) L, it generates a return statement
200 -- that compares all components of local temporaries named X and Y
201 -- (that are declared as formals at some upper level). E provides the Sloc
202 -- to be used for the generated code.
204 procedure Make_Predefined_Primitive_Specs
205 (Tag_Typ : Entity_Id;
206 Predef_List : out List_Id;
207 Renamed_Eq : out Node_Id);
208 -- Create a list with the specs of the predefined primitive operations.
209 -- The following entries are present for all tagged types, and provide
210 -- the results of the corresponding attribute applied to the object.
211 -- Dispatching is required in general, since the result of the attribute
212 -- will vary with the actual object subtype.
214 -- _alignment provides result of 'Alignment attribute
215 -- _size provides result of 'Size attribute
216 -- typSR provides result of 'Read attribute
217 -- typSW provides result of 'Write attribute
218 -- typSI provides result of 'Input attribute
219 -- typSO provides result of 'Output attribute
221 -- The following entries are additionally present for non-limited
222 -- tagged types, and implement additional dispatching operations
223 -- for predefined operations:
225 -- _equality implements "=" operator
226 -- _assign implements assignment operation
227 -- typDF implements deep finalization
228 -- typDA implements deep adust
230 -- The latter two are empty procedures unless the type contains some
231 -- controlled components that require finalization actions (the deep
232 -- in the name refers to the fact that the action applies to components).
234 -- The list is returned in Predef_List. The Parameter Renamed_Eq
235 -- either returns the value Empty, or else the defining unit name
236 -- for the predefined equality function in the case where the type
237 -- has a primitive operation that is a renaming of predefined equality
238 -- (but only if there is also an overriding user-defined equality
239 -- function). The returned Renamed_Eq will be passed to the
240 -- corresponding parameter of Predefined_Primitive_Bodies.
242 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean;
243 -- returns True if there are representation clauses for type T that
244 -- are not inherited. If the result is false, the init_proc and the
245 -- discriminant_checking functions of the parent can be reused by
246 -- a derived type.
248 function Predef_Spec_Or_Body
249 (Loc : Source_Ptr;
250 Tag_Typ : Entity_Id;
251 Name : Name_Id;
252 Profile : List_Id;
253 Ret_Type : Entity_Id := Empty;
254 For_Body : Boolean := False) return Node_Id;
255 -- This function generates the appropriate expansion for a predefined
256 -- primitive operation specified by its name, parameter profile and
257 -- return type (Empty means this is a procedure). If For_Body is false,
258 -- then the returned node is a subprogram declaration. If For_Body is
259 -- true, then the returned node is a empty subprogram body containing
260 -- no declarations and no statements.
262 function Predef_Stream_Attr_Spec
263 (Loc : Source_Ptr;
264 Tag_Typ : Entity_Id;
265 Name : TSS_Name_Type;
266 For_Body : Boolean := False) return Node_Id;
267 -- Specialized version of Predef_Spec_Or_Body that apply to read, write,
268 -- input and output attribute whose specs are constructed in Exp_Strm.
270 function Predef_Deep_Spec
271 (Loc : Source_Ptr;
272 Tag_Typ : Entity_Id;
273 Name : TSS_Name_Type;
274 For_Body : Boolean := False) return Node_Id;
275 -- Specialized version of Predef_Spec_Or_Body that apply to _deep_adjust
276 -- and _deep_finalize
278 function Predefined_Primitive_Bodies
279 (Tag_Typ : Entity_Id;
280 Renamed_Eq : Node_Id) return List_Id;
281 -- Create the bodies of the predefined primitives that are described in
282 -- Predefined_Primitive_Specs. When not empty, Renamed_Eq must denote
283 -- the defining unit name of the type's predefined equality as returned
284 -- by Make_Predefined_Primitive_Specs.
286 function Predefined_Primitive_Freeze (Tag_Typ : Entity_Id) return List_Id;
287 -- Freeze entities of all predefined primitive operations. This is needed
288 -- because the bodies of these operations do not normally do any freezeing.
290 --------------------------
291 -- Adjust_Discriminants --
292 --------------------------
294 -- This procedure attempts to define subtypes for discriminants that
295 -- are more restrictive than those declared. Such a replacement is
296 -- possible if we can demonstrate that values outside the restricted
297 -- range would cause constraint errors in any case. The advantage of
298 -- restricting the discriminant types in this way is tha the maximum
299 -- size of the variant record can be calculated more conservatively.
301 -- An example of a situation in which we can perform this type of
302 -- restriction is the following:
304 -- subtype B is range 1 .. 10;
305 -- type Q is array (B range <>) of Integer;
307 -- type V (N : Natural) is record
308 -- C : Q (1 .. N);
309 -- end record;
311 -- In this situation, we can restrict the upper bound of N to 10, since
312 -- any larger value would cause a constraint error in any case.
314 -- There are many situations in which such restriction is possible, but
315 -- for now, we just look for cases like the above, where the component
316 -- in question is a one dimensional array whose upper bound is one of
317 -- the record discriminants. Also the component must not be part of
318 -- any variant part, since then the component does not always exist.
320 procedure Adjust_Discriminants (Rtype : Entity_Id) is
321 Loc : constant Source_Ptr := Sloc (Rtype);
322 Comp : Entity_Id;
323 Ctyp : Entity_Id;
324 Ityp : Entity_Id;
325 Lo : Node_Id;
326 Hi : Node_Id;
327 P : Node_Id;
328 Loval : Uint;
329 Discr : Entity_Id;
330 Dtyp : Entity_Id;
331 Dhi : Node_Id;
332 Dhiv : Uint;
333 Ahi : Node_Id;
334 Ahiv : Uint;
335 Tnn : Entity_Id;
337 begin
338 Comp := First_Component (Rtype);
339 while Present (Comp) loop
341 -- If our parent is a variant, quit, we do not look at components
342 -- that are in variant parts, because they may not always exist.
344 P := Parent (Comp); -- component declaration
345 P := Parent (P); -- component list
347 exit when Nkind (Parent (P)) = N_Variant;
349 -- We are looking for a one dimensional array type
351 Ctyp := Etype (Comp);
353 if not Is_Array_Type (Ctyp)
354 or else Number_Dimensions (Ctyp) > 1
355 then
356 goto Continue;
357 end if;
359 -- The lower bound must be constant, and the upper bound is a
360 -- discriminant (which is a discriminant of the current record).
362 Ityp := Etype (First_Index (Ctyp));
363 Lo := Type_Low_Bound (Ityp);
364 Hi := Type_High_Bound (Ityp);
366 if not Compile_Time_Known_Value (Lo)
367 or else Nkind (Hi) /= N_Identifier
368 or else No (Entity (Hi))
369 or else Ekind (Entity (Hi)) /= E_Discriminant
370 then
371 goto Continue;
372 end if;
374 -- We have an array with appropriate bounds
376 Loval := Expr_Value (Lo);
377 Discr := Entity (Hi);
378 Dtyp := Etype (Discr);
380 -- See if the discriminant has a known upper bound
382 Dhi := Type_High_Bound (Dtyp);
384 if not Compile_Time_Known_Value (Dhi) then
385 goto Continue;
386 end if;
388 Dhiv := Expr_Value (Dhi);
390 -- See if base type of component array has known upper bound
392 Ahi := Type_High_Bound (Etype (First_Index (Base_Type (Ctyp))));
394 if not Compile_Time_Known_Value (Ahi) then
395 goto Continue;
396 end if;
398 Ahiv := Expr_Value (Ahi);
400 -- The condition for doing the restriction is that the high bound
401 -- of the discriminant is greater than the low bound of the array,
402 -- and is also greater than the high bound of the base type index.
404 if Dhiv > Loval and then Dhiv > Ahiv then
406 -- We can reset the upper bound of the discriminant type to
407 -- whichever is larger, the low bound of the component, or
408 -- the high bound of the base type array index.
410 -- We build a subtype that is declared as
412 -- subtype Tnn is discr_type range discr_type'First .. max;
414 -- And insert this declaration into the tree. The type of the
415 -- discriminant is then reset to this more restricted subtype.
417 Tnn := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
419 Insert_Action (Declaration_Node (Rtype),
420 Make_Subtype_Declaration (Loc,
421 Defining_Identifier => Tnn,
422 Subtype_Indication =>
423 Make_Subtype_Indication (Loc,
424 Subtype_Mark => New_Occurrence_Of (Dtyp, Loc),
425 Constraint =>
426 Make_Range_Constraint (Loc,
427 Range_Expression =>
428 Make_Range (Loc,
429 Low_Bound =>
430 Make_Attribute_Reference (Loc,
431 Attribute_Name => Name_First,
432 Prefix => New_Occurrence_Of (Dtyp, Loc)),
433 High_Bound =>
434 Make_Integer_Literal (Loc,
435 Intval => UI_Max (Loval, Ahiv)))))));
437 Set_Etype (Discr, Tnn);
438 end if;
440 <<Continue>>
441 Next_Component (Comp);
442 end loop;
443 end Adjust_Discriminants;
445 ---------------------------
446 -- Build_Array_Init_Proc --
447 ---------------------------
449 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id) is
450 Loc : constant Source_Ptr := Sloc (Nod);
451 Comp_Type : constant Entity_Id := Component_Type (A_Type);
452 Index_List : List_Id;
453 Proc_Id : Entity_Id;
454 Body_Stmts : List_Id;
456 function Init_Component return List_Id;
457 -- Create one statement to initialize one array component, designated
458 -- by a full set of indices.
460 function Init_One_Dimension (N : Int) return List_Id;
461 -- Create loop to initialize one dimension of the array. The single
462 -- statement in the loop body initializes the inner dimensions if any,
463 -- or else the single component. Note that this procedure is called
464 -- recursively, with N being the dimension to be initialized. A call
465 -- with N greater than the number of dimensions simply generates the
466 -- component initialization, terminating the recursion.
468 --------------------
469 -- Init_Component --
470 --------------------
472 function Init_Component return List_Id is
473 Comp : Node_Id;
475 begin
476 Comp :=
477 Make_Indexed_Component (Loc,
478 Prefix => Make_Identifier (Loc, Name_uInit),
479 Expressions => Index_List);
481 if Needs_Simple_Initialization (Comp_Type) then
482 Set_Assignment_OK (Comp);
483 return New_List (
484 Make_Assignment_Statement (Loc,
485 Name => Comp,
486 Expression => Get_Simple_Init_Val (Comp_Type, Loc)));
488 else
489 return
490 Build_Initialization_Call (Loc, Comp, Comp_Type, True, A_Type);
491 end if;
492 end Init_Component;
494 ------------------------
495 -- Init_One_Dimension --
496 ------------------------
498 function Init_One_Dimension (N : Int) return List_Id is
499 Index : Entity_Id;
501 begin
502 -- If the component does not need initializing, then there is nothing
503 -- to do here, so we return a null body. This occurs when generating
504 -- the dummy Init_Proc needed for Initialize_Scalars processing.
506 if not Has_Non_Null_Base_Init_Proc (Comp_Type)
507 and then not Needs_Simple_Initialization (Comp_Type)
508 and then not Has_Task (Comp_Type)
509 then
510 return New_List (Make_Null_Statement (Loc));
512 -- If all dimensions dealt with, we simply initialize the component
514 elsif N > Number_Dimensions (A_Type) then
515 return Init_Component;
517 -- Here we generate the required loop
519 else
520 Index :=
521 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
523 Append (New_Reference_To (Index, Loc), Index_List);
525 return New_List (
526 Make_Implicit_Loop_Statement (Nod,
527 Identifier => Empty,
528 Iteration_Scheme =>
529 Make_Iteration_Scheme (Loc,
530 Loop_Parameter_Specification =>
531 Make_Loop_Parameter_Specification (Loc,
532 Defining_Identifier => Index,
533 Discrete_Subtype_Definition =>
534 Make_Attribute_Reference (Loc,
535 Prefix => Make_Identifier (Loc, Name_uInit),
536 Attribute_Name => Name_Range,
537 Expressions => New_List (
538 Make_Integer_Literal (Loc, N))))),
539 Statements => Init_One_Dimension (N + 1)));
540 end if;
541 end Init_One_Dimension;
543 -- Start of processing for Build_Array_Init_Proc
545 begin
546 if Suppress_Init_Proc (A_Type) then
547 return;
548 end if;
550 Index_List := New_List;
552 -- We need an initialization procedure if any of the following is true:
554 -- 1. The component type has an initialization procedure
555 -- 2. The component type needs simple initialization
556 -- 3. Tasks are present
557 -- 4. The type is marked as a publc entity
559 -- The reason for the public entity test is to deal properly with the
560 -- Initialize_Scalars pragma. This pragma can be set in the client and
561 -- not in the declaring package, this means the client will make a call
562 -- to the initialization procedure (because one of conditions 1-3 must
563 -- apply in this case), and we must generate a procedure (even if it is
564 -- null) to satisfy the call in this case.
566 -- Exception: do not build an array init_proc for a type whose root type
567 -- is Standard.String or Standard.Wide_String, since there is no place
568 -- to put the code, and in any case we handle initialization of such
569 -- types (in the Initialize_Scalars case, that's the only time the issue
570 -- arises) in a special manner anyway which does not need an init_proc.
572 if Has_Non_Null_Base_Init_Proc (Comp_Type)
573 or else Needs_Simple_Initialization (Comp_Type)
574 or else Has_Task (Comp_Type)
575 or else (not Restriction_Active (No_Initialize_Scalars)
576 and then Is_Public (A_Type)
577 and then Root_Type (A_Type) /= Standard_String
578 and then Root_Type (A_Type) /= Standard_Wide_String)
579 then
580 Proc_Id :=
581 Make_Defining_Identifier (Loc, Make_Init_Proc_Name (A_Type));
583 Body_Stmts := Init_One_Dimension (1);
585 Discard_Node (
586 Make_Subprogram_Body (Loc,
587 Specification =>
588 Make_Procedure_Specification (Loc,
589 Defining_Unit_Name => Proc_Id,
590 Parameter_Specifications => Init_Formals (A_Type)),
591 Declarations => New_List,
592 Handled_Statement_Sequence =>
593 Make_Handled_Sequence_Of_Statements (Loc,
594 Statements => Body_Stmts)));
596 Set_Ekind (Proc_Id, E_Procedure);
597 Set_Is_Public (Proc_Id, Is_Public (A_Type));
598 Set_Is_Internal (Proc_Id);
599 Set_Has_Completion (Proc_Id);
601 if not Debug_Generated_Code then
602 Set_Debug_Info_Off (Proc_Id);
603 end if;
605 -- Set inlined unless controlled stuff or tasks around, in which
606 -- case we do not want to inline, because nested stuff may cause
607 -- difficulties in interunit inlining, and furthermore there is
608 -- in any case no point in inlining such complex init procs.
610 if not Has_Task (Proc_Id)
611 and then not Controlled_Type (Proc_Id)
612 then
613 Set_Is_Inlined (Proc_Id);
614 end if;
616 -- Associate Init_Proc with type, and determine if the procedure
617 -- is null (happens because of the Initialize_Scalars pragma case,
618 -- where we have to generate a null procedure in case it is called
619 -- by a client with Initialize_Scalars set). Such procedures have
620 -- to be generated, but do not have to be called, so we mark them
621 -- as null to suppress the call.
623 Set_Init_Proc (A_Type, Proc_Id);
625 if List_Length (Body_Stmts) = 1
626 and then Nkind (First (Body_Stmts)) = N_Null_Statement
627 then
628 Set_Is_Null_Init_Proc (Proc_Id);
629 end if;
630 end if;
631 end Build_Array_Init_Proc;
633 -----------------------------
634 -- Build_Class_Wide_Master --
635 -----------------------------
637 procedure Build_Class_Wide_Master (T : Entity_Id) is
638 Loc : constant Source_Ptr := Sloc (T);
639 M_Id : Entity_Id;
640 Decl : Node_Id;
641 P : Node_Id;
643 begin
644 -- Nothing to do if there is no task hierarchy.
646 if Restriction_Active (No_Task_Hierarchy) then
647 return;
648 end if;
650 -- Nothing to do if we already built a master entity for this scope
652 if not Has_Master_Entity (Scope (T)) then
653 -- first build the master entity
654 -- _Master : constant Master_Id := Current_Master.all;
655 -- and insert it just before the current declaration
657 Decl :=
658 Make_Object_Declaration (Loc,
659 Defining_Identifier =>
660 Make_Defining_Identifier (Loc, Name_uMaster),
661 Constant_Present => True,
662 Object_Definition => New_Reference_To (Standard_Integer, Loc),
663 Expression =>
664 Make_Explicit_Dereference (Loc,
665 New_Reference_To (RTE (RE_Current_Master), Loc)));
667 P := Parent (T);
668 Insert_Before (P, Decl);
669 Analyze (Decl);
670 Set_Has_Master_Entity (Scope (T));
672 -- Now mark the containing scope as a task master
674 while Nkind (P) /= N_Compilation_Unit loop
675 P := Parent (P);
677 -- If we fall off the top, we are at the outer level, and the
678 -- environment task is our effective master, so nothing to mark.
680 if Nkind (P) = N_Task_Body
681 or else Nkind (P) = N_Block_Statement
682 or else Nkind (P) = N_Subprogram_Body
683 then
684 Set_Is_Task_Master (P, True);
685 exit;
686 end if;
687 end loop;
688 end if;
690 -- Now define the renaming of the master_id.
692 M_Id :=
693 Make_Defining_Identifier (Loc,
694 New_External_Name (Chars (T), 'M'));
696 Decl :=
697 Make_Object_Renaming_Declaration (Loc,
698 Defining_Identifier => M_Id,
699 Subtype_Mark => New_Reference_To (Standard_Integer, Loc),
700 Name => Make_Identifier (Loc, Name_uMaster));
701 Insert_Before (Parent (T), Decl);
702 Analyze (Decl);
704 Set_Master_Id (T, M_Id);
706 exception
707 when RE_Not_Available =>
708 return;
709 end Build_Class_Wide_Master;
711 --------------------------------
712 -- Build_Discr_Checking_Funcs --
713 --------------------------------
715 procedure Build_Discr_Checking_Funcs (N : Node_Id) is
716 Rec_Id : Entity_Id;
717 Loc : Source_Ptr;
718 Enclosing_Func_Id : Entity_Id;
719 Sequence : Nat := 1;
720 Type_Def : Node_Id;
721 V : Node_Id;
723 function Build_Case_Statement
724 (Case_Id : Entity_Id;
725 Variant : Node_Id) return Node_Id;
726 -- Build a case statement containing only two alternatives. The
727 -- first alternative corresponds exactly to the discrete choices
728 -- given on the variant with contains the components that we are
729 -- generating the checks for. If the discriminant is one of these
730 -- return False. The second alternative is an OTHERS choice that
731 -- will return True indicating the discriminant did not match.
733 function Build_Dcheck_Function
734 (Case_Id : Entity_Id;
735 Variant : Node_Id) return Entity_Id;
736 -- Build the discriminant checking function for a given variant
738 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id);
739 -- Builds the discriminant checking function for each variant of the
740 -- given variant part of the record type.
742 --------------------------
743 -- Build_Case_Statement --
744 --------------------------
746 function Build_Case_Statement
747 (Case_Id : Entity_Id;
748 Variant : Node_Id) return Node_Id
750 Alt_List : constant List_Id := New_List;
751 Actuals_List : List_Id;
752 Case_Node : Node_Id;
753 Case_Alt_Node : Node_Id;
754 Choice : Node_Id;
755 Choice_List : List_Id;
756 D : Entity_Id;
757 Return_Node : Node_Id;
759 begin
760 Case_Node := New_Node (N_Case_Statement, Loc);
762 -- Replace the discriminant which controls the variant, with the
763 -- name of the formal of the checking function.
765 Set_Expression (Case_Node,
766 Make_Identifier (Loc, Chars (Case_Id)));
768 Choice := First (Discrete_Choices (Variant));
770 if Nkind (Choice) = N_Others_Choice then
771 Choice_List := New_Copy_List (Others_Discrete_Choices (Choice));
772 else
773 Choice_List := New_Copy_List (Discrete_Choices (Variant));
774 end if;
776 if not Is_Empty_List (Choice_List) then
777 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
778 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
780 -- In case this is a nested variant, we need to return the result
781 -- of the discriminant checking function for the immediately
782 -- enclosing variant.
784 if Present (Enclosing_Func_Id) then
785 Actuals_List := New_List;
787 D := First_Discriminant (Rec_Id);
788 while Present (D) loop
789 Append (Make_Identifier (Loc, Chars (D)), Actuals_List);
790 Next_Discriminant (D);
791 end loop;
793 Return_Node :=
794 Make_Return_Statement (Loc,
795 Expression =>
796 Make_Function_Call (Loc,
797 Name =>
798 New_Reference_To (Enclosing_Func_Id, Loc),
799 Parameter_Associations =>
800 Actuals_List));
802 else
803 Return_Node :=
804 Make_Return_Statement (Loc,
805 Expression =>
806 New_Reference_To (Standard_False, Loc));
807 end if;
809 Set_Statements (Case_Alt_Node, New_List (Return_Node));
810 Append (Case_Alt_Node, Alt_List);
811 end if;
813 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
814 Choice_List := New_List (New_Node (N_Others_Choice, Loc));
815 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
817 Return_Node :=
818 Make_Return_Statement (Loc,
819 Expression =>
820 New_Reference_To (Standard_True, Loc));
822 Set_Statements (Case_Alt_Node, New_List (Return_Node));
823 Append (Case_Alt_Node, Alt_List);
825 Set_Alternatives (Case_Node, Alt_List);
826 return Case_Node;
827 end Build_Case_Statement;
829 ---------------------------
830 -- Build_Dcheck_Function --
831 ---------------------------
833 function Build_Dcheck_Function
834 (Case_Id : Entity_Id;
835 Variant : Node_Id) return Entity_Id
837 Body_Node : Node_Id;
838 Func_Id : Entity_Id;
839 Parameter_List : List_Id;
840 Spec_Node : Node_Id;
842 begin
843 Body_Node := New_Node (N_Subprogram_Body, Loc);
844 Sequence := Sequence + 1;
846 Func_Id :=
847 Make_Defining_Identifier (Loc,
848 Chars => New_External_Name (Chars (Rec_Id), 'D', Sequence));
850 Spec_Node := New_Node (N_Function_Specification, Loc);
851 Set_Defining_Unit_Name (Spec_Node, Func_Id);
853 Parameter_List := Build_Discriminant_Formals (Rec_Id, False);
855 Set_Parameter_Specifications (Spec_Node, Parameter_List);
856 Set_Subtype_Mark (Spec_Node,
857 New_Reference_To (Standard_Boolean, Loc));
858 Set_Specification (Body_Node, Spec_Node);
859 Set_Declarations (Body_Node, New_List);
861 Set_Handled_Statement_Sequence (Body_Node,
862 Make_Handled_Sequence_Of_Statements (Loc,
863 Statements => New_List (
864 Build_Case_Statement (Case_Id, Variant))));
866 Set_Ekind (Func_Id, E_Function);
867 Set_Mechanism (Func_Id, Default_Mechanism);
868 Set_Is_Inlined (Func_Id, True);
869 Set_Is_Pure (Func_Id, True);
870 Set_Is_Public (Func_Id, Is_Public (Rec_Id));
871 Set_Is_Internal (Func_Id, True);
873 if not Debug_Generated_Code then
874 Set_Debug_Info_Off (Func_Id);
875 end if;
877 Analyze (Body_Node);
879 Append_Freeze_Action (Rec_Id, Body_Node);
880 Set_Dcheck_Function (Variant, Func_Id);
881 return Func_Id;
882 end Build_Dcheck_Function;
884 ----------------------------
885 -- Build_Dcheck_Functions --
886 ----------------------------
888 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id) is
889 Component_List_Node : Node_Id;
890 Decl : Entity_Id;
891 Discr_Name : Entity_Id;
892 Func_Id : Entity_Id;
893 Variant : Node_Id;
894 Saved_Enclosing_Func_Id : Entity_Id;
896 begin
897 -- Build the discriminant checking function for each variant, label
898 -- all components of that variant with the function's name.
900 Discr_Name := Entity (Name (Variant_Part_Node));
901 Variant := First_Non_Pragma (Variants (Variant_Part_Node));
903 while Present (Variant) loop
904 Func_Id := Build_Dcheck_Function (Discr_Name, Variant);
905 Component_List_Node := Component_List (Variant);
907 if not Null_Present (Component_List_Node) then
908 Decl :=
909 First_Non_Pragma (Component_Items (Component_List_Node));
911 while Present (Decl) loop
912 Set_Discriminant_Checking_Func
913 (Defining_Identifier (Decl), Func_Id);
915 Next_Non_Pragma (Decl);
916 end loop;
918 if Present (Variant_Part (Component_List_Node)) then
919 Saved_Enclosing_Func_Id := Enclosing_Func_Id;
920 Enclosing_Func_Id := Func_Id;
921 Build_Dcheck_Functions (Variant_Part (Component_List_Node));
922 Enclosing_Func_Id := Saved_Enclosing_Func_Id;
923 end if;
924 end if;
926 Next_Non_Pragma (Variant);
927 end loop;
928 end Build_Dcheck_Functions;
930 -- Start of processing for Build_Discr_Checking_Funcs
932 begin
933 -- Only build if not done already
935 if not Discr_Check_Funcs_Built (N) then
936 Type_Def := Type_Definition (N);
938 if Nkind (Type_Def) = N_Record_Definition then
939 if No (Component_List (Type_Def)) then -- null record.
940 return;
941 else
942 V := Variant_Part (Component_List (Type_Def));
943 end if;
945 else pragma Assert (Nkind (Type_Def) = N_Derived_Type_Definition);
946 if No (Component_List (Record_Extension_Part (Type_Def))) then
947 return;
948 else
949 V := Variant_Part
950 (Component_List (Record_Extension_Part (Type_Def)));
951 end if;
952 end if;
954 Rec_Id := Defining_Identifier (N);
956 if Present (V) and then not Is_Unchecked_Union (Rec_Id) then
957 Loc := Sloc (N);
958 Enclosing_Func_Id := Empty;
959 Build_Dcheck_Functions (V);
960 end if;
962 Set_Discr_Check_Funcs_Built (N);
963 end if;
964 end Build_Discr_Checking_Funcs;
966 --------------------------------
967 -- Build_Discriminant_Formals --
968 --------------------------------
970 function Build_Discriminant_Formals
971 (Rec_Id : Entity_Id;
972 Use_Dl : Boolean) return List_Id
974 Loc : Source_Ptr := Sloc (Rec_Id);
975 Parameter_List : constant List_Id := New_List;
976 D : Entity_Id;
977 Formal : Entity_Id;
978 Param_Spec_Node : Node_Id;
980 begin
981 if Has_Discriminants (Rec_Id) then
982 D := First_Discriminant (Rec_Id);
983 while Present (D) loop
984 Loc := Sloc (D);
986 if Use_Dl then
987 Formal := Discriminal (D);
988 else
989 Formal := Make_Defining_Identifier (Loc, Chars (D));
990 end if;
992 Param_Spec_Node :=
993 Make_Parameter_Specification (Loc,
994 Defining_Identifier => Formal,
995 Parameter_Type =>
996 New_Reference_To (Etype (D), Loc));
997 Append (Param_Spec_Node, Parameter_List);
998 Next_Discriminant (D);
999 end loop;
1000 end if;
1002 return Parameter_List;
1003 end Build_Discriminant_Formals;
1005 -------------------------------
1006 -- Build_Initialization_Call --
1007 -------------------------------
1009 -- References to a discriminant inside the record type declaration
1010 -- can appear either in the subtype_indication to constrain a
1011 -- record or an array, or as part of a larger expression given for
1012 -- the initial value of a component. In both of these cases N appears
1013 -- in the record initialization procedure and needs to be replaced by
1014 -- the formal parameter of the initialization procedure which
1015 -- corresponds to that discriminant.
1017 -- In the example below, references to discriminants D1 and D2 in proc_1
1018 -- are replaced by references to formals with the same name
1019 -- (discriminals)
1021 -- A similar replacement is done for calls to any record
1022 -- initialization procedure for any components that are themselves
1023 -- of a record type.
1025 -- type R (D1, D2 : Integer) is record
1026 -- X : Integer := F * D1;
1027 -- Y : Integer := F * D2;
1028 -- end record;
1030 -- procedure proc_1 (Out_2 : out R; D1 : Integer; D2 : Integer) is
1031 -- begin
1032 -- Out_2.D1 := D1;
1033 -- Out_2.D2 := D2;
1034 -- Out_2.X := F * D1;
1035 -- Out_2.Y := F * D2;
1036 -- end;
1038 function Build_Initialization_Call
1039 (Loc : Source_Ptr;
1040 Id_Ref : Node_Id;
1041 Typ : Entity_Id;
1042 In_Init_Proc : Boolean := False;
1043 Enclos_Type : Entity_Id := Empty;
1044 Discr_Map : Elist_Id := New_Elmt_List;
1045 With_Default_Init : Boolean := False) return List_Id
1047 First_Arg : Node_Id;
1048 Args : List_Id;
1049 Decls : List_Id;
1050 Decl : Node_Id;
1051 Discr : Entity_Id;
1052 Arg : Node_Id;
1053 Proc : constant Entity_Id := Base_Init_Proc (Typ);
1054 Init_Type : constant Entity_Id := Etype (First_Formal (Proc));
1055 Full_Init_Type : constant Entity_Id := Underlying_Type (Init_Type);
1056 Res : constant List_Id := New_List;
1057 Full_Type : Entity_Id := Typ;
1058 Controller_Typ : Entity_Id;
1060 begin
1061 -- Nothing to do if the Init_Proc is null, unless Initialize_Scalars
1062 -- is active (in which case we make the call anyway, since in the
1063 -- actual compiled client it may be non null).
1065 if Is_Null_Init_Proc (Proc) and then not Init_Or_Norm_Scalars then
1066 return Empty_List;
1067 end if;
1069 -- Go to full view if private type. In the case of successive
1070 -- private derivations, this can require more than one step.
1072 while Is_Private_Type (Full_Type)
1073 and then Present (Full_View (Full_Type))
1074 loop
1075 Full_Type := Full_View (Full_Type);
1076 end loop;
1078 -- If Typ is derived, the procedure is the initialization procedure for
1079 -- the root type. Wrap the argument in an conversion to make it type
1080 -- honest. Actually it isn't quite type honest, because there can be
1081 -- conflicts of views in the private type case. That is why we set
1082 -- Conversion_OK in the conversion node.
1083 if (Is_Record_Type (Typ)
1084 or else Is_Array_Type (Typ)
1085 or else Is_Private_Type (Typ))
1086 and then Init_Type /= Base_Type (Typ)
1087 then
1088 First_Arg := OK_Convert_To (Etype (Init_Type), Id_Ref);
1089 Set_Etype (First_Arg, Init_Type);
1091 else
1092 First_Arg := Id_Ref;
1093 end if;
1095 Args := New_List (Convert_Concurrent (First_Arg, Typ));
1097 -- In the tasks case, add _Master as the value of the _Master parameter
1098 -- and _Chain as the value of the _Chain parameter. At the outer level,
1099 -- these will be variables holding the corresponding values obtained
1100 -- from GNARL. At inner levels, they will be the parameters passed down
1101 -- through the outer routines.
1103 if Has_Task (Full_Type) then
1104 if Restriction_Active (No_Task_Hierarchy) then
1106 -- See comments in System.Tasking.Initialization.Init_RTS
1107 -- for the value 3 (should be rtsfindable constant ???)
1109 Append_To (Args, Make_Integer_Literal (Loc, 3));
1110 else
1111 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1112 end if;
1114 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1116 -- Ada 2005 (AI-287): In case of default initialized components
1117 -- with tasks, we generate a null string actual parameter.
1118 -- This is just a workaround that must be improved later???
1120 if With_Default_Init then
1121 declare
1122 S : String_Id;
1123 Null_String : Node_Id;
1124 begin
1125 Start_String;
1126 S := End_String;
1127 Null_String := Make_String_Literal (Loc, Strval => S);
1128 Append_To (Args, Null_String);
1129 end;
1130 else
1131 Decls := Build_Task_Image_Decls (Loc, Id_Ref, Enclos_Type);
1132 Decl := Last (Decls);
1134 Append_To (Args,
1135 New_Occurrence_Of (Defining_Identifier (Decl), Loc));
1136 Append_List (Decls, Res);
1137 end if;
1139 else
1140 Decls := No_List;
1141 Decl := Empty;
1142 end if;
1144 -- Add discriminant values if discriminants are present
1146 if Has_Discriminants (Full_Init_Type) then
1147 Discr := First_Discriminant (Full_Init_Type);
1149 while Present (Discr) loop
1151 -- If this is a discriminated concurrent type, the init_proc
1152 -- for the corresponding record is being called. Use that
1153 -- type directly to find the discriminant value, to handle
1154 -- properly intervening renamed discriminants.
1156 declare
1157 T : Entity_Id := Full_Type;
1159 begin
1160 if Is_Protected_Type (T) then
1161 T := Corresponding_Record_Type (T);
1163 elsif Is_Private_Type (T)
1164 and then Present (Underlying_Full_View (T))
1165 and then Is_Protected_Type (Underlying_Full_View (T))
1166 then
1167 T := Corresponding_Record_Type (Underlying_Full_View (T));
1168 end if;
1170 Arg :=
1171 Get_Discriminant_Value (
1172 Discr,
1174 Discriminant_Constraint (Full_Type));
1175 end;
1177 if In_Init_Proc then
1179 -- Replace any possible references to the discriminant in the
1180 -- call to the record initialization procedure with references
1181 -- to the appropriate formal parameter.
1183 if Nkind (Arg) = N_Identifier
1184 and then Ekind (Entity (Arg)) = E_Discriminant
1185 then
1186 Arg := New_Reference_To (Discriminal (Entity (Arg)), Loc);
1188 -- Case of access discriminants. We replace the reference
1189 -- to the type by a reference to the actual object
1191 elsif Nkind (Arg) = N_Attribute_Reference
1192 and then Is_Access_Type (Etype (Arg))
1193 and then Is_Entity_Name (Prefix (Arg))
1194 and then Is_Type (Entity (Prefix (Arg)))
1195 then
1196 Arg :=
1197 Make_Attribute_Reference (Loc,
1198 Prefix => New_Copy (Prefix (Id_Ref)),
1199 Attribute_Name => Name_Unrestricted_Access);
1201 -- Otherwise make a copy of the default expression. Note
1202 -- that we use the current Sloc for this, because we do not
1203 -- want the call to appear to be at the declaration point.
1204 -- Within the expression, replace discriminants with their
1205 -- discriminals.
1207 else
1208 Arg :=
1209 New_Copy_Tree (Arg, Map => Discr_Map, New_Sloc => Loc);
1210 end if;
1212 else
1213 if Is_Constrained (Full_Type) then
1214 Arg := Duplicate_Subexpr_No_Checks (Arg);
1215 else
1216 -- The constraints come from the discriminant default
1217 -- exps, they must be reevaluated, so we use New_Copy_Tree
1218 -- but we ensure the proper Sloc (for any embedded calls).
1220 Arg := New_Copy_Tree (Arg, New_Sloc => Loc);
1221 end if;
1222 end if;
1224 -- Ada 2005 (AI-287) In case of default initialized components,
1225 -- we need to generate the corresponding selected component node
1226 -- to access the discriminant value. In other cases this is not
1227 -- required because we are inside the init proc and we use the
1228 -- corresponding formal.
1230 if With_Default_Init
1231 and then Nkind (Id_Ref) = N_Selected_Component
1232 then
1233 Append_To (Args,
1234 Make_Selected_Component (Loc,
1235 Prefix => New_Copy_Tree (Prefix (Id_Ref)),
1236 Selector_Name => Arg));
1237 else
1238 Append_To (Args, Arg);
1239 end if;
1241 Next_Discriminant (Discr);
1242 end loop;
1243 end if;
1245 -- If this is a call to initialize the parent component of a derived
1246 -- tagged type, indicate that the tag should not be set in the parent.
1248 if Is_Tagged_Type (Full_Init_Type)
1249 and then not Is_CPP_Class (Full_Init_Type)
1250 and then Nkind (Id_Ref) = N_Selected_Component
1251 and then Chars (Selector_Name (Id_Ref)) = Name_uParent
1252 then
1253 Append_To (Args, New_Occurrence_Of (Standard_False, Loc));
1254 end if;
1256 Append_To (Res,
1257 Make_Procedure_Call_Statement (Loc,
1258 Name => New_Occurrence_Of (Proc, Loc),
1259 Parameter_Associations => Args));
1261 if Controlled_Type (Typ)
1262 and then Nkind (Id_Ref) = N_Selected_Component
1263 then
1264 if Chars (Selector_Name (Id_Ref)) /= Name_uParent then
1265 Append_List_To (Res,
1266 Make_Init_Call (
1267 Ref => New_Copy_Tree (First_Arg),
1268 Typ => Typ,
1269 Flist_Ref =>
1270 Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1271 With_Attach => Make_Integer_Literal (Loc, 1)));
1273 -- If the enclosing type is an extension with new controlled
1274 -- components, it has his own record controller. If the parent
1275 -- also had a record controller, attach it to the new one.
1276 -- Build_Init_Statements relies on the fact that in this specific
1277 -- case the last statement of the result is the attach call to
1278 -- the controller. If this is changed, it must be synchronized.
1280 elsif Present (Enclos_Type)
1281 and then Has_New_Controlled_Component (Enclos_Type)
1282 and then Has_Controlled_Component (Typ)
1283 then
1284 if Is_Return_By_Reference_Type (Typ) then
1285 Controller_Typ := RTE (RE_Limited_Record_Controller);
1286 else
1287 Controller_Typ := RTE (RE_Record_Controller);
1288 end if;
1290 Append_List_To (Res,
1291 Make_Init_Call (
1292 Ref =>
1293 Make_Selected_Component (Loc,
1294 Prefix => New_Copy_Tree (First_Arg),
1295 Selector_Name => Make_Identifier (Loc, Name_uController)),
1296 Typ => Controller_Typ,
1297 Flist_Ref => Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1298 With_Attach => Make_Integer_Literal (Loc, 1)));
1299 end if;
1300 end if;
1302 return Res;
1304 exception
1305 when RE_Not_Available =>
1306 return Empty_List;
1307 end Build_Initialization_Call;
1309 ---------------------------
1310 -- Build_Master_Renaming --
1311 ---------------------------
1313 procedure Build_Master_Renaming (N : Node_Id; T : Entity_Id) is
1314 Loc : constant Source_Ptr := Sloc (N);
1315 M_Id : Entity_Id;
1316 Decl : Node_Id;
1318 begin
1319 -- Nothing to do if there is no task hierarchy.
1321 if Restriction_Active (No_Task_Hierarchy) then
1322 return;
1323 end if;
1325 M_Id :=
1326 Make_Defining_Identifier (Loc,
1327 New_External_Name (Chars (T), 'M'));
1329 Decl :=
1330 Make_Object_Renaming_Declaration (Loc,
1331 Defining_Identifier => M_Id,
1332 Subtype_Mark => New_Reference_To (RTE (RE_Master_Id), Loc),
1333 Name => Make_Identifier (Loc, Name_uMaster));
1334 Insert_Before (N, Decl);
1335 Analyze (Decl);
1337 Set_Master_Id (T, M_Id);
1339 exception
1340 when RE_Not_Available =>
1341 return;
1342 end Build_Master_Renaming;
1344 ----------------------------
1345 -- Build_Record_Init_Proc --
1346 ----------------------------
1348 procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id) is
1349 Loc : Source_Ptr := Sloc (N);
1350 Discr_Map : constant Elist_Id := New_Elmt_List;
1351 Proc_Id : Entity_Id;
1352 Rec_Type : Entity_Id;
1353 Set_Tag : Entity_Id := Empty;
1355 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id;
1356 -- Build a assignment statement node which assigns to record
1357 -- component its default expression if defined. The left hand side
1358 -- of the assignment is marked Assignment_OK so that initialization
1359 -- of limited private records works correctly, Return also the
1360 -- adjustment call for controlled objects
1362 procedure Build_Discriminant_Assignments (Statement_List : List_Id);
1363 -- If the record has discriminants, adds assignment statements to
1364 -- statement list to initialize the discriminant values from the
1365 -- arguments of the initialization procedure.
1367 function Build_Init_Statements (Comp_List : Node_Id) return List_Id;
1368 -- Build a list representing a sequence of statements which initialize
1369 -- components of the given component list. This may involve building
1370 -- case statements for the variant parts.
1372 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id;
1373 -- Given a non-tagged type-derivation that declares discriminants,
1374 -- such as
1376 -- type R (R1, R2 : Integer) is record ... end record;
1378 -- type D (D1 : Integer) is new R (1, D1);
1380 -- we make the _init_proc of D be
1382 -- procedure _init_proc(X : D; D1 : Integer) is
1383 -- begin
1384 -- _init_proc( R(X), 1, D1);
1385 -- end _init_proc;
1387 -- This function builds the call statement in this _init_proc.
1389 procedure Build_Init_Procedure;
1390 -- Build the tree corresponding to the procedure specification and body
1391 -- of the initialization procedure (by calling all the preceding
1392 -- auxiliary routines), and install it as the _init TSS.
1394 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id);
1395 -- Add range checks to components of disciminated records. S is a
1396 -- subtype indication of a record component. Check_List is a list
1397 -- to which the check actions are appended.
1399 function Component_Needs_Simple_Initialization
1400 (T : Entity_Id) return Boolean;
1401 -- Determines if a component needs simple initialization, given its
1402 -- type T. This is the same as Needs_Simple_Initialization except
1403 -- for the following difference: the types Tag and Vtable_Ptr, which
1404 -- are access types which would normally require simple initialization
1405 -- to null, do not require initialization as components, since they
1406 -- are explicitly initialized by other means.
1408 procedure Constrain_Array
1409 (SI : Node_Id;
1410 Check_List : List_Id);
1411 -- Called from Build_Record_Checks.
1412 -- Apply a list of index constraints to an unconstrained array type.
1413 -- The first parameter is the entity for the resulting subtype.
1414 -- Check_List is a list to which the check actions are appended.
1416 procedure Constrain_Index
1417 (Index : Node_Id;
1418 S : Node_Id;
1419 Check_List : List_Id);
1420 -- Called from Build_Record_Checks.
1421 -- Process an index constraint in a constrained array declaration.
1422 -- The constraint can be a subtype name, or a range with or without
1423 -- an explicit subtype mark. The index is the corresponding index of the
1424 -- unconstrained array. S is the range expression. Check_List is a list
1425 -- to which the check actions are appended.
1427 function Parent_Subtype_Renaming_Discrims return Boolean;
1428 -- Returns True for base types N that rename discriminants, else False
1430 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean;
1431 -- Determines whether a record initialization procedure needs to be
1432 -- generated for the given record type.
1434 ----------------------
1435 -- Build_Assignment --
1436 ----------------------
1438 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id is
1439 Exp : Node_Id := N;
1440 Lhs : Node_Id;
1441 Typ : constant Entity_Id := Underlying_Type (Etype (Id));
1442 Kind : Node_Kind := Nkind (N);
1443 Res : List_Id;
1445 begin
1446 Loc := Sloc (N);
1447 Lhs :=
1448 Make_Selected_Component (Loc,
1449 Prefix => Make_Identifier (Loc, Name_uInit),
1450 Selector_Name => New_Occurrence_Of (Id, Loc));
1451 Set_Assignment_OK (Lhs);
1453 -- Case of an access attribute applied to the current instance.
1454 -- Replace the reference to the type by a reference to the actual
1455 -- object. (Note that this handles the case of the top level of
1456 -- the expression being given by such an attribute, but does not
1457 -- cover uses nested within an initial value expression. Nested
1458 -- uses are unlikely to occur in practice, but are theoretically
1459 -- possible. It is not clear how to handle them without fully
1460 -- traversing the expression. ???
1462 if Kind = N_Attribute_Reference
1463 and then (Attribute_Name (N) = Name_Unchecked_Access
1464 or else
1465 Attribute_Name (N) = Name_Unrestricted_Access)
1466 and then Is_Entity_Name (Prefix (N))
1467 and then Is_Type (Entity (Prefix (N)))
1468 and then Entity (Prefix (N)) = Rec_Type
1469 then
1470 Exp :=
1471 Make_Attribute_Reference (Loc,
1472 Prefix => Make_Identifier (Loc, Name_uInit),
1473 Attribute_Name => Name_Unrestricted_Access);
1474 end if;
1476 -- Ada 2005 (AI-231): Generate conversion to the null-excluding
1477 -- type to force the corresponding run-time check.
1479 if Ada_Version >= Ada_05
1480 and then Can_Never_Be_Null (Etype (Id)) -- Lhs
1481 and then Present (Etype (Exp))
1482 and then not Can_Never_Be_Null (Etype (Exp))
1483 then
1484 Rewrite (Exp, Convert_To (Etype (Id), Relocate_Node (Exp)));
1485 Analyze_And_Resolve (Exp, Etype (Id));
1486 end if;
1488 -- Take a copy of Exp to ensure that later copies of this
1489 -- component_declaration in derived types see the original tree,
1490 -- not a node rewritten during expansion of the init_proc.
1492 Exp := New_Copy_Tree (Exp);
1494 Res := New_List (
1495 Make_Assignment_Statement (Loc,
1496 Name => Lhs,
1497 Expression => Exp));
1499 Set_No_Ctrl_Actions (First (Res));
1501 -- Adjust the tag if tagged (because of possible view conversions).
1502 -- Suppress the tag adjustment when Java_VM because JVM tags are
1503 -- represented implicitly in objects.
1505 if Is_Tagged_Type (Typ) and then not Java_VM then
1506 Append_To (Res,
1507 Make_Assignment_Statement (Loc,
1508 Name =>
1509 Make_Selected_Component (Loc,
1510 Prefix => New_Copy_Tree (Lhs),
1511 Selector_Name =>
1512 New_Reference_To (Tag_Component (Typ), Loc)),
1514 Expression =>
1515 Unchecked_Convert_To (RTE (RE_Tag),
1516 New_Reference_To (Access_Disp_Table (Typ), Loc))));
1517 end if;
1519 -- Adjust the component if controlled except if it is an
1520 -- aggregate that will be expanded inline
1522 if Kind = N_Qualified_Expression then
1523 Kind := Nkind (Expression (N));
1524 end if;
1526 if Controlled_Type (Typ)
1527 and then not (Kind = N_Aggregate or else Kind = N_Extension_Aggregate)
1528 then
1529 Append_List_To (Res,
1530 Make_Adjust_Call (
1531 Ref => New_Copy_Tree (Lhs),
1532 Typ => Etype (Id),
1533 Flist_Ref =>
1534 Find_Final_List (Etype (Id), New_Copy_Tree (Lhs)),
1535 With_Attach => Make_Integer_Literal (Loc, 1)));
1536 end if;
1538 return Res;
1540 exception
1541 when RE_Not_Available =>
1542 return Empty_List;
1543 end Build_Assignment;
1545 ------------------------------------
1546 -- Build_Discriminant_Assignments --
1547 ------------------------------------
1549 procedure Build_Discriminant_Assignments (Statement_List : List_Id) is
1550 D : Entity_Id;
1551 Is_Tagged : constant Boolean := Is_Tagged_Type (Rec_Type);
1553 begin
1554 if Has_Discriminants (Rec_Type)
1555 and then not Is_Unchecked_Union (Rec_Type)
1556 then
1557 D := First_Discriminant (Rec_Type);
1559 while Present (D) loop
1560 -- Don't generate the assignment for discriminants in derived
1561 -- tagged types if the discriminant is a renaming of some
1562 -- ancestor discriminant. This initialization will be done
1563 -- when initializing the _parent field of the derived record.
1565 if Is_Tagged and then
1566 Present (Corresponding_Discriminant (D))
1567 then
1568 null;
1570 else
1571 Loc := Sloc (D);
1572 Append_List_To (Statement_List,
1573 Build_Assignment (D,
1574 New_Reference_To (Discriminal (D), Loc)));
1575 end if;
1577 Next_Discriminant (D);
1578 end loop;
1579 end if;
1580 end Build_Discriminant_Assignments;
1582 --------------------------
1583 -- Build_Init_Call_Thru --
1584 --------------------------
1586 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id is
1587 Parent_Proc : constant Entity_Id :=
1588 Base_Init_Proc (Etype (Rec_Type));
1590 Parent_Type : constant Entity_Id :=
1591 Etype (First_Formal (Parent_Proc));
1593 Uparent_Type : constant Entity_Id :=
1594 Underlying_Type (Parent_Type);
1596 First_Discr_Param : Node_Id;
1598 Parent_Discr : Entity_Id;
1599 First_Arg : Node_Id;
1600 Args : List_Id;
1601 Arg : Node_Id;
1602 Res : List_Id;
1604 begin
1605 -- First argument (_Init) is the object to be initialized.
1606 -- ??? not sure where to get a reasonable Loc for First_Arg
1608 First_Arg :=
1609 OK_Convert_To (Parent_Type,
1610 New_Reference_To (Defining_Identifier (First (Parameters)), Loc));
1612 Set_Etype (First_Arg, Parent_Type);
1614 Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
1616 -- In the tasks case,
1617 -- add _Master as the value of the _Master parameter
1618 -- add _Chain as the value of the _Chain parameter.
1619 -- add _Task_Name as the value of the _Task_Name parameter.
1620 -- At the outer level, these will be variables holding the
1621 -- corresponding values obtained from GNARL or the expander.
1623 -- At inner levels, they will be the parameters passed down through
1624 -- the outer routines.
1626 First_Discr_Param := Next (First (Parameters));
1628 if Has_Task (Rec_Type) then
1629 if Restriction_Active (No_Task_Hierarchy) then
1631 -- See comments in System.Tasking.Initialization.Init_RTS
1632 -- for the value 3.
1634 Append_To (Args, Make_Integer_Literal (Loc, 3));
1635 else
1636 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1637 end if;
1639 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1640 Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
1641 First_Discr_Param := Next (Next (Next (First_Discr_Param)));
1642 end if;
1644 -- Append discriminant values
1646 if Has_Discriminants (Uparent_Type) then
1647 pragma Assert (not Is_Tagged_Type (Uparent_Type));
1649 Parent_Discr := First_Discriminant (Uparent_Type);
1650 while Present (Parent_Discr) loop
1652 -- Get the initial value for this discriminant
1653 -- ??? needs to be cleaned up to use parent_Discr_Constr
1654 -- directly.
1656 declare
1657 Discr_Value : Elmt_Id :=
1658 First_Elmt
1659 (Stored_Constraint (Rec_Type));
1661 Discr : Entity_Id :=
1662 First_Stored_Discriminant (Uparent_Type);
1663 begin
1664 while Original_Record_Component (Parent_Discr) /= Discr loop
1665 Next_Stored_Discriminant (Discr);
1666 Next_Elmt (Discr_Value);
1667 end loop;
1669 Arg := Node (Discr_Value);
1670 end;
1672 -- Append it to the list
1674 if Nkind (Arg) = N_Identifier
1675 and then Ekind (Entity (Arg)) = E_Discriminant
1676 then
1677 Append_To (Args,
1678 New_Reference_To (Discriminal (Entity (Arg)), Loc));
1680 -- Case of access discriminants. We replace the reference
1681 -- to the type by a reference to the actual object
1683 -- ??? why is this code deleted without comment
1685 -- elsif Nkind (Arg) = N_Attribute_Reference
1686 -- and then Is_Entity_Name (Prefix (Arg))
1687 -- and then Is_Type (Entity (Prefix (Arg)))
1688 -- then
1689 -- Append_To (Args,
1690 -- Make_Attribute_Reference (Loc,
1691 -- Prefix => New_Copy (Prefix (Id_Ref)),
1692 -- Attribute_Name => Name_Unrestricted_Access));
1694 else
1695 Append_To (Args, New_Copy (Arg));
1696 end if;
1698 Next_Discriminant (Parent_Discr);
1699 end loop;
1700 end if;
1702 Res :=
1703 New_List (
1704 Make_Procedure_Call_Statement (Loc,
1705 Name => New_Occurrence_Of (Parent_Proc, Loc),
1706 Parameter_Associations => Args));
1708 return Res;
1709 end Build_Init_Call_Thru;
1711 --------------------------
1712 -- Build_Init_Procedure --
1713 --------------------------
1715 procedure Build_Init_Procedure is
1716 Body_Node : Node_Id;
1717 Handled_Stmt_Node : Node_Id;
1718 Parameters : List_Id;
1719 Proc_Spec_Node : Node_Id;
1720 Body_Stmts : List_Id;
1721 Record_Extension_Node : Node_Id;
1722 Init_Tag : Node_Id;
1724 begin
1725 Body_Stmts := New_List;
1726 Body_Node := New_Node (N_Subprogram_Body, Loc);
1728 Proc_Id :=
1729 Make_Defining_Identifier (Loc,
1730 Chars => Make_Init_Proc_Name (Rec_Type));
1731 Set_Ekind (Proc_Id, E_Procedure);
1733 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
1734 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
1736 Parameters := Init_Formals (Rec_Type);
1737 Append_List_To (Parameters,
1738 Build_Discriminant_Formals (Rec_Type, True));
1740 -- For tagged types, we add a flag to indicate whether the routine
1741 -- is called to initialize a parent component in the init_proc of
1742 -- a type extension. If the flag is false, we do not set the tag
1743 -- because it has been set already in the extension.
1745 if Is_Tagged_Type (Rec_Type)
1746 and then not Is_CPP_Class (Rec_Type)
1747 then
1748 Set_Tag :=
1749 Make_Defining_Identifier (Loc, New_Internal_Name ('P'));
1751 Append_To (Parameters,
1752 Make_Parameter_Specification (Loc,
1753 Defining_Identifier => Set_Tag,
1754 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
1755 Expression => New_Occurrence_Of (Standard_True, Loc)));
1756 end if;
1758 Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
1759 Set_Specification (Body_Node, Proc_Spec_Node);
1760 Set_Declarations (Body_Node, New_List);
1762 if Parent_Subtype_Renaming_Discrims then
1764 -- N is a Derived_Type_Definition that renames the parameters
1765 -- of the ancestor type. We init it by expanding our discrims
1766 -- and call the ancestor _init_proc with a type-converted object
1768 Append_List_To (Body_Stmts,
1769 Build_Init_Call_Thru (Parameters));
1771 elsif Nkind (Type_Definition (N)) = N_Record_Definition then
1772 Build_Discriminant_Assignments (Body_Stmts);
1774 if not Null_Present (Type_Definition (N)) then
1775 Append_List_To (Body_Stmts,
1776 Build_Init_Statements (
1777 Component_List (Type_Definition (N))));
1778 end if;
1780 else
1781 -- N is a Derived_Type_Definition with a possible non-empty
1782 -- extension. The initialization of a type extension consists
1783 -- in the initialization of the components in the extension.
1785 Build_Discriminant_Assignments (Body_Stmts);
1787 Record_Extension_Node :=
1788 Record_Extension_Part (Type_Definition (N));
1790 if not Null_Present (Record_Extension_Node) then
1791 declare
1792 Stmts : constant List_Id :=
1793 Build_Init_Statements (
1794 Component_List (Record_Extension_Node));
1796 begin
1797 -- The parent field must be initialized first because
1798 -- the offset of the new discriminants may depend on it
1800 Prepend_To (Body_Stmts, Remove_Head (Stmts));
1801 Append_List_To (Body_Stmts, Stmts);
1802 end;
1803 end if;
1804 end if;
1806 -- Add here the assignment to instantiate the Tag
1808 -- The assignement corresponds to the code:
1810 -- _Init._Tag := Typ'Tag;
1812 -- Suppress the tag assignment when Java_VM because JVM tags are
1813 -- represented implicitly in objects.
1815 if Is_Tagged_Type (Rec_Type)
1816 and then not Is_CPP_Class (Rec_Type)
1817 and then not Java_VM
1818 then
1819 Init_Tag :=
1820 Make_Assignment_Statement (Loc,
1821 Name =>
1822 Make_Selected_Component (Loc,
1823 Prefix => Make_Identifier (Loc, Name_uInit),
1824 Selector_Name =>
1825 New_Reference_To (Tag_Component (Rec_Type), Loc)),
1827 Expression =>
1828 New_Reference_To (Access_Disp_Table (Rec_Type), Loc));
1830 -- The tag must be inserted before the assignments to other
1831 -- components, because the initial value of the component may
1832 -- depend ot the tag (eg. through a dispatching operation on
1833 -- an access to the current type). The tag assignment is not done
1834 -- when initializing the parent component of a type extension,
1835 -- because in that case the tag is set in the extension.
1836 -- Extensions of imported C++ classes add a final complication,
1837 -- because we cannot inhibit tag setting in the constructor for
1838 -- the parent. In that case we insert the tag initialization
1839 -- after the calls to initialize the parent.
1841 Init_Tag :=
1842 Make_If_Statement (Loc,
1843 Condition => New_Occurrence_Of (Set_Tag, Loc),
1844 Then_Statements => New_List (Init_Tag));
1846 if not Is_CPP_Class (Etype (Rec_Type)) then
1847 Prepend_To (Body_Stmts, Init_Tag);
1849 else
1850 declare
1851 Nod : Node_Id := First (Body_Stmts);
1853 begin
1854 -- We assume the first init_proc call is for the parent
1856 while Present (Next (Nod))
1857 and then (Nkind (Nod) /= N_Procedure_Call_Statement
1858 or else not Is_Init_Proc (Name (Nod)))
1859 loop
1860 Nod := Next (Nod);
1861 end loop;
1863 Insert_After (Nod, Init_Tag);
1864 end;
1865 end if;
1866 end if;
1868 Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
1869 Set_Statements (Handled_Stmt_Node, Body_Stmts);
1870 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
1871 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
1873 if not Debug_Generated_Code then
1874 Set_Debug_Info_Off (Proc_Id);
1875 end if;
1877 -- Associate Init_Proc with type, and determine if the procedure
1878 -- is null (happens because of the Initialize_Scalars pragma case,
1879 -- where we have to generate a null procedure in case it is called
1880 -- by a client with Initialize_Scalars set). Such procedures have
1881 -- to be generated, but do not have to be called, so we mark them
1882 -- as null to suppress the call.
1884 Set_Init_Proc (Rec_Type, Proc_Id);
1886 if List_Length (Body_Stmts) = 1
1887 and then Nkind (First (Body_Stmts)) = N_Null_Statement
1888 then
1889 Set_Is_Null_Init_Proc (Proc_Id);
1890 end if;
1891 end Build_Init_Procedure;
1893 ---------------------------
1894 -- Build_Init_Statements --
1895 ---------------------------
1897 function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
1898 Check_List : constant List_Id := New_List;
1899 Alt_List : List_Id;
1900 Statement_List : List_Id;
1901 Stmts : List_Id;
1903 Per_Object_Constraint_Components : Boolean;
1905 Decl : Node_Id;
1906 Variant : Node_Id;
1908 Id : Entity_Id;
1909 Typ : Entity_Id;
1911 function Has_Access_Constraint (E : Entity_Id) return Boolean;
1912 -- Components with access discriminants that depend on the current
1913 -- instance must be initialized after all other components.
1915 ---------------------------
1916 -- Has_Access_Constraint --
1917 ---------------------------
1919 function Has_Access_Constraint (E : Entity_Id) return Boolean is
1920 Disc : Entity_Id;
1921 T : constant Entity_Id := Etype (E);
1923 begin
1924 if Has_Per_Object_Constraint (E)
1925 and then Has_Discriminants (T)
1926 then
1927 Disc := First_Discriminant (T);
1928 while Present (Disc) loop
1929 if Is_Access_Type (Etype (Disc)) then
1930 return True;
1931 end if;
1933 Next_Discriminant (Disc);
1934 end loop;
1936 return False;
1937 else
1938 return False;
1939 end if;
1940 end Has_Access_Constraint;
1942 -- Start of processing for Build_Init_Statements
1944 begin
1945 if Null_Present (Comp_List) then
1946 return New_List (Make_Null_Statement (Loc));
1947 end if;
1949 Statement_List := New_List;
1951 -- Loop through components, skipping pragmas, in 2 steps. The first
1952 -- step deals with regular components. The second step deals with
1953 -- components have per object constraints, and no explicit initia-
1954 -- lization.
1956 Per_Object_Constraint_Components := False;
1958 -- First step : regular components
1960 Decl := First_Non_Pragma (Component_Items (Comp_List));
1961 while Present (Decl) loop
1962 Loc := Sloc (Decl);
1963 Build_Record_Checks
1964 (Subtype_Indication (Component_Definition (Decl)), Check_List);
1966 Id := Defining_Identifier (Decl);
1967 Typ := Etype (Id);
1969 if Has_Access_Constraint (Id)
1970 and then No (Expression (Decl))
1971 then
1972 -- Skip processing for now and ask for a second pass
1974 Per_Object_Constraint_Components := True;
1976 else
1977 -- Case of explicit initialization
1979 if Present (Expression (Decl)) then
1980 Stmts := Build_Assignment (Id, Expression (Decl));
1982 -- Case of composite component with its own Init_Proc
1984 elsif Has_Non_Null_Base_Init_Proc (Typ) then
1985 Stmts :=
1986 Build_Initialization_Call
1987 (Loc,
1988 Make_Selected_Component (Loc,
1989 Prefix => Make_Identifier (Loc, Name_uInit),
1990 Selector_Name => New_Occurrence_Of (Id, Loc)),
1991 Typ,
1992 True,
1993 Rec_Type,
1994 Discr_Map => Discr_Map);
1996 -- Case of component needing simple initialization
1998 elsif Component_Needs_Simple_Initialization (Typ) then
1999 Stmts :=
2000 Build_Assignment (Id, Get_Simple_Init_Val (Typ, Loc));
2002 -- Nothing needed for this case
2004 else
2005 Stmts := No_List;
2006 end if;
2008 if Present (Check_List) then
2009 Append_List_To (Statement_List, Check_List);
2010 end if;
2012 if Present (Stmts) then
2014 -- Add the initialization of the record controller before
2015 -- the _Parent field is attached to it when the attachment
2016 -- can occur. It does not work to simply initialize the
2017 -- controller first: it must be initialized after the parent
2018 -- if the parent holds discriminants that can be used
2019 -- to compute the offset of the controller. We assume here
2020 -- that the last statement of the initialization call is the
2021 -- attachement of the parent (see Build_Initialization_Call)
2023 if Chars (Id) = Name_uController
2024 and then Rec_Type /= Etype (Rec_Type)
2025 and then Has_Controlled_Component (Etype (Rec_Type))
2026 and then Has_New_Controlled_Component (Rec_Type)
2027 then
2028 Insert_List_Before (Last (Statement_List), Stmts);
2029 else
2030 Append_List_To (Statement_List, Stmts);
2031 end if;
2032 end if;
2033 end if;
2035 Next_Non_Pragma (Decl);
2036 end loop;
2038 if Per_Object_Constraint_Components then
2040 -- Second pass: components with per-object constraints
2042 Decl := First_Non_Pragma (Component_Items (Comp_List));
2044 while Present (Decl) loop
2045 Loc := Sloc (Decl);
2046 Id := Defining_Identifier (Decl);
2047 Typ := Etype (Id);
2049 if Has_Access_Constraint (Id)
2050 and then No (Expression (Decl))
2051 then
2052 if Has_Non_Null_Base_Init_Proc (Typ) then
2053 Append_List_To (Statement_List,
2054 Build_Initialization_Call (Loc,
2055 Make_Selected_Component (Loc,
2056 Prefix => Make_Identifier (Loc, Name_uInit),
2057 Selector_Name => New_Occurrence_Of (Id, Loc)),
2058 Typ, True, Rec_Type, Discr_Map => Discr_Map));
2060 elsif Component_Needs_Simple_Initialization (Typ) then
2061 Append_List_To (Statement_List,
2062 Build_Assignment (Id, Get_Simple_Init_Val (Typ, Loc)));
2063 end if;
2064 end if;
2066 Next_Non_Pragma (Decl);
2067 end loop;
2068 end if;
2070 -- Process the variant part
2072 if Present (Variant_Part (Comp_List)) then
2073 Alt_List := New_List;
2074 Variant := First_Non_Pragma (Variants (Variant_Part (Comp_List)));
2076 while Present (Variant) loop
2077 Loc := Sloc (Variant);
2078 Append_To (Alt_List,
2079 Make_Case_Statement_Alternative (Loc,
2080 Discrete_Choices =>
2081 New_Copy_List (Discrete_Choices (Variant)),
2082 Statements =>
2083 Build_Init_Statements (Component_List (Variant))));
2085 Next_Non_Pragma (Variant);
2086 end loop;
2088 -- The expression of the case statement which is a reference
2089 -- to one of the discriminants is replaced by the appropriate
2090 -- formal parameter of the initialization procedure.
2092 Append_To (Statement_List,
2093 Make_Case_Statement (Loc,
2094 Expression =>
2095 New_Reference_To (Discriminal (
2096 Entity (Name (Variant_Part (Comp_List)))), Loc),
2097 Alternatives => Alt_List));
2098 end if;
2100 -- For a task record type, add the task create call and calls
2101 -- to bind any interrupt (signal) entries.
2103 if Is_Task_Record_Type (Rec_Type) then
2105 -- In the case of the restricted run time the ATCB has already
2106 -- been preallocated.
2108 if Restricted_Profile then
2109 Append_To (Statement_List,
2110 Make_Assignment_Statement (Loc,
2111 Name => Make_Selected_Component (Loc,
2112 Prefix => Make_Identifier (Loc, Name_uInit),
2113 Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
2114 Expression => Make_Attribute_Reference (Loc,
2115 Prefix =>
2116 Make_Selected_Component (Loc,
2117 Prefix => Make_Identifier (Loc, Name_uInit),
2118 Selector_Name =>
2119 Make_Identifier (Loc, Name_uATCB)),
2120 Attribute_Name => Name_Unchecked_Access)));
2121 end if;
2123 Append_To (Statement_List, Make_Task_Create_Call (Rec_Type));
2125 declare
2126 Task_Type : constant Entity_Id :=
2127 Corresponding_Concurrent_Type (Rec_Type);
2128 Task_Decl : constant Node_Id := Parent (Task_Type);
2129 Task_Def : constant Node_Id := Task_Definition (Task_Decl);
2130 Vis_Decl : Node_Id;
2131 Ent : Entity_Id;
2133 begin
2134 if Present (Task_Def) then
2135 Vis_Decl := First (Visible_Declarations (Task_Def));
2136 while Present (Vis_Decl) loop
2137 Loc := Sloc (Vis_Decl);
2139 if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
2140 if Get_Attribute_Id (Chars (Vis_Decl)) =
2141 Attribute_Address
2142 then
2143 Ent := Entity (Name (Vis_Decl));
2145 if Ekind (Ent) = E_Entry then
2146 Append_To (Statement_List,
2147 Make_Procedure_Call_Statement (Loc,
2148 Name => New_Reference_To (
2149 RTE (RE_Bind_Interrupt_To_Entry), Loc),
2150 Parameter_Associations => New_List (
2151 Make_Selected_Component (Loc,
2152 Prefix =>
2153 Make_Identifier (Loc, Name_uInit),
2154 Selector_Name =>
2155 Make_Identifier (Loc, Name_uTask_Id)),
2156 Entry_Index_Expression (
2157 Loc, Ent, Empty, Task_Type),
2158 Expression (Vis_Decl))));
2159 end if;
2160 end if;
2161 end if;
2163 Next (Vis_Decl);
2164 end loop;
2165 end if;
2166 end;
2167 end if;
2169 -- For a protected type, add statements generated by
2170 -- Make_Initialize_Protection.
2172 if Is_Protected_Record_Type (Rec_Type) then
2173 Append_List_To (Statement_List,
2174 Make_Initialize_Protection (Rec_Type));
2175 end if;
2177 -- If no initializations when generated for component declarations
2178 -- corresponding to this Statement_List, append a null statement
2179 -- to the Statement_List to make it a valid Ada tree.
2181 if Is_Empty_List (Statement_List) then
2182 Append (New_Node (N_Null_Statement, Loc), Statement_List);
2183 end if;
2185 return Statement_List;
2187 exception
2188 when RE_Not_Available =>
2189 return Empty_List;
2190 end Build_Init_Statements;
2192 -------------------------
2193 -- Build_Record_Checks --
2194 -------------------------
2196 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
2197 Subtype_Mark_Id : Entity_Id;
2199 begin
2200 if Nkind (S) = N_Subtype_Indication then
2201 Find_Type (Subtype_Mark (S));
2202 Subtype_Mark_Id := Entity (Subtype_Mark (S));
2204 -- Remaining processing depends on type
2206 case Ekind (Subtype_Mark_Id) is
2208 when Array_Kind =>
2209 Constrain_Array (S, Check_List);
2211 when others =>
2212 null;
2213 end case;
2214 end if;
2215 end Build_Record_Checks;
2217 -------------------------------------------
2218 -- Component_Needs_Simple_Initialization --
2219 -------------------------------------------
2221 function Component_Needs_Simple_Initialization
2222 (T : Entity_Id) return Boolean
2224 begin
2225 return
2226 Needs_Simple_Initialization (T)
2227 and then not Is_RTE (T, RE_Tag)
2228 and then not Is_RTE (T, RE_Vtable_Ptr);
2229 end Component_Needs_Simple_Initialization;
2231 ---------------------
2232 -- Constrain_Array --
2233 ---------------------
2235 procedure Constrain_Array
2236 (SI : Node_Id;
2237 Check_List : List_Id)
2239 C : constant Node_Id := Constraint (SI);
2240 Number_Of_Constraints : Nat := 0;
2241 Index : Node_Id;
2242 S, T : Entity_Id;
2244 begin
2245 T := Entity (Subtype_Mark (SI));
2247 if Ekind (T) in Access_Kind then
2248 T := Designated_Type (T);
2249 end if;
2251 S := First (Constraints (C));
2253 while Present (S) loop
2254 Number_Of_Constraints := Number_Of_Constraints + 1;
2255 Next (S);
2256 end loop;
2258 -- In either case, the index constraint must provide a discrete
2259 -- range for each index of the array type and the type of each
2260 -- discrete range must be the same as that of the corresponding
2261 -- index. (RM 3.6.1)
2263 S := First (Constraints (C));
2264 Index := First_Index (T);
2265 Analyze (Index);
2267 -- Apply constraints to each index type
2269 for J in 1 .. Number_Of_Constraints loop
2270 Constrain_Index (Index, S, Check_List);
2271 Next (Index);
2272 Next (S);
2273 end loop;
2275 end Constrain_Array;
2277 ---------------------
2278 -- Constrain_Index --
2279 ---------------------
2281 procedure Constrain_Index
2282 (Index : Node_Id;
2283 S : Node_Id;
2284 Check_List : List_Id)
2286 T : constant Entity_Id := Etype (Index);
2288 begin
2289 if Nkind (S) = N_Range then
2290 Process_Range_Expr_In_Decl (S, T, Check_List);
2291 end if;
2292 end Constrain_Index;
2294 --------------------------------------
2295 -- Parent_Subtype_Renaming_Discrims --
2296 --------------------------------------
2298 function Parent_Subtype_Renaming_Discrims return Boolean is
2299 De : Entity_Id;
2300 Dp : Entity_Id;
2302 begin
2303 if Base_Type (Pe) /= Pe then
2304 return False;
2305 end if;
2307 if Etype (Pe) = Pe
2308 or else not Has_Discriminants (Pe)
2309 or else Is_Constrained (Pe)
2310 or else Is_Tagged_Type (Pe)
2311 then
2312 return False;
2313 end if;
2315 -- If there are no explicit stored discriminants we have inherited
2316 -- the root type discriminants so far, so no renamings occurred.
2318 if First_Discriminant (Pe) = First_Stored_Discriminant (Pe) then
2319 return False;
2320 end if;
2322 -- Check if we have done some trivial renaming of the parent
2323 -- discriminants, i.e. someting like
2325 -- type DT (X1,X2: int) is new PT (X1,X2);
2327 De := First_Discriminant (Pe);
2328 Dp := First_Discriminant (Etype (Pe));
2330 while Present (De) loop
2331 pragma Assert (Present (Dp));
2333 if Corresponding_Discriminant (De) /= Dp then
2334 return True;
2335 end if;
2337 Next_Discriminant (De);
2338 Next_Discriminant (Dp);
2339 end loop;
2341 return Present (Dp);
2342 end Parent_Subtype_Renaming_Discrims;
2344 ------------------------
2345 -- Requires_Init_Proc --
2346 ------------------------
2348 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
2349 Comp_Decl : Node_Id;
2350 Id : Entity_Id;
2351 Typ : Entity_Id;
2353 begin
2354 -- Definitely do not need one if specifically suppressed
2356 if Suppress_Init_Proc (Rec_Id) then
2357 return False;
2358 end if;
2360 -- Otherwise we need to generate an initialization procedure if
2361 -- Is_CPP_Class is False and at least one of the following applies:
2363 -- 1. Discriminants are present, since they need to be initialized
2364 -- with the appropriate discriminant constraint expressions.
2365 -- However, the discriminant of an unchecked union does not
2366 -- count, since the discriminant is not present.
2368 -- 2. The type is a tagged type, since the implicit Tag component
2369 -- needs to be initialized with a pointer to the dispatch table.
2371 -- 3. The type contains tasks
2373 -- 4. One or more components has an initial value
2375 -- 5. One or more components is for a type which itself requires
2376 -- an initialization procedure.
2378 -- 6. One or more components is a type that requires simple
2379 -- initialization (see Needs_Simple_Initialization), except
2380 -- that types Tag and Vtable_Ptr are excluded, since fields
2381 -- of these types are initialized by other means.
2383 -- 7. The type is the record type built for a task type (since at
2384 -- the very least, Create_Task must be called)
2386 -- 8. The type is the record type built for a protected type (since
2387 -- at least Initialize_Protection must be called)
2389 -- 9. The type is marked as a public entity. The reason we add this
2390 -- case (even if none of the above apply) is to properly handle
2391 -- Initialize_Scalars. If a package is compiled without an IS
2392 -- pragma, and the client is compiled with an IS pragma, then
2393 -- the client will think an initialization procedure is present
2394 -- and call it, when in fact no such procedure is required, but
2395 -- since the call is generated, there had better be a routine
2396 -- at the other end of the call, even if it does nothing!)
2398 -- Note: the reason we exclude the CPP_Class case is ???
2400 if Is_CPP_Class (Rec_Id) then
2401 return False;
2403 elsif not Restriction_Active (No_Initialize_Scalars)
2404 and then Is_Public (Rec_Id)
2405 then
2406 return True;
2408 elsif (Has_Discriminants (Rec_Id)
2409 and then not Is_Unchecked_Union (Rec_Id))
2410 or else Is_Tagged_Type (Rec_Id)
2411 or else Is_Concurrent_Record_Type (Rec_Id)
2412 or else Has_Task (Rec_Id)
2413 then
2414 return True;
2415 end if;
2417 Id := First_Component (Rec_Id);
2419 while Present (Id) loop
2420 Comp_Decl := Parent (Id);
2421 Typ := Etype (Id);
2423 if Present (Expression (Comp_Decl))
2424 or else Has_Non_Null_Base_Init_Proc (Typ)
2425 or else Component_Needs_Simple_Initialization (Typ)
2426 then
2427 return True;
2428 end if;
2430 Next_Component (Id);
2431 end loop;
2433 return False;
2434 end Requires_Init_Proc;
2436 -- Start of processing for Build_Record_Init_Proc
2438 begin
2439 Rec_Type := Defining_Identifier (N);
2441 -- This may be full declaration of a private type, in which case
2442 -- the visible entity is a record, and the private entity has been
2443 -- exchanged with it in the private part of the current package.
2444 -- The initialization procedure is built for the record type, which
2445 -- is retrievable from the private entity.
2447 if Is_Incomplete_Or_Private_Type (Rec_Type) then
2448 Rec_Type := Underlying_Type (Rec_Type);
2449 end if;
2451 -- If there are discriminants, build the discriminant map to replace
2452 -- discriminants by their discriminals in complex bound expressions.
2453 -- These only arise for the corresponding records of protected types.
2455 if Is_Concurrent_Record_Type (Rec_Type)
2456 and then Has_Discriminants (Rec_Type)
2457 then
2458 declare
2459 Disc : Entity_Id;
2461 begin
2462 Disc := First_Discriminant (Rec_Type);
2464 while Present (Disc) loop
2465 Append_Elmt (Disc, Discr_Map);
2466 Append_Elmt (Discriminal (Disc), Discr_Map);
2467 Next_Discriminant (Disc);
2468 end loop;
2469 end;
2470 end if;
2472 -- Derived types that have no type extension can use the initialization
2473 -- procedure of their parent and do not need a procedure of their own.
2474 -- This is only correct if there are no representation clauses for the
2475 -- type or its parent, and if the parent has in fact been frozen so
2476 -- that its initialization procedure exists.
2478 if Is_Derived_Type (Rec_Type)
2479 and then not Is_Tagged_Type (Rec_Type)
2480 and then not Is_Unchecked_Union (Rec_Type)
2481 and then not Has_New_Non_Standard_Rep (Rec_Type)
2482 and then not Parent_Subtype_Renaming_Discrims
2483 and then Has_Non_Null_Base_Init_Proc (Etype (Rec_Type))
2484 then
2485 Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
2487 -- Otherwise if we need an initialization procedure, then build one,
2488 -- mark it as public and inlinable and as having a completion.
2490 elsif Requires_Init_Proc (Rec_Type)
2491 or else Is_Unchecked_Union (Rec_Type)
2492 then
2493 Build_Init_Procedure;
2494 Set_Is_Public (Proc_Id, Is_Public (Pe));
2496 -- The initialization of protected records is not worth inlining.
2497 -- In addition, when compiled for another unit for inlining purposes,
2498 -- it may make reference to entities that have not been elaborated
2499 -- yet. The initialization of controlled records contains a nested
2500 -- clean-up procedure that makes it impractical to inline as well,
2501 -- and leads to undefined symbols if inlined in a different unit.
2502 -- Similar considerations apply to task types.
2504 if not Is_Concurrent_Type (Rec_Type)
2505 and then not Has_Task (Rec_Type)
2506 and then not Controlled_Type (Rec_Type)
2507 then
2508 Set_Is_Inlined (Proc_Id);
2509 end if;
2511 Set_Is_Internal (Proc_Id);
2512 Set_Has_Completion (Proc_Id);
2514 if not Debug_Generated_Code then
2515 Set_Debug_Info_Off (Proc_Id);
2516 end if;
2517 end if;
2518 end Build_Record_Init_Proc;
2520 ----------------------------
2521 -- Build_Slice_Assignment --
2522 ----------------------------
2524 -- Generates the following subprogram:
2526 -- procedure Assign
2527 -- (Source, Target : Array_Type,
2528 -- Left_Lo, Left_Hi, Right_Lo, Right_Hi : Index;
2529 -- Rev : Boolean)
2530 -- is
2531 -- Li1 : Index;
2532 -- Ri1 : Index;
2534 -- begin
2535 -- if Rev then
2536 -- Li1 := Left_Hi;
2537 -- Ri1 := Right_Hi;
2538 -- else
2539 -- Li1 := Left_Lo;
2540 -- Ri1 := Right_Lo;
2541 -- end if;
2543 -- loop
2544 -- if Rev then
2545 -- exit when Li1 < Left_Lo;
2546 -- else
2547 -- exit when Li1 > Left_Hi;
2548 -- end if;
2550 -- Target (Li1) := Source (Ri1);
2552 -- if Rev then
2553 -- Li1 := Index'pred (Li1);
2554 -- Ri1 := Index'pred (Ri1);
2555 -- else
2556 -- Li1 := Index'succ (Li1);
2557 -- Ri1 := Index'succ (Ri1);
2558 -- end if;
2559 -- end loop;
2560 -- end Assign;
2562 procedure Build_Slice_Assignment (Typ : Entity_Id) is
2563 Loc : constant Source_Ptr := Sloc (Typ);
2564 Index : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
2566 -- Build formal parameters of procedure
2568 Larray : constant Entity_Id :=
2569 Make_Defining_Identifier
2570 (Loc, Chars => New_Internal_Name ('A'));
2571 Rarray : constant Entity_Id :=
2572 Make_Defining_Identifier
2573 (Loc, Chars => New_Internal_Name ('R'));
2574 Left_Lo : constant Entity_Id :=
2575 Make_Defining_Identifier
2576 (Loc, Chars => New_Internal_Name ('L'));
2577 Left_Hi : constant Entity_Id :=
2578 Make_Defining_Identifier
2579 (Loc, Chars => New_Internal_Name ('L'));
2580 Right_Lo : constant Entity_Id :=
2581 Make_Defining_Identifier
2582 (Loc, Chars => New_Internal_Name ('R'));
2583 Right_Hi : constant Entity_Id :=
2584 Make_Defining_Identifier
2585 (Loc, Chars => New_Internal_Name ('R'));
2586 Rev : constant Entity_Id :=
2587 Make_Defining_Identifier
2588 (Loc, Chars => New_Internal_Name ('D'));
2589 Proc_Name : constant Entity_Id :=
2590 Make_Defining_Identifier (Loc,
2591 Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
2593 Lnn : constant Entity_Id :=
2594 Make_Defining_Identifier (Loc, New_Internal_Name ('L'));
2595 Rnn : constant Entity_Id :=
2596 Make_Defining_Identifier (Loc, New_Internal_Name ('R'));
2597 -- Subscripts for left and right sides
2599 Decls : List_Id;
2600 Loops : Node_Id;
2601 Stats : List_Id;
2603 begin
2604 -- Build declarations for indices
2606 Decls := New_List;
2608 Append_To (Decls,
2609 Make_Object_Declaration (Loc,
2610 Defining_Identifier => Lnn,
2611 Object_Definition =>
2612 New_Occurrence_Of (Index, Loc)));
2614 Append_To (Decls,
2615 Make_Object_Declaration (Loc,
2616 Defining_Identifier => Rnn,
2617 Object_Definition =>
2618 New_Occurrence_Of (Index, Loc)));
2620 Stats := New_List;
2622 -- Build initializations for indices
2624 declare
2625 F_Init : constant List_Id := New_List;
2626 B_Init : constant List_Id := New_List;
2628 begin
2629 Append_To (F_Init,
2630 Make_Assignment_Statement (Loc,
2631 Name => New_Occurrence_Of (Lnn, Loc),
2632 Expression => New_Occurrence_Of (Left_Lo, Loc)));
2634 Append_To (F_Init,
2635 Make_Assignment_Statement (Loc,
2636 Name => New_Occurrence_Of (Rnn, Loc),
2637 Expression => New_Occurrence_Of (Right_Lo, Loc)));
2639 Append_To (B_Init,
2640 Make_Assignment_Statement (Loc,
2641 Name => New_Occurrence_Of (Lnn, Loc),
2642 Expression => New_Occurrence_Of (Left_Hi, Loc)));
2644 Append_To (B_Init,
2645 Make_Assignment_Statement (Loc,
2646 Name => New_Occurrence_Of (Rnn, Loc),
2647 Expression => New_Occurrence_Of (Right_Hi, Loc)));
2649 Append_To (Stats,
2650 Make_If_Statement (Loc,
2651 Condition => New_Occurrence_Of (Rev, Loc),
2652 Then_Statements => B_Init,
2653 Else_Statements => F_Init));
2654 end;
2656 -- Now construct the assignment statement
2658 Loops :=
2659 Make_Loop_Statement (Loc,
2660 Statements => New_List (
2661 Make_Assignment_Statement (Loc,
2662 Name =>
2663 Make_Indexed_Component (Loc,
2664 Prefix => New_Occurrence_Of (Larray, Loc),
2665 Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
2666 Expression =>
2667 Make_Indexed_Component (Loc,
2668 Prefix => New_Occurrence_Of (Rarray, Loc),
2669 Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
2670 End_Label => Empty);
2672 -- Build exit condition.
2674 declare
2675 F_Ass : constant List_Id := New_List;
2676 B_Ass : constant List_Id := New_List;
2678 begin
2679 Append_To (F_Ass,
2680 Make_Exit_Statement (Loc,
2681 Condition =>
2682 Make_Op_Gt (Loc,
2683 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
2684 Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
2686 Append_To (B_Ass,
2687 Make_Exit_Statement (Loc,
2688 Condition =>
2689 Make_Op_Lt (Loc,
2690 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
2691 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
2693 Prepend_To (Statements (Loops),
2694 Make_If_Statement (Loc,
2695 Condition => New_Occurrence_Of (Rev, Loc),
2696 Then_Statements => B_Ass,
2697 Else_Statements => F_Ass));
2698 end;
2700 -- Build the increment/decrement statements
2702 declare
2703 F_Ass : constant List_Id := New_List;
2704 B_Ass : constant List_Id := New_List;
2706 begin
2707 Append_To (F_Ass,
2708 Make_Assignment_Statement (Loc,
2709 Name => New_Occurrence_Of (Lnn, Loc),
2710 Expression =>
2711 Make_Attribute_Reference (Loc,
2712 Prefix =>
2713 New_Occurrence_Of (Index, Loc),
2714 Attribute_Name => Name_Succ,
2715 Expressions => New_List (
2716 New_Occurrence_Of (Lnn, Loc)))));
2718 Append_To (F_Ass,
2719 Make_Assignment_Statement (Loc,
2720 Name => New_Occurrence_Of (Rnn, Loc),
2721 Expression =>
2722 Make_Attribute_Reference (Loc,
2723 Prefix =>
2724 New_Occurrence_Of (Index, Loc),
2725 Attribute_Name => Name_Succ,
2726 Expressions => New_List (
2727 New_Occurrence_Of (Rnn, Loc)))));
2729 Append_To (B_Ass,
2730 Make_Assignment_Statement (Loc,
2731 Name => New_Occurrence_Of (Lnn, Loc),
2732 Expression =>
2733 Make_Attribute_Reference (Loc,
2734 Prefix =>
2735 New_Occurrence_Of (Index, Loc),
2736 Attribute_Name => Name_Pred,
2737 Expressions => New_List (
2738 New_Occurrence_Of (Lnn, Loc)))));
2740 Append_To (B_Ass,
2741 Make_Assignment_Statement (Loc,
2742 Name => New_Occurrence_Of (Rnn, Loc),
2743 Expression =>
2744 Make_Attribute_Reference (Loc,
2745 Prefix =>
2746 New_Occurrence_Of (Index, Loc),
2747 Attribute_Name => Name_Pred,
2748 Expressions => New_List (
2749 New_Occurrence_Of (Rnn, Loc)))));
2751 Append_To (Statements (Loops),
2752 Make_If_Statement (Loc,
2753 Condition => New_Occurrence_Of (Rev, Loc),
2754 Then_Statements => B_Ass,
2755 Else_Statements => F_Ass));
2756 end;
2758 Append_To (Stats, Loops);
2760 declare
2761 Spec : Node_Id;
2762 Formals : List_Id := New_List;
2764 begin
2765 Formals := New_List (
2766 Make_Parameter_Specification (Loc,
2767 Defining_Identifier => Larray,
2768 Out_Present => True,
2769 Parameter_Type =>
2770 New_Reference_To (Base_Type (Typ), Loc)),
2772 Make_Parameter_Specification (Loc,
2773 Defining_Identifier => Rarray,
2774 Parameter_Type =>
2775 New_Reference_To (Base_Type (Typ), Loc)),
2777 Make_Parameter_Specification (Loc,
2778 Defining_Identifier => Left_Lo,
2779 Parameter_Type =>
2780 New_Reference_To (Index, Loc)),
2782 Make_Parameter_Specification (Loc,
2783 Defining_Identifier => Left_Hi,
2784 Parameter_Type =>
2785 New_Reference_To (Index, Loc)),
2787 Make_Parameter_Specification (Loc,
2788 Defining_Identifier => Right_Lo,
2789 Parameter_Type =>
2790 New_Reference_To (Index, Loc)),
2792 Make_Parameter_Specification (Loc,
2793 Defining_Identifier => Right_Hi,
2794 Parameter_Type =>
2795 New_Reference_To (Index, Loc)));
2797 Append_To (Formals,
2798 Make_Parameter_Specification (Loc,
2799 Defining_Identifier => Rev,
2800 Parameter_Type =>
2801 New_Reference_To (Standard_Boolean, Loc)));
2803 Spec :=
2804 Make_Procedure_Specification (Loc,
2805 Defining_Unit_Name => Proc_Name,
2806 Parameter_Specifications => Formals);
2808 Discard_Node (
2809 Make_Subprogram_Body (Loc,
2810 Specification => Spec,
2811 Declarations => Decls,
2812 Handled_Statement_Sequence =>
2813 Make_Handled_Sequence_Of_Statements (Loc,
2814 Statements => Stats)));
2815 end;
2817 Set_TSS (Typ, Proc_Name);
2818 Set_Is_Pure (Proc_Name);
2819 end Build_Slice_Assignment;
2821 ------------------------------------
2822 -- Build_Variant_Record_Equality --
2823 ------------------------------------
2825 -- Generates:
2827 -- function _Equality (X, Y : T) return Boolean is
2828 -- begin
2829 -- -- Compare discriminants
2831 -- if False or else X.D1 /= Y.D1 or else X.D2 /= Y.D2 then
2832 -- return False;
2833 -- end if;
2835 -- -- Compare components
2837 -- if False or else X.C1 /= Y.C1 or else X.C2 /= Y.C2 then
2838 -- return False;
2839 -- end if;
2841 -- -- Compare variant part
2843 -- case X.D1 is
2844 -- when V1 =>
2845 -- if False or else X.C2 /= Y.C2 or else X.C3 /= Y.C3 then
2846 -- return False;
2847 -- end if;
2848 -- ...
2849 -- when Vn =>
2850 -- if False or else X.Cn /= Y.Cn then
2851 -- return False;
2852 -- end if;
2853 -- end case;
2854 -- return True;
2855 -- end _Equality;
2857 procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
2858 Loc : constant Source_Ptr := Sloc (Typ);
2860 F : constant Entity_Id :=
2861 Make_Defining_Identifier (Loc,
2862 Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
2864 X : constant Entity_Id :=
2865 Make_Defining_Identifier (Loc,
2866 Chars => Name_X);
2868 Y : constant Entity_Id :=
2869 Make_Defining_Identifier (Loc,
2870 Chars => Name_Y);
2872 Def : constant Node_Id := Parent (Typ);
2873 Comps : constant Node_Id := Component_List (Type_Definition (Def));
2874 Stmts : constant List_Id := New_List;
2875 Pspecs : constant List_Id := New_List;
2877 begin
2878 -- Derived Unchecked_Union types no longer inherit the equality function
2879 -- of their parent.
2881 if Is_Derived_Type (Typ)
2882 and then not Is_Unchecked_Union (Typ)
2883 and then not Has_New_Non_Standard_Rep (Typ)
2884 then
2885 declare
2886 Parent_Eq : constant Entity_Id :=
2887 TSS (Root_Type (Typ), TSS_Composite_Equality);
2889 begin
2890 if Present (Parent_Eq) then
2891 Copy_TSS (Parent_Eq, Typ);
2892 return;
2893 end if;
2894 end;
2895 end if;
2897 Discard_Node (
2898 Make_Subprogram_Body (Loc,
2899 Specification =>
2900 Make_Function_Specification (Loc,
2901 Defining_Unit_Name => F,
2902 Parameter_Specifications => Pspecs,
2903 Subtype_Mark => New_Reference_To (Standard_Boolean, Loc)),
2904 Declarations => New_List,
2905 Handled_Statement_Sequence =>
2906 Make_Handled_Sequence_Of_Statements (Loc,
2907 Statements => Stmts)));
2909 Append_To (Pspecs,
2910 Make_Parameter_Specification (Loc,
2911 Defining_Identifier => X,
2912 Parameter_Type => New_Reference_To (Typ, Loc)));
2914 Append_To (Pspecs,
2915 Make_Parameter_Specification (Loc,
2916 Defining_Identifier => Y,
2917 Parameter_Type => New_Reference_To (Typ, Loc)));
2919 -- Unchecked_Unions require additional machinery to support equality.
2920 -- Two extra parameters (A and B) are added to the equality function
2921 -- parameter list in order to capture the inferred values of the
2922 -- discriminants in later calls.
2924 if Is_Unchecked_Union (Typ) then
2925 declare
2926 Discr_Type : constant Node_Id := Etype (First_Discriminant (Typ));
2928 A : constant Node_Id :=
2929 Make_Defining_Identifier (Loc,
2930 Chars => Name_A);
2932 B : constant Node_Id :=
2933 Make_Defining_Identifier (Loc,
2934 Chars => Name_B);
2936 begin
2937 -- Add A and B to the parameter list
2939 Append_To (Pspecs,
2940 Make_Parameter_Specification (Loc,
2941 Defining_Identifier => A,
2942 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
2944 Append_To (Pspecs,
2945 Make_Parameter_Specification (Loc,
2946 Defining_Identifier => B,
2947 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
2949 -- Generate the following header code to compare the inferred
2950 -- discriminants:
2952 -- if a /= b then
2953 -- return False;
2954 -- end if;
2956 Append_To (Stmts,
2957 Make_If_Statement (Loc,
2958 Condition =>
2959 Make_Op_Ne (Loc,
2960 Left_Opnd => New_Reference_To (A, Loc),
2961 Right_Opnd => New_Reference_To (B, Loc)),
2962 Then_Statements => New_List (
2963 Make_Return_Statement (Loc,
2964 Expression => New_Occurrence_Of (Standard_False, Loc)))));
2966 -- Generate component-by-component comparison. Note that we must
2967 -- propagate one of the inferred discriminant formals to act as
2968 -- the case statement switch.
2970 Append_List_To (Stmts,
2971 Make_Eq_Case (Typ, Comps, A));
2973 end;
2975 -- Normal case (not unchecked union)
2977 else
2978 Append_To (Stmts,
2979 Make_Eq_If (Typ,
2980 Discriminant_Specifications (Def)));
2982 Append_List_To (Stmts,
2983 Make_Eq_Case (Typ, Comps));
2984 end if;
2986 Append_To (Stmts,
2987 Make_Return_Statement (Loc,
2988 Expression => New_Reference_To (Standard_True, Loc)));
2990 Set_TSS (Typ, F);
2991 Set_Is_Pure (F);
2993 if not Debug_Generated_Code then
2994 Set_Debug_Info_Off (F);
2995 end if;
2996 end Build_Variant_Record_Equality;
2998 -----------------------------
2999 -- Check_Stream_Attributes --
3000 -----------------------------
3002 procedure Check_Stream_Attributes (Typ : Entity_Id) is
3003 Comp : Entity_Id;
3004 Par : constant Entity_Id := Root_Type (Base_Type (Typ));
3005 Par_Read : constant Boolean := Present (TSS (Par, TSS_Stream_Read));
3006 Par_Write : constant Boolean := Present (TSS (Par, TSS_Stream_Write));
3008 begin
3009 if Par_Read or else Par_Write then
3010 Comp := First_Component (Typ);
3011 while Present (Comp) loop
3012 if Comes_From_Source (Comp)
3013 and then Original_Record_Component (Comp) = Comp
3014 and then Is_Limited_Type (Etype (Comp))
3015 then
3016 if (Par_Read and then
3017 No (TSS (Base_Type (Etype (Comp)), TSS_Stream_Read)))
3018 or else
3019 (Par_Write and then
3020 No (TSS (Base_Type (Etype (Comp)), TSS_Stream_Write)))
3021 then
3022 Error_Msg_N
3023 ("|component must have Stream attribute",
3024 Parent (Comp));
3025 end if;
3026 end if;
3028 Next_Component (Comp);
3029 end loop;
3030 end if;
3031 end Check_Stream_Attributes;
3033 -----------------------------
3034 -- Expand_Record_Extension --
3035 -----------------------------
3037 -- Add a field _parent at the beginning of the record extension. This is
3038 -- used to implement inheritance. Here are some examples of expansion:
3040 -- 1. no discriminants
3041 -- type T2 is new T1 with null record;
3042 -- gives
3043 -- type T2 is new T1 with record
3044 -- _Parent : T1;
3045 -- end record;
3047 -- 2. renamed discriminants
3048 -- type T2 (B, C : Int) is new T1 (A => B) with record
3049 -- _Parent : T1 (A => B);
3050 -- D : Int;
3051 -- end;
3053 -- 3. inherited discriminants
3054 -- type T2 is new T1 with record -- discriminant A inherited
3055 -- _Parent : T1 (A);
3056 -- D : Int;
3057 -- end;
3059 procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
3060 Indic : constant Node_Id := Subtype_Indication (Def);
3061 Loc : constant Source_Ptr := Sloc (Def);
3062 Rec_Ext_Part : Node_Id := Record_Extension_Part (Def);
3063 Par_Subtype : Entity_Id;
3064 Comp_List : Node_Id;
3065 Comp_Decl : Node_Id;
3066 Parent_N : Node_Id;
3067 D : Entity_Id;
3068 List_Constr : constant List_Id := New_List;
3070 begin
3071 -- Expand_Record_Extension is called directly from the semantics, so
3072 -- we must check to see whether expansion is active before proceeding
3074 if not Expander_Active then
3075 return;
3076 end if;
3078 -- This may be a derivation of an untagged private type whose full
3079 -- view is tagged, in which case the Derived_Type_Definition has no
3080 -- extension part. Build an empty one now.
3082 if No (Rec_Ext_Part) then
3083 Rec_Ext_Part :=
3084 Make_Record_Definition (Loc,
3085 End_Label => Empty,
3086 Component_List => Empty,
3087 Null_Present => True);
3089 Set_Record_Extension_Part (Def, Rec_Ext_Part);
3090 Mark_Rewrite_Insertion (Rec_Ext_Part);
3091 end if;
3093 Comp_List := Component_List (Rec_Ext_Part);
3095 Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
3097 -- If the derived type inherits its discriminants the type of the
3098 -- _parent field must be constrained by the inherited discriminants
3100 if Has_Discriminants (T)
3101 and then Nkind (Indic) /= N_Subtype_Indication
3102 and then not Is_Constrained (Entity (Indic))
3103 then
3104 D := First_Discriminant (T);
3105 while Present (D) loop
3106 Append_To (List_Constr, New_Occurrence_Of (D, Loc));
3107 Next_Discriminant (D);
3108 end loop;
3110 Par_Subtype :=
3111 Process_Subtype (
3112 Make_Subtype_Indication (Loc,
3113 Subtype_Mark => New_Reference_To (Entity (Indic), Loc),
3114 Constraint =>
3115 Make_Index_Or_Discriminant_Constraint (Loc,
3116 Constraints => List_Constr)),
3117 Def);
3119 -- Otherwise the original subtype_indication is just what is needed
3121 else
3122 Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
3123 end if;
3125 Set_Parent_Subtype (T, Par_Subtype);
3127 Comp_Decl :=
3128 Make_Component_Declaration (Loc,
3129 Defining_Identifier => Parent_N,
3130 Component_Definition =>
3131 Make_Component_Definition (Loc,
3132 Aliased_Present => False,
3133 Subtype_Indication => New_Reference_To (Par_Subtype, Loc)));
3135 if Null_Present (Rec_Ext_Part) then
3136 Set_Component_List (Rec_Ext_Part,
3137 Make_Component_List (Loc,
3138 Component_Items => New_List (Comp_Decl),
3139 Variant_Part => Empty,
3140 Null_Present => False));
3141 Set_Null_Present (Rec_Ext_Part, False);
3143 elsif Null_Present (Comp_List)
3144 or else Is_Empty_List (Component_Items (Comp_List))
3145 then
3146 Set_Component_Items (Comp_List, New_List (Comp_Decl));
3147 Set_Null_Present (Comp_List, False);
3149 else
3150 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
3151 end if;
3153 Analyze (Comp_Decl);
3154 end Expand_Record_Extension;
3156 ------------------------------------
3157 -- Expand_N_Full_Type_Declaration --
3158 ------------------------------------
3160 procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
3161 Def_Id : constant Entity_Id := Defining_Identifier (N);
3162 B_Id : constant Entity_Id := Base_Type (Def_Id);
3163 Par_Id : Entity_Id;
3164 FN : Node_Id;
3166 begin
3167 if Is_Access_Type (Def_Id) then
3169 -- Anonymous access types are created for the components of the
3170 -- record parameter for an entry declaration. No master is created
3171 -- for such a type.
3173 if Has_Task (Designated_Type (Def_Id))
3174 and then Comes_From_Source (N)
3175 then
3176 Build_Master_Entity (Def_Id);
3177 Build_Master_Renaming (Parent (Def_Id), Def_Id);
3179 -- Create a class-wide master because a Master_Id must be generated
3180 -- for access-to-limited-class-wide types, whose root may be extended
3181 -- with task components.
3183 elsif Is_Class_Wide_Type (Designated_Type (Def_Id))
3184 and then Is_Limited_Type (Designated_Type (Def_Id))
3185 and then Tasking_Allowed
3187 -- Don't create a class-wide master for types whose convention is
3188 -- Java since these types cannot embed Ada tasks anyway. Note that
3189 -- the following test cannot catch the following case:
3191 -- package java.lang.Object is
3192 -- type Typ is tagged limited private;
3193 -- type Ref is access all Typ'Class;
3194 -- private
3195 -- type Typ is tagged limited ...;
3196 -- pragma Convention (Typ, Java)
3197 -- end;
3199 -- Because the convention appears after we have done the
3200 -- processing for type Ref.
3202 and then Convention (Designated_Type (Def_Id)) /= Convention_Java
3203 then
3204 Build_Class_Wide_Master (Def_Id);
3206 elsif Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
3207 Expand_Access_Protected_Subprogram_Type (N);
3208 end if;
3210 elsif Has_Task (Def_Id) then
3211 Expand_Previous_Access_Type (Def_Id);
3212 end if;
3214 Par_Id := Etype (B_Id);
3216 -- The parent type is private then we need to inherit
3217 -- any TSS operations from the full view.
3219 if Ekind (Par_Id) in Private_Kind
3220 and then Present (Full_View (Par_Id))
3221 then
3222 Par_Id := Base_Type (Full_View (Par_Id));
3223 end if;
3225 if Nkind (Type_Definition (Original_Node (N)))
3226 = N_Derived_Type_Definition
3227 and then not Is_Tagged_Type (Def_Id)
3228 and then Present (Freeze_Node (Par_Id))
3229 and then Present (TSS_Elist (Freeze_Node (Par_Id)))
3230 then
3231 Ensure_Freeze_Node (B_Id);
3232 FN := Freeze_Node (B_Id);
3234 if No (TSS_Elist (FN)) then
3235 Set_TSS_Elist (FN, New_Elmt_List);
3236 end if;
3238 declare
3239 T_E : constant Elist_Id := TSS_Elist (FN);
3240 Elmt : Elmt_Id;
3242 begin
3243 Elmt := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
3245 while Present (Elmt) loop
3246 if Chars (Node (Elmt)) /= Name_uInit then
3247 Append_Elmt (Node (Elmt), T_E);
3248 end if;
3250 Next_Elmt (Elmt);
3251 end loop;
3253 -- If the derived type itself is private with a full view, then
3254 -- associate the full view with the inherited TSS_Elist as well.
3256 if Ekind (B_Id) in Private_Kind
3257 and then Present (Full_View (B_Id))
3258 then
3259 Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
3260 Set_TSS_Elist
3261 (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
3262 end if;
3263 end;
3264 end if;
3265 end Expand_N_Full_Type_Declaration;
3267 ---------------------------------
3268 -- Expand_N_Object_Declaration --
3269 ---------------------------------
3271 -- First we do special processing for objects of a tagged type where this
3272 -- is the point at which the type is frozen. The creation of the dispatch
3273 -- table and the initialization procedure have to be deferred to this
3274 -- point, since we reference previously declared primitive subprograms.
3276 -- For all types, we call an initialization procedure if there is one
3278 procedure Expand_N_Object_Declaration (N : Node_Id) is
3279 Def_Id : constant Entity_Id := Defining_Identifier (N);
3280 Typ : constant Entity_Id := Etype (Def_Id);
3281 Loc : constant Source_Ptr := Sloc (N);
3282 Expr : constant Node_Id := Expression (N);
3283 New_Ref : Node_Id;
3284 Id_Ref : Node_Id;
3285 Expr_Q : Node_Id;
3287 begin
3288 -- Don't do anything for deferred constants. All proper actions will
3289 -- be expanded during the full declaration.
3291 if No (Expr) and Constant_Present (N) then
3292 return;
3293 end if;
3295 -- Make shared memory routines for shared passive variable
3297 if Is_Shared_Passive (Def_Id) then
3298 Make_Shared_Var_Procs (N);
3299 end if;
3301 -- If tasks being declared, make sure we have an activation chain
3302 -- defined for the tasks (has no effect if we already have one), and
3303 -- also that a Master variable is established and that the appropriate
3304 -- enclosing construct is established as a task master.
3306 if Has_Task (Typ) then
3307 Build_Activation_Chain_Entity (N);
3308 Build_Master_Entity (Def_Id);
3309 end if;
3311 -- Default initialization required, and no expression present
3313 if No (Expr) then
3315 -- Expand Initialize call for controlled objects. One may wonder why
3316 -- the Initialize Call is not done in the regular Init procedure
3317 -- attached to the record type. That's because the init procedure is
3318 -- recursively called on each component, including _Parent, thus the
3319 -- Init call for a controlled object would generate not only one
3320 -- Initialize call as it is required but one for each ancestor of
3321 -- its type. This processing is suppressed if No_Initialization set.
3323 if not Controlled_Type (Typ)
3324 or else No_Initialization (N)
3325 then
3326 null;
3328 elsif not Abort_Allowed
3329 or else not Comes_From_Source (N)
3330 then
3331 Insert_Actions_After (N,
3332 Make_Init_Call (
3333 Ref => New_Occurrence_Of (Def_Id, Loc),
3334 Typ => Base_Type (Typ),
3335 Flist_Ref => Find_Final_List (Def_Id),
3336 With_Attach => Make_Integer_Literal (Loc, 1)));
3338 -- Abort allowed
3340 else
3341 -- We need to protect the initialize call
3343 -- begin
3344 -- Defer_Abort.all;
3345 -- Initialize (...);
3346 -- at end
3347 -- Undefer_Abort.all;
3348 -- end;
3350 -- ??? this won't protect the initialize call for controlled
3351 -- components which are part of the init proc, so this block
3352 -- should probably also contain the call to _init_proc but this
3353 -- requires some code reorganization...
3355 declare
3356 L : constant List_Id :=
3357 Make_Init_Call (
3358 Ref => New_Occurrence_Of (Def_Id, Loc),
3359 Typ => Base_Type (Typ),
3360 Flist_Ref => Find_Final_List (Def_Id),
3361 With_Attach => Make_Integer_Literal (Loc, 1));
3363 Blk : constant Node_Id :=
3364 Make_Block_Statement (Loc,
3365 Handled_Statement_Sequence =>
3366 Make_Handled_Sequence_Of_Statements (Loc, L));
3368 begin
3369 Prepend_To (L, Build_Runtime_Call (Loc, RE_Abort_Defer));
3370 Set_At_End_Proc (Handled_Statement_Sequence (Blk),
3371 New_Occurrence_Of (RTE (RE_Abort_Undefer_Direct), Loc));
3372 Insert_Actions_After (N, New_List (Blk));
3373 Expand_At_End_Handler
3374 (Handled_Statement_Sequence (Blk), Entity (Identifier (Blk)));
3375 end;
3376 end if;
3378 -- Call type initialization procedure if there is one. We build the
3379 -- call and put it immediately after the object declaration, so that
3380 -- it will be expanded in the usual manner. Note that this will
3381 -- result in proper handling of defaulted discriminants. The call
3382 -- to the Init_Proc is suppressed if No_Initialization is set.
3384 if Has_Non_Null_Base_Init_Proc (Typ)
3385 and then not No_Initialization (N)
3386 then
3387 -- The call to the initialization procedure does NOT freeze
3388 -- the object being initialized. This is because the call is
3389 -- not a source level call. This works fine, because the only
3390 -- possible statements depending on freeze status that can
3391 -- appear after the _Init call are rep clauses which can
3392 -- safely appear after actual references to the object.
3394 Id_Ref := New_Reference_To (Def_Id, Loc);
3395 Set_Must_Not_Freeze (Id_Ref);
3396 Set_Assignment_OK (Id_Ref);
3398 Insert_Actions_After (N,
3399 Build_Initialization_Call (Loc, Id_Ref, Typ));
3401 -- If simple initialization is required, then set an appropriate
3402 -- simple initialization expression in place. This special
3403 -- initialization is required even though No_Init_Flag is present.
3405 elsif Needs_Simple_Initialization (Typ) then
3406 Set_No_Initialization (N, False);
3407 Set_Expression (N, Get_Simple_Init_Val (Typ, Loc));
3408 Analyze_And_Resolve (Expression (N), Typ);
3409 end if;
3411 -- Explicit initialization present
3413 else
3414 -- Obtain actual expression from qualified expression
3416 if Nkind (Expr) = N_Qualified_Expression then
3417 Expr_Q := Expression (Expr);
3418 else
3419 Expr_Q := Expr;
3420 end if;
3422 -- When we have the appropriate type of aggregate in the
3423 -- expression (it has been determined during analysis of the
3424 -- aggregate by setting the delay flag), let's perform in
3425 -- place assignment and thus avoid creating a temporary.
3427 if Is_Delayed_Aggregate (Expr_Q) then
3428 Convert_Aggr_In_Object_Decl (N);
3430 else
3431 -- In most cases, we must check that the initial value meets
3432 -- any constraint imposed by the declared type. However, there
3433 -- is one very important exception to this rule. If the entity
3434 -- has an unconstrained nominal subtype, then it acquired its
3435 -- constraints from the expression in the first place, and not
3436 -- only does this mean that the constraint check is not needed,
3437 -- but an attempt to perform the constraint check can
3438 -- cause order of elaboration problems.
3440 if not Is_Constr_Subt_For_U_Nominal (Typ) then
3442 -- If this is an allocator for an aggregate that has been
3443 -- allocated in place, delay checks until assignments are
3444 -- made, because the discriminants are not initialized.
3446 if Nkind (Expr) = N_Allocator
3447 and then No_Initialization (Expr)
3448 then
3449 null;
3450 else
3451 Apply_Constraint_Check (Expr, Typ);
3452 end if;
3453 end if;
3455 -- If the type is controlled we attach the object to the final
3456 -- list and adjust the target after the copy. This
3458 if Controlled_Type (Typ) then
3459 declare
3460 Flist : Node_Id;
3461 F : Entity_Id;
3463 begin
3464 -- Attach the result to a dummy final list which will never
3465 -- be finalized if Delay_Finalize_Attachis set. It is
3466 -- important to attach to a dummy final list rather than
3467 -- not attaching at all in order to reset the pointers
3468 -- coming from the initial value. Equivalent code exists
3469 -- in the sec-stack case in Exp_Ch4.Expand_N_Allocator.
3471 if Delay_Finalize_Attach (N) then
3472 F :=
3473 Make_Defining_Identifier (Loc, New_Internal_Name ('F'));
3474 Insert_Action (N,
3475 Make_Object_Declaration (Loc,
3476 Defining_Identifier => F,
3477 Object_Definition =>
3478 New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
3480 Flist := New_Reference_To (F, Loc);
3482 else
3483 Flist := Find_Final_List (Def_Id);
3484 end if;
3486 Insert_Actions_After (N,
3487 Make_Adjust_Call (
3488 Ref => New_Reference_To (Def_Id, Loc),
3489 Typ => Base_Type (Typ),
3490 Flist_Ref => Flist,
3491 With_Attach => Make_Integer_Literal (Loc, 1)));
3492 end;
3493 end if;
3495 -- For tagged types, when an init value is given, the tag has
3496 -- to be re-initialized separately in order to avoid the
3497 -- propagation of a wrong tag coming from a view conversion
3498 -- unless the type is class wide (in this case the tag comes
3499 -- from the init value). Suppress the tag assignment when
3500 -- Java_VM because JVM tags are represented implicitly
3501 -- in objects. Ditto for types that are CPP_CLASS.
3503 if Is_Tagged_Type (Typ)
3504 and then not Is_Class_Wide_Type (Typ)
3505 and then not Is_CPP_Class (Typ)
3506 and then not Java_VM
3507 then
3508 -- The re-assignment of the tag has to be done even if
3509 -- the object is a constant
3511 New_Ref :=
3512 Make_Selected_Component (Loc,
3513 Prefix => New_Reference_To (Def_Id, Loc),
3514 Selector_Name =>
3515 New_Reference_To (Tag_Component (Typ), Loc));
3517 Set_Assignment_OK (New_Ref);
3519 Insert_After (N,
3520 Make_Assignment_Statement (Loc,
3521 Name => New_Ref,
3522 Expression =>
3523 Unchecked_Convert_To (RTE (RE_Tag),
3524 New_Reference_To
3525 (Access_Disp_Table (Base_Type (Typ)), Loc))));
3527 -- For discrete types, set the Is_Known_Valid flag if the
3528 -- initializing value is known to be valid.
3530 elsif Is_Discrete_Type (Typ)
3531 and then Expr_Known_Valid (Expr)
3532 then
3533 Set_Is_Known_Valid (Def_Id);
3535 elsif Is_Access_Type (Typ) then
3537 -- Ada 2005 (AI-231): Generate conversion to the null-excluding
3538 -- type to force the corresponding run-time check
3540 if Ada_Version >= Ada_05
3541 and then (Can_Never_Be_Null (Def_Id)
3542 or else Can_Never_Be_Null (Typ))
3543 then
3544 Rewrite
3545 (Expr_Q,
3546 Convert_To (Etype (Def_Id), Relocate_Node (Expr_Q)));
3547 Analyze_And_Resolve (Expr_Q, Etype (Def_Id));
3548 end if;
3550 -- For access types set the Is_Known_Non_Null flag if the
3551 -- initializing value is known to be non-null. We can also
3552 -- set Can_Never_Be_Null if this is a constant.
3554 if Known_Non_Null (Expr) then
3555 Set_Is_Known_Non_Null (Def_Id);
3557 if Constant_Present (N) then
3558 Set_Can_Never_Be_Null (Def_Id);
3559 end if;
3560 end if;
3561 end if;
3563 -- If validity checking on copies, validate initial expression
3565 if Validity_Checks_On
3566 and then Validity_Check_Copies
3567 then
3568 Ensure_Valid (Expr);
3569 Set_Is_Known_Valid (Def_Id);
3570 end if;
3571 end if;
3573 if Is_Possibly_Unaligned_Slice (Expr) then
3575 -- Make a separate assignment that will be expanded into a
3576 -- loop, to bypass back-end problems with misaligned arrays.
3578 declare
3579 Stat : constant Node_Id :=
3580 Make_Assignment_Statement (Loc,
3581 Name => New_Reference_To (Def_Id, Loc),
3582 Expression => Relocate_Node (Expr));
3584 begin
3585 Set_Expression (N, Empty);
3586 Set_No_Initialization (N);
3587 Set_Assignment_OK (Name (Stat));
3588 Insert_After (N, Stat);
3589 Analyze (Stat);
3590 end;
3591 end if;
3592 end if;
3594 -- For array type, check for size too large
3595 -- We really need this for record types too???
3597 if Is_Array_Type (Typ) then
3598 Apply_Array_Size_Check (N, Typ);
3599 end if;
3601 exception
3602 when RE_Not_Available =>
3603 return;
3604 end Expand_N_Object_Declaration;
3606 ---------------------------------
3607 -- Expand_N_Subtype_Indication --
3608 ---------------------------------
3610 -- Add a check on the range of the subtype. The static case is
3611 -- partially duplicated by Process_Range_Expr_In_Decl in Sem_Ch3,
3612 -- but we still need to check here for the static case in order to
3613 -- avoid generating extraneous expanded code.
3615 procedure Expand_N_Subtype_Indication (N : Node_Id) is
3616 Ran : constant Node_Id := Range_Expression (Constraint (N));
3617 Typ : constant Entity_Id := Entity (Subtype_Mark (N));
3619 begin
3620 if Nkind (Parent (N)) = N_Constrained_Array_Definition or else
3621 Nkind (Parent (N)) = N_Slice
3622 then
3623 Resolve (Ran, Typ);
3624 Apply_Range_Check (Ran, Typ);
3625 end if;
3626 end Expand_N_Subtype_Indication;
3628 ---------------------------
3629 -- Expand_N_Variant_Part --
3630 ---------------------------
3632 -- If the last variant does not contain the Others choice, replace
3633 -- it with an N_Others_Choice node since Gigi always wants an Others.
3634 -- Note that we do not bother to call Analyze on the modified variant
3635 -- part, since it's only effect would be to compute the contents of
3636 -- the Others_Discrete_Choices node laboriously, and of course we
3637 -- already know the list of choices that corresponds to the others
3638 -- choice (it's the list we are replacing!)
3640 procedure Expand_N_Variant_Part (N : Node_Id) is
3641 Last_Var : constant Node_Id := Last_Non_Pragma (Variants (N));
3642 Others_Node : Node_Id;
3644 begin
3645 if Nkind (First (Discrete_Choices (Last_Var))) /= N_Others_Choice then
3646 Others_Node := Make_Others_Choice (Sloc (Last_Var));
3647 Set_Others_Discrete_Choices
3648 (Others_Node, Discrete_Choices (Last_Var));
3649 Set_Discrete_Choices (Last_Var, New_List (Others_Node));
3650 end if;
3651 end Expand_N_Variant_Part;
3653 ---------------------------------
3654 -- Expand_Previous_Access_Type --
3655 ---------------------------------
3657 procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
3658 T : Entity_Id := First_Entity (Current_Scope);
3660 begin
3661 -- Find all access types declared in the current scope, whose
3662 -- designated type is Def_Id.
3664 while Present (T) loop
3665 if Is_Access_Type (T)
3666 and then Designated_Type (T) = Def_Id
3667 then
3668 Build_Master_Entity (Def_Id);
3669 Build_Master_Renaming (Parent (Def_Id), T);
3670 end if;
3672 Next_Entity (T);
3673 end loop;
3674 end Expand_Previous_Access_Type;
3676 ------------------------------
3677 -- Expand_Record_Controller --
3678 ------------------------------
3680 procedure Expand_Record_Controller (T : Entity_Id) is
3681 Def : Node_Id := Type_Definition (Parent (T));
3682 Comp_List : Node_Id;
3683 Comp_Decl : Node_Id;
3684 Loc : Source_Ptr;
3685 First_Comp : Node_Id;
3686 Controller_Type : Entity_Id;
3687 Ent : Entity_Id;
3689 begin
3690 if Nkind (Def) = N_Derived_Type_Definition then
3691 Def := Record_Extension_Part (Def);
3692 end if;
3694 if Null_Present (Def) then
3695 Set_Component_List (Def,
3696 Make_Component_List (Sloc (Def),
3697 Component_Items => Empty_List,
3698 Variant_Part => Empty,
3699 Null_Present => True));
3700 end if;
3702 Comp_List := Component_List (Def);
3704 if Null_Present (Comp_List)
3705 or else Is_Empty_List (Component_Items (Comp_List))
3706 then
3707 Loc := Sloc (Comp_List);
3708 else
3709 Loc := Sloc (First (Component_Items (Comp_List)));
3710 end if;
3712 if Is_Return_By_Reference_Type (T) then
3713 Controller_Type := RTE (RE_Limited_Record_Controller);
3714 else
3715 Controller_Type := RTE (RE_Record_Controller);
3716 end if;
3718 Ent := Make_Defining_Identifier (Loc, Name_uController);
3720 Comp_Decl :=
3721 Make_Component_Declaration (Loc,
3722 Defining_Identifier => Ent,
3723 Component_Definition =>
3724 Make_Component_Definition (Loc,
3725 Aliased_Present => False,
3726 Subtype_Indication => New_Reference_To (Controller_Type, Loc)));
3728 if Null_Present (Comp_List)
3729 or else Is_Empty_List (Component_Items (Comp_List))
3730 then
3731 Set_Component_Items (Comp_List, New_List (Comp_Decl));
3732 Set_Null_Present (Comp_List, False);
3734 else
3735 -- The controller cannot be placed before the _Parent field
3736 -- since gigi lays out field in order and _parent must be
3737 -- first to preserve the polymorphism of tagged types.
3739 First_Comp := First (Component_Items (Comp_List));
3741 if Chars (Defining_Identifier (First_Comp)) /= Name_uParent
3742 and then Chars (Defining_Identifier (First_Comp)) /= Name_uTag
3743 then
3744 Insert_Before (First_Comp, Comp_Decl);
3745 else
3746 Insert_After (First_Comp, Comp_Decl);
3747 end if;
3748 end if;
3750 New_Scope (T);
3751 Analyze (Comp_Decl);
3752 Set_Ekind (Ent, E_Component);
3753 Init_Component_Location (Ent);
3755 -- Move the _controller entity ahead in the list of internal
3756 -- entities of the enclosing record so that it is selected
3757 -- instead of a potentially inherited one.
3759 declare
3760 E : constant Entity_Id := Last_Entity (T);
3761 Comp : Entity_Id;
3763 begin
3764 pragma Assert (Chars (E) = Name_uController);
3766 Set_Next_Entity (E, First_Entity (T));
3767 Set_First_Entity (T, E);
3769 Comp := Next_Entity (E);
3770 while Next_Entity (Comp) /= E loop
3771 Next_Entity (Comp);
3772 end loop;
3774 Set_Next_Entity (Comp, Empty);
3775 Set_Last_Entity (T, Comp);
3776 end;
3778 End_Scope;
3780 exception
3781 when RE_Not_Available =>
3782 return;
3783 end Expand_Record_Controller;
3785 ------------------------
3786 -- Expand_Tagged_Root --
3787 ------------------------
3789 procedure Expand_Tagged_Root (T : Entity_Id) is
3790 Def : constant Node_Id := Type_Definition (Parent (T));
3791 Comp_List : Node_Id;
3792 Comp_Decl : Node_Id;
3793 Sloc_N : Source_Ptr;
3795 begin
3796 if Null_Present (Def) then
3797 Set_Component_List (Def,
3798 Make_Component_List (Sloc (Def),
3799 Component_Items => Empty_List,
3800 Variant_Part => Empty,
3801 Null_Present => True));
3802 end if;
3804 Comp_List := Component_List (Def);
3806 if Null_Present (Comp_List)
3807 or else Is_Empty_List (Component_Items (Comp_List))
3808 then
3809 Sloc_N := Sloc (Comp_List);
3810 else
3811 Sloc_N := Sloc (First (Component_Items (Comp_List)));
3812 end if;
3814 Comp_Decl :=
3815 Make_Component_Declaration (Sloc_N,
3816 Defining_Identifier => Tag_Component (T),
3817 Component_Definition =>
3818 Make_Component_Definition (Sloc_N,
3819 Aliased_Present => False,
3820 Subtype_Indication => New_Reference_To (RTE (RE_Tag), Sloc_N)));
3822 if Null_Present (Comp_List)
3823 or else Is_Empty_List (Component_Items (Comp_List))
3824 then
3825 Set_Component_Items (Comp_List, New_List (Comp_Decl));
3826 Set_Null_Present (Comp_List, False);
3828 else
3829 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
3830 end if;
3832 -- We don't Analyze the whole expansion because the tag component has
3833 -- already been analyzed previously. Here we just insure that the
3834 -- tree is coherent with the semantic decoration
3836 Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
3838 exception
3839 when RE_Not_Available =>
3840 return;
3841 end Expand_Tagged_Root;
3843 -----------------------
3844 -- Freeze_Array_Type --
3845 -----------------------
3847 procedure Freeze_Array_Type (N : Node_Id) is
3848 Typ : constant Entity_Id := Entity (N);
3849 Base : constant Entity_Id := Base_Type (Typ);
3851 begin
3852 if not Is_Bit_Packed_Array (Typ) then
3854 -- If the component contains tasks, so does the array type.
3855 -- This may not be indicated in the array type because the
3856 -- component may have been a private type at the point of
3857 -- definition. Same if component type is controlled.
3859 Set_Has_Task (Base, Has_Task (Component_Type (Typ)));
3860 Set_Has_Controlled_Component (Base,
3861 Has_Controlled_Component (Component_Type (Typ))
3862 or else Is_Controlled (Component_Type (Typ)));
3864 if No (Init_Proc (Base)) then
3866 -- If this is an anonymous array created for a declaration
3867 -- with an initial value, its init_proc will never be called.
3868 -- The initial value itself may have been expanded into assign-
3869 -- ments, in which case the object declaration is carries the
3870 -- No_Initialization flag.
3872 if Is_Itype (Base)
3873 and then Nkind (Associated_Node_For_Itype (Base)) =
3874 N_Object_Declaration
3875 and then (Present (Expression (Associated_Node_For_Itype (Base)))
3876 or else
3877 No_Initialization (Associated_Node_For_Itype (Base)))
3878 then
3879 null;
3881 -- We do not need an init proc for string or wide string, since
3882 -- the only time these need initialization in normalize or
3883 -- initialize scalars mode, and these types are treated specially
3884 -- and do not need initialization procedures.
3886 elsif Root_Type (Base) = Standard_String
3887 or else Root_Type (Base) = Standard_Wide_String
3888 then
3889 null;
3891 -- Otherwise we have to build an init proc for the subtype
3893 else
3894 Build_Array_Init_Proc (Base, N);
3895 end if;
3896 end if;
3898 if Typ = Base and then Has_Controlled_Component (Base) then
3899 Build_Controlling_Procs (Base);
3901 if not Is_Limited_Type (Component_Type (Typ))
3902 and then Number_Dimensions (Typ) = 1
3903 then
3904 Build_Slice_Assignment (Typ);
3905 end if;
3906 end if;
3908 -- For packed case, there is a default initialization, except
3909 -- if the component type is itself a packed structure with an
3910 -- initialization procedure.
3912 elsif Present (Init_Proc (Component_Type (Base)))
3913 and then No (Base_Init_Proc (Base))
3914 then
3915 Build_Array_Init_Proc (Base, N);
3916 end if;
3917 end Freeze_Array_Type;
3919 -----------------------------
3920 -- Freeze_Enumeration_Type --
3921 -----------------------------
3923 procedure Freeze_Enumeration_Type (N : Node_Id) is
3924 Typ : constant Entity_Id := Entity (N);
3925 Loc : constant Source_Ptr := Sloc (Typ);
3926 Ent : Entity_Id;
3927 Lst : List_Id;
3928 Num : Nat;
3929 Arr : Entity_Id;
3930 Fent : Entity_Id;
3931 Ityp : Entity_Id;
3932 Is_Contiguous : Boolean;
3933 Pos_Expr : Node_Id;
3934 Last_Repval : Uint;
3936 Func : Entity_Id;
3937 pragma Warnings (Off, Func);
3939 begin
3940 -- Various optimization are possible if the given representation
3941 -- is contiguous.
3943 Is_Contiguous := True;
3944 Ent := First_Literal (Typ);
3945 Last_Repval := Enumeration_Rep (Ent);
3946 Next_Literal (Ent);
3948 while Present (Ent) loop
3949 if Enumeration_Rep (Ent) - Last_Repval /= 1 then
3950 Is_Contiguous := False;
3951 exit;
3952 else
3953 Last_Repval := Enumeration_Rep (Ent);
3954 end if;
3956 Next_Literal (Ent);
3957 end loop;
3959 if Is_Contiguous then
3960 Set_Has_Contiguous_Rep (Typ);
3961 Ent := First_Literal (Typ);
3962 Num := 1;
3963 Lst := New_List (New_Reference_To (Ent, Sloc (Ent)));
3965 else
3966 -- Build list of literal references
3968 Lst := New_List;
3969 Num := 0;
3971 Ent := First_Literal (Typ);
3972 while Present (Ent) loop
3973 Append_To (Lst, New_Reference_To (Ent, Sloc (Ent)));
3974 Num := Num + 1;
3975 Next_Literal (Ent);
3976 end loop;
3977 end if;
3979 -- Now build an array declaration.
3981 -- typA : array (Natural range 0 .. num - 1) of ctype :=
3982 -- (v, v, v, v, v, ....)
3984 -- where ctype is the corresponding integer type. If the
3985 -- representation is contiguous, we only keep the first literal,
3986 -- which provides the offset for Pos_To_Rep computations.
3988 Arr :=
3989 Make_Defining_Identifier (Loc,
3990 Chars => New_External_Name (Chars (Typ), 'A'));
3992 Append_Freeze_Action (Typ,
3993 Make_Object_Declaration (Loc,
3994 Defining_Identifier => Arr,
3995 Constant_Present => True,
3997 Object_Definition =>
3998 Make_Constrained_Array_Definition (Loc,
3999 Discrete_Subtype_Definitions => New_List (
4000 Make_Subtype_Indication (Loc,
4001 Subtype_Mark => New_Reference_To (Standard_Natural, Loc),
4002 Constraint =>
4003 Make_Range_Constraint (Loc,
4004 Range_Expression =>
4005 Make_Range (Loc,
4006 Low_Bound =>
4007 Make_Integer_Literal (Loc, 0),
4008 High_Bound =>
4009 Make_Integer_Literal (Loc, Num - 1))))),
4011 Component_Definition =>
4012 Make_Component_Definition (Loc,
4013 Aliased_Present => False,
4014 Subtype_Indication => New_Reference_To (Typ, Loc))),
4016 Expression =>
4017 Make_Aggregate (Loc,
4018 Expressions => Lst)));
4020 Set_Enum_Pos_To_Rep (Typ, Arr);
4022 -- Now we build the function that converts representation values to
4023 -- position values. This function has the form:
4025 -- function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
4026 -- begin
4027 -- case ityp!(A) is
4028 -- when enum-lit'Enum_Rep => return posval;
4029 -- when enum-lit'Enum_Rep => return posval;
4030 -- ...
4031 -- when others =>
4032 -- [raise Constraint_Error when F "invalid data"]
4033 -- return -1;
4034 -- end case;
4035 -- end;
4037 -- Note: the F parameter determines whether the others case (no valid
4038 -- representation) raises Constraint_Error or returns a unique value
4039 -- of minus one. The latter case is used, e.g. in 'Valid code.
4041 -- Note: the reason we use Enum_Rep values in the case here is to
4042 -- avoid the code generator making inappropriate assumptions about
4043 -- the range of the values in the case where the value is invalid.
4044 -- ityp is a signed or unsigned integer type of appropriate width.
4046 -- Note: if exceptions are not supported, then we suppress the raise
4047 -- and return -1 unconditionally (this is an erroneous program in any
4048 -- case and there is no obligation to raise Constraint_Error here!)
4049 -- We also do this if pragma Restrictions (No_Exceptions) is active.
4051 -- Representations are signed
4053 if Enumeration_Rep (First_Literal (Typ)) < 0 then
4055 -- The underlying type is signed. Reset the Is_Unsigned_Type
4056 -- explicitly, because it might have been inherited from a
4057 -- parent type.
4059 Set_Is_Unsigned_Type (Typ, False);
4061 if Esize (Typ) <= Standard_Integer_Size then
4062 Ityp := Standard_Integer;
4063 else
4064 Ityp := Universal_Integer;
4065 end if;
4067 -- Representations are unsigned
4069 else
4070 if Esize (Typ) <= Standard_Integer_Size then
4071 Ityp := RTE (RE_Unsigned);
4072 else
4073 Ityp := RTE (RE_Long_Long_Unsigned);
4074 end if;
4075 end if;
4077 -- The body of the function is a case statement. First collect
4078 -- case alternatives, or optimize the contiguous case.
4080 Lst := New_List;
4082 -- If representation is contiguous, Pos is computed by subtracting
4083 -- the representation of the first literal.
4085 if Is_Contiguous then
4086 Ent := First_Literal (Typ);
4088 if Enumeration_Rep (Ent) = Last_Repval then
4090 -- Another special case: for a single literal, Pos is zero.
4092 Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
4094 else
4095 Pos_Expr :=
4096 Convert_To (Standard_Integer,
4097 Make_Op_Subtract (Loc,
4098 Left_Opnd =>
4099 Unchecked_Convert_To (Ityp,
4100 Make_Identifier (Loc, Name_uA)),
4101 Right_Opnd =>
4102 Make_Integer_Literal (Loc,
4103 Intval =>
4104 Enumeration_Rep (First_Literal (Typ)))));
4105 end if;
4107 Append_To (Lst,
4108 Make_Case_Statement_Alternative (Loc,
4109 Discrete_Choices => New_List (
4110 Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
4111 Low_Bound =>
4112 Make_Integer_Literal (Loc,
4113 Intval => Enumeration_Rep (Ent)),
4114 High_Bound =>
4115 Make_Integer_Literal (Loc, Intval => Last_Repval))),
4117 Statements => New_List (
4118 Make_Return_Statement (Loc,
4119 Expression => Pos_Expr))));
4121 else
4122 Ent := First_Literal (Typ);
4124 while Present (Ent) loop
4125 Append_To (Lst,
4126 Make_Case_Statement_Alternative (Loc,
4127 Discrete_Choices => New_List (
4128 Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
4129 Intval => Enumeration_Rep (Ent))),
4131 Statements => New_List (
4132 Make_Return_Statement (Loc,
4133 Expression =>
4134 Make_Integer_Literal (Loc,
4135 Intval => Enumeration_Pos (Ent))))));
4137 Next_Literal (Ent);
4138 end loop;
4139 end if;
4141 -- In normal mode, add the others clause with the test
4143 if not Restriction_Active (No_Exception_Handlers) then
4144 Append_To (Lst,
4145 Make_Case_Statement_Alternative (Loc,
4146 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
4147 Statements => New_List (
4148 Make_Raise_Constraint_Error (Loc,
4149 Condition => Make_Identifier (Loc, Name_uF),
4150 Reason => CE_Invalid_Data),
4151 Make_Return_Statement (Loc,
4152 Expression =>
4153 Make_Integer_Literal (Loc, -1)))));
4155 -- If Restriction (No_Exceptions_Handlers) is active then we always
4156 -- return -1 (since we cannot usefully raise Constraint_Error in
4157 -- this case). See description above for further details.
4159 else
4160 Append_To (Lst,
4161 Make_Case_Statement_Alternative (Loc,
4162 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
4163 Statements => New_List (
4164 Make_Return_Statement (Loc,
4165 Expression =>
4166 Make_Integer_Literal (Loc, -1)))));
4167 end if;
4169 -- Now we can build the function body
4171 Fent :=
4172 Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
4174 Func :=
4175 Make_Subprogram_Body (Loc,
4176 Specification =>
4177 Make_Function_Specification (Loc,
4178 Defining_Unit_Name => Fent,
4179 Parameter_Specifications => New_List (
4180 Make_Parameter_Specification (Loc,
4181 Defining_Identifier =>
4182 Make_Defining_Identifier (Loc, Name_uA),
4183 Parameter_Type => New_Reference_To (Typ, Loc)),
4184 Make_Parameter_Specification (Loc,
4185 Defining_Identifier =>
4186 Make_Defining_Identifier (Loc, Name_uF),
4187 Parameter_Type => New_Reference_To (Standard_Boolean, Loc))),
4189 Subtype_Mark => New_Reference_To (Standard_Integer, Loc)),
4191 Declarations => Empty_List,
4193 Handled_Statement_Sequence =>
4194 Make_Handled_Sequence_Of_Statements (Loc,
4195 Statements => New_List (
4196 Make_Case_Statement (Loc,
4197 Expression =>
4198 Unchecked_Convert_To (Ityp,
4199 Make_Identifier (Loc, Name_uA)),
4200 Alternatives => Lst))));
4202 Set_TSS (Typ, Fent);
4203 Set_Is_Pure (Fent);
4205 if not Debug_Generated_Code then
4206 Set_Debug_Info_Off (Fent);
4207 end if;
4209 exception
4210 when RE_Not_Available =>
4211 return;
4212 end Freeze_Enumeration_Type;
4214 ------------------------
4215 -- Freeze_Record_Type --
4216 ------------------------
4218 procedure Freeze_Record_Type (N : Node_Id) is
4219 Def_Id : constant Node_Id := Entity (N);
4220 Comp : Entity_Id;
4221 Type_Decl : constant Node_Id := Parent (Def_Id);
4222 Predef_List : List_Id;
4224 Renamed_Eq : Node_Id := Empty;
4225 -- Could use some comments ???
4227 begin
4228 -- Build discriminant checking functions if not a derived type (for
4229 -- derived types that are not tagged types, we always use the
4230 -- discriminant checking functions of the parent type). However, for
4231 -- untagged types the derivation may have taken place before the
4232 -- parent was frozen, so we copy explicitly the discriminant checking
4233 -- functions from the parent into the components of the derived type.
4235 if not Is_Derived_Type (Def_Id)
4236 or else Has_New_Non_Standard_Rep (Def_Id)
4237 or else Is_Tagged_Type (Def_Id)
4238 then
4239 Build_Discr_Checking_Funcs (Type_Decl);
4241 elsif Is_Derived_Type (Def_Id)
4242 and then not Is_Tagged_Type (Def_Id)
4244 -- If we have a derived Unchecked_Union, we do not inherit the
4245 -- discriminant checking functions from the parent type since the
4246 -- discriminants are non existent.
4248 and then not Is_Unchecked_Union (Def_Id)
4249 and then Has_Discriminants (Def_Id)
4250 then
4251 declare
4252 Old_Comp : Entity_Id;
4254 begin
4255 Old_Comp :=
4256 First_Component (Base_Type (Underlying_Type (Etype (Def_Id))));
4257 Comp := First_Component (Def_Id);
4258 while Present (Comp) loop
4259 if Ekind (Comp) = E_Component
4260 and then Chars (Comp) = Chars (Old_Comp)
4261 then
4262 Set_Discriminant_Checking_Func (Comp,
4263 Discriminant_Checking_Func (Old_Comp));
4264 end if;
4266 Next_Component (Old_Comp);
4267 Next_Component (Comp);
4268 end loop;
4269 end;
4270 end if;
4272 if Is_Derived_Type (Def_Id)
4273 and then Is_Limited_Type (Def_Id)
4274 and then Is_Tagged_Type (Def_Id)
4275 then
4276 Check_Stream_Attributes (Def_Id);
4277 end if;
4279 -- Update task and controlled component flags, because some of the
4280 -- component types may have been private at the point of the record
4281 -- declaration.
4283 Comp := First_Component (Def_Id);
4285 while Present (Comp) loop
4286 if Has_Task (Etype (Comp)) then
4287 Set_Has_Task (Def_Id);
4289 elsif Has_Controlled_Component (Etype (Comp))
4290 or else (Chars (Comp) /= Name_uParent
4291 and then Is_Controlled (Etype (Comp)))
4292 then
4293 Set_Has_Controlled_Component (Def_Id);
4294 end if;
4296 Next_Component (Comp);
4297 end loop;
4299 -- Creation of the Dispatch Table. Note that a Dispatch Table is
4300 -- created for regular tagged types as well as for Ada types
4301 -- deriving from a C++ Class, but not for tagged types directly
4302 -- corresponding to the C++ classes. In the later case we assume
4303 -- that the Vtable is created in the C++ side and we just use it.
4305 if Is_Tagged_Type (Def_Id) then
4306 if Is_CPP_Class (Def_Id) then
4307 Set_All_DT_Position (Def_Id);
4308 Set_Default_Constructor (Def_Id);
4310 else
4311 -- Usually inherited primitives are not delayed but the first
4312 -- Ada extension of a CPP_Class is an exception since the
4313 -- address of the inherited subprogram has to be inserted in
4314 -- the new Ada Dispatch Table and this is a freezing action
4315 -- (usually the inherited primitive address is inserted in the
4316 -- DT by Inherit_DT)
4318 -- Similarly, if this is an inherited operation whose parent
4319 -- is not frozen yet, it is not in the DT of the parent, and
4320 -- we generate an explicit freeze node for the inherited
4321 -- operation, so that it is properly inserted in the DT of the
4322 -- current type.
4324 declare
4325 Elmt : Elmt_Id := First_Elmt (Primitive_Operations (Def_Id));
4326 Subp : Entity_Id;
4328 begin
4329 while Present (Elmt) loop
4330 Subp := Node (Elmt);
4332 if Present (Alias (Subp)) then
4333 if Is_CPP_Class (Etype (Def_Id)) then
4334 Set_Has_Delayed_Freeze (Subp);
4336 elsif Has_Delayed_Freeze (Alias (Subp))
4337 and then not Is_Frozen (Alias (Subp))
4338 then
4339 Set_Is_Frozen (Subp, False);
4340 Set_Has_Delayed_Freeze (Subp);
4341 end if;
4342 end if;
4344 Next_Elmt (Elmt);
4345 end loop;
4346 end;
4348 if Underlying_Type (Etype (Def_Id)) = Def_Id then
4349 Expand_Tagged_Root (Def_Id);
4350 end if;
4352 -- Unfreeze momentarily the type to add the predefined
4353 -- primitives operations. The reason we unfreeze is so
4354 -- that these predefined operations will indeed end up
4355 -- as primitive operations (which must be before the
4356 -- freeze point).
4358 Set_Is_Frozen (Def_Id, False);
4359 Make_Predefined_Primitive_Specs
4360 (Def_Id, Predef_List, Renamed_Eq);
4361 Insert_List_Before_And_Analyze (N, Predef_List);
4362 Set_Is_Frozen (Def_Id, True);
4363 Set_All_DT_Position (Def_Id);
4365 -- Add the controlled component before the freezing actions
4366 -- it is referenced in those actions.
4368 if Has_New_Controlled_Component (Def_Id) then
4369 Expand_Record_Controller (Def_Id);
4370 end if;
4372 -- Suppress creation of a dispatch table when Java_VM because
4373 -- the dispatching mechanism is handled internally by the JVM.
4375 if not Java_VM then
4376 Append_Freeze_Actions (Def_Id, Make_DT (Def_Id));
4377 end if;
4379 -- Make sure that the primitives Initialize, Adjust and
4380 -- Finalize are Frozen before other TSS subprograms. We
4381 -- don't want them Frozen inside.
4383 if Is_Controlled (Def_Id) then
4384 if not Is_Limited_Type (Def_Id) then
4385 Append_Freeze_Actions (Def_Id,
4386 Freeze_Entity
4387 (Find_Prim_Op (Def_Id, Name_Adjust), Sloc (Def_Id)));
4388 end if;
4390 Append_Freeze_Actions (Def_Id,
4391 Freeze_Entity
4392 (Find_Prim_Op (Def_Id, Name_Initialize), Sloc (Def_Id)));
4394 Append_Freeze_Actions (Def_Id,
4395 Freeze_Entity
4396 (Find_Prim_Op (Def_Id, Name_Finalize), Sloc (Def_Id)));
4397 end if;
4399 -- Freeze rest of primitive operations
4401 Append_Freeze_Actions
4402 (Def_Id, Predefined_Primitive_Freeze (Def_Id));
4403 end if;
4405 -- In the non-tagged case, an equality function is provided only
4406 -- for variant records (that are not unchecked unions).
4408 elsif Has_Discriminants (Def_Id)
4409 and then not Is_Limited_Type (Def_Id)
4410 then
4411 declare
4412 Comps : constant Node_Id :=
4413 Component_List (Type_Definition (Type_Decl));
4415 begin
4416 if Present (Comps)
4417 and then Present (Variant_Part (Comps))
4418 then
4419 Build_Variant_Record_Equality (Def_Id);
4420 end if;
4421 end;
4422 end if;
4424 -- Before building the record initialization procedure, if we are
4425 -- dealing with a concurrent record value type, then we must go
4426 -- through the discriminants, exchanging discriminals between the
4427 -- concurrent type and the concurrent record value type. See the
4428 -- section "Handling of Discriminants" in the Einfo spec for details.
4430 if Is_Concurrent_Record_Type (Def_Id)
4431 and then Has_Discriminants (Def_Id)
4432 then
4433 declare
4434 Ctyp : constant Entity_Id :=
4435 Corresponding_Concurrent_Type (Def_Id);
4436 Conc_Discr : Entity_Id;
4437 Rec_Discr : Entity_Id;
4438 Temp : Entity_Id;
4440 begin
4441 Conc_Discr := First_Discriminant (Ctyp);
4442 Rec_Discr := First_Discriminant (Def_Id);
4444 while Present (Conc_Discr) loop
4445 Temp := Discriminal (Conc_Discr);
4446 Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
4447 Set_Discriminal (Rec_Discr, Temp);
4449 Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
4450 Set_Discriminal_Link (Discriminal (Rec_Discr), Rec_Discr);
4452 Next_Discriminant (Conc_Discr);
4453 Next_Discriminant (Rec_Discr);
4454 end loop;
4455 end;
4456 end if;
4458 if Has_Controlled_Component (Def_Id) then
4459 if No (Controller_Component (Def_Id)) then
4460 Expand_Record_Controller (Def_Id);
4461 end if;
4463 Build_Controlling_Procs (Def_Id);
4464 end if;
4466 Adjust_Discriminants (Def_Id);
4467 Build_Record_Init_Proc (Type_Decl, Def_Id);
4469 -- For tagged type, build bodies of primitive operations. Note
4470 -- that we do this after building the record initialization
4471 -- experiment, since the primitive operations may need the
4472 -- initialization routine
4474 if Is_Tagged_Type (Def_Id) then
4475 Predef_List := Predefined_Primitive_Bodies (Def_Id, Renamed_Eq);
4476 Append_Freeze_Actions (Def_Id, Predef_List);
4477 end if;
4479 end Freeze_Record_Type;
4481 ------------------------------
4482 -- Freeze_Stream_Operations --
4483 ------------------------------
4485 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
4486 Names : constant array (1 .. 4) of TSS_Name_Type :=
4487 (TSS_Stream_Input,
4488 TSS_Stream_Output,
4489 TSS_Stream_Read,
4490 TSS_Stream_Write);
4491 Stream_Op : Entity_Id;
4493 begin
4494 -- Primitive operations of tagged types are frozen when the dispatch
4495 -- table is constructed.
4497 if not Comes_From_Source (Typ)
4498 or else Is_Tagged_Type (Typ)
4499 then
4500 return;
4501 end if;
4503 for J in Names'Range loop
4504 Stream_Op := TSS (Typ, Names (J));
4506 if Present (Stream_Op)
4507 and then Is_Subprogram (Stream_Op)
4508 and then Nkind (Unit_Declaration_Node (Stream_Op)) =
4509 N_Subprogram_Declaration
4510 and then not Is_Frozen (Stream_Op)
4511 then
4512 Append_Freeze_Actions
4513 (Typ, Freeze_Entity (Stream_Op, Sloc (N)));
4514 end if;
4515 end loop;
4516 end Freeze_Stream_Operations;
4518 -----------------
4519 -- Freeze_Type --
4520 -----------------
4522 -- Full type declarations are expanded at the point at which the type
4523 -- is frozen. The formal N is the Freeze_Node for the type. Any statements
4524 -- or declarations generated by the freezing (e.g. the procedure generated
4525 -- for initialization) are chained in the Acions field list of the freeze
4526 -- node using Append_Freeze_Actions.
4528 procedure Freeze_Type (N : Node_Id) is
4529 Def_Id : constant Entity_Id := Entity (N);
4530 RACW_Seen : Boolean := False;
4532 begin
4533 -- Process associated access types needing special processing
4535 if Present (Access_Types_To_Process (N)) then
4536 declare
4537 E : Elmt_Id := First_Elmt (Access_Types_To_Process (N));
4538 begin
4539 while Present (E) loop
4541 if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
4542 RACW_Seen := True;
4543 end if;
4545 E := Next_Elmt (E);
4546 end loop;
4547 end;
4549 if RACW_Seen then
4551 -- If there are RACWs designating this type, make stubs now.
4553 Remote_Types_Tagged_Full_View_Encountered (Def_Id);
4554 end if;
4555 end if;
4557 -- Freeze processing for record types
4559 if Is_Record_Type (Def_Id) then
4560 if Ekind (Def_Id) = E_Record_Type then
4561 Freeze_Record_Type (N);
4563 -- The subtype may have been declared before the type was frozen.
4564 -- If the type has controlled components it is necessary to create
4565 -- the entity for the controller explicitly because it did not
4566 -- exist at the point of the subtype declaration. Only the entity is
4567 -- needed, the back-end will obtain the layout from the type.
4568 -- This is only necessary if this is constrained subtype whose
4569 -- component list is not shared with the base type.
4571 elsif Ekind (Def_Id) = E_Record_Subtype
4572 and then Has_Discriminants (Def_Id)
4573 and then Last_Entity (Def_Id) /= Last_Entity (Base_Type (Def_Id))
4574 and then Present (Controller_Component (Def_Id))
4575 then
4576 declare
4577 Old_C : constant Entity_Id := Controller_Component (Def_Id);
4578 New_C : Entity_Id;
4580 begin
4581 if Scope (Old_C) = Base_Type (Def_Id) then
4583 -- The entity is the one in the parent. Create new one.
4585 New_C := New_Copy (Old_C);
4586 Set_Parent (New_C, Parent (Old_C));
4587 New_Scope (Def_Id);
4588 Enter_Name (New_C);
4589 End_Scope;
4590 end if;
4591 end;
4593 -- Similar process if the controller of the subtype is not
4594 -- present but the parent has it. This can happen with constrained
4595 -- record components where the subtype is an itype.
4597 elsif Ekind (Def_Id) = E_Record_Subtype
4598 and then Is_Itype (Def_Id)
4599 and then No (Controller_Component (Def_Id))
4600 and then Present (Controller_Component (Etype (Def_Id)))
4601 then
4602 declare
4603 Old_C : constant Entity_Id :=
4604 Controller_Component (Etype (Def_Id));
4605 New_C : constant Entity_Id := New_Copy (Old_C);
4607 begin
4608 Set_Next_Entity (New_C, First_Entity (Def_Id));
4609 Set_First_Entity (Def_Id, New_C);
4611 -- The freeze node is only used to introduce the controller,
4612 -- the back-end has no use for it for a discriminated
4613 -- component.
4615 Set_Freeze_Node (Def_Id, Empty);
4616 Set_Has_Delayed_Freeze (Def_Id, False);
4617 Remove (N);
4618 end;
4619 end if;
4621 -- Freeze processing for array types
4623 elsif Is_Array_Type (Def_Id) then
4624 Freeze_Array_Type (N);
4626 -- Freeze processing for access types
4628 -- For pool-specific access types, find out the pool object used for
4629 -- this type, needs actual expansion of it in some cases. Here are the
4630 -- different cases :
4632 -- 1. Rep Clause "for Def_Id'Storage_Size use 0;"
4633 -- ---> don't use any storage pool
4635 -- 2. Rep Clause : for Def_Id'Storage_Size use Expr.
4636 -- Expand:
4637 -- Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
4639 -- 3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
4640 -- ---> Storage Pool is the specified one
4642 -- See GNAT Pool packages in the Run-Time for more details
4644 elsif Ekind (Def_Id) = E_Access_Type
4645 or else Ekind (Def_Id) = E_General_Access_Type
4646 then
4647 declare
4648 Loc : constant Source_Ptr := Sloc (N);
4649 Desig_Type : constant Entity_Id := Designated_Type (Def_Id);
4650 Pool_Object : Entity_Id;
4651 Siz_Exp : Node_Id;
4653 Freeze_Action_Typ : Entity_Id;
4655 begin
4656 if Has_Storage_Size_Clause (Def_Id) then
4657 Siz_Exp := Expression (Parent (Storage_Size_Variable (Def_Id)));
4658 else
4659 Siz_Exp := Empty;
4660 end if;
4662 -- Case 1
4664 -- Rep Clause "for Def_Id'Storage_Size use 0;"
4665 -- ---> don't use any storage pool
4667 if Has_Storage_Size_Clause (Def_Id)
4668 and then Compile_Time_Known_Value (Siz_Exp)
4669 and then Expr_Value (Siz_Exp) = 0
4670 then
4671 null;
4673 -- Case 2
4675 -- Rep Clause : for Def_Id'Storage_Size use Expr.
4676 -- ---> Expand:
4677 -- Def_Id__Pool : Stack_Bounded_Pool
4678 -- (Expr, DT'Size, DT'Alignment);
4680 elsif Has_Storage_Size_Clause (Def_Id) then
4681 declare
4682 DT_Size : Node_Id;
4683 DT_Align : Node_Id;
4685 begin
4686 -- For unconstrained composite types we give a size of
4687 -- zero so that the pool knows that it needs a special
4688 -- algorithm for variable size object allocation.
4690 if Is_Composite_Type (Desig_Type)
4691 and then not Is_Constrained (Desig_Type)
4692 then
4693 DT_Size :=
4694 Make_Integer_Literal (Loc, 0);
4696 DT_Align :=
4697 Make_Integer_Literal (Loc, Maximum_Alignment);
4699 else
4700 DT_Size :=
4701 Make_Attribute_Reference (Loc,
4702 Prefix => New_Reference_To (Desig_Type, Loc),
4703 Attribute_Name => Name_Max_Size_In_Storage_Elements);
4705 DT_Align :=
4706 Make_Attribute_Reference (Loc,
4707 Prefix => New_Reference_To (Desig_Type, Loc),
4708 Attribute_Name => Name_Alignment);
4709 end if;
4711 Pool_Object :=
4712 Make_Defining_Identifier (Loc,
4713 Chars => New_External_Name (Chars (Def_Id), 'P'));
4715 -- We put the code associated with the pools in the
4716 -- entity that has the later freeze node, usually the
4717 -- acces type but it can also be the designated_type;
4718 -- because the pool code requires both those types to be
4719 -- frozen
4721 if Is_Frozen (Desig_Type)
4722 and then (not Present (Freeze_Node (Desig_Type))
4723 or else Analyzed (Freeze_Node (Desig_Type)))
4724 then
4725 Freeze_Action_Typ := Def_Id;
4727 -- A Taft amendment type cannot get the freeze actions
4728 -- since the full view is not there.
4730 elsif Is_Incomplete_Or_Private_Type (Desig_Type)
4731 and then No (Full_View (Desig_Type))
4732 then
4733 Freeze_Action_Typ := Def_Id;
4735 else
4736 Freeze_Action_Typ := Desig_Type;
4737 end if;
4739 Append_Freeze_Action (Freeze_Action_Typ,
4740 Make_Object_Declaration (Loc,
4741 Defining_Identifier => Pool_Object,
4742 Object_Definition =>
4743 Make_Subtype_Indication (Loc,
4744 Subtype_Mark =>
4745 New_Reference_To
4746 (RTE (RE_Stack_Bounded_Pool), Loc),
4748 Constraint =>
4749 Make_Index_Or_Discriminant_Constraint (Loc,
4750 Constraints => New_List (
4752 -- First discriminant is the Pool Size
4754 New_Reference_To (
4755 Storage_Size_Variable (Def_Id), Loc),
4757 -- Second discriminant is the element size
4759 DT_Size,
4761 -- Third discriminant is the alignment
4763 DT_Align)))));
4764 end;
4766 Set_Associated_Storage_Pool (Def_Id, Pool_Object);
4768 -- Case 3
4770 -- Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
4771 -- ---> Storage Pool is the specified one
4773 elsif Present (Associated_Storage_Pool (Def_Id)) then
4775 -- Nothing to do the associated storage pool has been attached
4776 -- when analyzing the rep. clause
4778 null;
4779 end if;
4781 -- For access-to-controlled types (including class-wide types
4782 -- and Taft-amendment types which potentially have controlled
4783 -- components), expand the list controller object that will
4784 -- store the dynamically allocated objects. Do not do this
4785 -- transformation for expander-generated access types, but do it
4786 -- for types that are the full view of types derived from other
4787 -- private types. Also suppress the list controller in the case
4788 -- of a designated type with convention Java, since this is used
4789 -- when binding to Java API specs, where there's no equivalent
4790 -- of a finalization list and we don't want to pull in the
4791 -- finalization support if not needed.
4793 if not Comes_From_Source (Def_Id)
4794 and then not Has_Private_Declaration (Def_Id)
4795 then
4796 null;
4798 elsif (Controlled_Type (Desig_Type)
4799 and then Convention (Desig_Type) /= Convention_Java)
4800 or else
4801 (Is_Incomplete_Or_Private_Type (Desig_Type)
4802 and then No (Full_View (Desig_Type))
4804 -- An exception is made for types defined in the run-time
4805 -- because Ada.Tags.Tag itself is such a type and cannot
4806 -- afford this unnecessary overhead that would generates a
4807 -- loop in the expansion scheme...
4809 and then not In_Runtime (Def_Id)
4811 -- Another exception is if Restrictions (No_Finalization)
4812 -- is active, since then we know nothing is controlled.
4814 and then not Restriction_Active (No_Finalization))
4816 -- If the designated type is not frozen yet, its controlled
4817 -- status must be retrieved explicitly.
4819 or else (Is_Array_Type (Desig_Type)
4820 and then not Is_Frozen (Desig_Type)
4821 and then Controlled_Type (Component_Type (Desig_Type)))
4822 then
4823 Set_Associated_Final_Chain (Def_Id,
4824 Make_Defining_Identifier (Loc,
4825 New_External_Name (Chars (Def_Id), 'L')));
4827 Append_Freeze_Action (Def_Id,
4828 Make_Object_Declaration (Loc,
4829 Defining_Identifier => Associated_Final_Chain (Def_Id),
4830 Object_Definition =>
4831 New_Reference_To (RTE (RE_List_Controller), Loc)));
4832 end if;
4833 end;
4835 -- Freeze processing for enumeration types
4837 elsif Ekind (Def_Id) = E_Enumeration_Type then
4839 -- We only have something to do if we have a non-standard
4840 -- representation (i.e. at least one literal whose pos value
4841 -- is not the same as its representation)
4843 if Has_Non_Standard_Rep (Def_Id) then
4844 Freeze_Enumeration_Type (N);
4845 end if;
4847 -- Private types that are completed by a derivation from a private
4848 -- type have an internally generated full view, that needs to be
4849 -- frozen. This must be done explicitly because the two views share
4850 -- the freeze node, and the underlying full view is not visible when
4851 -- the freeze node is analyzed.
4853 elsif Is_Private_Type (Def_Id)
4854 and then Is_Derived_Type (Def_Id)
4855 and then Present (Full_View (Def_Id))
4856 and then Is_Itype (Full_View (Def_Id))
4857 and then Has_Private_Declaration (Full_View (Def_Id))
4858 and then Freeze_Node (Full_View (Def_Id)) = N
4859 then
4860 Set_Entity (N, Full_View (Def_Id));
4861 Freeze_Type (N);
4862 Set_Entity (N, Def_Id);
4864 -- All other types require no expander action. There are such
4865 -- cases (e.g. task types and protected types). In such cases,
4866 -- the freeze nodes are there for use by Gigi.
4868 end if;
4870 Freeze_Stream_Operations (N, Def_Id);
4872 exception
4873 when RE_Not_Available =>
4874 return;
4875 end Freeze_Type;
4877 -------------------------
4878 -- Get_Simple_Init_Val --
4879 -------------------------
4881 function Get_Simple_Init_Val
4882 (T : Entity_Id;
4883 Loc : Source_Ptr) return Node_Id
4885 Val : Node_Id;
4886 Typ : Node_Id;
4887 Result : Node_Id;
4888 Val_RE : RE_Id;
4890 begin
4891 -- For a private type, we should always have an underlying type
4892 -- (because this was already checked in Needs_Simple_Initialization).
4893 -- What we do is to get the value for the underlying type and then
4894 -- do an Unchecked_Convert to the private type.
4896 if Is_Private_Type (T) then
4897 Val := Get_Simple_Init_Val (Underlying_Type (T), Loc);
4899 -- A special case, if the underlying value is null, then qualify
4900 -- it with the underlying type, so that the null is properly typed
4901 -- Similarly, if it is an aggregate it must be qualified, because
4902 -- an unchecked conversion does not provide a context for it.
4904 if Nkind (Val) = N_Null
4905 or else Nkind (Val) = N_Aggregate
4906 then
4907 Val :=
4908 Make_Qualified_Expression (Loc,
4909 Subtype_Mark =>
4910 New_Occurrence_Of (Underlying_Type (T), Loc),
4911 Expression => Val);
4912 end if;
4914 Result := Unchecked_Convert_To (T, Val);
4916 -- Don't truncate result (important for Initialize/Normalize_Scalars)
4918 if Nkind (Result) = N_Unchecked_Type_Conversion
4919 and then Is_Scalar_Type (Underlying_Type (T))
4920 then
4921 Set_No_Truncation (Result);
4922 end if;
4924 return Result;
4926 -- For scalars, we must have normalize/initialize scalars case
4928 elsif Is_Scalar_Type (T) then
4929 pragma Assert (Init_Or_Norm_Scalars);
4931 -- Processing for Normalize_Scalars case
4933 if Normalize_Scalars then
4935 -- First prepare a value (out of subtype range if possible)
4937 if Is_Real_Type (T) or else Is_Integer_Type (T) then
4938 Val :=
4939 Make_Attribute_Reference (Loc,
4940 Prefix => New_Occurrence_Of (Base_Type (T), Loc),
4941 Attribute_Name => Name_First);
4943 elsif Is_Modular_Integer_Type (T) then
4944 Val :=
4945 Make_Attribute_Reference (Loc,
4946 Prefix => New_Occurrence_Of (Base_Type (T), Loc),
4947 Attribute_Name => Name_Last);
4949 else
4950 pragma Assert (Is_Enumeration_Type (T));
4952 if Esize (T) <= 8 then
4953 Typ := RTE (RE_Unsigned_8);
4954 elsif Esize (T) <= 16 then
4955 Typ := RTE (RE_Unsigned_16);
4956 elsif Esize (T) <= 32 then
4957 Typ := RTE (RE_Unsigned_32);
4958 else
4959 Typ := RTE (RE_Unsigned_64);
4960 end if;
4962 Val :=
4963 Make_Attribute_Reference (Loc,
4964 Prefix => New_Occurrence_Of (Typ, Loc),
4965 Attribute_Name => Name_Last);
4966 end if;
4968 -- Here for Initialize_Scalars case
4970 else
4971 if Is_Floating_Point_Type (T) then
4972 if Root_Type (T) = Standard_Short_Float then
4973 Val_RE := RE_IS_Isf;
4974 elsif Root_Type (T) = Standard_Float then
4975 Val_RE := RE_IS_Ifl;
4976 elsif Root_Type (T) = Standard_Long_Float then
4977 Val_RE := RE_IS_Ilf;
4978 else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
4979 Val_RE := RE_IS_Ill;
4980 end if;
4982 elsif Is_Unsigned_Type (Base_Type (T)) then
4983 if Esize (T) = 8 then
4984 Val_RE := RE_IS_Iu1;
4985 elsif Esize (T) = 16 then
4986 Val_RE := RE_IS_Iu2;
4987 elsif Esize (T) = 32 then
4988 Val_RE := RE_IS_Iu4;
4989 else pragma Assert (Esize (T) = 64);
4990 Val_RE := RE_IS_Iu8;
4991 end if;
4993 else -- signed type
4994 if Esize (T) = 8 then
4995 Val_RE := RE_IS_Is1;
4996 elsif Esize (T) = 16 then
4997 Val_RE := RE_IS_Is2;
4998 elsif Esize (T) = 32 then
4999 Val_RE := RE_IS_Is4;
5000 else pragma Assert (Esize (T) = 64);
5001 Val_RE := RE_IS_Is8;
5002 end if;
5003 end if;
5005 Val := New_Occurrence_Of (RTE (Val_RE), Loc);
5006 end if;
5008 -- The final expression is obtained by doing an unchecked
5009 -- conversion of this result to the base type of the
5010 -- required subtype. We use the base type to avoid the
5011 -- unchecked conversion from chopping bits, and then we
5012 -- set Kill_Range_Check to preserve the "bad" value.
5014 Result := Unchecked_Convert_To (Base_Type (T), Val);
5016 -- Ensure result is not truncated, since we want the "bad" bits
5017 -- and also kill range check on result.
5019 if Nkind (Result) = N_Unchecked_Type_Conversion then
5020 Set_No_Truncation (Result);
5021 Set_Kill_Range_Check (Result, True);
5022 end if;
5024 return Result;
5026 -- String or Wide_String (must have Initialize_Scalars set)
5028 elsif Root_Type (T) = Standard_String
5029 or else
5030 Root_Type (T) = Standard_Wide_String
5031 then
5032 pragma Assert (Init_Or_Norm_Scalars);
5034 return
5035 Make_Aggregate (Loc,
5036 Component_Associations => New_List (
5037 Make_Component_Association (Loc,
5038 Choices => New_List (
5039 Make_Others_Choice (Loc)),
5040 Expression =>
5041 Get_Simple_Init_Val (Component_Type (T), Loc))));
5043 -- Access type is initialized to null
5045 elsif Is_Access_Type (T) then
5046 return
5047 Make_Null (Loc);
5049 -- No other possibilities should arise, since we should only be
5050 -- calling Get_Simple_Init_Val if Needs_Simple_Initialization
5051 -- returned True, indicating one of the above cases held.
5053 else
5054 raise Program_Error;
5055 end if;
5057 exception
5058 when RE_Not_Available =>
5059 return Empty;
5060 end Get_Simple_Init_Val;
5062 ------------------------------
5063 -- Has_New_Non_Standard_Rep --
5064 ------------------------------
5066 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
5067 begin
5068 if not Is_Derived_Type (T) then
5069 return Has_Non_Standard_Rep (T)
5070 or else Has_Non_Standard_Rep (Root_Type (T));
5072 -- If Has_Non_Standard_Rep is not set on the derived type, the
5073 -- representation is fully inherited.
5075 elsif not Has_Non_Standard_Rep (T) then
5076 return False;
5078 else
5079 return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
5081 -- May need a more precise check here: the First_Rep_Item may
5082 -- be a stream attribute, which does not affect the representation
5083 -- of the type ???
5084 end if;
5085 end Has_New_Non_Standard_Rep;
5087 ----------------
5088 -- In_Runtime --
5089 ----------------
5091 function In_Runtime (E : Entity_Id) return Boolean is
5092 S1 : Entity_Id := Scope (E);
5094 begin
5095 while Scope (S1) /= Standard_Standard loop
5096 S1 := Scope (S1);
5097 end loop;
5099 return Chars (S1) = Name_System or else Chars (S1) = Name_Ada;
5100 end In_Runtime;
5102 ------------------
5103 -- Init_Formals --
5104 ------------------
5106 function Init_Formals (Typ : Entity_Id) return List_Id is
5107 Loc : constant Source_Ptr := Sloc (Typ);
5108 Formals : List_Id;
5110 begin
5111 -- First parameter is always _Init : in out typ. Note that we need
5112 -- this to be in/out because in the case of the task record value,
5113 -- there are default record fields (_Priority, _Size, -Task_Info)
5114 -- that may be referenced in the generated initialization routine.
5116 Formals := New_List (
5117 Make_Parameter_Specification (Loc,
5118 Defining_Identifier =>
5119 Make_Defining_Identifier (Loc, Name_uInit),
5120 In_Present => True,
5121 Out_Present => True,
5122 Parameter_Type => New_Reference_To (Typ, Loc)));
5124 -- For task record value, or type that contains tasks, add two more
5125 -- formals, _Master : Master_Id and _Chain : in out Activation_Chain
5126 -- We also add these parameters for the task record type case.
5128 if Has_Task (Typ)
5129 or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
5130 then
5131 Append_To (Formals,
5132 Make_Parameter_Specification (Loc,
5133 Defining_Identifier =>
5134 Make_Defining_Identifier (Loc, Name_uMaster),
5135 Parameter_Type => New_Reference_To (RTE (RE_Master_Id), Loc)));
5137 Append_To (Formals,
5138 Make_Parameter_Specification (Loc,
5139 Defining_Identifier =>
5140 Make_Defining_Identifier (Loc, Name_uChain),
5141 In_Present => True,
5142 Out_Present => True,
5143 Parameter_Type =>
5144 New_Reference_To (RTE (RE_Activation_Chain), Loc)));
5146 Append_To (Formals,
5147 Make_Parameter_Specification (Loc,
5148 Defining_Identifier =>
5149 Make_Defining_Identifier (Loc, Name_uTask_Name),
5150 In_Present => True,
5151 Parameter_Type =>
5152 New_Reference_To (Standard_String, Loc)));
5153 end if;
5155 return Formals;
5157 exception
5158 when RE_Not_Available =>
5159 return Empty_List;
5160 end Init_Formals;
5162 ------------------
5163 -- Make_Eq_Case --
5164 ------------------
5166 -- <Make_Eq_if shared components>
5167 -- case X.D1 is
5168 -- when V1 => <Make_Eq_Case> on subcomponents
5169 -- ...
5170 -- when Vn => <Make_Eq_Case> on subcomponents
5171 -- end case;
5173 function Make_Eq_Case
5174 (E : Entity_Id;
5175 CL : Node_Id;
5176 Discr : Entity_Id := Empty) return List_Id
5178 Loc : constant Source_Ptr := Sloc (E);
5179 Result : constant List_Id := New_List;
5180 Variant : Node_Id;
5181 Alt_List : List_Id;
5183 begin
5184 Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
5186 if No (Variant_Part (CL)) then
5187 return Result;
5188 end if;
5190 Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
5192 if No (Variant) then
5193 return Result;
5194 end if;
5196 Alt_List := New_List;
5198 while Present (Variant) loop
5199 Append_To (Alt_List,
5200 Make_Case_Statement_Alternative (Loc,
5201 Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
5202 Statements => Make_Eq_Case (E, Component_List (Variant))));
5204 Next_Non_Pragma (Variant);
5205 end loop;
5207 -- If we have an Unchecked_Union, use one of the parameters that
5208 -- captures the discriminants.
5210 if Is_Unchecked_Union (E) then
5211 Append_To (Result,
5212 Make_Case_Statement (Loc,
5213 Expression => New_Reference_To (Discr, Loc),
5214 Alternatives => Alt_List));
5216 else
5217 Append_To (Result,
5218 Make_Case_Statement (Loc,
5219 Expression =>
5220 Make_Selected_Component (Loc,
5221 Prefix => Make_Identifier (Loc, Name_X),
5222 Selector_Name => New_Copy (Name (Variant_Part (CL)))),
5223 Alternatives => Alt_List));
5224 end if;
5226 return Result;
5227 end Make_Eq_Case;
5229 ----------------
5230 -- Make_Eq_If --
5231 ----------------
5233 -- Generates:
5235 -- if
5236 -- X.C1 /= Y.C1
5237 -- or else
5238 -- X.C2 /= Y.C2
5239 -- ...
5240 -- then
5241 -- return False;
5242 -- end if;
5244 -- or a null statement if the list L is empty
5246 function Make_Eq_If
5247 (E : Entity_Id;
5248 L : List_Id) return Node_Id
5250 Loc : constant Source_Ptr := Sloc (E);
5251 C : Node_Id;
5252 Field_Name : Name_Id;
5253 Cond : Node_Id;
5255 begin
5256 if No (L) then
5257 return Make_Null_Statement (Loc);
5259 else
5260 Cond := Empty;
5262 C := First_Non_Pragma (L);
5263 while Present (C) loop
5264 Field_Name := Chars (Defining_Identifier (C));
5266 -- The tags must not be compared they are not part of the value.
5267 -- Note also that in the following, we use Make_Identifier for
5268 -- the component names. Use of New_Reference_To to identify the
5269 -- components would be incorrect because the wrong entities for
5270 -- discriminants could be picked up in the private type case.
5272 if Field_Name /= Name_uTag then
5273 Evolve_Or_Else (Cond,
5274 Make_Op_Ne (Loc,
5275 Left_Opnd =>
5276 Make_Selected_Component (Loc,
5277 Prefix => Make_Identifier (Loc, Name_X),
5278 Selector_Name =>
5279 Make_Identifier (Loc, Field_Name)),
5281 Right_Opnd =>
5282 Make_Selected_Component (Loc,
5283 Prefix => Make_Identifier (Loc, Name_Y),
5284 Selector_Name =>
5285 Make_Identifier (Loc, Field_Name))));
5286 end if;
5288 Next_Non_Pragma (C);
5289 end loop;
5291 if No (Cond) then
5292 return Make_Null_Statement (Loc);
5294 else
5295 return
5296 Make_Implicit_If_Statement (E,
5297 Condition => Cond,
5298 Then_Statements => New_List (
5299 Make_Return_Statement (Loc,
5300 Expression => New_Occurrence_Of (Standard_False, Loc))));
5301 end if;
5302 end if;
5303 end Make_Eq_If;
5305 -------------------------------------
5306 -- Make_Predefined_Primitive_Specs --
5307 -------------------------------------
5309 procedure Make_Predefined_Primitive_Specs
5310 (Tag_Typ : Entity_Id;
5311 Predef_List : out List_Id;
5312 Renamed_Eq : out Node_Id)
5314 Loc : constant Source_Ptr := Sloc (Tag_Typ);
5315 Res : constant List_Id := New_List;
5316 Prim : Elmt_Id;
5317 Eq_Needed : Boolean;
5318 Eq_Spec : Node_Id;
5319 Eq_Name : Name_Id := Name_Op_Eq;
5321 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
5322 -- Returns true if Prim is a renaming of an unresolved predefined
5323 -- equality operation.
5325 -------------------------------
5326 -- Is_Predefined_Eq_Renaming --
5327 -------------------------------
5329 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
5330 begin
5331 return Chars (Prim) /= Name_Op_Eq
5332 and then Present (Alias (Prim))
5333 and then Comes_From_Source (Prim)
5334 and then Is_Intrinsic_Subprogram (Alias (Prim))
5335 and then Chars (Alias (Prim)) = Name_Op_Eq;
5336 end Is_Predefined_Eq_Renaming;
5338 -- Start of processing for Make_Predefined_Primitive_Specs
5340 begin
5341 Renamed_Eq := Empty;
5343 -- Spec of _Alignment
5345 Append_To (Res, Predef_Spec_Or_Body (Loc,
5346 Tag_Typ => Tag_Typ,
5347 Name => Name_uAlignment,
5348 Profile => New_List (
5349 Make_Parameter_Specification (Loc,
5350 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5351 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
5353 Ret_Type => Standard_Integer));
5355 -- Spec of _Size
5357 Append_To (Res, Predef_Spec_Or_Body (Loc,
5358 Tag_Typ => Tag_Typ,
5359 Name => Name_uSize,
5360 Profile => New_List (
5361 Make_Parameter_Specification (Loc,
5362 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5363 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
5365 Ret_Type => Standard_Long_Long_Integer));
5367 -- Specs for dispatching stream attributes. We skip these for limited
5368 -- types, since there is no question of dispatching in the limited case.
5370 -- We also skip these operations if dispatching is not available
5371 -- or if streams are not available (since what's the point?)
5373 if not Is_Limited_Type (Tag_Typ)
5374 and then RTE_Available (RE_Tag)
5375 and then RTE_Available (RE_Root_Stream_Type)
5376 then
5377 Append_To (Res,
5378 Predef_Stream_Attr_Spec (Loc, Tag_Typ, TSS_Stream_Read));
5379 Append_To (Res,
5380 Predef_Stream_Attr_Spec (Loc, Tag_Typ, TSS_Stream_Write));
5381 Append_To (Res,
5382 Predef_Stream_Attr_Spec (Loc, Tag_Typ, TSS_Stream_Input));
5383 Append_To (Res,
5384 Predef_Stream_Attr_Spec (Loc, Tag_Typ, TSS_Stream_Output));
5385 end if;
5387 -- Spec of "=" if expanded if the type is not limited and if a
5388 -- user defined "=" was not already declared for the non-full
5389 -- view of a private extension
5391 if not Is_Limited_Type (Tag_Typ) then
5392 Eq_Needed := True;
5394 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
5395 while Present (Prim) loop
5397 -- If a primitive is encountered that renames the predefined
5398 -- equality operator before reaching any explicit equality
5399 -- primitive, then we still need to create a predefined
5400 -- equality function, because calls to it can occur via
5401 -- the renaming. A new name is created for the equality
5402 -- to avoid conflicting with any user-defined equality.
5403 -- (Note that this doesn't account for renamings of
5404 -- equality nested within subpackages???)
5406 if Is_Predefined_Eq_Renaming (Node (Prim)) then
5407 Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
5409 elsif Chars (Node (Prim)) = Name_Op_Eq
5410 and then (No (Alias (Node (Prim)))
5411 or else Nkind (Unit_Declaration_Node (Node (Prim))) =
5412 N_Subprogram_Renaming_Declaration)
5413 and then Etype (First_Formal (Node (Prim))) =
5414 Etype (Next_Formal (First_Formal (Node (Prim))))
5415 and then Base_Type (Etype (Node (Prim))) = Standard_Boolean
5417 then
5418 Eq_Needed := False;
5419 exit;
5421 -- If the parent equality is abstract, the inherited equality is
5422 -- abstract as well, and no body can be created for for it.
5424 elsif Chars (Node (Prim)) = Name_Op_Eq
5425 and then Present (Alias (Node (Prim)))
5426 and then Is_Abstract (Alias (Node (Prim)))
5427 then
5428 Eq_Needed := False;
5429 exit;
5430 end if;
5432 Next_Elmt (Prim);
5433 end loop;
5435 -- If a renaming of predefined equality was found
5436 -- but there was no user-defined equality (so Eq_Needed
5437 -- is still true), then set the name back to Name_Op_Eq.
5438 -- But in the case where a user-defined equality was
5439 -- located after such a renaming, then the predefined
5440 -- equality function is still needed, so Eq_Needed must
5441 -- be set back to True.
5443 if Eq_Name /= Name_Op_Eq then
5444 if Eq_Needed then
5445 Eq_Name := Name_Op_Eq;
5446 else
5447 Eq_Needed := True;
5448 end if;
5449 end if;
5451 if Eq_Needed then
5452 Eq_Spec := Predef_Spec_Or_Body (Loc,
5453 Tag_Typ => Tag_Typ,
5454 Name => Eq_Name,
5455 Profile => New_List (
5456 Make_Parameter_Specification (Loc,
5457 Defining_Identifier =>
5458 Make_Defining_Identifier (Loc, Name_X),
5459 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
5460 Make_Parameter_Specification (Loc,
5461 Defining_Identifier =>
5462 Make_Defining_Identifier (Loc, Name_Y),
5463 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
5464 Ret_Type => Standard_Boolean);
5465 Append_To (Res, Eq_Spec);
5467 if Eq_Name /= Name_Op_Eq then
5468 Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
5470 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
5471 while Present (Prim) loop
5473 -- Any renamings of equality that appeared before an
5474 -- overriding equality must be updated to refer to
5475 -- the entity for the predefined equality, otherwise
5476 -- calls via the renaming would get incorrectly
5477 -- resolved to call the user-defined equality function.
5479 if Is_Predefined_Eq_Renaming (Node (Prim)) then
5480 Set_Alias (Node (Prim), Renamed_Eq);
5482 -- Exit upon encountering a user-defined equality
5484 elsif Chars (Node (Prim)) = Name_Op_Eq
5485 and then No (Alias (Node (Prim)))
5486 then
5487 exit;
5488 end if;
5490 Next_Elmt (Prim);
5491 end loop;
5492 end if;
5493 end if;
5495 -- Spec for dispatching assignment
5497 Append_To (Res, Predef_Spec_Or_Body (Loc,
5498 Tag_Typ => Tag_Typ,
5499 Name => Name_uAssign,
5500 Profile => New_List (
5501 Make_Parameter_Specification (Loc,
5502 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5503 Out_Present => True,
5504 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
5506 Make_Parameter_Specification (Loc,
5507 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
5508 Parameter_Type => New_Reference_To (Tag_Typ, Loc)))));
5509 end if;
5511 -- Specs for finalization actions that may be required in case a
5512 -- future extension contain a controlled element. We generate those
5513 -- only for root tagged types where they will get dummy bodies or
5514 -- when the type has controlled components and their body must be
5515 -- generated. It is also impossible to provide those for tagged
5516 -- types defined within s-finimp since it would involve circularity
5517 -- problems
5519 if In_Finalization_Root (Tag_Typ) then
5520 null;
5522 -- We also skip these if finalization is not available
5524 elsif Restriction_Active (No_Finalization) then
5525 null;
5527 elsif Etype (Tag_Typ) = Tag_Typ or else Controlled_Type (Tag_Typ) then
5528 if not Is_Limited_Type (Tag_Typ) then
5529 Append_To (Res,
5530 Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
5531 end if;
5533 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
5534 end if;
5536 Predef_List := Res;
5537 end Make_Predefined_Primitive_Specs;
5539 ---------------------------------
5540 -- Needs_Simple_Initialization --
5541 ---------------------------------
5543 function Needs_Simple_Initialization (T : Entity_Id) return Boolean is
5544 begin
5545 -- Check for private type, in which case test applies to the
5546 -- underlying type of the private type.
5548 if Is_Private_Type (T) then
5549 declare
5550 RT : constant Entity_Id := Underlying_Type (T);
5552 begin
5553 if Present (RT) then
5554 return Needs_Simple_Initialization (RT);
5555 else
5556 return False;
5557 end if;
5558 end;
5560 -- Cases needing simple initialization are access types, and, if pragma
5561 -- Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
5562 -- types.
5564 elsif Is_Access_Type (T)
5565 or else (Init_Or_Norm_Scalars and then (Is_Scalar_Type (T)))
5566 then
5567 return True;
5569 -- If Initialize/Normalize_Scalars is in effect, string objects also
5570 -- need initialization, unless they are created in the course of
5571 -- expanding an aggregate (since in the latter case they will be
5572 -- filled with appropriate initializing values before they are used).
5574 elsif Init_Or_Norm_Scalars
5575 and then
5576 (Root_Type (T) = Standard_String
5577 or else Root_Type (T) = Standard_Wide_String)
5578 and then
5579 (not Is_Itype (T)
5580 or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
5581 then
5582 return True;
5584 else
5585 return False;
5586 end if;
5587 end Needs_Simple_Initialization;
5589 ----------------------
5590 -- Predef_Deep_Spec --
5591 ----------------------
5593 function Predef_Deep_Spec
5594 (Loc : Source_Ptr;
5595 Tag_Typ : Entity_Id;
5596 Name : TSS_Name_Type;
5597 For_Body : Boolean := False) return Node_Id
5599 Prof : List_Id;
5600 Type_B : Entity_Id;
5602 begin
5603 if Name = TSS_Deep_Finalize then
5604 Prof := New_List;
5605 Type_B := Standard_Boolean;
5607 else
5608 Prof := New_List (
5609 Make_Parameter_Specification (Loc,
5610 Defining_Identifier => Make_Defining_Identifier (Loc, Name_L),
5611 In_Present => True,
5612 Out_Present => True,
5613 Parameter_Type =>
5614 New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
5615 Type_B := Standard_Short_Short_Integer;
5616 end if;
5618 Append_To (Prof,
5619 Make_Parameter_Specification (Loc,
5620 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
5621 In_Present => True,
5622 Out_Present => True,
5623 Parameter_Type => New_Reference_To (Tag_Typ, Loc)));
5625 Append_To (Prof,
5626 Make_Parameter_Specification (Loc,
5627 Defining_Identifier => Make_Defining_Identifier (Loc, Name_B),
5628 Parameter_Type => New_Reference_To (Type_B, Loc)));
5630 return Predef_Spec_Or_Body (Loc,
5631 Name => Make_TSS_Name (Tag_Typ, Name),
5632 Tag_Typ => Tag_Typ,
5633 Profile => Prof,
5634 For_Body => For_Body);
5636 exception
5637 when RE_Not_Available =>
5638 return Empty;
5639 end Predef_Deep_Spec;
5641 -------------------------
5642 -- Predef_Spec_Or_Body --
5643 -------------------------
5645 function Predef_Spec_Or_Body
5646 (Loc : Source_Ptr;
5647 Tag_Typ : Entity_Id;
5648 Name : Name_Id;
5649 Profile : List_Id;
5650 Ret_Type : Entity_Id := Empty;
5651 For_Body : Boolean := False) return Node_Id
5653 Id : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
5654 Spec : Node_Id;
5656 begin
5657 Set_Is_Public (Id, Is_Public (Tag_Typ));
5659 -- The internal flag is set to mark these declarations because
5660 -- they have specific properties. First they are primitives even
5661 -- if they are not defined in the type scope (the freezing point
5662 -- is not necessarily in the same scope), furthermore the
5663 -- predefined equality can be overridden by a user-defined
5664 -- equality, no body will be generated in this case.
5666 Set_Is_Internal (Id);
5668 if not Debug_Generated_Code then
5669 Set_Debug_Info_Off (Id);
5670 end if;
5672 if No (Ret_Type) then
5673 Spec :=
5674 Make_Procedure_Specification (Loc,
5675 Defining_Unit_Name => Id,
5676 Parameter_Specifications => Profile);
5677 else
5678 Spec :=
5679 Make_Function_Specification (Loc,
5680 Defining_Unit_Name => Id,
5681 Parameter_Specifications => Profile,
5682 Subtype_Mark =>
5683 New_Reference_To (Ret_Type, Loc));
5684 end if;
5686 -- If body case, return empty subprogram body. Note that this is
5687 -- ill-formed, because there is not even a null statement, and
5688 -- certainly not a return in the function case. The caller is
5689 -- expected to do surgery on the body to add the appropriate stuff.
5691 if For_Body then
5692 return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
5694 -- For the case of Input/Output attributes applied to an abstract type,
5695 -- generate abstract specifications. These will never be called,
5696 -- but we need the slots allocated in the dispatching table so
5697 -- that typ'Class'Input and typ'Class'Output will work properly.
5699 elsif (Is_TSS (Name, TSS_Stream_Input)
5700 or else
5701 Is_TSS (Name, TSS_Stream_Output))
5702 and then Is_Abstract (Tag_Typ)
5703 then
5704 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
5706 -- Normal spec case, where we return a subprogram declaration
5708 else
5709 return Make_Subprogram_Declaration (Loc, Spec);
5710 end if;
5711 end Predef_Spec_Or_Body;
5713 -----------------------------
5714 -- Predef_Stream_Attr_Spec --
5715 -----------------------------
5717 function Predef_Stream_Attr_Spec
5718 (Loc : Source_Ptr;
5719 Tag_Typ : Entity_Id;
5720 Name : TSS_Name_Type;
5721 For_Body : Boolean := False) return Node_Id
5723 Ret_Type : Entity_Id;
5725 begin
5726 if Name = TSS_Stream_Input then
5727 Ret_Type := Tag_Typ;
5728 else
5729 Ret_Type := Empty;
5730 end if;
5732 return Predef_Spec_Or_Body (Loc,
5733 Name => Make_TSS_Name (Tag_Typ, Name),
5734 Tag_Typ => Tag_Typ,
5735 Profile => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
5736 Ret_Type => Ret_Type,
5737 For_Body => For_Body);
5738 end Predef_Stream_Attr_Spec;
5740 ---------------------------------
5741 -- Predefined_Primitive_Bodies --
5742 ---------------------------------
5744 function Predefined_Primitive_Bodies
5745 (Tag_Typ : Entity_Id;
5746 Renamed_Eq : Node_Id) return List_Id
5748 Loc : constant Source_Ptr := Sloc (Tag_Typ);
5749 Res : constant List_Id := New_List;
5750 Decl : Node_Id;
5751 Prim : Elmt_Id;
5752 Eq_Needed : Boolean;
5753 Eq_Name : Name_Id;
5754 Ent : Entity_Id;
5756 begin
5757 -- See if we have a predefined "=" operator
5759 if Present (Renamed_Eq) then
5760 Eq_Needed := True;
5761 Eq_Name := Chars (Renamed_Eq);
5763 else
5764 Eq_Needed := False;
5765 Eq_Name := No_Name;
5767 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
5768 while Present (Prim) loop
5769 if Chars (Node (Prim)) = Name_Op_Eq
5770 and then Is_Internal (Node (Prim))
5771 then
5772 Eq_Needed := True;
5773 Eq_Name := Name_Op_Eq;
5774 end if;
5776 Next_Elmt (Prim);
5777 end loop;
5778 end if;
5780 -- Body of _Alignment
5782 Decl := Predef_Spec_Or_Body (Loc,
5783 Tag_Typ => Tag_Typ,
5784 Name => Name_uAlignment,
5785 Profile => New_List (
5786 Make_Parameter_Specification (Loc,
5787 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5788 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
5790 Ret_Type => Standard_Integer,
5791 For_Body => True);
5793 Set_Handled_Statement_Sequence (Decl,
5794 Make_Handled_Sequence_Of_Statements (Loc, New_List (
5795 Make_Return_Statement (Loc,
5796 Expression =>
5797 Make_Attribute_Reference (Loc,
5798 Prefix => Make_Identifier (Loc, Name_X),
5799 Attribute_Name => Name_Alignment)))));
5801 Append_To (Res, Decl);
5803 -- Body of _Size
5805 Decl := Predef_Spec_Or_Body (Loc,
5806 Tag_Typ => Tag_Typ,
5807 Name => Name_uSize,
5808 Profile => New_List (
5809 Make_Parameter_Specification (Loc,
5810 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5811 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
5813 Ret_Type => Standard_Long_Long_Integer,
5814 For_Body => True);
5816 Set_Handled_Statement_Sequence (Decl,
5817 Make_Handled_Sequence_Of_Statements (Loc, New_List (
5818 Make_Return_Statement (Loc,
5819 Expression =>
5820 Make_Attribute_Reference (Loc,
5821 Prefix => Make_Identifier (Loc, Name_X),
5822 Attribute_Name => Name_Size)))));
5824 Append_To (Res, Decl);
5826 -- Bodies for Dispatching stream IO routines. We need these only for
5827 -- non-limited types (in the limited case there is no dispatching).
5828 -- We also skip them if dispatching is not available.
5830 if not Is_Limited_Type (Tag_Typ)
5831 and then not Restriction_Active (No_Finalization)
5832 then
5833 if No (TSS (Tag_Typ, TSS_Stream_Read)) then
5834 Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
5835 Append_To (Res, Decl);
5836 end if;
5838 if No (TSS (Tag_Typ, TSS_Stream_Write)) then
5839 Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
5840 Append_To (Res, Decl);
5841 end if;
5843 -- Skip bodies of _Input and _Output for the abstract case, since
5844 -- the corresponding specs are abstract (see Predef_Spec_Or_Body)
5846 if not Is_Abstract (Tag_Typ) then
5847 if No (TSS (Tag_Typ, TSS_Stream_Input)) then
5848 Build_Record_Or_Elementary_Input_Function
5849 (Loc, Tag_Typ, Decl, Ent);
5850 Append_To (Res, Decl);
5851 end if;
5853 if No (TSS (Tag_Typ, TSS_Stream_Output)) then
5854 Build_Record_Or_Elementary_Output_Procedure
5855 (Loc, Tag_Typ, Decl, Ent);
5856 Append_To (Res, Decl);
5857 end if;
5858 end if;
5859 end if;
5861 if not Is_Limited_Type (Tag_Typ) then
5863 -- Body for equality
5865 if Eq_Needed then
5867 Decl := Predef_Spec_Or_Body (Loc,
5868 Tag_Typ => Tag_Typ,
5869 Name => Eq_Name,
5870 Profile => New_List (
5871 Make_Parameter_Specification (Loc,
5872 Defining_Identifier =>
5873 Make_Defining_Identifier (Loc, Name_X),
5874 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
5876 Make_Parameter_Specification (Loc,
5877 Defining_Identifier =>
5878 Make_Defining_Identifier (Loc, Name_Y),
5879 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
5881 Ret_Type => Standard_Boolean,
5882 For_Body => True);
5884 declare
5885 Def : constant Node_Id := Parent (Tag_Typ);
5886 Stmts : constant List_Id := New_List;
5887 Variant_Case : Boolean := Has_Discriminants (Tag_Typ);
5888 Comps : Node_Id := Empty;
5889 Typ_Def : Node_Id := Type_Definition (Def);
5891 begin
5892 if Variant_Case then
5893 if Nkind (Typ_Def) = N_Derived_Type_Definition then
5894 Typ_Def := Record_Extension_Part (Typ_Def);
5895 end if;
5897 if Present (Typ_Def) then
5898 Comps := Component_List (Typ_Def);
5899 end if;
5901 Variant_Case := Present (Comps)
5902 and then Present (Variant_Part (Comps));
5903 end if;
5905 if Variant_Case then
5906 Append_To (Stmts,
5907 Make_Eq_If (Tag_Typ, Discriminant_Specifications (Def)));
5908 Append_List_To (Stmts, Make_Eq_Case (Tag_Typ, Comps));
5909 Append_To (Stmts,
5910 Make_Return_Statement (Loc,
5911 Expression => New_Reference_To (Standard_True, Loc)));
5913 else
5914 Append_To (Stmts,
5915 Make_Return_Statement (Loc,
5916 Expression =>
5917 Expand_Record_Equality (Tag_Typ,
5918 Typ => Tag_Typ,
5919 Lhs => Make_Identifier (Loc, Name_X),
5920 Rhs => Make_Identifier (Loc, Name_Y),
5921 Bodies => Declarations (Decl))));
5922 end if;
5924 Set_Handled_Statement_Sequence (Decl,
5925 Make_Handled_Sequence_Of_Statements (Loc, Stmts));
5926 end;
5927 Append_To (Res, Decl);
5928 end if;
5930 -- Body for dispatching assignment
5932 Decl := Predef_Spec_Or_Body (Loc,
5933 Tag_Typ => Tag_Typ,
5934 Name => Name_uAssign,
5935 Profile => New_List (
5936 Make_Parameter_Specification (Loc,
5937 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5938 Out_Present => True,
5939 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
5941 Make_Parameter_Specification (Loc,
5942 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
5943 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
5944 For_Body => True);
5946 Set_Handled_Statement_Sequence (Decl,
5947 Make_Handled_Sequence_Of_Statements (Loc, New_List (
5948 Make_Assignment_Statement (Loc,
5949 Name => Make_Identifier (Loc, Name_X),
5950 Expression => Make_Identifier (Loc, Name_Y)))));
5952 Append_To (Res, Decl);
5953 end if;
5955 -- Generate dummy bodies for finalization actions of types that have
5956 -- no controlled components.
5958 -- Skip this processing if we are in the finalization routine in the
5959 -- runtime itself, otherwise we get hopelessly circularly confused!
5961 if In_Finalization_Root (Tag_Typ) then
5962 null;
5964 -- Skip this if finalization is not available
5966 elsif Restriction_Active (No_Finalization) then
5967 null;
5969 elsif (Etype (Tag_Typ) = Tag_Typ or else Is_Controlled (Tag_Typ))
5970 and then not Has_Controlled_Component (Tag_Typ)
5971 then
5972 if not Is_Limited_Type (Tag_Typ) then
5973 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
5975 if Is_Controlled (Tag_Typ) then
5976 Set_Handled_Statement_Sequence (Decl,
5977 Make_Handled_Sequence_Of_Statements (Loc,
5978 Make_Adjust_Call (
5979 Ref => Make_Identifier (Loc, Name_V),
5980 Typ => Tag_Typ,
5981 Flist_Ref => Make_Identifier (Loc, Name_L),
5982 With_Attach => Make_Identifier (Loc, Name_B))));
5984 else
5985 Set_Handled_Statement_Sequence (Decl,
5986 Make_Handled_Sequence_Of_Statements (Loc, New_List (
5987 Make_Null_Statement (Loc))));
5988 end if;
5990 Append_To (Res, Decl);
5991 end if;
5993 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
5995 if Is_Controlled (Tag_Typ) then
5996 Set_Handled_Statement_Sequence (Decl,
5997 Make_Handled_Sequence_Of_Statements (Loc,
5998 Make_Final_Call (
5999 Ref => Make_Identifier (Loc, Name_V),
6000 Typ => Tag_Typ,
6001 With_Detach => Make_Identifier (Loc, Name_B))));
6003 else
6004 Set_Handled_Statement_Sequence (Decl,
6005 Make_Handled_Sequence_Of_Statements (Loc, New_List (
6006 Make_Null_Statement (Loc))));
6007 end if;
6009 Append_To (Res, Decl);
6010 end if;
6012 return Res;
6013 end Predefined_Primitive_Bodies;
6015 ---------------------------------
6016 -- Predefined_Primitive_Freeze --
6017 ---------------------------------
6019 function Predefined_Primitive_Freeze
6020 (Tag_Typ : Entity_Id) return List_Id
6022 Loc : constant Source_Ptr := Sloc (Tag_Typ);
6023 Res : constant List_Id := New_List;
6024 Prim : Elmt_Id;
6025 Frnodes : List_Id;
6027 begin
6028 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
6029 while Present (Prim) loop
6030 if Is_Internal (Node (Prim)) then
6031 Frnodes := Freeze_Entity (Node (Prim), Loc);
6033 if Present (Frnodes) then
6034 Append_List_To (Res, Frnodes);
6035 end if;
6036 end if;
6038 Next_Elmt (Prim);
6039 end loop;
6041 return Res;
6042 end Predefined_Primitive_Freeze;
6043 end Exp_Ch3;