OSDN Git Service

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