OSDN Git Service

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