OSDN Git Service

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