OSDN Git Service

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