OSDN Git Service

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