OSDN Git Service

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