OSDN Git Service

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