OSDN Git Service

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