OSDN Git Service

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