OSDN Git Service

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