OSDN Git Service

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