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