OSDN Git Service

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