OSDN Git Service

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