OSDN Git Service

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