OSDN Git Service

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