OSDN Git Service

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