OSDN Git Service

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