OSDN Git Service

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