18249d83a44a0aef99594f3c9576f89ba5def3ec
[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
3718       begin
3719          Invariant_Found := True;
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          Call :=
3748            Make_Procedure_Call_Statement (Loc,
3749              Name                   =>
3750                New_Occurrence_Of (Invariant_Procedure (Base_Type (Typ)), Loc),
3751              Parameter_Associations => New_List (Sel_Comp));
3752
3753          if Is_Access_Type (Etype (Comp)) then
3754             Call :=
3755               Make_If_Statement (Loc,
3756                 Condition =>
3757                   Make_Op_Ne (Loc,
3758                     Left_Opnd   => Make_Null (Loc),
3759                     Right_Opnd  =>
3760                        Make_Selected_Component (Loc,
3761                          Prefix      => New_Occurrence_Of (Object_Entity, Loc),
3762                          Selector_Name => New_Occurrence_Of (Comp, Loc))),
3763                 Then_Statements => New_List (Call));
3764          end if;
3765
3766          return Call;
3767       end Build_Component_Invariant_Call;
3768
3769       ----------------------------
3770       -- Build_Invariant_Checks --
3771       ----------------------------
3772
3773       function Build_Invariant_Checks (Comp_List : Node_Id) return List_Id is
3774          Decl     : Node_Id;
3775          Id       : Entity_Id;
3776          Stmts    : List_Id;
3777
3778       begin
3779          Stmts := New_List;
3780          Decl := First_Non_Pragma (Component_Items (Comp_List));
3781          while Present (Decl) loop
3782             if Nkind (Decl) = N_Component_Declaration then
3783                Id := Defining_Identifier (Decl);
3784
3785                if Has_Invariants (Etype (Id))
3786                  and then In_Open_Scopes (Scope (R_Type))
3787                then
3788                   if Has_Unchecked_Union (R_Type) then
3789                      Error_Msg_NE
3790                        ("invariants cannot be checked on components of "
3791                          & "unchecked_union type&?", Decl, R_Type);
3792                      return Empty_List;
3793
3794                   else
3795                      Append_To (Stmts, Build_Component_Invariant_Call (Id));
3796                   end if;
3797
3798                elsif Is_Access_Type (Etype (Id))
3799                  and then not Is_Access_Constant (Etype (Id))
3800                  and then Has_Invariants (Designated_Type (Etype (Id)))
3801                  and then In_Open_Scopes (Scope (Designated_Type (Etype (Id))))
3802                then
3803                   Append_To (Stmts, Build_Component_Invariant_Call (Id));
3804                end if;
3805             end if;
3806
3807             Next (Decl);
3808          end loop;
3809
3810          if Present (Variant_Part (Comp_List)) then
3811             declare
3812                Variant_Alts  : constant List_Id := New_List;
3813                Var_Loc       : Source_Ptr;
3814                Variant       : Node_Id;
3815                Variant_Stmts : List_Id;
3816
3817             begin
3818                Variant :=
3819                  First_Non_Pragma (Variants (Variant_Part (Comp_List)));
3820                while Present (Variant) loop
3821                   Variant_Stmts :=
3822                     Build_Invariant_Checks (Component_List (Variant));
3823                   Var_Loc := Sloc (Variant);
3824                   Append_To (Variant_Alts,
3825                     Make_Case_Statement_Alternative (Var_Loc,
3826                       Discrete_Choices =>
3827                         New_Copy_List (Discrete_Choices (Variant)),
3828                       Statements => Variant_Stmts));
3829
3830                   Next_Non_Pragma (Variant);
3831                end loop;
3832
3833                --  The expression in the case statement is the reference to
3834                --  the discriminant of the target object.
3835
3836                Append_To (Stmts,
3837                  Make_Case_Statement (Var_Loc,
3838                    Expression =>
3839                      Make_Selected_Component (Var_Loc,
3840                       Prefix => New_Occurrence_Of (Object_Entity, Var_Loc),
3841                       Selector_Name => New_Occurrence_Of
3842                         (Entity
3843                           (Name (Variant_Part (Comp_List))), Var_Loc)),
3844                       Alternatives => Variant_Alts));
3845             end;
3846          end if;
3847
3848          return Stmts;
3849       end Build_Invariant_Checks;
3850
3851    --  Start of processing for Build_Record_Invariant_Proc
3852
3853    begin
3854       Invariant_Found := False;
3855       Type_Def := Type_Definition (Parent (R_Type));
3856
3857       if Nkind (Type_Def) = N_Record_Definition
3858         and then not Null_Present (Type_Def)
3859       then
3860          Stmts := Build_Invariant_Checks (Component_List (Type_Def));
3861       else
3862          return Empty;
3863       end if;
3864
3865       if not Invariant_Found then
3866          return Empty;
3867       end if;
3868
3869       --  The name of the invariant procedure reflects the fact that the
3870       --  checks correspond to invariants on the component types. The
3871       --  record type itself may have invariants that will create a separate
3872       --  procedure whose name carries the Invariant suffix.
3873
3874       Proc_Id :=
3875         Make_Defining_Identifier (Loc,
3876            Chars => New_External_Name (Chars (R_Type), "CInvariant"));
3877
3878       Proc_Body :=
3879         Make_Subprogram_Body (Loc,
3880           Specification =>
3881             Make_Procedure_Specification (Loc,
3882               Defining_Unit_Name       => Proc_Id,
3883               Parameter_Specifications => New_List (
3884                 Make_Parameter_Specification (Loc,
3885                   Defining_Identifier => Object_Entity,
3886                   Parameter_Type      => New_Occurrence_Of (R_Type, Loc)))),
3887
3888           Declarations               => Empty_List,
3889           Handled_Statement_Sequence =>
3890             Make_Handled_Sequence_Of_Statements (Loc,
3891               Statements => Stmts));
3892
3893       Set_Ekind          (Proc_Id, E_Procedure);
3894       Set_Is_Public      (Proc_Id, Is_Public (R_Type));
3895       Set_Is_Internal    (Proc_Id);
3896       Set_Has_Completion (Proc_Id);
3897
3898       return Proc_Body;
3899       --  Insert_After (Nod, Proc_Body);
3900       --  Analyze (Proc_Body);
3901    end Build_Record_Invariant_Proc;
3902
3903    ----------------------------
3904    -- Build_Slice_Assignment --
3905    ----------------------------
3906
3907    --  Generates the following subprogram:
3908
3909    --    procedure Assign
3910    --     (Source,  Target    : Array_Type,
3911    --      Left_Lo, Left_Hi   : Index;
3912    --      Right_Lo, Right_Hi : Index;
3913    --      Rev                : Boolean)
3914    --    is
3915    --       Li1 : Index;
3916    --       Ri1 : Index;
3917
3918    --    begin
3919
3920    --       if Left_Hi < Left_Lo then
3921    --          return;
3922    --       end if;
3923
3924    --       if Rev then
3925    --          Li1 := Left_Hi;
3926    --          Ri1 := Right_Hi;
3927    --       else
3928    --          Li1 := Left_Lo;
3929    --          Ri1 := Right_Lo;
3930    --       end if;
3931
3932    --       loop
3933    --          Target (Li1) := Source (Ri1);
3934
3935    --          if Rev then
3936    --             exit when Li1 = Left_Lo;
3937    --             Li1 := Index'pred (Li1);
3938    --             Ri1 := Index'pred (Ri1);
3939    --          else
3940    --             exit when Li1 = Left_Hi;
3941    --             Li1 := Index'succ (Li1);
3942    --             Ri1 := Index'succ (Ri1);
3943    --          end if;
3944    --       end loop;
3945    --    end Assign;
3946
3947    procedure Build_Slice_Assignment (Typ : Entity_Id) is
3948       Loc   : constant Source_Ptr := Sloc (Typ);
3949       Index : constant Entity_Id  := Base_Type (Etype (First_Index (Typ)));
3950
3951       Larray    : constant Entity_Id := Make_Temporary (Loc, 'A');
3952       Rarray    : constant Entity_Id := Make_Temporary (Loc, 'R');
3953       Left_Lo   : constant Entity_Id := Make_Temporary (Loc, 'L');
3954       Left_Hi   : constant Entity_Id := Make_Temporary (Loc, 'L');
3955       Right_Lo  : constant Entity_Id := Make_Temporary (Loc, 'R');
3956       Right_Hi  : constant Entity_Id := Make_Temporary (Loc, 'R');
3957       Rev       : constant Entity_Id := Make_Temporary (Loc, 'D');
3958       --  Formal parameters of procedure
3959
3960       Proc_Name : constant Entity_Id :=
3961                     Make_Defining_Identifier (Loc,
3962                       Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
3963
3964       Lnn : constant Entity_Id := Make_Temporary (Loc, 'L');
3965       Rnn : constant Entity_Id := Make_Temporary (Loc, 'R');
3966       --  Subscripts for left and right sides
3967
3968       Decls : List_Id;
3969       Loops : Node_Id;
3970       Stats : List_Id;
3971
3972    begin
3973       --  Build declarations for indexes
3974
3975       Decls := New_List;
3976
3977       Append_To (Decls,
3978          Make_Object_Declaration (Loc,
3979            Defining_Identifier => Lnn,
3980            Object_Definition  =>
3981              New_Occurrence_Of (Index, Loc)));
3982
3983       Append_To (Decls,
3984         Make_Object_Declaration (Loc,
3985           Defining_Identifier => Rnn,
3986           Object_Definition  =>
3987             New_Occurrence_Of (Index, Loc)));
3988
3989       Stats := New_List;
3990
3991       --  Build test for empty slice case
3992
3993       Append_To (Stats,
3994         Make_If_Statement (Loc,
3995           Condition =>
3996              Make_Op_Lt (Loc,
3997                Left_Opnd  => New_Occurrence_Of (Left_Hi, Loc),
3998                Right_Opnd => New_Occurrence_Of (Left_Lo, Loc)),
3999           Then_Statements => New_List (Make_Simple_Return_Statement (Loc))));
4000
4001       --  Build initializations for indexes
4002
4003       declare
4004          F_Init : constant List_Id := New_List;
4005          B_Init : constant List_Id := New_List;
4006
4007       begin
4008          Append_To (F_Init,
4009            Make_Assignment_Statement (Loc,
4010              Name => New_Occurrence_Of (Lnn, Loc),
4011              Expression => New_Occurrence_Of (Left_Lo, Loc)));
4012
4013          Append_To (F_Init,
4014            Make_Assignment_Statement (Loc,
4015              Name => New_Occurrence_Of (Rnn, Loc),
4016              Expression => New_Occurrence_Of (Right_Lo, Loc)));
4017
4018          Append_To (B_Init,
4019            Make_Assignment_Statement (Loc,
4020              Name => New_Occurrence_Of (Lnn, Loc),
4021              Expression => New_Occurrence_Of (Left_Hi, Loc)));
4022
4023          Append_To (B_Init,
4024            Make_Assignment_Statement (Loc,
4025              Name => New_Occurrence_Of (Rnn, Loc),
4026              Expression => New_Occurrence_Of (Right_Hi, Loc)));
4027
4028          Append_To (Stats,
4029            Make_If_Statement (Loc,
4030              Condition => New_Occurrence_Of (Rev, Loc),
4031              Then_Statements => B_Init,
4032              Else_Statements => F_Init));
4033       end;
4034
4035       --  Now construct the assignment statement
4036
4037       Loops :=
4038         Make_Loop_Statement (Loc,
4039           Statements => New_List (
4040             Make_Assignment_Statement (Loc,
4041               Name =>
4042                 Make_Indexed_Component (Loc,
4043                   Prefix => New_Occurrence_Of (Larray, Loc),
4044                   Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
4045               Expression =>
4046                 Make_Indexed_Component (Loc,
4047                   Prefix => New_Occurrence_Of (Rarray, Loc),
4048                   Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
4049           End_Label  => Empty);
4050
4051       --  Build the exit condition and increment/decrement statements
4052
4053       declare
4054          F_Ass : constant List_Id := New_List;
4055          B_Ass : constant List_Id := New_List;
4056
4057       begin
4058          Append_To (F_Ass,
4059            Make_Exit_Statement (Loc,
4060              Condition =>
4061                Make_Op_Eq (Loc,
4062                  Left_Opnd  => New_Occurrence_Of (Lnn, Loc),
4063                  Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
4064
4065          Append_To (F_Ass,
4066            Make_Assignment_Statement (Loc,
4067              Name => New_Occurrence_Of (Lnn, Loc),
4068              Expression =>
4069                Make_Attribute_Reference (Loc,
4070                  Prefix =>
4071                    New_Occurrence_Of (Index, Loc),
4072                  Attribute_Name => Name_Succ,
4073                  Expressions => New_List (
4074                    New_Occurrence_Of (Lnn, Loc)))));
4075
4076          Append_To (F_Ass,
4077            Make_Assignment_Statement (Loc,
4078              Name => New_Occurrence_Of (Rnn, Loc),
4079              Expression =>
4080                Make_Attribute_Reference (Loc,
4081                  Prefix =>
4082                    New_Occurrence_Of (Index, Loc),
4083                  Attribute_Name => Name_Succ,
4084                  Expressions => New_List (
4085                    New_Occurrence_Of (Rnn, Loc)))));
4086
4087          Append_To (B_Ass,
4088            Make_Exit_Statement (Loc,
4089              Condition =>
4090                Make_Op_Eq (Loc,
4091                  Left_Opnd  => New_Occurrence_Of (Lnn, Loc),
4092                  Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
4093
4094          Append_To (B_Ass,
4095            Make_Assignment_Statement (Loc,
4096              Name => New_Occurrence_Of (Lnn, Loc),
4097              Expression =>
4098                Make_Attribute_Reference (Loc,
4099                  Prefix =>
4100                    New_Occurrence_Of (Index, Loc),
4101                  Attribute_Name => Name_Pred,
4102                    Expressions => New_List (
4103                      New_Occurrence_Of (Lnn, Loc)))));
4104
4105          Append_To (B_Ass,
4106            Make_Assignment_Statement (Loc,
4107              Name => New_Occurrence_Of (Rnn, Loc),
4108              Expression =>
4109                Make_Attribute_Reference (Loc,
4110                  Prefix =>
4111                    New_Occurrence_Of (Index, Loc),
4112                  Attribute_Name => Name_Pred,
4113                  Expressions => New_List (
4114                    New_Occurrence_Of (Rnn, Loc)))));
4115
4116          Append_To (Statements (Loops),
4117            Make_If_Statement (Loc,
4118              Condition => New_Occurrence_Of (Rev, Loc),
4119              Then_Statements => B_Ass,
4120              Else_Statements => F_Ass));
4121       end;
4122
4123       Append_To (Stats, Loops);
4124
4125       declare
4126          Spec    : Node_Id;
4127          Formals : List_Id := New_List;
4128
4129       begin
4130          Formals := New_List (
4131            Make_Parameter_Specification (Loc,
4132              Defining_Identifier => Larray,
4133              Out_Present => True,
4134              Parameter_Type =>
4135                New_Occurrence_Of (Base_Type (Typ), Loc)),
4136
4137            Make_Parameter_Specification (Loc,
4138              Defining_Identifier => Rarray,
4139              Parameter_Type =>
4140                New_Occurrence_Of (Base_Type (Typ), Loc)),
4141
4142            Make_Parameter_Specification (Loc,
4143              Defining_Identifier => Left_Lo,
4144              Parameter_Type =>
4145                New_Occurrence_Of (Index, Loc)),
4146
4147            Make_Parameter_Specification (Loc,
4148              Defining_Identifier => Left_Hi,
4149              Parameter_Type =>
4150                New_Occurrence_Of (Index, Loc)),
4151
4152            Make_Parameter_Specification (Loc,
4153              Defining_Identifier => Right_Lo,
4154              Parameter_Type =>
4155                New_Occurrence_Of (Index, Loc)),
4156
4157            Make_Parameter_Specification (Loc,
4158              Defining_Identifier => Right_Hi,
4159              Parameter_Type =>
4160                New_Occurrence_Of (Index, Loc)));
4161
4162          Append_To (Formals,
4163            Make_Parameter_Specification (Loc,
4164              Defining_Identifier => Rev,
4165              Parameter_Type =>
4166                New_Occurrence_Of (Standard_Boolean, Loc)));
4167
4168          Spec :=
4169            Make_Procedure_Specification (Loc,
4170              Defining_Unit_Name       => Proc_Name,
4171              Parameter_Specifications => Formals);
4172
4173          Discard_Node (
4174            Make_Subprogram_Body (Loc,
4175              Specification              => Spec,
4176              Declarations               => Decls,
4177              Handled_Statement_Sequence =>
4178                Make_Handled_Sequence_Of_Statements (Loc,
4179                  Statements => Stats)));
4180       end;
4181
4182       Set_TSS (Typ, Proc_Name);
4183       Set_Is_Pure (Proc_Name);
4184    end Build_Slice_Assignment;
4185
4186    -----------------------------
4187    -- Build_Untagged_Equality --
4188    -----------------------------
4189
4190    procedure Build_Untagged_Equality (Typ : Entity_Id) is
4191       Build_Eq : Boolean;
4192       Comp     : Entity_Id;
4193       Decl     : Node_Id;
4194       Op       : Entity_Id;
4195       Prim     : Elmt_Id;
4196       Eq_Op    : Entity_Id;
4197
4198       function User_Defined_Eq (T : Entity_Id) return Entity_Id;
4199       --  Check whether the type T has a user-defined primitive equality. If so
4200       --  return it, else return Empty. If true for a component of Typ, we have
4201       --  to build the primitive equality for it.
4202
4203       ---------------------
4204       -- User_Defined_Eq --
4205       ---------------------
4206
4207       function User_Defined_Eq (T : Entity_Id) return Entity_Id is
4208          Prim : Elmt_Id;
4209          Op   : Entity_Id;
4210
4211       begin
4212          Op := TSS (T, TSS_Composite_Equality);
4213
4214          if Present (Op) then
4215             return Op;
4216          end if;
4217
4218          Prim := First_Elmt (Collect_Primitive_Operations (T));
4219          while Present (Prim) loop
4220             Op := Node (Prim);
4221
4222             if Chars (Op) = Name_Op_Eq
4223               and then Etype (Op) = Standard_Boolean
4224               and then Etype (First_Formal (Op)) = T
4225               and then Etype (Next_Formal (First_Formal (Op))) = T
4226             then
4227                return Op;
4228             end if;
4229
4230             Next_Elmt (Prim);
4231          end loop;
4232
4233          return Empty;
4234       end User_Defined_Eq;
4235
4236    --  Start of processing for Build_Untagged_Equality
4237
4238    begin
4239       --  If a record component has a primitive equality operation, we must
4240       --  build the corresponding one for the current type.
4241
4242       Build_Eq := False;
4243       Comp := First_Component (Typ);
4244       while Present (Comp) loop
4245          if Is_Record_Type (Etype (Comp))
4246            and then Present (User_Defined_Eq (Etype (Comp)))
4247          then
4248             Build_Eq := True;
4249          end if;
4250
4251          Next_Component (Comp);
4252       end loop;
4253
4254       --  If there is a user-defined equality for the type, we do not create
4255       --  the implicit one.
4256
4257       Prim := First_Elmt (Collect_Primitive_Operations (Typ));
4258       Eq_Op := Empty;
4259       while Present (Prim) loop
4260          if Chars (Node (Prim)) = Name_Op_Eq
4261            and then Comes_From_Source (Node (Prim))
4262
4263          --  Don't we also need to check formal types and return type as in
4264          --  User_Defined_Eq above???
4265
4266          then
4267             Eq_Op := Node (Prim);
4268             Build_Eq := False;
4269             exit;
4270          end if;
4271
4272          Next_Elmt (Prim);
4273       end loop;
4274
4275       --  If the type is derived, inherit the operation, if present, from the
4276       --  parent type. It may have been declared after the type derivation. If
4277       --  the parent type itself is derived, it may have inherited an operation
4278       --  that has itself been overridden, so update its alias and related
4279       --  flags. Ditto for inequality.
4280
4281       if No (Eq_Op) and then Is_Derived_Type (Typ) then
4282          Prim := First_Elmt (Collect_Primitive_Operations (Etype (Typ)));
4283          while Present (Prim) loop
4284             if Chars (Node (Prim)) = Name_Op_Eq then
4285                Copy_TSS (Node (Prim), Typ);
4286                Build_Eq := False;
4287
4288                declare
4289                   Op    : constant Entity_Id := User_Defined_Eq (Typ);
4290                   Eq_Op : constant Entity_Id := Node (Prim);
4291                   NE_Op : constant Entity_Id := Next_Entity (Eq_Op);
4292
4293                begin
4294                   if Present (Op) then
4295                      Set_Alias (Op, Eq_Op);
4296                      Set_Is_Abstract_Subprogram
4297                        (Op, Is_Abstract_Subprogram (Eq_Op));
4298
4299                      if Chars (Next_Entity (Op)) = Name_Op_Ne then
4300                         Set_Is_Abstract_Subprogram
4301                           (Next_Entity (Op), Is_Abstract_Subprogram (NE_Op));
4302                      end if;
4303                   end if;
4304                end;
4305
4306                exit;
4307             end if;
4308
4309             Next_Elmt (Prim);
4310          end loop;
4311       end if;
4312
4313       --  If not inherited and not user-defined, build body as for a type with
4314       --  tagged components.
4315
4316       if Build_Eq then
4317          Decl :=
4318            Make_Eq_Body (Typ, Make_TSS_Name (Typ, TSS_Composite_Equality));
4319          Op := Defining_Entity (Decl);
4320          Set_TSS (Typ, Op);
4321          Set_Is_Pure (Op);
4322
4323          if Is_Library_Level_Entity (Typ) then
4324             Set_Is_Public (Op);
4325          end if;
4326       end if;
4327    end Build_Untagged_Equality;
4328
4329    -----------------------------------
4330    -- Build_Variant_Record_Equality --
4331    -----------------------------------
4332
4333    --  Generates:
4334
4335    --    function _Equality (X, Y : T) return Boolean is
4336    --    begin
4337    --       --  Compare discriminants
4338
4339    --       if X.D1 /= Y.D1 or else X.D2 /= Y.D2 or else ... then
4340    --          return False;
4341    --       end if;
4342
4343    --       --  Compare components
4344
4345    --       if X.C1 /= Y.C1 or else X.C2 /= Y.C2 or else ... then
4346    --          return False;
4347    --       end if;
4348
4349    --       --  Compare variant part
4350
4351    --       case X.D1 is
4352    --          when V1 =>
4353    --             if X.C2 /= Y.C2 or else X.C3 /= Y.C3 or else ... then
4354    --                return False;
4355    --             end if;
4356    --          ...
4357    --          when Vn =>
4358    --             if X.Cn /= Y.Cn or else ... then
4359    --                return False;
4360    --             end if;
4361    --       end case;
4362
4363    --       return True;
4364    --    end _Equality;
4365
4366    procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
4367       Loc : constant Source_Ptr := Sloc (Typ);
4368
4369       F : constant Entity_Id :=
4370             Make_Defining_Identifier (Loc,
4371               Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
4372
4373       X : constant Entity_Id := Make_Defining_Identifier (Loc, Name_X);
4374       Y : constant Entity_Id := Make_Defining_Identifier (Loc, Name_Y);
4375
4376       Def    : constant Node_Id := Parent (Typ);
4377       Comps  : constant Node_Id := Component_List (Type_Definition (Def));
4378       Stmts  : constant List_Id := New_List;
4379       Pspecs : constant List_Id := New_List;
4380
4381    begin
4382       --  If we have a variant record with restriction No_Implicit_Conditionals
4383       --  in effect, then we skip building the procedure. This is safe because
4384       --  if we can see the restriction, so can any caller, calls to equality
4385       --  test routines are not allowed for variant records if this restriction
4386       --  is active.
4387
4388       if Restriction_Active (No_Implicit_Conditionals) then
4389          return;
4390       end if;
4391
4392       --  Derived Unchecked_Union types no longer inherit the equality function
4393       --  of their parent.
4394
4395       if Is_Derived_Type (Typ)
4396         and then not Is_Unchecked_Union (Typ)
4397         and then not Has_New_Non_Standard_Rep (Typ)
4398       then
4399          declare
4400             Parent_Eq : constant Entity_Id :=
4401                           TSS (Root_Type (Typ), TSS_Composite_Equality);
4402          begin
4403             if Present (Parent_Eq) then
4404                Copy_TSS (Parent_Eq, Typ);
4405                return;
4406             end if;
4407          end;
4408       end if;
4409
4410       Discard_Node (
4411         Make_Subprogram_Body (Loc,
4412           Specification =>
4413             Make_Function_Specification (Loc,
4414               Defining_Unit_Name       => F,
4415               Parameter_Specifications => Pspecs,
4416               Result_Definition => New_Occurrence_Of (Standard_Boolean, Loc)),
4417           Declarations               => New_List,
4418           Handled_Statement_Sequence =>
4419             Make_Handled_Sequence_Of_Statements (Loc, Statements => Stmts)));
4420
4421       Append_To (Pspecs,
4422         Make_Parameter_Specification (Loc,
4423           Defining_Identifier => X,
4424           Parameter_Type      => New_Occurrence_Of (Typ, Loc)));
4425
4426       Append_To (Pspecs,
4427         Make_Parameter_Specification (Loc,
4428           Defining_Identifier => Y,
4429           Parameter_Type      => New_Occurrence_Of (Typ, Loc)));
4430
4431       --  Unchecked_Unions require additional machinery to support equality.
4432       --  Two extra parameters (A and B) are added to the equality function
4433       --  parameter list for each discriminant of the type, in order to
4434       --  capture the inferred values of the discriminants in equality calls.
4435       --  The names of the parameters match the names of the corresponding
4436       --  discriminant, with an added suffix.
4437
4438       if Is_Unchecked_Union (Typ) then
4439          declare
4440             Discr      : Entity_Id;
4441             Discr_Type : Entity_Id;
4442             A, B       : Entity_Id;
4443             New_Discrs : Elist_Id;
4444
4445          begin
4446             New_Discrs := New_Elmt_List;
4447
4448             Discr := First_Discriminant (Typ);
4449             while Present (Discr) loop
4450                Discr_Type := Etype (Discr);
4451                A := Make_Defining_Identifier (Loc,
4452                       Chars => New_External_Name (Chars (Discr), 'A'));
4453
4454                B := Make_Defining_Identifier (Loc,
4455                       Chars => New_External_Name (Chars (Discr), 'B'));
4456
4457                --  Add new parameters to the parameter list
4458
4459                Append_To (Pspecs,
4460                  Make_Parameter_Specification (Loc,
4461                    Defining_Identifier => A,
4462                    Parameter_Type      =>
4463                      New_Occurrence_Of (Discr_Type, Loc)));
4464
4465                Append_To (Pspecs,
4466                  Make_Parameter_Specification (Loc,
4467                    Defining_Identifier => B,
4468                    Parameter_Type      =>
4469                      New_Occurrence_Of (Discr_Type, Loc)));
4470
4471                Append_Elmt (A, New_Discrs);
4472
4473                --  Generate the following code to compare each of the inferred
4474                --  discriminants:
4475
4476                --  if a /= b then
4477                --     return False;
4478                --  end if;
4479
4480                Append_To (Stmts,
4481                  Make_If_Statement (Loc,
4482                    Condition       =>
4483                      Make_Op_Ne (Loc,
4484                        Left_Opnd  => New_Occurrence_Of (A, Loc),
4485                        Right_Opnd => New_Occurrence_Of (B, Loc)),
4486                    Then_Statements => New_List (
4487                      Make_Simple_Return_Statement (Loc,
4488                        Expression =>
4489                          New_Occurrence_Of (Standard_False, Loc)))));
4490                Next_Discriminant (Discr);
4491             end loop;
4492
4493             --  Generate component-by-component comparison. Note that we must
4494             --  propagate the inferred discriminants formals to act as
4495             --  the case statement switch. Their value is added when an
4496             --  equality call on unchecked unions is expanded.
4497
4498             Append_List_To (Stmts, Make_Eq_Case (Typ, Comps, New_Discrs));
4499          end;
4500
4501       --  Normal case (not unchecked union)
4502
4503       else
4504          Append_To (Stmts,
4505            Make_Eq_If (Typ, Discriminant_Specifications (Def)));
4506          Append_List_To (Stmts, Make_Eq_Case (Typ, Comps));
4507       end if;
4508
4509       Append_To (Stmts,
4510         Make_Simple_Return_Statement (Loc,
4511           Expression => New_Occurrence_Of (Standard_True, Loc)));
4512
4513       Set_TSS (Typ, F);
4514       Set_Is_Pure (F);
4515
4516       if not Debug_Generated_Code then
4517          Set_Debug_Info_Off (F);
4518       end if;
4519    end Build_Variant_Record_Equality;
4520
4521    -----------------------------
4522    -- Check_Stream_Attributes --
4523    -----------------------------
4524
4525    procedure Check_Stream_Attributes (Typ : Entity_Id) is
4526       Comp      : Entity_Id;
4527       Par_Read  : constant Boolean :=
4528                     Stream_Attribute_Available (Typ, TSS_Stream_Read)
4529                       and then not Has_Specified_Stream_Read (Typ);
4530       Par_Write : constant Boolean :=
4531                     Stream_Attribute_Available (Typ, TSS_Stream_Write)
4532                       and then not Has_Specified_Stream_Write (Typ);
4533
4534       procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type);
4535       --  Check that Comp has a user-specified Nam stream attribute
4536
4537       ----------------
4538       -- Check_Attr --
4539       ----------------
4540
4541       procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type) is
4542       begin
4543          if not Stream_Attribute_Available (Etype (Comp), TSS_Nam) then
4544             Error_Msg_Name_1 := Nam;
4545             Error_Msg_N
4546               ("|component& in limited extension must have% attribute", Comp);
4547          end if;
4548       end Check_Attr;
4549
4550    --  Start of processing for Check_Stream_Attributes
4551
4552    begin
4553       if Par_Read or else Par_Write then
4554          Comp := First_Component (Typ);
4555          while Present (Comp) loop
4556             if Comes_From_Source (Comp)
4557               and then Original_Record_Component (Comp) = Comp
4558               and then Is_Limited_Type (Etype (Comp))
4559             then
4560                if Par_Read then
4561                   Check_Attr (Name_Read, TSS_Stream_Read);
4562                end if;
4563
4564                if Par_Write then
4565                   Check_Attr (Name_Write, TSS_Stream_Write);
4566                end if;
4567             end if;
4568
4569             Next_Component (Comp);
4570          end loop;
4571       end if;
4572    end Check_Stream_Attributes;
4573
4574    ----------------------
4575    -- Clean_Task_Names --
4576    ----------------------
4577
4578    procedure Clean_Task_Names
4579      (Typ     : Entity_Id;
4580       Proc_Id : Entity_Id)
4581    is
4582    begin
4583       if Has_Task (Typ)
4584         and then not Restriction_Active (No_Implicit_Heap_Allocations)
4585         and then not Global_Discard_Names
4586         and then Tagged_Type_Expansion
4587       then
4588          Set_Uses_Sec_Stack (Proc_Id);
4589       end if;
4590    end Clean_Task_Names;
4591
4592    ------------------------------
4593    -- Expand_Freeze_Array_Type --
4594    ------------------------------
4595
4596    procedure Expand_Freeze_Array_Type (N : Node_Id) is
4597       Typ      : constant Entity_Id := Entity (N);
4598       Base     : constant Entity_Id := Base_Type (Typ);
4599       Comp_Typ : constant Entity_Id := Component_Type (Typ);
4600
4601       Save_Ghost_Mode : constant Ghost_Mode_Type := Ghost_Mode;
4602
4603    begin
4604       --  Ensure that all freezing activities are properly flagged as Ghost
4605
4606       Set_Ghost_Mode_From_Entity (Typ);
4607
4608       if not Is_Bit_Packed_Array (Typ) then
4609
4610          --  If the component contains tasks, so does the array type. This may
4611          --  not be indicated in the array type because the component may have
4612          --  been a private type at the point of definition. Same if component
4613          --  type is controlled or contains protected objects.
4614
4615          Set_Has_Task       (Base, Has_Task      (Comp_Typ));
4616          Set_Has_Protected  (Base, Has_Protected (Comp_Typ));
4617          Set_Has_Controlled_Component
4618                             (Base, Has_Controlled_Component
4619                                                  (Comp_Typ)
4620                                      or else
4621                                    Is_Controlled (Comp_Typ));
4622
4623          if No (Init_Proc (Base)) then
4624
4625             --  If this is an anonymous array created for a declaration with
4626             --  an initial value, its init_proc will never be called. The
4627             --  initial value itself may have been expanded into assignments,
4628             --  in which case the object declaration is carries the
4629             --  No_Initialization flag.
4630
4631             if Is_Itype (Base)
4632               and then Nkind (Associated_Node_For_Itype (Base)) =
4633                                                     N_Object_Declaration
4634               and then
4635                 (Present (Expression (Associated_Node_For_Itype (Base)))
4636                   or else No_Initialization (Associated_Node_For_Itype (Base)))
4637             then
4638                null;
4639
4640             --  We do not need an init proc for string or wide [wide] string,
4641             --  since the only time these need initialization in normalize or
4642             --  initialize scalars mode, and these types are treated specially
4643             --  and do not need initialization procedures.
4644
4645             elsif Is_Standard_String_Type (Base) then
4646                null;
4647
4648             --  Otherwise we have to build an init proc for the subtype
4649
4650             else
4651                Build_Array_Init_Proc (Base, N);
4652             end if;
4653          end if;
4654
4655          if Typ = Base and then Has_Controlled_Component (Base) then
4656             Build_Controlling_Procs (Base);
4657
4658             if not Is_Limited_Type (Comp_Typ)
4659               and then Number_Dimensions (Typ) = 1
4660             then
4661                Build_Slice_Assignment (Typ);
4662             end if;
4663          end if;
4664
4665       --  For packed case, default initialization, except if the component type
4666       --  is itself a packed structure with an initialization procedure, or
4667       --  initialize/normalize scalars active, and we have a base type, or the
4668       --  type is public, because in that case a client might specify
4669       --  Normalize_Scalars and there better be a public Init_Proc for it.
4670
4671       elsif (Present (Init_Proc (Component_Type (Base)))
4672               and then No (Base_Init_Proc (Base)))
4673         or else (Init_Or_Norm_Scalars and then Base = Typ)
4674         or else Is_Public (Typ)
4675       then
4676          Build_Array_Init_Proc (Base, N);
4677       end if;
4678
4679       if Has_Invariants (Component_Type (Base))
4680         and then Typ = Base
4681         and then In_Open_Scopes (Scope (Component_Type (Base)))
4682       then
4683          --  Generate component invariant checking procedure. This is only
4684          --  relevant if the array type is within the scope of the component
4685          --  type. Otherwise an array object can only be built using the public
4686          --  subprograms for the component type, and calls to those will have
4687          --  invariant checks. The invariant procedure is only generated for
4688          --  a base type, not a subtype.
4689
4690          Insert_Component_Invariant_Checks
4691            (N, Base, Build_Array_Invariant_Proc (Base, N));
4692       end if;
4693
4694       Ghost_Mode := Save_Ghost_Mode;
4695    end Expand_Freeze_Array_Type;
4696
4697    -----------------------------------
4698    -- Expand_Freeze_Class_Wide_Type --
4699    -----------------------------------
4700
4701    procedure Expand_Freeze_Class_Wide_Type (N : Node_Id) is
4702       function Is_C_Derivation (Typ : Entity_Id) return Boolean;
4703       --  Given a type, determine whether it is derived from a C or C++ root
4704
4705       ---------------------
4706       -- Is_C_Derivation --
4707       ---------------------
4708
4709       function Is_C_Derivation (Typ : Entity_Id) return Boolean is
4710          T : Entity_Id;
4711
4712       begin
4713          T := Typ;
4714          loop
4715             if Is_CPP_Class (T)
4716               or else Convention (T) = Convention_C
4717               or else Convention (T) = Convention_CPP
4718             then
4719                return True;
4720             end if;
4721
4722             exit when T = Etype (T);
4723
4724             T := Etype (T);
4725          end loop;
4726
4727          return False;
4728       end Is_C_Derivation;
4729
4730       --  Local variables
4731
4732       Typ  : constant Entity_Id := Entity (N);
4733       Root : constant Entity_Id := Root_Type (Typ);
4734
4735       Save_Ghost_Mode : constant Ghost_Mode_Type := Ghost_Mode;
4736
4737    --  Start of processing for Expand_Freeze_Class_Wide_Type
4738
4739    begin
4740       --  Certain run-time configurations and targets do not provide support
4741       --  for controlled types.
4742
4743       if Restriction_Active (No_Finalization) then
4744          return;
4745
4746       --  Do not create TSS routine Finalize_Address when dispatching calls are
4747       --  disabled since the core of the routine is a dispatching call.
4748
4749       elsif Restriction_Active (No_Dispatching_Calls) then
4750          return;
4751
4752       --  Do not create TSS routine Finalize_Address for concurrent class-wide
4753       --  types. Ignore C, C++, CIL and Java types since it is assumed that the
4754       --  non-Ada side will handle their destruction.
4755
4756       elsif Is_Concurrent_Type (Root)
4757         or else Is_C_Derivation (Root)
4758         or else Convention (Typ) = Convention_CPP
4759       then
4760          return;
4761
4762       --  Do not create TSS routine Finalize_Address when compiling in CodePeer
4763       --  mode since the routine contains an Unchecked_Conversion.
4764
4765       elsif CodePeer_Mode then
4766          return;
4767       end if;
4768
4769       --  Ensure that all freezing activities are properly flagged as Ghost
4770
4771       Set_Ghost_Mode_From_Entity (Typ);
4772
4773       --  Create the body of TSS primitive Finalize_Address. This automatically
4774       --  sets the TSS entry for the class-wide type.
4775
4776       Make_Finalize_Address_Body (Typ);
4777       Ghost_Mode := Save_Ghost_Mode;
4778    end Expand_Freeze_Class_Wide_Type;
4779
4780    ------------------------------------
4781    -- Expand_Freeze_Enumeration_Type --
4782    ------------------------------------
4783
4784    procedure Expand_Freeze_Enumeration_Type (N : Node_Id) is
4785       Typ : constant Entity_Id  := Entity (N);
4786       Loc : constant Source_Ptr := Sloc (Typ);
4787
4788       Save_Ghost_Mode : constant Ghost_Mode_Type := Ghost_Mode;
4789
4790       Arr           : Entity_Id;
4791       Ent           : Entity_Id;
4792       Fent          : Entity_Id;
4793       Is_Contiguous : Boolean;
4794       Ityp          : Entity_Id;
4795       Last_Repval   : Uint;
4796       Lst           : List_Id;
4797       Num           : Nat;
4798       Pos_Expr      : Node_Id;
4799
4800       Func : Entity_Id;
4801       pragma Warnings (Off, Func);
4802
4803    begin
4804       --  Ensure that all freezing activities are properly flagged as Ghost
4805
4806       Set_Ghost_Mode_From_Entity (Typ);
4807
4808       --  Various optimizations possible if given representation is contiguous
4809
4810       Is_Contiguous := True;
4811
4812       Ent := First_Literal (Typ);
4813       Last_Repval := Enumeration_Rep (Ent);
4814
4815       Next_Literal (Ent);
4816       while Present (Ent) loop
4817          if Enumeration_Rep (Ent) - Last_Repval /= 1 then
4818             Is_Contiguous := False;
4819             exit;
4820          else
4821             Last_Repval := Enumeration_Rep (Ent);
4822          end if;
4823
4824          Next_Literal (Ent);
4825       end loop;
4826
4827       if Is_Contiguous then
4828          Set_Has_Contiguous_Rep (Typ);
4829          Ent := First_Literal (Typ);
4830          Num := 1;
4831          Lst := New_List (New_Occurrence_Of (Ent, Sloc (Ent)));
4832
4833       else
4834          --  Build list of literal references
4835
4836          Lst := New_List;
4837          Num := 0;
4838
4839          Ent := First_Literal (Typ);
4840          while Present (Ent) loop
4841             Append_To (Lst, New_Occurrence_Of (Ent, Sloc (Ent)));
4842             Num := Num + 1;
4843             Next_Literal (Ent);
4844          end loop;
4845       end if;
4846
4847       --  Now build an array declaration
4848
4849       --    typA : array (Natural range 0 .. num - 1) of ctype :=
4850       --             (v, v, v, v, v, ....)
4851
4852       --  where ctype is the corresponding integer type. If the representation
4853       --  is contiguous, we only keep the first literal, which provides the
4854       --  offset for Pos_To_Rep computations.
4855
4856       Arr :=
4857         Make_Defining_Identifier (Loc,
4858           Chars => New_External_Name (Chars (Typ), 'A'));
4859
4860       Append_Freeze_Action (Typ,
4861         Make_Object_Declaration (Loc,
4862           Defining_Identifier => Arr,
4863           Constant_Present    => True,
4864
4865           Object_Definition   =>
4866             Make_Constrained_Array_Definition (Loc,
4867               Discrete_Subtype_Definitions => New_List (
4868                 Make_Subtype_Indication (Loc,
4869                   Subtype_Mark => New_Occurrence_Of (Standard_Natural, Loc),
4870                   Constraint =>
4871                     Make_Range_Constraint (Loc,
4872                       Range_Expression =>
4873                         Make_Range (Loc,
4874                           Low_Bound  =>
4875                             Make_Integer_Literal (Loc, 0),
4876                           High_Bound =>
4877                             Make_Integer_Literal (Loc, Num - 1))))),
4878
4879               Component_Definition =>
4880                 Make_Component_Definition (Loc,
4881                   Aliased_Present => False,
4882                   Subtype_Indication => New_Occurrence_Of (Typ, Loc))),
4883
4884           Expression =>
4885             Make_Aggregate (Loc,
4886               Expressions => Lst)));
4887
4888       Set_Enum_Pos_To_Rep (Typ, Arr);
4889
4890       --  Now we build the function that converts representation values to
4891       --  position values. This function has the form:
4892
4893       --    function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
4894       --    begin
4895       --       case ityp!(A) is
4896       --         when enum-lit'Enum_Rep => return posval;
4897       --         when enum-lit'Enum_Rep => return posval;
4898       --         ...
4899       --         when others   =>
4900       --           [raise Constraint_Error when F "invalid data"]
4901       --           return -1;
4902       --       end case;
4903       --    end;
4904
4905       --  Note: the F parameter determines whether the others case (no valid
4906       --  representation) raises Constraint_Error or returns a unique value
4907       --  of minus one. The latter case is used, e.g. in 'Valid code.
4908
4909       --  Note: the reason we use Enum_Rep values in the case here is to avoid
4910       --  the code generator making inappropriate assumptions about the range
4911       --  of the values in the case where the value is invalid. ityp is a
4912       --  signed or unsigned integer type of appropriate width.
4913
4914       --  Note: if exceptions are not supported, then we suppress the raise
4915       --  and return -1 unconditionally (this is an erroneous program in any
4916       --  case and there is no obligation to raise Constraint_Error here). We
4917       --  also do this if pragma Restrictions (No_Exceptions) is active.
4918
4919       --  Is this right??? What about No_Exception_Propagation???
4920
4921       --  Representations are signed
4922
4923       if Enumeration_Rep (First_Literal (Typ)) < 0 then
4924
4925          --  The underlying type is signed. Reset the Is_Unsigned_Type
4926          --  explicitly, because it might have been inherited from
4927          --  parent type.
4928
4929          Set_Is_Unsigned_Type (Typ, False);
4930
4931          if Esize (Typ) <= Standard_Integer_Size then
4932             Ityp := Standard_Integer;
4933          else
4934             Ityp := Universal_Integer;
4935          end if;
4936
4937       --  Representations are unsigned
4938
4939       else
4940          if Esize (Typ) <= Standard_Integer_Size then
4941             Ityp := RTE (RE_Unsigned);
4942          else
4943             Ityp := RTE (RE_Long_Long_Unsigned);
4944          end if;
4945       end if;
4946
4947       --  The body of the function is a case statement. First collect case
4948       --  alternatives, or optimize the contiguous case.
4949
4950       Lst := New_List;
4951
4952       --  If representation is contiguous, Pos is computed by subtracting
4953       --  the representation of the first literal.
4954
4955       if Is_Contiguous then
4956          Ent := First_Literal (Typ);
4957
4958          if Enumeration_Rep (Ent) = Last_Repval then
4959
4960             --  Another special case: for a single literal, Pos is zero
4961
4962             Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
4963
4964          else
4965             Pos_Expr :=
4966               Convert_To (Standard_Integer,
4967                 Make_Op_Subtract (Loc,
4968                   Left_Opnd  =>
4969                     Unchecked_Convert_To
4970                      (Ityp, Make_Identifier (Loc, Name_uA)),
4971                   Right_Opnd =>
4972                     Make_Integer_Literal (Loc,
4973                       Intval => Enumeration_Rep (First_Literal (Typ)))));
4974          end if;
4975
4976          Append_To (Lst,
4977            Make_Case_Statement_Alternative (Loc,
4978              Discrete_Choices => New_List (
4979                Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
4980                  Low_Bound =>
4981                    Make_Integer_Literal (Loc,
4982                     Intval =>  Enumeration_Rep (Ent)),
4983                  High_Bound =>
4984                    Make_Integer_Literal (Loc, Intval => Last_Repval))),
4985
4986              Statements => New_List (
4987                Make_Simple_Return_Statement (Loc,
4988                  Expression => Pos_Expr))));
4989
4990       else
4991          Ent := First_Literal (Typ);
4992          while Present (Ent) loop
4993             Append_To (Lst,
4994               Make_Case_Statement_Alternative (Loc,
4995                 Discrete_Choices => New_List (
4996                   Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
4997                     Intval => Enumeration_Rep (Ent))),
4998
4999                 Statements => New_List (
5000                   Make_Simple_Return_Statement (Loc,
5001                     Expression =>
5002                       Make_Integer_Literal (Loc,
5003                         Intval => Enumeration_Pos (Ent))))));
5004
5005             Next_Literal (Ent);
5006          end loop;
5007       end if;
5008
5009       --  In normal mode, add the others clause with the test.
5010       --  If Predicates_Ignored is True, validity checks do not apply to
5011       --  the subtype.
5012
5013       if not No_Exception_Handlers_Set
5014         and then not Predicates_Ignored (Typ)
5015       then
5016          Append_To (Lst,
5017            Make_Case_Statement_Alternative (Loc,
5018              Discrete_Choices => New_List (Make_Others_Choice (Loc)),
5019              Statements       => New_List (
5020                Make_Raise_Constraint_Error (Loc,
5021                  Condition => Make_Identifier (Loc, Name_uF),
5022                  Reason    => CE_Invalid_Data),
5023                Make_Simple_Return_Statement (Loc,
5024                  Expression => Make_Integer_Literal (Loc, -1)))));
5025
5026       --  If either of the restrictions No_Exceptions_Handlers/Propagation is
5027       --  active then return -1 (we cannot usefully raise Constraint_Error in
5028       --  this case). See description above for further details.
5029
5030       else
5031          Append_To (Lst,
5032            Make_Case_Statement_Alternative (Loc,
5033              Discrete_Choices => New_List (Make_Others_Choice (Loc)),
5034              Statements       => New_List (
5035                Make_Simple_Return_Statement (Loc,
5036                  Expression => Make_Integer_Literal (Loc, -1)))));
5037       end if;
5038
5039       --  Now we can build the function body
5040
5041       Fent :=
5042         Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
5043
5044       Func :=
5045         Make_Subprogram_Body (Loc,
5046           Specification =>
5047             Make_Function_Specification (Loc,
5048               Defining_Unit_Name       => Fent,
5049               Parameter_Specifications => New_List (
5050                 Make_Parameter_Specification (Loc,
5051                   Defining_Identifier =>
5052                     Make_Defining_Identifier (Loc, Name_uA),
5053                   Parameter_Type => New_Occurrence_Of (Typ, Loc)),
5054                 Make_Parameter_Specification (Loc,
5055                   Defining_Identifier =>
5056                     Make_Defining_Identifier (Loc, Name_uF),
5057                   Parameter_Type =>
5058                     New_Occurrence_Of (Standard_Boolean, Loc))),
5059
5060               Result_Definition => New_Occurrence_Of (Standard_Integer, Loc)),
5061
5062             Declarations => Empty_List,
5063
5064             Handled_Statement_Sequence =>
5065               Make_Handled_Sequence_Of_Statements (Loc,
5066                 Statements => New_List (
5067                   Make_Case_Statement (Loc,
5068                     Expression =>
5069                       Unchecked_Convert_To
5070                         (Ityp, Make_Identifier (Loc, Name_uA)),
5071                     Alternatives => Lst))));
5072
5073       Set_TSS (Typ, Fent);
5074
5075       --  Set Pure flag (it will be reset if the current context is not Pure).
5076       --  We also pretend there was a pragma Pure_Function so that for purposes
5077       --  of optimization and constant-folding, we will consider the function
5078       --  Pure even if we are not in a Pure context).
5079
5080       Set_Is_Pure (Fent);
5081       Set_Has_Pragma_Pure_Function (Fent);
5082
5083       --  Unless we are in -gnatD mode, where we are debugging generated code,
5084       --  this is an internal entity for which we don't need debug info.
5085
5086       if not Debug_Generated_Code then
5087          Set_Debug_Info_Off (Fent);
5088       end if;
5089
5090       Ghost_Mode := Save_Ghost_Mode;
5091
5092    exception
5093       when RE_Not_Available =>
5094          Ghost_Mode := Save_Ghost_Mode;
5095          return;
5096    end Expand_Freeze_Enumeration_Type;
5097
5098    -------------------------------
5099    -- Expand_Freeze_Record_Type --
5100    -------------------------------
5101
5102    procedure Expand_Freeze_Record_Type (N : Node_Id) is
5103       Typ      : constant Node_Id := Entity (N);
5104       Typ_Decl : constant Node_Id := Parent (Typ);
5105
5106       Save_Ghost_Mode : constant Ghost_Mode_Type := Ghost_Mode;
5107
5108       Comp        : Entity_Id;
5109       Comp_Typ    : Entity_Id;
5110       Predef_List : List_Id;
5111
5112       Wrapper_Decl_List : List_Id := No_List;
5113       Wrapper_Body_List : List_Id := No_List;
5114
5115       Renamed_Eq : Node_Id := Empty;
5116       --  Defining unit name for the predefined equality function in the case
5117       --  where the type has a primitive operation that is a renaming of
5118       --  predefined equality (but only if there is also an overriding
5119       --  user-defined equality function). Used to pass this entity from
5120       --  Make_Predefined_Primitive_Specs to Predefined_Primitive_Bodies.
5121
5122    --  Start of processing for Expand_Freeze_Record_Type
5123
5124    begin
5125       --  Ensure that all freezing activities are properly flagged as Ghost
5126
5127       Set_Ghost_Mode_From_Entity (Typ);
5128
5129       --  Build discriminant checking functions if not a derived type (for
5130       --  derived types that are not tagged types, always use the discriminant
5131       --  checking functions of the parent type). However, for untagged types
5132       --  the derivation may have taken place before the parent was frozen, so
5133       --  we copy explicitly the discriminant checking functions from the
5134       --  parent into the components of the derived type.
5135
5136       if not Is_Derived_Type (Typ)
5137         or else Has_New_Non_Standard_Rep (Typ)
5138         or else Is_Tagged_Type (Typ)
5139       then
5140          Build_Discr_Checking_Funcs (Typ_Decl);
5141
5142       elsif Is_Derived_Type (Typ)
5143         and then not Is_Tagged_Type (Typ)
5144
5145         --  If we have a derived Unchecked_Union, we do not inherit the
5146         --  discriminant checking functions from the parent type since the
5147         --  discriminants are non existent.
5148
5149         and then not Is_Unchecked_Union (Typ)
5150         and then Has_Discriminants (Typ)
5151       then
5152          declare
5153             Old_Comp : Entity_Id;
5154
5155          begin
5156             Old_Comp :=
5157               First_Component (Base_Type (Underlying_Type (Etype (Typ))));
5158             Comp := First_Component (Typ);
5159             while Present (Comp) loop
5160                if Ekind (Comp) = E_Component
5161                  and then Chars (Comp) = Chars (Old_Comp)
5162                then
5163                   Set_Discriminant_Checking_Func
5164                     (Comp, Discriminant_Checking_Func (Old_Comp));
5165                end if;
5166
5167                Next_Component (Old_Comp);
5168                Next_Component (Comp);
5169             end loop;
5170          end;
5171       end if;
5172
5173       if Is_Derived_Type (Typ)
5174         and then Is_Limited_Type (Typ)
5175         and then Is_Tagged_Type (Typ)
5176       then
5177          Check_Stream_Attributes (Typ);
5178       end if;
5179
5180       --  Update task, protected, and controlled component flags, because some
5181       --  of the component types may have been private at the point of the
5182       --  record declaration. Detect anonymous access-to-controlled components.
5183
5184       Comp := First_Component (Typ);
5185       while Present (Comp) loop
5186          Comp_Typ := Etype (Comp);
5187
5188          if Has_Task (Comp_Typ) then
5189             Set_Has_Task (Typ);
5190          end if;
5191
5192          if Has_Protected (Comp_Typ) then
5193             Set_Has_Protected (Typ);
5194          end if;
5195
5196          --  Do not set Has_Controlled_Component on a class-wide equivalent
5197          --  type. See Make_CW_Equivalent_Type.
5198
5199          if not Is_Class_Wide_Equivalent_Type (Typ)
5200            and then
5201              (Has_Controlled_Component (Comp_Typ)
5202                or else (Chars (Comp) /= Name_uParent
5203                          and then (Is_Controlled_Active (Comp_Typ))))
5204          then
5205             Set_Has_Controlled_Component (Typ);
5206          end if;
5207
5208          Next_Component (Comp);
5209       end loop;
5210
5211       --  Handle constructors of untagged CPP_Class types
5212
5213       if not Is_Tagged_Type (Typ) and then Is_CPP_Class (Typ) then
5214          Set_CPP_Constructors (Typ);
5215       end if;
5216
5217       --  Creation of the Dispatch Table. Note that a Dispatch Table is built
5218       --  for regular tagged types as well as for Ada types deriving from a C++
5219       --  Class, but not for tagged types directly corresponding to C++ classes
5220       --  In the later case we assume that it is created in the C++ side and we
5221       --  just use it.
5222
5223       if Is_Tagged_Type (Typ) then
5224
5225          --  Add the _Tag component
5226
5227          if Underlying_Type (Etype (Typ)) = Typ then
5228             Expand_Tagged_Root (Typ);
5229          end if;
5230
5231          if Is_CPP_Class (Typ) then
5232             Set_All_DT_Position (Typ);
5233
5234             --  Create the tag entities with a minimum decoration
5235
5236             if Tagged_Type_Expansion then
5237                Append_Freeze_Actions (Typ, Make_Tags (Typ));
5238             end if;
5239
5240             Set_CPP_Constructors (Typ);
5241
5242          else
5243             if not Building_Static_DT (Typ) then
5244
5245                --  Usually inherited primitives are not delayed but the first
5246                --  Ada extension of a CPP_Class is an exception since the
5247                --  address of the inherited subprogram has to be inserted in
5248                --  the new Ada Dispatch Table and this is a freezing action.
5249
5250                --  Similarly, if this is an inherited operation whose parent is
5251                --  not frozen yet, it is not in the DT of the parent, and we
5252                --  generate an explicit freeze node for the inherited operation
5253                --  so it is properly inserted in the DT of the current type.
5254
5255                declare
5256                   Elmt : Elmt_Id;
5257                   Subp : Entity_Id;
5258
5259                begin
5260                   Elmt := First_Elmt (Primitive_Operations (Typ));
5261                   while Present (Elmt) loop
5262                      Subp := Node (Elmt);
5263
5264                      if Present (Alias (Subp)) then
5265                         if Is_CPP_Class (Etype (Typ)) then
5266                            Set_Has_Delayed_Freeze (Subp);
5267
5268                         elsif Has_Delayed_Freeze (Alias (Subp))
5269                           and then not Is_Frozen (Alias (Subp))
5270                         then
5271                            Set_Is_Frozen (Subp, False);
5272                            Set_Has_Delayed_Freeze (Subp);
5273                         end if;
5274                      end if;
5275
5276                      Next_Elmt (Elmt);
5277                   end loop;
5278                end;
5279             end if;
5280
5281             --  Unfreeze momentarily the type to add the predefined primitives
5282             --  operations. The reason we unfreeze is so that these predefined
5283             --  operations will indeed end up as primitive operations (which
5284             --  must be before the freeze point).
5285
5286             Set_Is_Frozen (Typ, False);
5287
5288             --  Do not add the spec of predefined primitives in case of
5289             --  CPP tagged type derivations that have convention CPP.
5290
5291             if Is_CPP_Class (Root_Type (Typ))
5292               and then Convention (Typ) = Convention_CPP
5293             then
5294                null;
5295
5296             --  Do not add the spec of the predefined primitives if we are
5297             --  compiling under restriction No_Dispatching_Calls.
5298
5299             elsif not Restriction_Active (No_Dispatching_Calls) then
5300                Make_Predefined_Primitive_Specs (Typ, Predef_List, Renamed_Eq);
5301                Insert_List_Before_And_Analyze (N, Predef_List);
5302             end if;
5303
5304             --  Ada 2005 (AI-391): For a nonabstract null extension, create
5305             --  wrapper functions for each nonoverridden inherited function
5306             --  with a controlling result of the type. The wrapper for such
5307             --  a function returns an extension aggregate that invokes the
5308             --  parent function.
5309
5310             if Ada_Version >= Ada_2005
5311               and then not Is_Abstract_Type (Typ)
5312               and then Is_Null_Extension (Typ)
5313             then
5314                Make_Controlling_Function_Wrappers
5315                  (Typ, Wrapper_Decl_List, Wrapper_Body_List);
5316                Insert_List_Before_And_Analyze (N, Wrapper_Decl_List);
5317             end if;
5318
5319             --  Ada 2005 (AI-251): For a nonabstract type extension, build
5320             --  null procedure declarations for each set of homographic null
5321             --  procedures that are inherited from interface types but not
5322             --  overridden. This is done to ensure that the dispatch table
5323             --  entry associated with such null primitives are properly filled.
5324
5325             if Ada_Version >= Ada_2005
5326               and then Etype (Typ) /= Typ
5327               and then not Is_Abstract_Type (Typ)
5328               and then Has_Interfaces (Typ)
5329             then
5330                Insert_Actions (N, Make_Null_Procedure_Specs (Typ));
5331             end if;
5332
5333             Set_Is_Frozen (Typ);
5334
5335             if not Is_Derived_Type (Typ)
5336               or else Is_Tagged_Type (Etype (Typ))
5337             then
5338                Set_All_DT_Position (Typ);
5339
5340             --  If this is a type derived from an untagged private type whose
5341             --  full view is tagged, the type is marked tagged for layout
5342             --  reasons, but it has no dispatch table.
5343
5344             elsif Is_Derived_Type (Typ)
5345               and then Is_Private_Type (Etype (Typ))
5346               and then not Is_Tagged_Type (Etype (Typ))
5347             then
5348                return;
5349             end if;
5350
5351             --  Create and decorate the tags. Suppress their creation when
5352             --  not Tagged_Type_Expansion because the dispatching mechanism is
5353             --  handled internally by the virtual target.
5354
5355             if Tagged_Type_Expansion then
5356                Append_Freeze_Actions (Typ, Make_Tags (Typ));
5357
5358                --  Generate dispatch table of locally defined tagged type.
5359                --  Dispatch tables of library level tagged types are built
5360                --  later (see Analyze_Declarations).
5361
5362                if not Building_Static_DT (Typ) then
5363                   Append_Freeze_Actions (Typ, Make_DT (Typ));
5364                end if;
5365             end if;
5366
5367             --  If the type has unknown discriminants, propagate dispatching
5368             --  information to its underlying record view, which does not get
5369             --  its own dispatch table.
5370
5371             if Is_Derived_Type (Typ)
5372               and then Has_Unknown_Discriminants (Typ)
5373               and then Present (Underlying_Record_View (Typ))
5374             then
5375                declare
5376                   Rep : constant Entity_Id := Underlying_Record_View (Typ);
5377                begin
5378                   Set_Access_Disp_Table
5379                     (Rep, Access_Disp_Table           (Typ));
5380                   Set_Dispatch_Table_Wrappers
5381                     (Rep, Dispatch_Table_Wrappers     (Typ));
5382                   Set_Direct_Primitive_Operations
5383                     (Rep, Direct_Primitive_Operations (Typ));
5384                end;
5385             end if;
5386
5387             --  Make sure that the primitives Initialize, Adjust and Finalize
5388             --  are Frozen before other TSS subprograms. We don't want them
5389             --  Frozen inside.
5390
5391             if Is_Controlled (Typ) then
5392                if not Is_Limited_Type (Typ) then
5393                   Append_Freeze_Actions (Typ,
5394                     Freeze_Entity (Find_Prim_Op (Typ, Name_Adjust), Typ));
5395                end if;
5396
5397                Append_Freeze_Actions (Typ,
5398                  Freeze_Entity (Find_Prim_Op (Typ, Name_Initialize), Typ));
5399
5400                Append_Freeze_Actions (Typ,
5401                  Freeze_Entity (Find_Prim_Op (Typ, Name_Finalize), Typ));
5402             end if;
5403
5404             --  Freeze rest of primitive operations. There is no need to handle
5405             --  the predefined primitives if we are compiling under restriction
5406             --  No_Dispatching_Calls.
5407
5408             if not Restriction_Active (No_Dispatching_Calls) then
5409                Append_Freeze_Actions (Typ, Predefined_Primitive_Freeze (Typ));
5410             end if;
5411          end if;
5412
5413       --  In the untagged case, ever since Ada 83 an equality function must
5414       --  be  provided for variant records that are not unchecked unions.
5415       --  In Ada 2012 the equality function composes, and thus must be built
5416       --  explicitly just as for tagged records.
5417
5418       elsif Has_Discriminants (Typ)
5419         and then not Is_Limited_Type (Typ)
5420       then
5421          declare
5422             Comps : constant Node_Id :=
5423                       Component_List (Type_Definition (Typ_Decl));
5424          begin
5425             if Present (Comps)
5426               and then Present (Variant_Part (Comps))
5427             then
5428                Build_Variant_Record_Equality (Typ);
5429             end if;
5430          end;
5431
5432       --  Otherwise create primitive equality operation (AI05-0123)
5433
5434       --  This is done unconditionally to ensure that tools can be linked
5435       --  properly with user programs compiled with older language versions.
5436       --  In addition, this is needed because "=" composes for bounded strings
5437       --  in all language versions (see Exp_Ch4.Expand_Composite_Equality).
5438
5439       elsif Comes_From_Source (Typ)
5440         and then Convention (Typ) = Convention_Ada
5441         and then not Is_Limited_Type (Typ)
5442       then
5443          Build_Untagged_Equality (Typ);
5444       end if;
5445
5446       --  Before building the record initialization procedure, if we are
5447       --  dealing with a concurrent record value type, then we must go through
5448       --  the discriminants, exchanging discriminals between the concurrent
5449       --  type and the concurrent record value type. See the section "Handling
5450       --  of Discriminants" in the Einfo spec for details.
5451
5452       if Is_Concurrent_Record_Type (Typ)
5453         and then Has_Discriminants (Typ)
5454       then
5455          declare
5456             Ctyp       : constant Entity_Id :=
5457                            Corresponding_Concurrent_Type (Typ);
5458             Conc_Discr : Entity_Id;
5459             Rec_Discr  : Entity_Id;
5460             Temp       : Entity_Id;
5461
5462          begin
5463             Conc_Discr := First_Discriminant (Ctyp);
5464             Rec_Discr  := First_Discriminant (Typ);
5465             while Present (Conc_Discr) loop
5466                Temp := Discriminal (Conc_Discr);
5467                Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
5468                Set_Discriminal (Rec_Discr, Temp);
5469
5470                Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
5471                Set_Discriminal_Link (Discriminal (Rec_Discr),  Rec_Discr);
5472
5473                Next_Discriminant (Conc_Discr);
5474                Next_Discriminant (Rec_Discr);
5475             end loop;
5476          end;
5477       end if;
5478
5479       if Has_Controlled_Component (Typ) then
5480          Build_Controlling_Procs (Typ);
5481       end if;
5482
5483       Adjust_Discriminants (Typ);
5484
5485       --  Do not need init for interfaces on virtual targets since they're
5486       --  abstract.
5487
5488       if Tagged_Type_Expansion or else not Is_Interface (Typ) then
5489          Build_Record_Init_Proc (Typ_Decl, Typ);
5490       end if;
5491
5492       --  For tagged type that are not interfaces, build bodies of primitive
5493       --  operations. Note: do this after building the record initialization
5494       --  procedure, since the primitive operations may need the initialization
5495       --  routine. There is no need to add predefined primitives of interfaces
5496       --  because all their predefined primitives are abstract.
5497
5498       if Is_Tagged_Type (Typ) and then not Is_Interface (Typ) then
5499
5500          --  Do not add the body of predefined primitives in case of CPP tagged
5501          --  type derivations that have convention CPP.
5502
5503          if Is_CPP_Class (Root_Type (Typ))
5504            and then Convention (Typ) = Convention_CPP
5505          then
5506             null;
5507
5508          --  Do not add the body of the predefined primitives if we are
5509          --  compiling under restriction No_Dispatching_Calls or if we are
5510          --  compiling a CPP tagged type.
5511
5512          elsif not Restriction_Active (No_Dispatching_Calls) then
5513
5514             --  Create the body of TSS primitive Finalize_Address. This must
5515             --  be done before the bodies of all predefined primitives are
5516             --  created. If Typ is limited, Stream_Input and Stream_Read may
5517             --  produce build-in-place allocations and for those the expander
5518             --  needs Finalize_Address.
5519
5520             Make_Finalize_Address_Body (Typ);
5521             Predef_List := Predefined_Primitive_Bodies (Typ, Renamed_Eq);
5522             Append_Freeze_Actions (Typ, Predef_List);
5523          end if;
5524
5525          --  Ada 2005 (AI-391): If any wrappers were created for nonoverridden
5526          --  inherited functions, then add their bodies to the freeze actions.
5527
5528          if Present (Wrapper_Body_List) then
5529             Append_Freeze_Actions (Typ, Wrapper_Body_List);
5530          end if;
5531
5532          --  Create extra formals for the primitive operations of the type.
5533          --  This must be done before analyzing the body of the initialization
5534          --  procedure, because a self-referential type might call one of these
5535          --  primitives in the body of the init_proc itself.
5536
5537          declare
5538             Elmt : Elmt_Id;
5539             Subp : Entity_Id;
5540
5541          begin
5542             Elmt := First_Elmt (Primitive_Operations (Typ));
5543             while Present (Elmt) loop
5544                Subp := Node (Elmt);
5545                if not Has_Foreign_Convention (Subp)
5546                  and then not Is_Predefined_Dispatching_Operation (Subp)
5547                then
5548                   Create_Extra_Formals (Subp);
5549                end if;
5550
5551                Next_Elmt (Elmt);
5552             end loop;
5553          end;
5554       end if;
5555
5556       --  Check whether individual components have a defined invariant, and add
5557       --  the corresponding component invariant checks.
5558
5559       --  Do not create an invariant procedure for some internally generated
5560       --  subtypes, in particular those created for objects of a class-wide
5561       --  type. Such types may have components to which invariant apply, but
5562       --  the corresponding checks will be applied when an object of the parent
5563       --  type is constructed.
5564
5565       --  Such objects will show up in a class-wide postcondition, and the
5566       --  invariant will be checked, if necessary, upon return from the
5567       --  enclosing subprogram.
5568
5569       if not Is_Class_Wide_Equivalent_Type (Typ) then
5570          Insert_Component_Invariant_Checks
5571            (N, Typ, Build_Record_Invariant_Proc (Typ, N));
5572       end if;
5573
5574       Ghost_Mode := Save_Ghost_Mode;
5575    end Expand_Freeze_Record_Type;
5576
5577    ------------------------------------
5578    -- Expand_N_Full_Type_Declaration --
5579    ------------------------------------
5580
5581    procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
5582       procedure Build_Master (Ptr_Typ : Entity_Id);
5583       --  Create the master associated with Ptr_Typ
5584
5585       ------------------
5586       -- Build_Master --
5587       ------------------
5588
5589       procedure Build_Master (Ptr_Typ : Entity_Id) is
5590          Desig_Typ : Entity_Id := Designated_Type (Ptr_Typ);
5591
5592       begin
5593          --  If the designated type is an incomplete view coming from a
5594          --  limited-with'ed package, we need to use the nonlimited view in
5595          --  case it has tasks.
5596
5597          if Ekind (Desig_Typ) in Incomplete_Kind
5598            and then Present (Non_Limited_View (Desig_Typ))
5599          then
5600             Desig_Typ := Non_Limited_View (Desig_Typ);
5601          end if;
5602
5603          --  Anonymous access types are created for the components of the
5604          --  record parameter for an entry declaration. No master is created
5605          --  for such a type.
5606
5607          if Comes_From_Source (N) and then Has_Task (Desig_Typ) then
5608             Build_Master_Entity (Ptr_Typ);
5609             Build_Master_Renaming (Ptr_Typ);
5610
5611          --  Create a class-wide master because a Master_Id must be generated
5612          --  for access-to-limited-class-wide types whose root may be extended
5613          --  with task components.
5614
5615          --  Note: This code covers access-to-limited-interfaces because they
5616          --        can be used to reference tasks implementing them.
5617
5618          elsif Is_Limited_Class_Wide_Type (Desig_Typ)
5619            and then Tasking_Allowed
5620          then
5621             Build_Class_Wide_Master (Ptr_Typ);
5622          end if;
5623       end Build_Master;
5624
5625       --  Local declarations
5626
5627       Def_Id : constant Entity_Id := Defining_Identifier (N);
5628       B_Id   : constant Entity_Id := Base_Type (Def_Id);
5629       FN     : Node_Id;
5630       Par_Id : Entity_Id;
5631
5632    --  Start of processing for Expand_N_Full_Type_Declaration
5633
5634    begin
5635       if Is_Access_Type (Def_Id) then
5636          Build_Master (Def_Id);
5637
5638          if Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
5639             Expand_Access_Protected_Subprogram_Type (N);
5640          end if;
5641
5642       --  Array of anonymous access-to-task pointers
5643
5644       elsif Ada_Version >= Ada_2005
5645         and then Is_Array_Type (Def_Id)
5646         and then Is_Access_Type (Component_Type (Def_Id))
5647         and then Ekind (Component_Type (Def_Id)) = E_Anonymous_Access_Type
5648       then
5649          Build_Master (Component_Type (Def_Id));
5650
5651       elsif Has_Task (Def_Id) then
5652          Expand_Previous_Access_Type (Def_Id);
5653
5654       --  Check the components of a record type or array of records for
5655       --  anonymous access-to-task pointers.
5656
5657       elsif Ada_Version >= Ada_2005
5658         and then (Is_Record_Type (Def_Id)
5659                    or else
5660                      (Is_Array_Type (Def_Id)
5661                        and then Is_Record_Type (Component_Type (Def_Id))))
5662       then
5663          declare
5664             Comp  : Entity_Id;
5665             First : Boolean;
5666             M_Id  : Entity_Id;
5667             Typ   : Entity_Id;
5668
5669          begin
5670             if Is_Array_Type (Def_Id) then
5671                Comp := First_Entity (Component_Type (Def_Id));
5672             else
5673                Comp := First_Entity (Def_Id);
5674             end if;
5675
5676             --  Examine all components looking for anonymous access-to-task
5677             --  types.
5678
5679             First := True;
5680             while Present (Comp) loop
5681                Typ := Etype (Comp);
5682
5683                if Ekind (Typ) = E_Anonymous_Access_Type
5684                  and then Has_Task (Available_View (Designated_Type (Typ)))
5685                  and then No (Master_Id (Typ))
5686                then
5687                   --  Ensure that the record or array type have a _master
5688
5689                   if First then
5690                      Build_Master_Entity (Def_Id);
5691                      Build_Master_Renaming (Typ);
5692                      M_Id := Master_Id (Typ);
5693
5694                      First := False;
5695
5696                   --  Reuse the same master to service any additional types
5697
5698                   else
5699                      Set_Master_Id (Typ, M_Id);
5700                   end if;
5701                end if;
5702
5703                Next_Entity (Comp);
5704             end loop;
5705          end;
5706       end if;
5707
5708       Par_Id := Etype (B_Id);
5709
5710       --  The parent type is private then we need to inherit any TSS operations
5711       --  from the full view.
5712
5713       if Ekind (Par_Id) in Private_Kind
5714         and then Present (Full_View (Par_Id))
5715       then
5716          Par_Id := Base_Type (Full_View (Par_Id));
5717       end if;
5718
5719       if Nkind (Type_Definition (Original_Node (N))) =
5720                                                    N_Derived_Type_Definition
5721         and then not Is_Tagged_Type (Def_Id)
5722         and then Present (Freeze_Node (Par_Id))
5723         and then Present (TSS_Elist (Freeze_Node (Par_Id)))
5724       then
5725          Ensure_Freeze_Node (B_Id);
5726          FN := Freeze_Node (B_Id);
5727
5728          if No (TSS_Elist (FN)) then
5729             Set_TSS_Elist (FN, New_Elmt_List);
5730          end if;
5731
5732          declare
5733             T_E  : constant Elist_Id := TSS_Elist (FN);
5734             Elmt : Elmt_Id;
5735
5736          begin
5737             Elmt := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
5738             while Present (Elmt) loop
5739                if Chars (Node (Elmt)) /= Name_uInit then
5740                   Append_Elmt (Node (Elmt), T_E);
5741                end if;
5742
5743                Next_Elmt (Elmt);
5744             end loop;
5745
5746             --  If the derived type itself is private with a full view, then
5747             --  associate the full view with the inherited TSS_Elist as well.
5748
5749             if Ekind (B_Id) in Private_Kind
5750               and then Present (Full_View (B_Id))
5751             then
5752                Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
5753                Set_TSS_Elist
5754                  (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
5755             end if;
5756          end;
5757       end if;
5758    end Expand_N_Full_Type_Declaration;
5759
5760    ---------------------------------
5761    -- Expand_N_Object_Declaration --
5762    ---------------------------------
5763
5764    procedure Expand_N_Object_Declaration (N : Node_Id) is
5765       Loc      : constant Source_Ptr := Sloc (N);
5766       Def_Id   : constant Entity_Id  := Defining_Identifier (N);
5767       Expr     : constant Node_Id    := Expression (N);
5768       Obj_Def  : constant Node_Id    := Object_Definition (N);
5769       Typ      : constant Entity_Id  := Etype (Def_Id);
5770       Base_Typ : constant Entity_Id  := Base_Type (Typ);
5771       Expr_Q   : Node_Id;
5772
5773       function Build_Equivalent_Aggregate return Boolean;
5774       --  If the object has a constrained discriminated type and no initial
5775       --  value, it may be possible to build an equivalent aggregate instead,
5776       --  and prevent an actual call to the initialization procedure.
5777
5778       procedure Default_Initialize_Object (After : Node_Id);
5779       --  Generate all default initialization actions for object Def_Id. Any
5780       --  new code is inserted after node After.
5781
5782       function Rewrite_As_Renaming return Boolean;
5783       --  Indicate whether to rewrite a declaration with initialization into an
5784       --  object renaming declaration (see below).
5785
5786       --------------------------------
5787       -- Build_Equivalent_Aggregate --
5788       --------------------------------
5789
5790       function Build_Equivalent_Aggregate return Boolean is
5791          Aggr      : Node_Id;
5792          Comp      : Entity_Id;
5793          Discr     : Elmt_Id;
5794          Full_Type : Entity_Id;
5795
5796       begin
5797          Full_Type := Typ;
5798
5799          if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
5800             Full_Type := Full_View (Typ);
5801          end if;
5802
5803          --  Only perform this transformation if Elaboration_Code is forbidden
5804          --  or undesirable, and if this is a global entity of a constrained
5805          --  record type.
5806
5807          --  If Initialize_Scalars might be active this  transformation cannot
5808          --  be performed either, because it will lead to different semantics
5809          --  or because elaboration code will in fact be created.
5810
5811          if Ekind (Full_Type) /= E_Record_Subtype
5812            or else not Has_Discriminants (Full_Type)
5813            or else not Is_Constrained (Full_Type)
5814            or else Is_Controlled (Full_Type)
5815            or else Is_Limited_Type (Full_Type)
5816            or else not Restriction_Active (No_Initialize_Scalars)
5817          then
5818             return False;
5819          end if;
5820
5821          if Ekind (Current_Scope) = E_Package
5822            and then
5823              (Restriction_Active (No_Elaboration_Code)
5824                or else Is_Preelaborated (Current_Scope))
5825          then
5826             --  Building a static aggregate is possible if the discriminants
5827             --  have static values and the other components have static
5828             --  defaults or none.
5829
5830             Discr := First_Elmt (Discriminant_Constraint (Full_Type));
5831             while Present (Discr) loop
5832                if not Is_OK_Static_Expression (Node (Discr)) then
5833                   return False;
5834                end if;
5835
5836                Next_Elmt (Discr);
5837             end loop;
5838
5839             --  Check that initialized components are OK, and that non-
5840             --  initialized components do not require a call to their own
5841             --  initialization procedure.
5842
5843             Comp := First_Component (Full_Type);
5844             while Present (Comp) loop
5845                if Ekind (Comp) = E_Component
5846                  and then Present (Expression (Parent (Comp)))
5847                  and then
5848                    not Is_OK_Static_Expression (Expression (Parent (Comp)))
5849                then
5850                   return False;
5851
5852                elsif Has_Non_Null_Base_Init_Proc (Etype (Comp)) then
5853                   return False;
5854
5855                end if;
5856
5857                Next_Component (Comp);
5858             end loop;
5859
5860             --  Everything is static, assemble the aggregate, discriminant
5861             --  values first.
5862
5863             Aggr :=
5864                Make_Aggregate (Loc,
5865                 Expressions            => New_List,
5866                 Component_Associations => New_List);
5867
5868             Discr := First_Elmt (Discriminant_Constraint (Full_Type));
5869             while Present (Discr) loop
5870                Append_To (Expressions (Aggr), New_Copy (Node (Discr)));
5871                Next_Elmt (Discr);
5872             end loop;
5873
5874             --  Now collect values of initialized components
5875
5876             Comp := First_Component (Full_Type);
5877             while Present (Comp) loop
5878                if Ekind (Comp) = E_Component
5879                  and then Present (Expression (Parent (Comp)))
5880                then
5881                   Append_To (Component_Associations (Aggr),
5882                     Make_Component_Association (Loc,
5883                       Choices    => New_List (New_Occurrence_Of (Comp, Loc)),
5884                       Expression => New_Copy_Tree
5885                                       (Expression (Parent (Comp)))));
5886                end if;
5887
5888                Next_Component (Comp);
5889             end loop;
5890
5891             --  Finally, box-initialize remaining components
5892
5893             Append_To (Component_Associations (Aggr),
5894               Make_Component_Association (Loc,
5895                 Choices    => New_List (Make_Others_Choice (Loc)),
5896                 Expression => Empty));
5897             Set_Box_Present (Last (Component_Associations (Aggr)));
5898             Set_Expression (N, Aggr);
5899
5900             if Typ /= Full_Type then
5901                Analyze_And_Resolve (Aggr, Full_View (Base_Type (Full_Type)));
5902                Rewrite (Aggr, Unchecked_Convert_To (Typ, Aggr));
5903                Analyze_And_Resolve (Aggr, Typ);
5904             else
5905                Analyze_And_Resolve (Aggr, Full_Type);
5906             end if;
5907
5908             return True;
5909
5910          else
5911             return False;
5912          end if;
5913       end Build_Equivalent_Aggregate;
5914
5915       -------------------------------
5916       -- Default_Initialize_Object --
5917       -------------------------------
5918
5919       procedure Default_Initialize_Object (After : Node_Id) is
5920          function New_Object_Reference return Node_Id;
5921          --  Return a new reference to Def_Id with attributes Assignment_OK and
5922          --  Must_Not_Freeze already set.
5923
5924          --------------------------
5925          -- New_Object_Reference --
5926          --------------------------
5927
5928          function New_Object_Reference return Node_Id is
5929             Obj_Ref : constant Node_Id := New_Occurrence_Of (Def_Id, Loc);
5930
5931          begin
5932             --  The call to the type init proc or [Deep_]Finalize must not
5933             --  freeze the related object as the call is internally generated.
5934             --  This way legal rep clauses that apply to the object will not be
5935             --  flagged. Note that the initialization call may be removed if
5936             --  pragma Import is encountered or moved to the freeze actions of
5937             --  the object because of an address clause.
5938
5939             Set_Assignment_OK   (Obj_Ref);
5940             Set_Must_Not_Freeze (Obj_Ref);
5941
5942             return Obj_Ref;
5943          end New_Object_Reference;
5944
5945          --  Local variables
5946
5947          Exceptions_OK : constant Boolean :=
5948                            not Restriction_Active (No_Exception_Propagation);
5949
5950          Abrt_Blk    : Node_Id;
5951          Abrt_Blk_Id : Entity_Id;
5952          Abrt_HSS    : Node_Id;
5953          Aggr_Init   : Node_Id;
5954          AUD         : Entity_Id;
5955          Comp_Init   : List_Id := No_List;
5956          Fin_Call    : Node_Id;
5957          Init_Stmts  : List_Id := No_List;
5958          Obj_Init    : Node_Id := Empty;
5959          Obj_Ref     : Node_Id;
5960
5961       --  Start of processing for Default_Initialize_Object
5962
5963       begin
5964          --  Default initialization is suppressed for objects that are already
5965          --  known to be imported (i.e. whose declaration specifies the Import
5966          --  aspect). Note that for objects with a pragma Import, we generate
5967          --  initialization here, and then remove it downstream when processing
5968          --  the pragma. It is also suppressed for variables for which a pragma
5969          --  Suppress_Initialization has been explicitly given
5970
5971          if Is_Imported (Def_Id) or else Suppress_Initialization (Def_Id) then
5972             return;
5973          end if;
5974
5975          --  The expansion performed by this routine is as follows:
5976
5977          --    begin
5978          --       Abort_Defer;
5979          --       Type_Init_Proc (Obj);
5980
5981          --       begin
5982          --          [Deep_]Initialize (Obj);
5983
5984          --       exception
5985          --          when others =>
5986          --             [Deep_]Finalize (Obj, Self => False);
5987          --             raise;
5988          --       end;
5989          --    at end
5990          --       Abort_Undefer_Direct;
5991          --    end;
5992
5993          --  Initialize the components of the object
5994
5995          if Has_Non_Null_Base_Init_Proc (Typ)
5996            and then not No_Initialization (N)
5997            and then not Initialization_Suppressed (Typ)
5998          then
5999             --  Do not initialize the components if No_Default_Initialization
6000             --  applies as the actual restriction check will occur later
6001             --  when the object is frozen as it is not known yet whether the
6002             --  object is imported or not.
6003
6004             if not Restriction_Active (No_Default_Initialization) then
6005
6006                --  If the values of the components are compile-time known, use
6007                --  their prebuilt aggregate form directly.
6008
6009                Aggr_Init := Static_Initialization (Base_Init_Proc (Typ));
6010
6011                if Present (Aggr_Init) then
6012                   Set_Expression
6013                     (N, New_Copy_Tree (Aggr_Init, New_Scope => Current_Scope));
6014
6015                --  If type has discriminants, try to build an equivalent
6016                --  aggregate using discriminant values from the declaration.
6017                --  This is a useful optimization, in particular if restriction
6018                --  No_Elaboration_Code is active.
6019
6020                elsif Build_Equivalent_Aggregate then
6021                   null;
6022
6023                --  Otherwise invoke the type init proc, generate:
6024                --    Type_Init_Proc (Obj);
6025
6026                else
6027                   Obj_Ref := New_Object_Reference;
6028
6029                   if Comes_From_Source (Def_Id) then
6030                      Initialization_Warning (Obj_Ref);
6031                   end if;
6032
6033                   Comp_Init := Build_Initialization_Call (Loc, Obj_Ref, Typ);
6034                end if;
6035             end if;
6036
6037          --  Provide a default value if the object needs simple initialization
6038          --  and does not already have an initial value. A generated temporary
6039          --  does not require initialization because it will be assigned later.
6040
6041          elsif Needs_Simple_Initialization
6042                  (Typ, Initialize_Scalars
6043                          and then No (Following_Address_Clause (N)))
6044            and then not Is_Internal (Def_Id)
6045            and then not Has_Init_Expression (N)
6046          then
6047             Set_No_Initialization (N, False);
6048             Set_Expression (N, Get_Simple_Init_Val (Typ, N, Esize (Def_Id)));
6049             Analyze_And_Resolve (Expression (N), Typ);
6050          end if;
6051
6052          --  Initialize the object, generate:
6053          --    [Deep_]Initialize (Obj);
6054
6055          if Needs_Finalization (Typ) and then not No_Initialization (N) then
6056             Obj_Init :=
6057               Make_Init_Call
6058                 (Obj_Ref => New_Occurrence_Of (Def_Id, Loc),
6059                  Typ     => Typ);
6060          end if;
6061
6062          --  Build a special finalization block when both the object and its
6063          --  controlled components are to be initialized. The block finalizes
6064          --  the components if the object initialization fails. Generate:
6065
6066          --    begin
6067          --       <Obj_Init>
6068
6069          --    exception
6070          --       when others =>
6071          --          <Fin_Call>
6072          --          raise;
6073          --    end;
6074
6075          if Has_Controlled_Component (Typ)
6076            and then Present (Comp_Init)
6077            and then Present (Obj_Init)
6078            and then Exceptions_OK
6079          then
6080             Init_Stmts := Comp_Init;
6081
6082             Fin_Call :=
6083               Make_Final_Call
6084                 (Obj_Ref   => New_Object_Reference,
6085                  Typ       => Typ,
6086                  Skip_Self => True);
6087
6088             if Present (Fin_Call) then
6089
6090                --  Do not emit warnings related to the elaboration order when a
6091                --  controlled object is declared before the body of Finalize is
6092                --  seen.
6093
6094                Set_No_Elaboration_Check (Fin_Call);
6095
6096                Append_To (Init_Stmts,
6097                  Make_Block_Statement (Loc,
6098                    Declarations               => No_List,
6099
6100                    Handled_Statement_Sequence =>
6101                      Make_Handled_Sequence_Of_Statements (Loc,
6102                        Statements         => New_List (Obj_Init),
6103
6104                        Exception_Handlers => New_List (
6105                          Make_Exception_Handler (Loc,
6106                            Exception_Choices => New_List (
6107                              Make_Others_Choice (Loc)),
6108
6109                            Statements        => New_List (
6110                              Fin_Call,
6111                              Make_Raise_Statement (Loc)))))));
6112             end if;
6113
6114          --  Otherwise finalization is not required, the initialization calls
6115          --  are passed to the abort block building circuitry, generate:
6116
6117          --    Type_Init_Proc (Obj);
6118          --    [Deep_]Initialize (Obj);
6119
6120          else
6121             if Present (Comp_Init) then
6122                Init_Stmts := Comp_Init;
6123             end if;
6124
6125             if Present (Obj_Init) then
6126                if No (Init_Stmts) then
6127                   Init_Stmts := New_List;
6128                end if;
6129
6130                Append_To (Init_Stmts, Obj_Init);
6131             end if;
6132          end if;
6133
6134          --  Build an abort block to protect the initialization calls
6135
6136          if Abort_Allowed
6137            and then Present (Comp_Init)
6138            and then Present (Obj_Init)
6139          then
6140             --  Generate:
6141             --    Abort_Defer;
6142
6143             Prepend_To (Init_Stmts, Build_Runtime_Call (Loc, RE_Abort_Defer));
6144
6145             --  When exceptions are propagated, abort deferral must take place
6146             --  in the presence of initialization or finalization exceptions.
6147             --  Generate:
6148
6149             --    begin
6150             --       Abort_Defer;
6151             --       <Init_Stmts>
6152             --    at end
6153             --       Abort_Undefer_Direct;
6154             --    end;
6155
6156             if Exceptions_OK then
6157                AUD := RTE (RE_Abort_Undefer_Direct);
6158
6159                Abrt_HSS :=
6160                  Make_Handled_Sequence_Of_Statements (Loc,
6161                    Statements  => Init_Stmts,
6162                    At_End_Proc => New_Occurrence_Of (AUD, Loc));
6163
6164                Abrt_Blk :=
6165                  Make_Block_Statement (Loc,
6166                    Handled_Statement_Sequence => Abrt_HSS);
6167
6168                Add_Block_Identifier  (Abrt_Blk, Abrt_Blk_Id);
6169                Expand_At_End_Handler (Abrt_HSS, Abrt_Blk_Id);
6170
6171                --  Present the Abort_Undefer_Direct function to the backend so
6172                --  that it can inline the call to the function.
6173
6174                Add_Inlined_Body (AUD, N);
6175
6176                Init_Stmts := New_List (Abrt_Blk);
6177
6178             --  Otherwise exceptions are not propagated. Generate:
6179
6180             --    Abort_Defer;
6181             --    <Init_Stmts>
6182             --    Abort_Undefer;
6183
6184             else
6185                Append_To (Init_Stmts,
6186                  Build_Runtime_Call (Loc, RE_Abort_Undefer));
6187             end if;
6188          end if;
6189
6190          --  Insert the whole initialization sequence into the tree. If the
6191          --  object has a delayed freeze, as will be the case when it has
6192          --  aspect specifications, the initialization sequence is part of
6193          --  the freeze actions.
6194
6195          if Present (Init_Stmts) then
6196             if Has_Delayed_Freeze (Def_Id) then
6197                Append_Freeze_Actions (Def_Id, Init_Stmts);
6198             else
6199                Insert_Actions_After (After, Init_Stmts);
6200             end if;
6201          end if;
6202       end Default_Initialize_Object;
6203
6204       -------------------------
6205       -- Rewrite_As_Renaming --
6206       -------------------------
6207
6208       function Rewrite_As_Renaming return Boolean is
6209       begin
6210          --  If the object declaration appears in the form
6211
6212          --    Obj : Ctrl_Typ := Func (...);
6213
6214          --  where Ctrl_Typ is controlled but not immutably limited type, then
6215          --  the expansion of the function call should use a dereference of the
6216          --  result to reference the value on the secondary stack.
6217
6218          --    Obj : Ctrl_Typ renames Func (...).all;
6219
6220          --  As a result, the call avoids an extra copy. This an optimization,
6221          --  but it is required for passing ACATS tests in some cases where it
6222          --  would otherwise make two copies. The RM allows removing redunant
6223          --  Adjust/Finalize calls, but does not allow insertion of extra ones.
6224
6225          --  This part is disabled for now, because it breaks GPS builds
6226
6227          return (False -- ???
6228              and then Nkind (Expr_Q) = N_Explicit_Dereference
6229              and then not Comes_From_Source (Expr_Q)
6230              and then Nkind (Original_Node (Expr_Q)) = N_Function_Call
6231              and then Nkind (Object_Definition (N)) in N_Has_Entity
6232              and then (Needs_Finalization (Entity (Object_Definition (N)))))
6233
6234            --  If the initializing expression is for a variable with attribute
6235            --  OK_To_Rename set, then transform:
6236
6237            --     Obj : Typ := Expr;
6238
6239            --  into
6240
6241            --     Obj : Typ renames Expr;
6242
6243            --  provided that Obj is not aliased. The aliased case has to be
6244            --  excluded in general because Expr will not be aliased in
6245            --  general.
6246
6247            or else
6248              (not Aliased_Present (N)
6249                and then Is_Entity_Name (Expr_Q)
6250                and then Ekind (Entity (Expr_Q)) = E_Variable
6251                and then OK_To_Rename (Entity (Expr_Q))
6252                and then Is_Entity_Name (Obj_Def));
6253       end Rewrite_As_Renaming;
6254
6255       --  Local variables
6256
6257       Next_N     : constant Node_Id := Next (N);
6258       Id_Ref     : Node_Id;
6259       Tag_Assign : Node_Id;
6260
6261       Init_After : Node_Id := N;
6262       --  Node after which the initialization actions are to be inserted. This
6263       --  is normally N, except for the case of a shared passive variable, in
6264       --  which case the init proc call must be inserted only after the bodies
6265       --  of the shared variable procedures have been seen.
6266
6267    --  Start of processing for Expand_N_Object_Declaration
6268
6269    begin
6270       --  Don't do anything for deferred constants. All proper actions will be
6271       --  expanded during the full declaration.
6272
6273       if No (Expr) and Constant_Present (N) then
6274          return;
6275       end if;
6276
6277       --  The type of the object cannot be abstract. This is diagnosed at the
6278       --  point the object is frozen, which happens after the declaration is
6279       --  fully expanded, so simply return now.
6280
6281       if Is_Abstract_Type (Typ) then
6282          return;
6283       end if;
6284
6285       --  First we do special processing for objects of a tagged type where
6286       --  this is the point at which the type is frozen. The creation of the
6287       --  dispatch table and the initialization procedure have to be deferred
6288       --  to this point, since we reference previously declared primitive
6289       --  subprograms.
6290
6291       --  Force construction of dispatch tables of library level tagged types
6292
6293       if Tagged_Type_Expansion
6294         and then Static_Dispatch_Tables
6295         and then Is_Library_Level_Entity (Def_Id)
6296         and then Is_Library_Level_Tagged_Type (Base_Typ)
6297         and then Ekind_In (Base_Typ, E_Record_Type,
6298                                      E_Protected_Type,
6299                                      E_Task_Type)
6300         and then not Has_Dispatch_Table (Base_Typ)
6301       then
6302          declare
6303             New_Nodes : List_Id := No_List;
6304
6305          begin
6306             if Is_Concurrent_Type (Base_Typ) then
6307                New_Nodes := Make_DT (Corresponding_Record_Type (Base_Typ), N);
6308             else
6309                New_Nodes := Make_DT (Base_Typ, N);
6310             end if;
6311
6312             if not Is_Empty_List (New_Nodes) then
6313                Insert_List_Before (N, New_Nodes);
6314             end if;
6315          end;
6316       end if;
6317
6318       --  Make shared memory routines for shared passive variable
6319
6320       if Is_Shared_Passive (Def_Id) then
6321          Init_After := Make_Shared_Var_Procs (N);
6322       end if;
6323
6324       --  If tasks being declared, make sure we have an activation chain
6325       --  defined for the tasks (has no effect if we already have one), and
6326       --  also that a Master variable is established and that the appropriate
6327       --  enclosing construct is established as a task master.
6328
6329       if Has_Task (Typ) then
6330          Build_Activation_Chain_Entity (N);
6331          Build_Master_Entity (Def_Id);
6332       end if;
6333
6334       --  Default initialization required, and no expression present
6335
6336       if No (Expr) then
6337
6338          --  If we have a type with a variant part, the initialization proc
6339          --  will contain implicit tests of the discriminant values, which
6340          --  counts as a violation of the restriction No_Implicit_Conditionals.
6341
6342          if Has_Variant_Part (Typ) then
6343             declare
6344                Msg : Boolean;
6345
6346             begin
6347                Check_Restriction (Msg, No_Implicit_Conditionals, Obj_Def);
6348
6349                if Msg then
6350                   Error_Msg_N
6351                     ("\initialization of variant record tests discriminants",
6352                      Obj_Def);
6353                   return;
6354                end if;
6355             end;
6356          end if;
6357
6358          --  For the default initialization case, if we have a private type
6359          --  with invariants, and invariant checks are enabled, then insert an
6360          --  invariant check after the object declaration. Note that it is OK
6361          --  to clobber the object with an invalid value since if the exception
6362          --  is raised, then the object will go out of scope. In the case where
6363          --  an array object is initialized with an aggregate, the expression
6364          --  is removed. Check flag Has_Init_Expression to avoid generating a
6365          --  junk invariant check and flag No_Initialization to avoid checking
6366          --  an uninitialized object such as a compiler temporary used for an
6367          --  aggregate.
6368
6369          if Has_Invariants (Base_Typ)
6370            and then Present (Invariant_Procedure (Base_Typ))
6371            and then not Has_Init_Expression (N)
6372            and then not No_Initialization (N)
6373          then
6374             --  If entity has an address clause or aspect, make invariant
6375             --  call into a freeze action for the explicit freeze node for
6376             --  object. Otherwise insert invariant check after declaration.
6377
6378             if Present (Following_Address_Clause (N))
6379               or else Has_Aspect (Def_Id, Aspect_Address)
6380             then
6381                Ensure_Freeze_Node (Def_Id);
6382                Set_Has_Delayed_Freeze (Def_Id);
6383                Set_Is_Frozen (Def_Id, False);
6384
6385                if not Partial_View_Has_Unknown_Discr (Typ) then
6386                   Append_Freeze_Action (Def_Id,
6387                     Make_Invariant_Call (New_Occurrence_Of (Def_Id, Loc)));
6388                end if;
6389
6390             elsif not Partial_View_Has_Unknown_Discr (Typ) then
6391                Insert_After (N,
6392                  Make_Invariant_Call (New_Occurrence_Of (Def_Id, Loc)));
6393             end if;
6394          end if;
6395
6396          Default_Initialize_Object (Init_After);
6397
6398          --  Generate attribute for Persistent_BSS if needed
6399
6400          if Persistent_BSS_Mode
6401            and then Comes_From_Source (N)
6402            and then Is_Potentially_Persistent_Type (Typ)
6403            and then not Has_Init_Expression (N)
6404            and then Is_Library_Level_Entity (Def_Id)
6405          then
6406             declare
6407                Prag : Node_Id;
6408             begin
6409                Prag :=
6410                  Make_Linker_Section_Pragma
6411                    (Def_Id, Sloc (N), ".persistent.bss");
6412                Insert_After (N, Prag);
6413                Analyze (Prag);
6414             end;
6415          end if;
6416
6417          --  If access type, then we know it is null if not initialized
6418
6419          if Is_Access_Type (Typ) then
6420             Set_Is_Known_Null (Def_Id);
6421          end if;
6422
6423       --  Explicit initialization present
6424
6425       else
6426          --  Obtain actual expression from qualified expression
6427
6428          if Nkind (Expr) = N_Qualified_Expression then
6429             Expr_Q := Expression (Expr);
6430          else
6431             Expr_Q := Expr;
6432          end if;
6433
6434          --  When we have the appropriate type of aggregate in the expression
6435          --  (it has been determined during analysis of the aggregate by
6436          --  setting the delay flag), let's perform in place assignment and
6437          --  thus avoid creating a temporary.
6438
6439          if Is_Delayed_Aggregate (Expr_Q) then
6440             Convert_Aggr_In_Object_Decl (N);
6441
6442          --  Ada 2005 (AI-318-02): If the initialization expression is a call
6443          --  to a build-in-place function, then access to the declared object
6444          --  must be passed to the function. Currently we limit such functions
6445          --  to those with constrained limited result subtypes, but eventually
6446          --  plan to expand the allowed forms of functions that are treated as
6447          --  build-in-place.
6448
6449          elsif Ada_Version >= Ada_2005
6450            and then Is_Build_In_Place_Function_Call (Expr_Q)
6451          then
6452             Make_Build_In_Place_Call_In_Object_Declaration (N, Expr_Q);
6453
6454             --  The previous call expands the expression initializing the
6455             --  built-in-place object into further code that will be analyzed
6456             --  later. No further expansion needed here.
6457
6458             return;
6459
6460          --  Ada 2005 (AI-251): Rewrite the expression that initializes a
6461          --  class-wide interface object to ensure that we copy the full
6462          --  object, unless we are targetting a VM where interfaces are handled
6463          --  by VM itself. Note that if the root type of Typ is an ancestor of
6464          --  Expr's type, both types share the same dispatch table and there is
6465          --  no need to displace the pointer.
6466
6467          elsif Is_Interface (Typ)
6468
6469            --  Avoid never-ending recursion because if Equivalent_Type is set
6470            --  then we've done it already and must not do it again.
6471
6472            and then not
6473              (Nkind (Obj_Def) = N_Identifier
6474                and then Present (Equivalent_Type (Entity (Obj_Def))))
6475          then
6476             pragma Assert (Is_Class_Wide_Type (Typ));
6477
6478             --  If the object is a return object of an inherently limited type,
6479             --  which implies build-in-place treatment, bypass the special
6480             --  treatment of class-wide interface initialization below. In this
6481             --  case, the expansion of the return statement will take care of
6482             --  creating the object (via allocator) and initializing it.
6483
6484             if Is_Return_Object (Def_Id) and then Is_Limited_View (Typ) then
6485                null;
6486
6487             elsif Tagged_Type_Expansion then
6488                declare
6489                   Iface    : constant Entity_Id := Root_Type (Typ);
6490                   Expr_N   : Node_Id := Expr;
6491                   Expr_Typ : Entity_Id;
6492                   New_Expr : Node_Id;
6493                   Obj_Id   : Entity_Id;
6494                   Tag_Comp : Node_Id;
6495
6496                begin
6497                   --  If the original node of the expression was a conversion
6498                   --  to this specific class-wide interface type then restore
6499                   --  the original node because we must copy the object before
6500                   --  displacing the pointer to reference the secondary tag
6501                   --  component. This code must be kept synchronized with the
6502                   --  expansion done by routine Expand_Interface_Conversion
6503
6504                   if not Comes_From_Source (Expr_N)
6505                     and then Nkind (Expr_N) = N_Explicit_Dereference
6506                     and then Nkind (Original_Node (Expr_N)) = N_Type_Conversion
6507                     and then Etype (Original_Node (Expr_N)) = Typ
6508                   then
6509                      Rewrite (Expr_N, Original_Node (Expression (N)));
6510                   end if;
6511
6512                   --  Avoid expansion of redundant interface conversion
6513
6514                   if Is_Interface (Etype (Expr_N))
6515                     and then Nkind (Expr_N) = N_Type_Conversion
6516                     and then Etype (Expr_N) = Typ
6517                   then
6518                      Expr_N := Expression (Expr_N);
6519                      Set_Expression (N, Expr_N);
6520                   end if;
6521
6522                   Obj_Id   := Make_Temporary (Loc, 'D', Expr_N);
6523                   Expr_Typ := Base_Type (Etype (Expr_N));
6524
6525                   if Is_Class_Wide_Type (Expr_Typ) then
6526                      Expr_Typ := Root_Type (Expr_Typ);
6527                   end if;
6528
6529                   --  Replace
6530                   --     CW : I'Class := Obj;
6531                   --  by
6532                   --     Tmp : T := Obj;
6533                   --     type Ityp is not null access I'Class;
6534                   --     CW  : I'Class renames Ityp (Tmp.I_Tag'Address).all;
6535
6536                   if Comes_From_Source (Expr_N)
6537                     and then Nkind (Expr_N) = N_Identifier
6538                     and then not Is_Interface (Expr_Typ)
6539                     and then Interface_Present_In_Ancestor (Expr_Typ, Typ)
6540                     and then (Expr_Typ = Etype (Expr_Typ)
6541                                or else not
6542                                  Is_Variable_Size_Record (Etype (Expr_Typ)))
6543                   then
6544                      --  Copy the object
6545
6546                      Insert_Action (N,
6547                        Make_Object_Declaration (Loc,
6548                          Defining_Identifier => Obj_Id,
6549                          Object_Definition   =>
6550                            New_Occurrence_Of (Expr_Typ, Loc),
6551                          Expression          => Relocate_Node (Expr_N)));
6552
6553                      --  Statically reference the tag associated with the
6554                      --  interface
6555
6556                      Tag_Comp :=
6557                        Make_Selected_Component (Loc,
6558                          Prefix        => New_Occurrence_Of (Obj_Id, Loc),
6559                          Selector_Name =>
6560                            New_Occurrence_Of
6561                              (Find_Interface_Tag (Expr_Typ, Iface), Loc));
6562
6563                   --  Replace
6564                   --     IW : I'Class := Obj;
6565                   --  by
6566                   --     type Equiv_Record is record ... end record;
6567                   --     implicit subtype CW is <Class_Wide_Subtype>;
6568                   --     Tmp : CW := CW!(Obj);
6569                   --     type Ityp is not null access I'Class;
6570                   --     IW : I'Class renames
6571                   --            Ityp!(Displace (Temp'Address, I'Tag)).all;
6572
6573                   else
6574                      --  Generate the equivalent record type and update the
6575                      --  subtype indication to reference it.
6576
6577                      Expand_Subtype_From_Expr
6578                        (N             => N,
6579                         Unc_Type      => Typ,
6580                         Subtype_Indic => Obj_Def,
6581                         Exp           => Expr_N);
6582
6583                      if not Is_Interface (Etype (Expr_N)) then
6584                         New_Expr := Relocate_Node (Expr_N);
6585
6586                      --  For interface types we use 'Address which displaces
6587                      --  the pointer to the base of the object (if required)
6588
6589                      else
6590                         New_Expr :=
6591                           Unchecked_Convert_To (Etype (Obj_Def),
6592                             Make_Explicit_Dereference (Loc,
6593                               Unchecked_Convert_To (RTE (RE_Tag_Ptr),
6594                                 Make_Attribute_Reference (Loc,
6595                                   Prefix => Relocate_Node (Expr_N),
6596                                   Attribute_Name => Name_Address))));
6597                      end if;
6598
6599                      --  Copy the object
6600
6601                      if not Is_Limited_Record (Expr_Typ) then
6602                         Insert_Action (N,
6603                           Make_Object_Declaration (Loc,
6604                             Defining_Identifier => Obj_Id,
6605                             Object_Definition   =>
6606                               New_Occurrence_Of (Etype (Obj_Def), Loc),
6607                             Expression => New_Expr));
6608
6609                      --  Rename limited type object since they cannot be copied
6610                      --  This case occurs when the initialization expression
6611                      --  has been previously expanded into a temporary object.
6612
6613                      else pragma Assert (not Comes_From_Source (Expr_Q));
6614                         Insert_Action (N,
6615                           Make_Object_Renaming_Declaration (Loc,
6616                             Defining_Identifier => Obj_Id,
6617                             Subtype_Mark        =>
6618                               New_Occurrence_Of (Etype (Obj_Def), Loc),
6619                             Name                =>
6620                               Unchecked_Convert_To
6621                                 (Etype (Obj_Def), New_Expr)));
6622                      end if;
6623
6624                      --  Dynamically reference the tag associated with the
6625                      --  interface.
6626
6627                      Tag_Comp :=
6628                        Make_Function_Call (Loc,
6629                          Name => New_Occurrence_Of (RTE (RE_Displace), Loc),
6630                          Parameter_Associations => New_List (
6631                            Make_Attribute_Reference (Loc,
6632                              Prefix => New_Occurrence_Of (Obj_Id, Loc),
6633                              Attribute_Name => Name_Address),
6634                            New_Occurrence_Of
6635                              (Node (First_Elmt (Access_Disp_Table (Iface))),
6636                               Loc)));
6637                   end if;
6638
6639                   Rewrite (N,
6640                     Make_Object_Renaming_Declaration (Loc,
6641                       Defining_Identifier => Make_Temporary (Loc, 'D'),
6642                       Subtype_Mark        => New_Occurrence_Of (Typ, Loc),
6643                       Name                =>
6644                         Convert_Tag_To_Interface (Typ, Tag_Comp)));
6645
6646                   --  If the original entity comes from source, then mark the
6647                   --  new entity as needing debug information, even though it's
6648                   --  defined by a generated renaming that does not come from
6649                   --  source, so that Materialize_Entity will be set on the
6650                   --  entity when Debug_Renaming_Declaration is called during
6651                   --  analysis.
6652
6653                   if Comes_From_Source (Def_Id) then
6654                      Set_Debug_Info_Needed (Defining_Identifier (N));
6655                   end if;
6656
6657                   Analyze (N, Suppress => All_Checks);
6658
6659                   --  Replace internal identifier of rewritten node by the
6660                   --  identifier found in the sources. We also have to exchange
6661                   --  entities containing their defining identifiers to ensure
6662                   --  the correct replacement of the object declaration by this
6663                   --  object renaming declaration because these identifiers
6664                   --  were previously added by Enter_Name to the current scope.
6665                   --  We must preserve the homonym chain of the source entity
6666                   --  as well. We must also preserve the kind of the entity,
6667                   --  which may be a constant. Preserve entity chain because
6668                   --  itypes may have been generated already, and the full
6669                   --  chain must be preserved for final freezing. Finally,
6670                   --  preserve Comes_From_Source setting, so that debugging
6671                   --  and cross-referencing information is properly kept, and
6672                   --  preserve source location, to prevent spurious errors when
6673                   --  entities are declared (they must have their own Sloc).
6674
6675                   declare
6676                      New_Id    : constant Entity_Id := Defining_Identifier (N);
6677                      Next_Temp : constant Entity_Id := Next_Entity (New_Id);
6678                      S_Flag    : constant Boolean   :=
6679                                    Comes_From_Source (Def_Id);
6680
6681                   begin
6682                      Set_Next_Entity (New_Id, Next_Entity (Def_Id));
6683                      Set_Next_Entity (Def_Id, Next_Temp);
6684
6685                      Set_Chars   (Defining_Identifier (N), Chars   (Def_Id));
6686                      Set_Homonym (Defining_Identifier (N), Homonym (Def_Id));
6687                      Set_Ekind   (Defining_Identifier (N), Ekind   (Def_Id));
6688                      Set_Sloc    (Defining_Identifier (N), Sloc    (Def_Id));
6689
6690                      Set_Comes_From_Source (Def_Id, False);
6691                      Exchange_Entities (Defining_Identifier (N), Def_Id);
6692                      Set_Comes_From_Source (Def_Id, S_Flag);
6693                   end;
6694                end;
6695             end if;
6696
6697             return;
6698
6699          --  Common case of explicit object initialization
6700
6701          else
6702             --  In most cases, we must check that the initial value meets any
6703             --  constraint imposed by the declared type. However, there is one
6704             --  very important exception to this rule. If the entity has an
6705             --  unconstrained nominal subtype, then it acquired its constraints
6706             --  from the expression in the first place, and not only does this
6707             --  mean that the constraint check is not needed, but an attempt to
6708             --  perform the constraint check can cause order of elaboration
6709             --  problems.
6710
6711             if not Is_Constr_Subt_For_U_Nominal (Typ) then
6712
6713                --  If this is an allocator for an aggregate that has been
6714                --  allocated in place, delay checks until assignments are
6715                --  made, because the discriminants are not initialized.
6716
6717                if Nkind (Expr) = N_Allocator and then No_Initialization (Expr)
6718                then
6719                   null;
6720
6721                --  Otherwise apply a constraint check now if no prev error
6722
6723                elsif Nkind (Expr) /= N_Error then
6724                   Apply_Constraint_Check (Expr, Typ);
6725
6726                   --  Deal with possible range check
6727
6728                   if Do_Range_Check (Expr) then
6729
6730                      --  If assignment checks are suppressed, turn off flag
6731
6732                      if Suppress_Assignment_Checks (N) then
6733                         Set_Do_Range_Check (Expr, False);
6734
6735                      --  Otherwise generate the range check
6736
6737                      else
6738                         Generate_Range_Check
6739                           (Expr, Typ, CE_Range_Check_Failed);
6740                      end if;
6741                   end if;
6742                end if;
6743             end if;
6744
6745             --  If the type is controlled and not inherently limited, then
6746             --  the target is adjusted after the copy and attached to the
6747             --  finalization list. However, no adjustment is done in the case
6748             --  where the object was initialized by a call to a function whose
6749             --  result is built in place, since no copy occurred. (Eventually
6750             --  we plan to support in-place function results for some cases
6751             --  of nonlimited types. ???) Similarly, no adjustment is required
6752             --  if we are going to rewrite the object declaration into a
6753             --  renaming declaration.
6754
6755             if Needs_Finalization (Typ)
6756               and then not Is_Limited_View (Typ)
6757               and then not Rewrite_As_Renaming
6758             then
6759                Insert_Action_After (Init_After,
6760                  Make_Adjust_Call (
6761                    Obj_Ref => New_Occurrence_Of (Def_Id, Loc),
6762                    Typ     => Base_Typ));
6763             end if;
6764
6765             --  For tagged types, when an init value is given, the tag has to
6766             --  be re-initialized separately in order to avoid the propagation
6767             --  of a wrong tag coming from a view conversion unless the type
6768             --  is class wide (in this case the tag comes from the init value).
6769             --  Suppress the tag assignment when not Tagged_Type_Expansion
6770             --  because tags are represented implicitly in objects. Ditto for
6771             --  types that are CPP_CLASS, and for initializations that are
6772             --  aggregates, because they have to have the right tag.
6773
6774             --  The re-assignment of the tag has to be done even if the object
6775             --  is a constant. The assignment must be analyzed after the
6776             --  declaration. If an address clause follows, this is handled as
6777             --  part of the freeze actions for the object, otherwise insert
6778             --  tag assignment here.
6779
6780             Tag_Assign := Make_Tag_Assignment (N);
6781
6782             if Present (Tag_Assign) then
6783                if Present (Following_Address_Clause (N)) then
6784                   Ensure_Freeze_Node (Def_Id);
6785
6786                else
6787                   Insert_Action_After (Init_After, Tag_Assign);
6788                end if;
6789
6790             --  Handle C++ constructor calls. Note that we do not check that
6791             --  Typ is a tagged type since the equivalent Ada type of a C++
6792             --  class that has no virtual methods is an untagged limited
6793             --  record type.
6794
6795             elsif Is_CPP_Constructor_Call (Expr) then
6796
6797                --  The call to the initialization procedure does NOT freeze the
6798                --  object being initialized.
6799
6800                Id_Ref := New_Occurrence_Of (Def_Id, Loc);
6801                Set_Must_Not_Freeze (Id_Ref);
6802                Set_Assignment_OK (Id_Ref);
6803
6804                Insert_Actions_After (Init_After,
6805                  Build_Initialization_Call (Loc, Id_Ref, Typ,
6806                    Constructor_Ref => Expr));
6807
6808                --  We remove here the original call to the constructor
6809                --  to avoid its management in the backend
6810
6811                Set_Expression (N, Empty);
6812                return;
6813
6814             --  Handle initialization of limited tagged types
6815
6816             elsif Is_Tagged_Type (Typ)
6817               and then Is_Class_Wide_Type (Typ)
6818               and then Is_Limited_Record (Typ)
6819               and then not Is_Limited_Interface (Typ)
6820             then
6821                --  Given that the type is limited we cannot perform a copy. If
6822                --  Expr_Q is the reference to a variable we mark the variable
6823                --  as OK_To_Rename to expand this declaration into a renaming
6824                --  declaration (see bellow).
6825
6826                if Is_Entity_Name (Expr_Q) then
6827                   Set_OK_To_Rename (Entity (Expr_Q));
6828
6829                --  If we cannot convert the expression into a renaming we must
6830                --  consider it an internal error because the backend does not
6831                --  have support to handle it.
6832
6833                else
6834                   pragma Assert (False);
6835                   raise Program_Error;
6836                end if;
6837
6838             --  For discrete types, set the Is_Known_Valid flag if the
6839             --  initializing value is known to be valid. Only do this for
6840             --  source assignments, since otherwise we can end up turning
6841             --  on the known valid flag prematurely from inserted code.
6842
6843             elsif Comes_From_Source (N)
6844               and then Is_Discrete_Type (Typ)
6845               and then Expr_Known_Valid (Expr)
6846             then
6847                Set_Is_Known_Valid (Def_Id);
6848
6849             elsif Is_Access_Type (Typ) then
6850
6851                --  For access types set the Is_Known_Non_Null flag if the
6852                --  initializing value is known to be non-null. We can also set
6853                --  Can_Never_Be_Null if this is a constant.
6854
6855                if Known_Non_Null (Expr) then
6856                   Set_Is_Known_Non_Null (Def_Id, True);
6857
6858                   if Constant_Present (N) then
6859                      Set_Can_Never_Be_Null (Def_Id);
6860                   end if;
6861                end if;
6862             end if;
6863
6864             --  If validity checking on copies, validate initial expression.
6865             --  But skip this if declaration is for a generic type, since it
6866             --  makes no sense to validate generic types. Not clear if this
6867             --  can happen for legal programs, but it definitely can arise
6868             --  from previous instantiation errors.
6869
6870             if Validity_Checks_On
6871               and then Comes_From_Source (N)
6872               and then Validity_Check_Copies
6873               and then not Is_Generic_Type (Etype (Def_Id))
6874             then
6875                Ensure_Valid (Expr);
6876                Set_Is_Known_Valid (Def_Id);
6877             end if;
6878          end if;
6879
6880          --  Cases where the back end cannot handle the initialization directly
6881          --  In such cases, we expand an assignment that will be appropriately
6882          --  handled by Expand_N_Assignment_Statement.
6883
6884          --  The exclusion of the unconstrained case is wrong, but for now it
6885          --  is too much trouble ???
6886
6887          if (Is_Possibly_Unaligned_Slice (Expr)
6888               or else (Is_Possibly_Unaligned_Object (Expr)
6889                         and then not Represented_As_Scalar (Etype (Expr))))
6890            and then not (Is_Array_Type (Etype (Expr))
6891                           and then not Is_Constrained (Etype (Expr)))
6892          then
6893             declare
6894                Stat : constant Node_Id :=
6895                        Make_Assignment_Statement (Loc,
6896                          Name       => New_Occurrence_Of (Def_Id, Loc),
6897                          Expression => Relocate_Node (Expr));
6898             begin
6899                Set_Expression (N, Empty);
6900                Set_No_Initialization (N);
6901                Set_Assignment_OK (Name (Stat));
6902                Set_No_Ctrl_Actions (Stat);
6903                Insert_After_And_Analyze (Init_After, Stat);
6904             end;
6905          end if;
6906       end if;
6907
6908       if Nkind (Obj_Def) = N_Access_Definition
6909         and then not Is_Local_Anonymous_Access (Etype (Def_Id))
6910       then
6911          --  An Ada 2012 stand-alone object of an anonymous access type
6912
6913          declare
6914             Loc : constant Source_Ptr := Sloc (N);
6915
6916             Level : constant Entity_Id :=
6917                       Make_Defining_Identifier (Sloc (N),
6918                         Chars =>
6919                           New_External_Name (Chars (Def_Id), Suffix => "L"));
6920
6921             Level_Expr : Node_Id;
6922             Level_Decl : Node_Id;
6923
6924          begin
6925             Set_Ekind (Level, Ekind (Def_Id));
6926             Set_Etype (Level, Standard_Natural);
6927             Set_Scope (Level, Scope (Def_Id));
6928
6929             if No (Expr) then
6930
6931                --  Set accessibility level of null
6932
6933                Level_Expr :=
6934                  Make_Integer_Literal (Loc, Scope_Depth (Standard_Standard));
6935
6936             else
6937                Level_Expr := Dynamic_Accessibility_Level (Expr);
6938             end if;
6939
6940             Level_Decl :=
6941               Make_Object_Declaration (Loc,
6942                 Defining_Identifier => Level,
6943                 Object_Definition   =>
6944                   New_Occurrence_Of (Standard_Natural, Loc),
6945                 Expression          => Level_Expr,
6946                 Constant_Present    => Constant_Present (N),
6947                 Has_Init_Expression => True);
6948
6949             Insert_Action_After (Init_After, Level_Decl);
6950
6951             Set_Extra_Accessibility (Def_Id, Level);
6952          end;
6953       end if;
6954
6955       --  If the object is default initialized and its type is subject to
6956       --  pragma Default_Initial_Condition, add a runtime check to verify
6957       --  the assumption of the pragma (SPARK RM 7.3.3). Generate:
6958
6959       --    <Base_Typ>Default_Init_Cond (<Base_Typ> (Def_Id));
6960
6961       --  Note that the check is generated for source objects only
6962
6963       if Comes_From_Source (Def_Id)
6964         and then (Has_Default_Init_Cond (Typ)
6965                     or else
6966                   Has_Inherited_Default_Init_Cond (Typ))
6967         and then not Has_Init_Expression (N)
6968       then
6969          declare
6970             DIC_Call : constant Node_Id :=
6971                          Build_Default_Init_Cond_Call (Loc, Def_Id, Typ);
6972          begin
6973             if Present (Next_N) then
6974                Insert_Before_And_Analyze (Next_N, DIC_Call);
6975
6976             --  The object declaration is the last node in a declarative or a
6977             --  statement list.
6978
6979             else
6980                Append_To (List_Containing (N), DIC_Call);
6981                Analyze (DIC_Call);
6982             end if;
6983          end;
6984       end if;
6985
6986       --  Final transformation - turn the object declaration into a renaming
6987       --  if appropriate. If this is the completion of a deferred constant
6988       --  declaration, then this transformation generates what would be
6989       --  illegal code if written by hand, but that's OK.
6990
6991       if Present (Expr) then
6992          if Rewrite_As_Renaming then
6993             Rewrite (N,
6994               Make_Object_Renaming_Declaration (Loc,
6995                 Defining_Identifier => Defining_Identifier (N),
6996                 Subtype_Mark        => Obj_Def,
6997                 Name                => Expr_Q));
6998
6999             --  We do not analyze this renaming declaration, because all its
7000             --  components have already been analyzed, and if we were to go
7001             --  ahead and analyze it, we would in effect be trying to generate
7002             --  another declaration of X, which won't do.
7003
7004             Set_Renamed_Object (Defining_Identifier (N), Expr_Q);
7005             Set_Analyzed (N);
7006
7007             --  We do need to deal with debug issues for this renaming
7008
7009             --  First, if entity comes from source, then mark it as needing
7010             --  debug information, even though it is defined by a generated
7011             --  renaming that does not come from source.
7012
7013             if Comes_From_Source (Defining_Identifier (N)) then
7014                Set_Debug_Info_Needed (Defining_Identifier (N));
7015             end if;
7016
7017             --  Now call the routine to generate debug info for the renaming
7018
7019             declare
7020                Decl : constant Node_Id := Debug_Renaming_Declaration (N);
7021             begin
7022                if Present (Decl) then
7023                   Insert_Action (N, Decl);
7024                end if;
7025             end;
7026          end if;
7027       end if;
7028
7029    --  Exception on library entity not available
7030
7031    exception
7032       when RE_Not_Available =>
7033          return;
7034    end Expand_N_Object_Declaration;
7035
7036    ---------------------------------
7037    -- Expand_N_Subtype_Indication --
7038    ---------------------------------
7039
7040    --  Add a check on the range of the subtype. The static case is partially
7041    --  duplicated by Process_Range_Expr_In_Decl in Sem_Ch3, but we still need
7042    --  to check here for the static case in order to avoid generating
7043    --  extraneous expanded code. Also deal with validity checking.
7044
7045    procedure Expand_N_Subtype_Indication (N : Node_Id) is
7046       Ran : constant Node_Id   := Range_Expression (Constraint (N));
7047       Typ : constant Entity_Id := Entity (Subtype_Mark (N));
7048
7049    begin
7050       if Nkind (Constraint (N)) = N_Range_Constraint then
7051          Validity_Check_Range (Range_Expression (Constraint (N)));
7052       end if;
7053
7054       if Nkind_In (Parent (N), N_Constrained_Array_Definition, N_Slice) then
7055          Apply_Range_Check (Ran, Typ);
7056       end if;
7057    end Expand_N_Subtype_Indication;
7058
7059    ---------------------------
7060    -- Expand_N_Variant_Part --
7061    ---------------------------
7062
7063    --  Note: this procedure no longer has any effect. It used to be that we
7064    --  would replace the choices in the last variant by a when others, and
7065    --  also expanded static predicates in variant choices here, but both of
7066    --  those activities were being done too early, since we can't check the
7067    --  choices until the statically predicated subtypes are frozen, which can
7068    --  happen as late as the free point of the record, and we can't change the
7069    --  last choice to an others before checking the choices, which is now done
7070    --  at the freeze point of the record.
7071
7072    procedure Expand_N_Variant_Part (N : Node_Id) is
7073    begin
7074       null;
7075    end Expand_N_Variant_Part;
7076
7077    ---------------------------------
7078    -- Expand_Previous_Access_Type --
7079    ---------------------------------
7080
7081    procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
7082       Ptr_Typ : Entity_Id;
7083
7084    begin
7085       --  Find all access types in the current scope whose designated type is
7086       --  Def_Id and build master renamings for them.
7087
7088       Ptr_Typ := First_Entity (Current_Scope);
7089       while Present (Ptr_Typ) loop
7090          if Is_Access_Type (Ptr_Typ)
7091            and then Designated_Type (Ptr_Typ) = Def_Id
7092            and then No (Master_Id (Ptr_Typ))
7093          then
7094             --  Ensure that the designated type has a master
7095
7096             Build_Master_Entity (Def_Id);
7097
7098             --  Private and incomplete types complicate the insertion of master
7099             --  renamings because the access type may precede the full view of
7100             --  the designated type. For this reason, the master renamings are
7101             --  inserted relative to the designated type.
7102
7103             Build_Master_Renaming (Ptr_Typ, Ins_Nod => Parent (Def_Id));
7104          end if;
7105
7106          Next_Entity (Ptr_Typ);
7107       end loop;
7108    end Expand_Previous_Access_Type;
7109
7110    -----------------------------
7111    -- Expand_Record_Extension --
7112    -----------------------------
7113
7114    --  Add a field _parent at the beginning of the record extension. This is
7115    --  used to implement inheritance. Here are some examples of expansion:
7116
7117    --  1. no discriminants
7118    --      type T2 is new T1 with null record;
7119    --   gives
7120    --      type T2 is new T1 with record
7121    --        _Parent : T1;
7122    --      end record;
7123
7124    --  2. renamed discriminants
7125    --    type T2 (B, C : Int) is new T1 (A => B) with record
7126    --       _Parent : T1 (A => B);
7127    --       D : Int;
7128    --    end;
7129
7130    --  3. inherited discriminants
7131    --    type T2 is new T1 with record -- discriminant A inherited
7132    --       _Parent : T1 (A);
7133    --       D : Int;
7134    --    end;
7135
7136    procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
7137       Indic        : constant Node_Id    := Subtype_Indication (Def);
7138       Loc          : constant Source_Ptr := Sloc (Def);
7139       Rec_Ext_Part : Node_Id             := Record_Extension_Part (Def);
7140       Par_Subtype  : Entity_Id;
7141       Comp_List    : Node_Id;
7142       Comp_Decl    : Node_Id;
7143       Parent_N     : Node_Id;
7144       D            : Entity_Id;
7145       List_Constr  : constant List_Id    := New_List;
7146
7147    begin
7148       --  Expand_Record_Extension is called directly from the semantics, so
7149       --  we must check to see whether expansion is active before proceeding,
7150       --  because this affects the visibility of selected components in bodies
7151       --  of instances.
7152
7153       if not Expander_Active then
7154          return;
7155       end if;
7156
7157       --  This may be a derivation of an untagged private type whose full
7158       --  view is tagged, in which case the Derived_Type_Definition has no
7159       --  extension part. Build an empty one now.
7160
7161       if No (Rec_Ext_Part) then
7162          Rec_Ext_Part :=
7163            Make_Record_Definition (Loc,
7164              End_Label      => Empty,
7165              Component_List => Empty,
7166              Null_Present   => True);
7167
7168          Set_Record_Extension_Part (Def, Rec_Ext_Part);
7169          Mark_Rewrite_Insertion (Rec_Ext_Part);
7170       end if;
7171
7172       Comp_List := Component_List (Rec_Ext_Part);
7173
7174       Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
7175
7176       --  If the derived type inherits its discriminants the type of the
7177       --  _parent field must be constrained by the inherited discriminants
7178
7179       if Has_Discriminants (T)
7180         and then Nkind (Indic) /= N_Subtype_Indication
7181         and then not Is_Constrained (Entity (Indic))
7182       then
7183          D := First_Discriminant (T);
7184          while Present (D) loop
7185             Append_To (List_Constr, New_Occurrence_Of (D, Loc));
7186             Next_Discriminant (D);
7187          end loop;
7188
7189          Par_Subtype :=
7190            Process_Subtype (
7191              Make_Subtype_Indication (Loc,
7192                Subtype_Mark => New_Occurrence_Of (Entity (Indic), Loc),
7193                Constraint   =>
7194                  Make_Index_Or_Discriminant_Constraint (Loc,
7195                    Constraints => List_Constr)),
7196              Def);
7197
7198       --  Otherwise the original subtype_indication is just what is needed
7199
7200       else
7201          Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
7202       end if;
7203
7204       Set_Parent_Subtype (T, Par_Subtype);
7205
7206       Comp_Decl :=
7207         Make_Component_Declaration (Loc,
7208           Defining_Identifier => Parent_N,
7209           Component_Definition =>
7210             Make_Component_Definition (Loc,
7211               Aliased_Present => False,
7212               Subtype_Indication => New_Occurrence_Of (Par_Subtype, Loc)));
7213
7214       if Null_Present (Rec_Ext_Part) then
7215          Set_Component_List (Rec_Ext_Part,
7216            Make_Component_List (Loc,
7217              Component_Items => New_List (Comp_Decl),
7218              Variant_Part => Empty,
7219              Null_Present => False));
7220          Set_Null_Present (Rec_Ext_Part, False);
7221
7222       elsif Null_Present (Comp_List)
7223         or else Is_Empty_List (Component_Items (Comp_List))
7224       then
7225          Set_Component_Items (Comp_List, New_List (Comp_Decl));
7226          Set_Null_Present (Comp_List, False);
7227
7228       else
7229          Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
7230       end if;
7231
7232       Analyze (Comp_Decl);
7233    end Expand_Record_Extension;
7234
7235    ------------------------
7236    -- Expand_Tagged_Root --
7237    ------------------------
7238
7239    procedure Expand_Tagged_Root (T : Entity_Id) is
7240       Def       : constant Node_Id := Type_Definition (Parent (T));
7241       Comp_List : Node_Id;
7242       Comp_Decl : Node_Id;
7243       Sloc_N    : Source_Ptr;
7244
7245    begin
7246       if Null_Present (Def) then
7247          Set_Component_List (Def,
7248            Make_Component_List (Sloc (Def),
7249              Component_Items => Empty_List,
7250              Variant_Part => Empty,
7251              Null_Present => True));
7252       end if;
7253
7254       Comp_List := Component_List (Def);
7255
7256       if Null_Present (Comp_List)
7257         or else Is_Empty_List (Component_Items (Comp_List))
7258       then
7259          Sloc_N := Sloc (Comp_List);
7260       else
7261          Sloc_N := Sloc (First (Component_Items (Comp_List)));
7262       end if;
7263
7264       Comp_Decl :=
7265         Make_Component_Declaration (Sloc_N,
7266           Defining_Identifier => First_Tag_Component (T),
7267           Component_Definition =>
7268             Make_Component_Definition (Sloc_N,
7269               Aliased_Present => False,
7270               Subtype_Indication => New_Occurrence_Of (RTE (RE_Tag), Sloc_N)));
7271
7272       if Null_Present (Comp_List)
7273         or else Is_Empty_List (Component_Items (Comp_List))
7274       then
7275          Set_Component_Items (Comp_List, New_List (Comp_Decl));
7276          Set_Null_Present (Comp_List, False);
7277
7278       else
7279          Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
7280       end if;
7281
7282       --  We don't Analyze the whole expansion because the tag component has
7283       --  already been analyzed previously. Here we just insure that the tree
7284       --  is coherent with the semantic decoration
7285
7286       Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
7287
7288    exception
7289       when RE_Not_Available =>
7290          return;
7291    end Expand_Tagged_Root;
7292
7293    ------------------------------
7294    -- Freeze_Stream_Operations --
7295    ------------------------------
7296
7297    procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
7298       Names     : constant array (1 .. 4) of TSS_Name_Type :=
7299                     (TSS_Stream_Input,
7300                      TSS_Stream_Output,
7301                      TSS_Stream_Read,
7302                      TSS_Stream_Write);
7303       Stream_Op : Entity_Id;
7304
7305    begin
7306       --  Primitive operations of tagged types are frozen when the dispatch
7307       --  table is constructed.
7308
7309       if not Comes_From_Source (Typ) or else Is_Tagged_Type (Typ) then
7310          return;
7311       end if;
7312
7313       for J in Names'Range loop
7314          Stream_Op := TSS (Typ, Names (J));
7315
7316          if Present (Stream_Op)
7317            and then Is_Subprogram (Stream_Op)
7318            and then Nkind (Unit_Declaration_Node (Stream_Op)) =
7319                                                     N_Subprogram_Declaration
7320            and then not Is_Frozen (Stream_Op)
7321          then
7322             Append_Freeze_Actions (Typ, Freeze_Entity (Stream_Op, N));
7323          end if;
7324       end loop;
7325    end Freeze_Stream_Operations;
7326
7327    -----------------
7328    -- Freeze_Type --
7329    -----------------
7330
7331    --  Full type declarations are expanded at the point at which the type is
7332    --  frozen. The formal N is the Freeze_Node for the type. Any statements or
7333    --  declarations generated by the freezing (e.g. the procedure generated
7334    --  for initialization) are chained in the Actions field list of the freeze
7335    --  node using Append_Freeze_Actions.
7336
7337    function Freeze_Type (N : Node_Id) return Boolean is
7338       procedure Process_RACW_Types (Typ : Entity_Id);
7339       --  Validate and generate stubs for all RACW types associated with type
7340       --  Typ.
7341
7342       procedure Process_Pending_Access_Types (Typ : Entity_Id);
7343       --  Associate type Typ's Finalize_Address primitive with the finalization
7344       --  masters of pending access-to-Typ types.
7345
7346       ------------------------
7347       -- Process_RACW_Types --
7348       ------------------------
7349
7350       procedure Process_RACW_Types (Typ : Entity_Id) is
7351          List : constant Elist_Id := Access_Types_To_Process (N);
7352          E    : Elmt_Id;
7353          Seen : Boolean := False;
7354
7355       begin
7356          if Present (List) then
7357             E := First_Elmt (List);
7358             while Present (E) loop
7359                if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
7360                   Validate_RACW_Primitives (Node (E));
7361                   Seen := True;
7362                end if;
7363
7364                Next_Elmt (E);
7365             end loop;
7366          end if;
7367
7368          --  If there are RACWs designating this type, make stubs now
7369
7370          if Seen then
7371             Remote_Types_Tagged_Full_View_Encountered (Typ);
7372          end if;
7373       end Process_RACW_Types;
7374
7375       ----------------------------------
7376       -- Process_Pending_Access_Types --
7377       ----------------------------------
7378
7379       procedure Process_Pending_Access_Types (Typ : Entity_Id) is
7380          E : Elmt_Id;
7381
7382       begin
7383          --  Finalize_Address is not generated in CodePeer mode because the
7384          --  body contains address arithmetic. This processing is disabled.
7385
7386          if CodePeer_Mode then
7387             null;
7388
7389          --  Certain itypes are generated for contexts that cannot allocate
7390          --  objects and should not set primitive Finalize_Address.
7391
7392          elsif Is_Itype (Typ)
7393            and then Nkind (Associated_Node_For_Itype (Typ)) =
7394                       N_Explicit_Dereference
7395          then
7396             null;
7397
7398          --  When an access type is declared after the incomplete view of a
7399          --  Taft-amendment type, the access type is considered pending in
7400          --  case the full view of the Taft-amendment type is controlled. If
7401          --  this is indeed the case, associate the Finalize_Address routine
7402          --  of the full view with the finalization masters of all pending
7403          --  access types. This scenario applies to anonymous access types as
7404          --  well.
7405
7406          elsif Needs_Finalization (Typ)
7407            and then Present (Pending_Access_Types (Typ))
7408          then
7409             E := First_Elmt (Pending_Access_Types (Typ));
7410             while Present (E) loop
7411
7412                --  Generate:
7413                --    Set_Finalize_Address
7414                --      (Ptr_Typ, <Typ>FD'Unrestricted_Access);
7415
7416                Append_Freeze_Action (Typ,
7417                  Make_Set_Finalize_Address_Call
7418                    (Loc     => Sloc (N),
7419                     Ptr_Typ => Node (E)));
7420
7421                Next_Elmt (E);
7422             end loop;
7423          end if;
7424       end Process_Pending_Access_Types;
7425
7426       --  Local variables
7427
7428       Def_Id : constant Entity_Id := Entity (N);
7429       Result : Boolean := False;
7430
7431       Save_Ghost_Mode : constant Ghost_Mode_Type := Ghost_Mode;
7432
7433    --  Start of processing for Freeze_Type
7434
7435    begin
7436       --  The type being frozen may be subject to pragma Ghost. Set the mode
7437       --  now to ensure that any nodes generated during freezing are properly
7438       --  marked as Ghost.
7439
7440       Set_Ghost_Mode (N, Def_Id);
7441
7442       --  Process any remote access-to-class-wide types designating the type
7443       --  being frozen.
7444
7445       Process_RACW_Types (Def_Id);
7446
7447       --  Freeze processing for record types
7448
7449       if Is_Record_Type (Def_Id) then
7450          if Ekind (Def_Id) = E_Record_Type then
7451             Expand_Freeze_Record_Type (N);
7452          elsif Is_Class_Wide_Type (Def_Id) then
7453             Expand_Freeze_Class_Wide_Type (N);
7454          end if;
7455
7456       --  Freeze processing for array types
7457
7458       elsif Is_Array_Type (Def_Id) then
7459          Expand_Freeze_Array_Type (N);
7460
7461       --  Freeze processing for access types
7462
7463       --  For pool-specific access types, find out the pool object used for
7464       --  this type, needs actual expansion of it in some cases. Here are the
7465       --  different cases :
7466
7467       --  1. Rep Clause "for Def_Id'Storage_Size use 0;"
7468       --      ---> don't use any storage pool
7469
7470       --  2. Rep Clause : for Def_Id'Storage_Size use Expr.
7471       --     Expand:
7472       --      Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
7473
7474       --  3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
7475       --      ---> Storage Pool is the specified one
7476
7477       --  See GNAT Pool packages in the Run-Time for more details
7478
7479       elsif Ekind_In (Def_Id, E_Access_Type, E_General_Access_Type) then
7480          declare
7481             Loc         : constant Source_Ptr := Sloc (N);
7482             Desig_Type  : constant Entity_Id  := Designated_Type (Def_Id);
7483             Pool_Object : Entity_Id;
7484
7485             Freeze_Action_Typ : Entity_Id;
7486
7487          begin
7488             --  Case 1
7489
7490             --    Rep Clause "for Def_Id'Storage_Size use 0;"
7491             --    ---> don't use any storage pool
7492
7493             if No_Pool_Assigned (Def_Id) then
7494                null;
7495
7496             --  Case 2
7497
7498             --    Rep Clause : for Def_Id'Storage_Size use Expr.
7499             --    ---> Expand:
7500             --           Def_Id__Pool : Stack_Bounded_Pool
7501             --                            (Expr, DT'Size, DT'Alignment);
7502
7503             elsif Has_Storage_Size_Clause (Def_Id) then
7504                declare
7505                   DT_Size  : Node_Id;
7506                   DT_Align : Node_Id;
7507
7508                begin
7509                   --  For unconstrained composite types we give a size of zero
7510                   --  so that the pool knows that it needs a special algorithm
7511                   --  for variable size object allocation.
7512
7513                   if Is_Composite_Type (Desig_Type)
7514                     and then not Is_Constrained (Desig_Type)
7515                   then
7516                      DT_Size  := Make_Integer_Literal (Loc, 0);
7517                      DT_Align := Make_Integer_Literal (Loc, Maximum_Alignment);
7518
7519                   else
7520                      DT_Size :=
7521                        Make_Attribute_Reference (Loc,
7522                          Prefix         => New_Occurrence_Of (Desig_Type, Loc),
7523                          Attribute_Name => Name_Max_Size_In_Storage_Elements);
7524
7525                      DT_Align :=
7526                        Make_Attribute_Reference (Loc,
7527                          Prefix         => New_Occurrence_Of (Desig_Type, Loc),
7528                          Attribute_Name => Name_Alignment);
7529                   end if;
7530
7531                   Pool_Object :=
7532                     Make_Defining_Identifier (Loc,
7533                       Chars => New_External_Name (Chars (Def_Id), 'P'));
7534
7535                   --  We put the code associated with the pools in the entity
7536                   --  that has the later freeze node, usually the access type
7537                   --  but it can also be the designated_type; because the pool
7538                   --  code requires both those types to be frozen
7539
7540                   if Is_Frozen (Desig_Type)
7541                     and then (No (Freeze_Node (Desig_Type))
7542                                or else Analyzed (Freeze_Node (Desig_Type)))
7543                   then
7544                      Freeze_Action_Typ := Def_Id;
7545
7546                   --  A Taft amendment type cannot get the freeze actions
7547                   --  since the full view is not there.
7548
7549                   elsif Is_Incomplete_Or_Private_Type (Desig_Type)
7550                     and then No (Full_View (Desig_Type))
7551                   then
7552                      Freeze_Action_Typ := Def_Id;
7553
7554                   else
7555                      Freeze_Action_Typ := Desig_Type;
7556                   end if;
7557
7558                   Append_Freeze_Action (Freeze_Action_Typ,
7559                     Make_Object_Declaration (Loc,
7560                       Defining_Identifier => Pool_Object,
7561                       Object_Definition   =>
7562                         Make_Subtype_Indication (Loc,
7563                           Subtype_Mark =>
7564                             New_Occurrence_Of
7565                               (RTE (RE_Stack_Bounded_Pool), Loc),
7566
7567                           Constraint   =>
7568                             Make_Index_Or_Discriminant_Constraint (Loc,
7569                               Constraints => New_List (
7570
7571                                 --  First discriminant is the Pool Size
7572
7573                                 New_Occurrence_Of (
7574                                   Storage_Size_Variable (Def_Id), Loc),
7575
7576                                 --  Second discriminant is the element size
7577
7578                                 DT_Size,
7579
7580                                 --  Third discriminant is the alignment
7581
7582                                 DT_Align)))));
7583                end;
7584
7585                Set_Associated_Storage_Pool (Def_Id, Pool_Object);
7586
7587             --  Case 3
7588
7589             --    Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
7590             --    ---> Storage Pool is the specified one
7591
7592             --  When compiling in Ada 2012 mode, ensure that the accessibility
7593             --  level of the subpool access type is not deeper than that of the
7594             --  pool_with_subpools.
7595
7596             elsif Ada_Version >= Ada_2012
7597               and then Present (Associated_Storage_Pool (Def_Id))
7598
7599               --  Omit this check for the case of a configurable run-time that
7600               --  does not provide package System.Storage_Pools.Subpools.
7601
7602               and then RTE_Available (RE_Root_Storage_Pool_With_Subpools)
7603             then
7604                declare
7605                   Loc   : constant Source_Ptr := Sloc (Def_Id);
7606                   Pool  : constant Entity_Id :=
7607                             Associated_Storage_Pool (Def_Id);
7608                   RSPWS : constant Entity_Id :=
7609                             RTE (RE_Root_Storage_Pool_With_Subpools);
7610
7611                begin
7612                   --  It is known that the accessibility level of the access
7613                   --  type is deeper than that of the pool.
7614
7615                   if Type_Access_Level (Def_Id) > Object_Access_Level (Pool)
7616                     and then not Accessibility_Checks_Suppressed (Def_Id)
7617                     and then not Accessibility_Checks_Suppressed (Pool)
7618                   then
7619                      --  Static case: the pool is known to be a descendant of
7620                      --  Root_Storage_Pool_With_Subpools.
7621
7622                      if Is_Ancestor (RSPWS, Etype (Pool)) then
7623                         Error_Msg_N
7624                           ("??subpool access type has deeper accessibility "
7625                            & "level than pool", Def_Id);
7626
7627                         Append_Freeze_Action (Def_Id,
7628                           Make_Raise_Program_Error (Loc,
7629                             Reason => PE_Accessibility_Check_Failed));
7630
7631                      --  Dynamic case: when the pool is of a class-wide type,
7632                      --  it may or may not support subpools depending on the
7633                      --  path of derivation. Generate:
7634
7635                      --    if Def_Id in RSPWS'Class then
7636                      --       raise Program_Error;
7637                      --    end if;
7638
7639                      elsif Is_Class_Wide_Type (Etype (Pool)) then
7640                         Append_Freeze_Action (Def_Id,
7641                           Make_If_Statement (Loc,
7642                             Condition       =>
7643                               Make_In (Loc,
7644                                 Left_Opnd  => New_Occurrence_Of (Pool, Loc),
7645                                 Right_Opnd =>
7646                                   New_Occurrence_Of
7647                                     (Class_Wide_Type (RSPWS), Loc)),
7648
7649                             Then_Statements => New_List (
7650                               Make_Raise_Program_Error (Loc,
7651                                 Reason => PE_Accessibility_Check_Failed))));
7652                      end if;
7653                   end if;
7654                end;
7655             end if;
7656
7657             --  For access-to-controlled types (including class-wide types and
7658             --  Taft-amendment types, which potentially have controlled
7659             --  components), expand the list controller object that will store
7660             --  the dynamically allocated objects. Don't do this transformation
7661             --  for expander-generated access types, but do it for types that
7662             --  are the full view of types derived from other private types.
7663             --  Also suppress the list controller in the case of a designated
7664             --  type with convention Java, since this is used when binding to
7665             --  Java API specs, where there's no equivalent of a finalization
7666             --  list and we don't want to pull in the finalization support if
7667             --  not needed.
7668
7669             if not Comes_From_Source (Def_Id)
7670               and then not Has_Private_Declaration (Def_Id)
7671             then
7672                null;
7673
7674             --  An exception is made for types defined in the run-time because
7675             --  Ada.Tags.Tag itself is such a type and cannot afford this
7676             --  unnecessary overhead that would generates a loop in the
7677             --  expansion scheme. Another exception is if Restrictions
7678             --  (No_Finalization) is active, since then we know nothing is
7679             --  controlled.
7680
7681             elsif Restriction_Active (No_Finalization)
7682               or else In_Runtime (Def_Id)
7683             then
7684                null;
7685
7686             --  Create a finalization master for an access-to-controlled type
7687             --  or an access-to-incomplete type. It is assumed that the full
7688             --  view will be controlled.
7689
7690             elsif Needs_Finalization (Desig_Type)
7691               or else (Is_Incomplete_Type (Desig_Type)
7692                         and then No (Full_View (Desig_Type)))
7693             then
7694                Build_Finalization_Master (Def_Id);
7695
7696             --  Create a finalization master when the designated type contains
7697             --  a private component. It is assumed that the full view will be
7698             --  controlled.
7699
7700             elsif Has_Private_Component (Desig_Type) then
7701                Build_Finalization_Master
7702                  (Typ            => Def_Id,
7703                   For_Private    => True,
7704                   Context_Scope  => Scope (Def_Id),
7705                   Insertion_Node => Declaration_Node (Desig_Type));
7706             end if;
7707          end;
7708
7709       --  Freeze processing for enumeration types
7710
7711       elsif Ekind (Def_Id) = E_Enumeration_Type then
7712
7713          --  We only have something to do if we have a non-standard
7714          --  representation (i.e. at least one literal whose pos value
7715          --  is not the same as its representation)
7716
7717          if Has_Non_Standard_Rep (Def_Id) then
7718             Expand_Freeze_Enumeration_Type (N);
7719          end if;
7720
7721       --  Private types that are completed by a derivation from a private
7722       --  type have an internally generated full view, that needs to be
7723       --  frozen. This must be done explicitly because the two views share
7724       --  the freeze node, and the underlying full view is not visible when
7725       --  the freeze node is analyzed.
7726
7727       elsif Is_Private_Type (Def_Id)
7728         and then Is_Derived_Type (Def_Id)
7729         and then Present (Full_View (Def_Id))
7730         and then Is_Itype (Full_View (Def_Id))
7731         and then Has_Private_Declaration (Full_View (Def_Id))
7732         and then Freeze_Node (Full_View (Def_Id)) = N
7733       then
7734          Set_Entity (N, Full_View (Def_Id));
7735          Result := Freeze_Type (N);
7736          Set_Entity (N, Def_Id);
7737
7738       --  All other types require no expander action. There are such cases
7739       --  (e.g. task types and protected types). In such cases, the freeze
7740       --  nodes are there for use by Gigi.
7741
7742       end if;
7743
7744       --  Complete the initialization of all pending access types' finalization
7745       --  masters now that the designated type has been is frozen and primitive
7746       --  Finalize_Address generated.
7747
7748       Process_Pending_Access_Types (Def_Id);
7749       Freeze_Stream_Operations (N, Def_Id);
7750
7751       Ghost_Mode := Save_Ghost_Mode;
7752       return Result;
7753
7754    exception
7755       when RE_Not_Available =>
7756          Ghost_Mode := Save_Ghost_Mode;
7757          return False;
7758    end Freeze_Type;
7759
7760    -------------------------
7761    -- Get_Simple_Init_Val --
7762    -------------------------
7763
7764    function Get_Simple_Init_Val
7765      (T    : Entity_Id;
7766       N    : Node_Id;
7767       Size : Uint := No_Uint) return Node_Id
7768    is
7769       Loc    : constant Source_Ptr := Sloc (N);
7770       Val    : Node_Id;
7771       Result : Node_Id;
7772       Val_RE : RE_Id;
7773
7774       Size_To_Use : Uint;
7775       --  This is the size to be used for computation of the appropriate
7776       --  initial value for the Normalize_Scalars and Initialize_Scalars case.
7777
7778       IV_Attribute : constant Boolean :=
7779                        Nkind (N) = N_Attribute_Reference
7780                          and then Attribute_Name (N) = Name_Invalid_Value;
7781
7782       Lo_Bound : Uint;
7783       Hi_Bound : Uint;
7784       --  These are the values computed by the procedure Check_Subtype_Bounds
7785
7786       procedure Check_Subtype_Bounds;
7787       --  This procedure examines the subtype T, and its ancestor subtypes and
7788       --  derived types to determine the best known information about the
7789       --  bounds of the subtype. After the call Lo_Bound is set either to
7790       --  No_Uint if no information can be determined, or to a value which
7791       --  represents a known low bound, i.e. a valid value of the subtype can
7792       --  not be less than this value. Hi_Bound is similarly set to a known
7793       --  high bound (valid value cannot be greater than this).
7794
7795       --------------------------
7796       -- Check_Subtype_Bounds --
7797       --------------------------
7798
7799       procedure Check_Subtype_Bounds is
7800          ST1  : Entity_Id;
7801          ST2  : Entity_Id;
7802          Lo   : Node_Id;
7803          Hi   : Node_Id;
7804          Loval : Uint;
7805          Hival : Uint;
7806
7807       begin
7808          Lo_Bound := No_Uint;
7809          Hi_Bound := No_Uint;
7810
7811          --  Loop to climb ancestor subtypes and derived types
7812
7813          ST1 := T;
7814          loop
7815             if not Is_Discrete_Type (ST1) then
7816                return;
7817             end if;
7818
7819             Lo := Type_Low_Bound (ST1);
7820             Hi := Type_High_Bound (ST1);
7821
7822             if Compile_Time_Known_Value (Lo) then
7823                Loval := Expr_Value (Lo);
7824
7825                if Lo_Bound = No_Uint or else Lo_Bound < Loval then
7826                   Lo_Bound := Loval;
7827                end if;
7828             end if;
7829
7830             if Compile_Time_Known_Value (Hi) then
7831                Hival := Expr_Value (Hi);
7832
7833                if Hi_Bound = No_Uint or else Hi_Bound > Hival then
7834                   Hi_Bound := Hival;
7835                end if;
7836             end if;
7837
7838             ST2 := Ancestor_Subtype (ST1);
7839
7840             if No (ST2) then
7841                ST2 := Etype (ST1);
7842             end if;
7843
7844             exit when ST1 = ST2;
7845             ST1 := ST2;
7846          end loop;
7847       end Check_Subtype_Bounds;
7848
7849    --  Start of processing for Get_Simple_Init_Val
7850
7851    begin
7852       --  For a private type, we should always have an underlying type (because
7853       --  this was already checked in Needs_Simple_Initialization). What we do
7854       --  is to get the value for the underlying type and then do an unchecked
7855       --  conversion to the private type.
7856
7857       if Is_Private_Type (T) then
7858          Val := Get_Simple_Init_Val (Underlying_Type (T), N, Size);
7859
7860          --  A special case, if the underlying value is null, then qualify it
7861          --  with the underlying type, so that the null is properly typed.
7862          --  Similarly, if it is an aggregate it must be qualified, because an
7863          --  unchecked conversion does not provide a context for it.
7864
7865          if Nkind_In (Val, N_Null, N_Aggregate) then
7866             Val :=
7867               Make_Qualified_Expression (Loc,
7868                 Subtype_Mark =>
7869                   New_Occurrence_Of (Underlying_Type (T), Loc),
7870                 Expression => Val);
7871          end if;
7872
7873          Result := Unchecked_Convert_To (T, Val);
7874
7875          --  Don't truncate result (important for Initialize/Normalize_Scalars)
7876
7877          if Nkind (Result) = N_Unchecked_Type_Conversion
7878            and then Is_Scalar_Type (Underlying_Type (T))
7879          then
7880             Set_No_Truncation (Result);
7881          end if;
7882
7883          return Result;
7884
7885       --  Scalars with Default_Value aspect. The first subtype may now be
7886       --  private, so retrieve value from underlying type.
7887
7888       elsif Is_Scalar_Type (T) and then Has_Default_Aspect (T) then
7889          if Is_Private_Type (First_Subtype (T)) then
7890             return Unchecked_Convert_To (T,
7891               Default_Aspect_Value (Full_View (First_Subtype (T))));
7892          else
7893             return
7894               Convert_To (T, Default_Aspect_Value (First_Subtype (T)));
7895          end if;
7896
7897       --  Otherwise, for scalars, we must have normalize/initialize scalars
7898       --  case, or if the node N is an 'Invalid_Value attribute node.
7899
7900       elsif Is_Scalar_Type (T) then
7901          pragma Assert (Init_Or_Norm_Scalars or IV_Attribute);
7902
7903          --  Compute size of object. If it is given by the caller, we can use
7904          --  it directly, otherwise we use Esize (T) as an estimate. As far as
7905          --  we know this covers all cases correctly.
7906
7907          if Size = No_Uint or else Size <= Uint_0 then
7908             Size_To_Use := UI_Max (Uint_1, Esize (T));
7909          else
7910             Size_To_Use := Size;
7911          end if;
7912
7913          --  Maximum size to use is 64 bits, since we will create values of
7914          --  type Unsigned_64 and the range must fit this type.
7915
7916          if Size_To_Use /= No_Uint and then Size_To_Use > Uint_64 then
7917             Size_To_Use := Uint_64;
7918          end if;
7919
7920          --  Check known bounds of subtype
7921
7922          Check_Subtype_Bounds;
7923
7924          --  Processing for Normalize_Scalars case
7925
7926          if Normalize_Scalars and then not IV_Attribute then
7927
7928             --  If zero is invalid, it is a convenient value to use that is
7929             --  for sure an appropriate invalid value in all situations.
7930
7931             if Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
7932                Val := Make_Integer_Literal (Loc, 0);
7933
7934             --  Cases where all one bits is the appropriate invalid value
7935
7936             --  For modular types, all 1 bits is either invalid or valid. If
7937             --  it is valid, then there is nothing that can be done since there
7938             --  are no invalid values (we ruled out zero already).
7939
7940             --  For signed integer types that have no negative values, either
7941             --  there is room for negative values, or there is not. If there
7942             --  is, then all 1-bits may be interpreted as minus one, which is
7943             --  certainly invalid. Alternatively it is treated as the largest
7944             --  positive value, in which case the observation for modular types
7945             --  still applies.
7946
7947             --  For float types, all 1-bits is a NaN (not a number), which is
7948             --  certainly an appropriately invalid value.
7949
7950             elsif Is_Unsigned_Type (T)
7951               or else Is_Floating_Point_Type (T)
7952               or else Is_Enumeration_Type (T)
7953             then
7954                Val := Make_Integer_Literal (Loc, 2 ** Size_To_Use - 1);
7955
7956                --  Resolve as Unsigned_64, because the largest number we can
7957                --  generate is out of range of universal integer.
7958
7959                Analyze_And_Resolve (Val, RTE (RE_Unsigned_64));
7960
7961             --  Case of signed types
7962
7963             else
7964                declare
7965                   Signed_Size : constant Uint :=
7966                                   UI_Min (Uint_63, Size_To_Use - 1);
7967
7968                begin
7969                   --  Normally we like to use the most negative number. The one
7970                   --  exception is when this number is in the known subtype
7971                   --  range and the largest positive number is not in the known
7972                   --  subtype range.
7973
7974                   --  For this exceptional case, use largest positive value
7975
7976                   if Lo_Bound /= No_Uint and then Hi_Bound /= No_Uint
7977                     and then Lo_Bound <= (-(2 ** Signed_Size))
7978                     and then Hi_Bound < 2 ** Signed_Size
7979                   then
7980                      Val := Make_Integer_Literal (Loc, 2 ** Signed_Size - 1);
7981
7982                   --  Normal case of largest negative value
7983
7984                   else
7985                      Val := Make_Integer_Literal (Loc, -(2 ** Signed_Size));
7986                   end if;
7987                end;
7988             end if;
7989
7990          --  Here for Initialize_Scalars case (or Invalid_Value attribute used)
7991
7992          else
7993             --  For float types, use float values from System.Scalar_Values
7994
7995             if Is_Floating_Point_Type (T) then
7996                if Root_Type (T) = Standard_Short_Float then
7997                   Val_RE := RE_IS_Isf;
7998                elsif Root_Type (T) = Standard_Float then
7999                   Val_RE := RE_IS_Ifl;
8000                elsif Root_Type (T) = Standard_Long_Float then
8001                   Val_RE := RE_IS_Ilf;
8002                else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
8003                   Val_RE := RE_IS_Ill;
8004                end if;
8005
8006             --  If zero is invalid, use zero values from System.Scalar_Values
8007
8008             elsif Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
8009                if Size_To_Use <= 8 then
8010                   Val_RE := RE_IS_Iz1;
8011                elsif Size_To_Use <= 16 then
8012                   Val_RE := RE_IS_Iz2;
8013                elsif Size_To_Use <= 32 then
8014                   Val_RE := RE_IS_Iz4;
8015                else
8016                   Val_RE := RE_IS_Iz8;
8017                end if;
8018
8019             --  For unsigned, use unsigned values from System.Scalar_Values
8020
8021             elsif Is_Unsigned_Type (T) then
8022                if Size_To_Use <= 8 then
8023                   Val_RE := RE_IS_Iu1;
8024                elsif Size_To_Use <= 16 then
8025                   Val_RE := RE_IS_Iu2;
8026                elsif Size_To_Use <= 32 then
8027                   Val_RE := RE_IS_Iu4;
8028                else
8029                   Val_RE := RE_IS_Iu8;
8030                end if;
8031
8032             --  For signed, use signed values from System.Scalar_Values
8033
8034             else
8035                if Size_To_Use <= 8 then
8036                   Val_RE := RE_IS_Is1;
8037                elsif Size_To_Use <= 16 then
8038                   Val_RE := RE_IS_Is2;
8039                elsif Size_To_Use <= 32 then
8040                   Val_RE := RE_IS_Is4;
8041                else
8042                   Val_RE := RE_IS_Is8;
8043                end if;
8044             end if;
8045
8046             Val := New_Occurrence_Of (RTE (Val_RE), Loc);
8047          end if;
8048
8049          --  The final expression is obtained by doing an unchecked conversion
8050          --  of this result to the base type of the required subtype. Use the
8051          --  base type to prevent the unchecked conversion from chopping bits,
8052          --  and then we set Kill_Range_Check to preserve the "bad" value.
8053
8054          Result := Unchecked_Convert_To (Base_Type (T), Val);
8055
8056          --  Ensure result is not truncated, since we want the "bad" bits, and
8057          --  also kill range check on result.
8058
8059          if Nkind (Result) = N_Unchecked_Type_Conversion then
8060             Set_No_Truncation (Result);
8061             Set_Kill_Range_Check (Result, True);
8062          end if;
8063
8064          return Result;
8065
8066       --  String or Wide_[Wide]_String (must have Initialize_Scalars set)
8067
8068       elsif Is_Standard_String_Type (T) then
8069          pragma Assert (Init_Or_Norm_Scalars);
8070
8071          return
8072            Make_Aggregate (Loc,
8073              Component_Associations => New_List (
8074                Make_Component_Association (Loc,
8075                  Choices    => New_List (
8076                    Make_Others_Choice (Loc)),
8077                  Expression =>
8078                    Get_Simple_Init_Val
8079                      (Component_Type (T), N, Esize (Root_Type (T))))));
8080
8081       --  Access type is initialized to null
8082
8083       elsif Is_Access_Type (T) then
8084          return Make_Null (Loc);
8085
8086       --  No other possibilities should arise, since we should only be calling
8087       --  Get_Simple_Init_Val if Needs_Simple_Initialization returned True,
8088       --  indicating one of the above cases held.
8089
8090       else
8091          raise Program_Error;
8092       end if;
8093
8094    exception
8095       when RE_Not_Available =>
8096          return Empty;
8097    end Get_Simple_Init_Val;
8098
8099    ------------------------------
8100    -- Has_New_Non_Standard_Rep --
8101    ------------------------------
8102
8103    function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
8104    begin
8105       if not Is_Derived_Type (T) then
8106          return Has_Non_Standard_Rep (T)
8107            or else Has_Non_Standard_Rep (Root_Type (T));
8108
8109       --  If Has_Non_Standard_Rep is not set on the derived type, the
8110       --  representation is fully inherited.
8111
8112       elsif not Has_Non_Standard_Rep (T) then
8113          return False;
8114
8115       else
8116          return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
8117
8118          --  May need a more precise check here: the First_Rep_Item may be a
8119          --  stream attribute, which does not affect the representation of the
8120          --  type ???
8121
8122       end if;
8123    end Has_New_Non_Standard_Rep;
8124
8125    ----------------------
8126    -- Inline_Init_Proc --
8127    ----------------------
8128
8129    function Inline_Init_Proc (Typ : Entity_Id) return Boolean is
8130    begin
8131       --  The initialization proc of protected records is not worth inlining.
8132       --  In addition, when compiled for another unit for inlining purposes,
8133       --  it may make reference to entities that have not been elaborated yet.
8134       --  The initialization proc of records that need finalization contains
8135       --  a nested clean-up procedure that makes it impractical to inline as
8136       --  well, except for simple controlled types themselves. And similar
8137       --  considerations apply to task types.
8138
8139       if Is_Concurrent_Type (Typ) then
8140          return False;
8141
8142       elsif Needs_Finalization (Typ) and then not Is_Controlled (Typ) then
8143          return False;
8144
8145       elsif Has_Task (Typ) then
8146          return False;
8147
8148       else
8149          return True;
8150       end if;
8151    end Inline_Init_Proc;
8152
8153    ----------------
8154    -- In_Runtime --
8155    ----------------
8156
8157    function In_Runtime (E : Entity_Id) return Boolean is
8158       S1 : Entity_Id;
8159
8160    begin
8161       S1 := Scope (E);
8162       while Scope (S1) /= Standard_Standard loop
8163          S1 := Scope (S1);
8164       end loop;
8165
8166       return Is_RTU (S1, System) or else Is_RTU (S1, Ada);
8167    end In_Runtime;
8168
8169    ---------------------------------------
8170    -- Insert_Component_Invariant_Checks --
8171    ---------------------------------------
8172
8173    procedure Insert_Component_Invariant_Checks
8174      (N   : Node_Id;
8175      Typ  : Entity_Id;
8176      Proc : Node_Id)
8177    is
8178       Loc     : constant Source_Ptr := Sloc (Typ);
8179       Proc_Id : Entity_Id;
8180
8181    begin
8182       if Present (Proc) then
8183          Proc_Id := Defining_Entity (Proc);
8184
8185          if not Has_Invariants (Typ) then
8186             Set_Has_Invariants (Typ);
8187             Set_Is_Invariant_Procedure (Proc_Id);
8188             Set_Invariant_Procedure (Typ, Proc_Id);
8189             Insert_After (N, Proc);
8190             Analyze (Proc);
8191
8192          else
8193
8194             --  Find already created invariant subprogram, insert body of
8195             --  component invariant proc in its body, and add call after
8196             --  other checks.
8197
8198             declare
8199                Bod    : Node_Id;
8200                Inv_Id : constant Entity_Id := Invariant_Procedure (Typ);
8201                Call   : constant Node_Id   :=
8202                  Make_Procedure_Call_Statement (Sloc (N),
8203                    Name                   => New_Occurrence_Of (Proc_Id, Loc),
8204                    Parameter_Associations =>
8205                      New_List
8206                        (New_Occurrence_Of (First_Formal (Inv_Id), Loc)));
8207
8208             begin
8209                --  The invariant  body has not been analyzed yet, so we do a
8210                --  sequential search forward, and retrieve it by name.
8211
8212                Bod := Next (N);
8213                while Present (Bod) loop
8214                   exit when Nkind (Bod) = N_Subprogram_Body
8215                     and then Chars (Defining_Entity (Bod)) = Chars (Inv_Id);
8216                   Next (Bod);
8217                end loop;
8218
8219                --  If the body is not found, it is the case of an invariant
8220                --  appearing on a full declaration in a private part, in
8221                --  which case the type has been frozen but the invariant
8222                --  procedure for the composite type not created yet. Create
8223                --  body now.
8224
8225                if No (Bod) then
8226                   Build_Invariant_Procedure (Typ, Parent (Current_Scope));
8227                   Bod := Unit_Declaration_Node
8228                     (Corresponding_Body (Unit_Declaration_Node (Inv_Id)));
8229                end if;
8230
8231                Append_To (Declarations (Bod), Proc);
8232                Append_To (Statements (Handled_Statement_Sequence (Bod)), Call);
8233                Analyze (Proc);
8234                Analyze (Call);
8235             end;
8236          end if;
8237       end if;
8238    end Insert_Component_Invariant_Checks;
8239
8240    ----------------------------
8241    -- Initialization_Warning --
8242    ----------------------------
8243
8244    procedure Initialization_Warning (E : Entity_Id) is
8245       Warning_Needed : Boolean;
8246
8247    begin
8248       Warning_Needed := False;
8249
8250       if Ekind (Current_Scope) = E_Package
8251         and then Static_Elaboration_Desired (Current_Scope)
8252       then
8253          if Is_Type (E) then
8254             if Is_Record_Type (E) then
8255                if Has_Discriminants (E)
8256                  or else Is_Limited_Type (E)
8257                  or else Has_Non_Standard_Rep (E)
8258                then
8259                   Warning_Needed := True;
8260
8261                else
8262                   --  Verify that at least one component has an initialization
8263                   --  expression. No need for a warning on a type if all its
8264                   --  components have no initialization.
8265
8266                   declare
8267                      Comp : Entity_Id;
8268
8269                   begin
8270                      Comp := First_Component (E);
8271                      while Present (Comp) loop
8272                         if Ekind (Comp) = E_Discriminant
8273                           or else
8274                             (Nkind (Parent (Comp)) = N_Component_Declaration
8275                               and then Present (Expression (Parent (Comp))))
8276                         then
8277                            Warning_Needed := True;
8278                            exit;
8279                         end if;
8280
8281                         Next_Component (Comp);
8282                      end loop;
8283                   end;
8284                end if;
8285
8286                if Warning_Needed then
8287                   Error_Msg_N
8288                     ("Objects of the type cannot be initialized statically "
8289                      & "by default??", Parent (E));
8290                end if;
8291             end if;
8292
8293          else
8294             Error_Msg_N ("Object cannot be initialized statically??", E);
8295          end if;
8296       end if;
8297    end Initialization_Warning;
8298
8299    ------------------
8300    -- Init_Formals --
8301    ------------------
8302
8303    function Init_Formals (Typ : Entity_Id) return List_Id is
8304       Loc     : constant Source_Ptr := Sloc (Typ);
8305       Formals : List_Id;
8306
8307    begin
8308       --  First parameter is always _Init : in out typ. Note that we need this
8309       --  to be in/out because in the case of the task record value, there
8310       --  are default record fields (_Priority, _Size, -Task_Info) that may
8311       --  be referenced in the generated initialization routine.
8312
8313       Formals := New_List (
8314         Make_Parameter_Specification (Loc,
8315           Defining_Identifier => Make_Defining_Identifier (Loc, Name_uInit),
8316           In_Present          => True,
8317           Out_Present         => True,
8318           Parameter_Type      => New_Occurrence_Of (Typ, Loc)));
8319
8320       --  For task record value, or type that contains tasks, add two more
8321       --  formals, _Master : Master_Id and _Chain : in out Activation_Chain
8322       --  We also add these parameters for the task record type case.
8323
8324       if Has_Task (Typ)
8325         or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
8326       then
8327          Append_To (Formals,
8328            Make_Parameter_Specification (Loc,
8329              Defining_Identifier =>
8330                Make_Defining_Identifier (Loc, Name_uMaster),
8331              Parameter_Type      =>
8332                New_Occurrence_Of (RTE (RE_Master_Id), Loc)));
8333
8334          --  Add _Chain (not done for sequential elaboration policy, see
8335          --  comment for Create_Restricted_Task_Sequential in s-tarest.ads).
8336
8337          if Partition_Elaboration_Policy /= 'S' then
8338             Append_To (Formals,
8339               Make_Parameter_Specification (Loc,
8340                 Defining_Identifier =>
8341                   Make_Defining_Identifier (Loc, Name_uChain),
8342                 In_Present          => True,
8343                 Out_Present         => True,
8344                 Parameter_Type      =>
8345                   New_Occurrence_Of (RTE (RE_Activation_Chain), Loc)));
8346          end if;
8347
8348          Append_To (Formals,
8349            Make_Parameter_Specification (Loc,
8350              Defining_Identifier =>
8351                Make_Defining_Identifier (Loc, Name_uTask_Name),
8352              In_Present          => True,
8353              Parameter_Type      => New_Occurrence_Of (Standard_String, Loc)));
8354       end if;
8355
8356       return Formals;
8357
8358    exception
8359       when RE_Not_Available =>
8360          return Empty_List;
8361    end Init_Formals;
8362
8363    -------------------------
8364    -- Init_Secondary_Tags --
8365    -------------------------
8366
8367    procedure Init_Secondary_Tags
8368      (Typ            : Entity_Id;
8369       Target         : Node_Id;
8370       Stmts_List     : List_Id;
8371       Fixed_Comps    : Boolean := True;
8372       Variable_Comps : Boolean := True)
8373    is
8374       Loc : constant Source_Ptr := Sloc (Target);
8375
8376       --  Inherit the C++ tag of the secondary dispatch table of Typ associated
8377       --  with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
8378
8379       procedure Initialize_Tag
8380         (Typ       : Entity_Id;
8381          Iface     : Entity_Id;
8382          Tag_Comp  : Entity_Id;
8383          Iface_Tag : Node_Id);
8384       --  Initialize the tag of the secondary dispatch table of Typ associated
8385       --  with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
8386       --  Compiling under the CPP full ABI compatibility mode, if the ancestor
8387       --  of Typ CPP tagged type we generate code to inherit the contents of
8388       --  the dispatch table directly from the ancestor.
8389
8390       --------------------
8391       -- Initialize_Tag --
8392       --------------------
8393
8394       procedure Initialize_Tag
8395         (Typ       : Entity_Id;
8396          Iface     : Entity_Id;
8397          Tag_Comp  : Entity_Id;
8398          Iface_Tag : Node_Id)
8399       is
8400          Comp_Typ           : Entity_Id;
8401          Offset_To_Top_Comp : Entity_Id := Empty;
8402
8403       begin
8404          --  Initialize pointer to secondary DT associated with the interface
8405
8406          if not Is_Ancestor (Iface, Typ, Use_Full_View => True) then
8407             Append_To (Stmts_List,
8408               Make_Assignment_Statement (Loc,
8409                 Name       =>
8410                   Make_Selected_Component (Loc,
8411                     Prefix        => New_Copy_Tree (Target),
8412                     Selector_Name => New_Occurrence_Of (Tag_Comp, Loc)),
8413                 Expression =>
8414                   New_Occurrence_Of (Iface_Tag, Loc)));
8415          end if;
8416
8417          Comp_Typ := Scope (Tag_Comp);
8418
8419          --  Initialize the entries of the table of interfaces. We generate a
8420          --  different call when the parent of the type has variable size
8421          --  components.
8422
8423          if Comp_Typ /= Etype (Comp_Typ)
8424            and then Is_Variable_Size_Record (Etype (Comp_Typ))
8425            and then Chars (Tag_Comp) /= Name_uTag
8426          then
8427             pragma Assert (Present (DT_Offset_To_Top_Func (Tag_Comp)));
8428
8429             --  Issue error if Set_Dynamic_Offset_To_Top is not available in a
8430             --  configurable run-time environment.
8431
8432             if not RTE_Available (RE_Set_Dynamic_Offset_To_Top) then
8433                Error_Msg_CRT
8434                  ("variable size record with interface types", Typ);
8435                return;
8436             end if;
8437
8438             --  Generate:
8439             --    Set_Dynamic_Offset_To_Top
8440             --      (This         => Init,
8441             --       Interface_T  => Iface'Tag,
8442             --       Offset_Value => n,
8443             --       Offset_Func  => Fn'Address)
8444
8445             Append_To (Stmts_List,
8446               Make_Procedure_Call_Statement (Loc,
8447                 Name                   =>
8448                   New_Occurrence_Of (RTE (RE_Set_Dynamic_Offset_To_Top), Loc),
8449                 Parameter_Associations => New_List (
8450                   Make_Attribute_Reference (Loc,
8451                     Prefix         => New_Copy_Tree (Target),
8452                     Attribute_Name => Name_Address),
8453
8454                   Unchecked_Convert_To (RTE (RE_Tag),
8455                     New_Occurrence_Of
8456                       (Node (First_Elmt (Access_Disp_Table (Iface))),
8457                        Loc)),
8458
8459                   Unchecked_Convert_To
8460                     (RTE (RE_Storage_Offset),
8461                      Make_Attribute_Reference (Loc,
8462                        Prefix         =>
8463                          Make_Selected_Component (Loc,
8464                            Prefix        => New_Copy_Tree (Target),
8465                            Selector_Name =>
8466                              New_Occurrence_Of (Tag_Comp, Loc)),
8467                        Attribute_Name => Name_Position)),
8468
8469                   Unchecked_Convert_To (RTE (RE_Offset_To_Top_Function_Ptr),
8470                     Make_Attribute_Reference (Loc,
8471                       Prefix => New_Occurrence_Of
8472                                   (DT_Offset_To_Top_Func (Tag_Comp), Loc),
8473                       Attribute_Name => Name_Address)))));
8474
8475             --  In this case the next component stores the value of the offset
8476             --  to the top.
8477
8478             Offset_To_Top_Comp := Next_Entity (Tag_Comp);
8479             pragma Assert (Present (Offset_To_Top_Comp));
8480
8481             Append_To (Stmts_List,
8482               Make_Assignment_Statement (Loc,
8483                 Name       =>
8484                   Make_Selected_Component (Loc,
8485                     Prefix        => New_Copy_Tree (Target),
8486                     Selector_Name =>
8487                       New_Occurrence_Of (Offset_To_Top_Comp, Loc)),
8488
8489                 Expression =>
8490                   Make_Attribute_Reference (Loc,
8491                     Prefix       =>
8492                       Make_Selected_Component (Loc,
8493                         Prefix        => New_Copy_Tree (Target),
8494                         Selector_Name => New_Occurrence_Of (Tag_Comp, Loc)),
8495                   Attribute_Name => Name_Position)));
8496
8497          --  Normal case: No discriminants in the parent type
8498
8499          else
8500             --  Don't need to set any value if this interface shares the
8501             --  primary dispatch table.
8502
8503             if not Is_Ancestor (Iface, Typ, Use_Full_View => True) then
8504                Append_To (Stmts_List,
8505                  Build_Set_Static_Offset_To_Top (Loc,
8506                    Iface_Tag    => New_Occurrence_Of (Iface_Tag, Loc),
8507                    Offset_Value =>
8508                      Unchecked_Convert_To (RTE (RE_Storage_Offset),
8509                        Make_Attribute_Reference (Loc,
8510                          Prefix         =>
8511                            Make_Selected_Component (Loc,
8512                              Prefix        => New_Copy_Tree (Target),
8513                              Selector_Name =>
8514                                New_Occurrence_Of (Tag_Comp, Loc)),
8515                          Attribute_Name => Name_Position))));
8516             end if;
8517
8518             --  Generate:
8519             --    Register_Interface_Offset
8520             --      (This         => Init,
8521             --       Interface_T  => Iface'Tag,
8522             --       Is_Constant  => True,
8523             --       Offset_Value => n,
8524             --       Offset_Func  => null);
8525
8526             if RTE_Available (RE_Register_Interface_Offset) then
8527                Append_To (Stmts_List,
8528                  Make_Procedure_Call_Statement (Loc,
8529                    Name                   =>
8530                      New_Occurrence_Of
8531                        (RTE (RE_Register_Interface_Offset), Loc),
8532                    Parameter_Associations => New_List (
8533                      Make_Attribute_Reference (Loc,
8534                        Prefix         => New_Copy_Tree (Target),
8535                        Attribute_Name => Name_Address),
8536
8537                      Unchecked_Convert_To (RTE (RE_Tag),
8538                        New_Occurrence_Of
8539                          (Node (First_Elmt (Access_Disp_Table (Iface))), Loc)),
8540
8541                      New_Occurrence_Of (Standard_True, Loc),
8542
8543                      Unchecked_Convert_To (RTE (RE_Storage_Offset),
8544                        Make_Attribute_Reference (Loc,
8545                          Prefix         =>
8546                            Make_Selected_Component (Loc,
8547                              Prefix         => New_Copy_Tree (Target),
8548                              Selector_Name  =>
8549                                New_Occurrence_Of (Tag_Comp, Loc)),
8550                          Attribute_Name => Name_Position)),
8551
8552                      Make_Null (Loc))));
8553             end if;
8554          end if;
8555       end Initialize_Tag;
8556
8557       --  Local variables
8558
8559       Full_Typ         : Entity_Id;
8560       Ifaces_List      : Elist_Id;
8561       Ifaces_Comp_List : Elist_Id;
8562       Ifaces_Tag_List  : Elist_Id;
8563       Iface_Elmt       : Elmt_Id;
8564       Iface_Comp_Elmt  : Elmt_Id;
8565       Iface_Tag_Elmt   : Elmt_Id;
8566       Tag_Comp         : Node_Id;
8567       In_Variable_Pos  : Boolean;
8568
8569    --  Start of processing for Init_Secondary_Tags
8570
8571    begin
8572       --  Handle private types
8573
8574       if Present (Full_View (Typ)) then
8575          Full_Typ := Full_View (Typ);
8576       else
8577          Full_Typ := Typ;
8578       end if;
8579
8580       Collect_Interfaces_Info
8581         (Full_Typ, Ifaces_List, Ifaces_Comp_List, Ifaces_Tag_List);
8582
8583       Iface_Elmt      := First_Elmt (Ifaces_List);
8584       Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
8585       Iface_Tag_Elmt  := First_Elmt (Ifaces_Tag_List);
8586       while Present (Iface_Elmt) loop
8587          Tag_Comp := Node (Iface_Comp_Elmt);
8588
8589          --  Check if parent of record type has variable size components
8590
8591          In_Variable_Pos := Scope (Tag_Comp) /= Etype (Scope (Tag_Comp))
8592            and then Is_Variable_Size_Record (Etype (Scope (Tag_Comp)));
8593
8594          --  If we are compiling under the CPP full ABI compatibility mode and
8595          --  the ancestor is a CPP_Pragma tagged type then we generate code to
8596          --  initialize the secondary tag components from tags that reference
8597          --  secondary tables filled with copy of parent slots.
8598
8599          if Is_CPP_Class (Root_Type (Full_Typ)) then
8600
8601             --  Reject interface components located at variable offset in
8602             --  C++ derivations. This is currently unsupported.
8603
8604             if not Fixed_Comps and then In_Variable_Pos then
8605
8606                --  Locate the first dynamic component of the record. Done to
8607                --  improve the text of the warning.
8608
8609                declare
8610                   Comp     : Entity_Id;
8611                   Comp_Typ : Entity_Id;
8612
8613                begin
8614                   Comp := First_Entity (Typ);
8615                   while Present (Comp) loop
8616                      Comp_Typ := Etype (Comp);
8617
8618                      if Ekind (Comp) /= E_Discriminant
8619                        and then not Is_Tag (Comp)
8620                      then
8621                         exit when
8622                           (Is_Record_Type (Comp_Typ)
8623                             and then
8624                               Is_Variable_Size_Record (Base_Type (Comp_Typ)))
8625                          or else
8626                            (Is_Array_Type (Comp_Typ)
8627                              and then Is_Variable_Size_Array (Comp_Typ));
8628                      end if;
8629
8630                      Next_Entity (Comp);
8631                   end loop;
8632
8633                   pragma Assert (Present (Comp));
8634                   Error_Msg_Node_2 := Comp;
8635                   Error_Msg_NE
8636                     ("parent type & with dynamic component & cannot be parent"
8637                      & " of 'C'P'P derivation if new interfaces are present",
8638                      Typ, Scope (Original_Record_Component (Comp)));
8639
8640                   Error_Msg_Sloc :=
8641                     Sloc (Scope (Original_Record_Component (Comp)));
8642                   Error_Msg_NE
8643                     ("type derived from 'C'P'P type & defined #",
8644                      Typ, Scope (Original_Record_Component (Comp)));
8645
8646                   --  Avoid duplicated warnings
8647
8648                   exit;
8649                end;
8650
8651             --  Initialize secondary tags
8652
8653             else
8654                Append_To (Stmts_List,
8655                  Make_Assignment_Statement (Loc,
8656                    Name =>
8657                      Make_Selected_Component (Loc,
8658                        Prefix => New_Copy_Tree (Target),
8659                        Selector_Name =>
8660                          New_Occurrence_Of (Node (Iface_Comp_Elmt), Loc)),
8661                    Expression =>
8662                      New_Occurrence_Of (Node (Iface_Tag_Elmt), Loc)));
8663             end if;
8664
8665          --  Otherwise generate code to initialize the tag
8666
8667          else
8668             if (In_Variable_Pos and then Variable_Comps)
8669               or else (not In_Variable_Pos and then Fixed_Comps)
8670             then
8671                Initialize_Tag (Full_Typ,
8672                  Iface     => Node (Iface_Elmt),
8673                  Tag_Comp  => Tag_Comp,
8674                  Iface_Tag => Node (Iface_Tag_Elmt));
8675             end if;
8676          end if;
8677
8678          Next_Elmt (Iface_Elmt);
8679          Next_Elmt (Iface_Comp_Elmt);
8680          Next_Elmt (Iface_Tag_Elmt);
8681       end loop;
8682    end Init_Secondary_Tags;
8683
8684    ------------------------
8685    -- Is_User_Defined_Eq --
8686    ------------------------
8687
8688    function Is_User_Defined_Equality (Prim : Node_Id) return Boolean is
8689    begin
8690       return Chars (Prim) = Name_Op_Eq
8691         and then Etype (First_Formal (Prim)) =
8692                  Etype (Next_Formal (First_Formal (Prim)))
8693         and then Base_Type (Etype (Prim)) = Standard_Boolean;
8694    end Is_User_Defined_Equality;
8695
8696    ----------------------------------------
8697    -- Make_Controlling_Function_Wrappers --
8698    ----------------------------------------
8699
8700    procedure Make_Controlling_Function_Wrappers
8701      (Tag_Typ   : Entity_Id;
8702       Decl_List : out List_Id;
8703       Body_List : out List_Id)
8704    is
8705       Loc         : constant Source_Ptr := Sloc (Tag_Typ);
8706       Prim_Elmt   : Elmt_Id;
8707       Subp        : Entity_Id;
8708       Actual_List : List_Id;
8709       Formal_List : List_Id;
8710       Formal      : Entity_Id;
8711       Par_Formal  : Entity_Id;
8712       Formal_Node : Node_Id;
8713       Func_Body   : Node_Id;
8714       Func_Decl   : Node_Id;
8715       Func_Spec   : Node_Id;
8716       Return_Stmt : Node_Id;
8717
8718    begin
8719       Decl_List := New_List;
8720       Body_List := New_List;
8721
8722       Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
8723       while Present (Prim_Elmt) loop
8724          Subp := Node (Prim_Elmt);
8725
8726          --  If a primitive function with a controlling result of the type has
8727          --  not been overridden by the user, then we must create a wrapper
8728          --  function here that effectively overrides it and invokes the
8729          --  (non-abstract) parent function. This can only occur for a null
8730          --  extension. Note that functions with anonymous controlling access
8731          --  results don't qualify and must be overridden. We also exclude
8732          --  Input attributes, since each type will have its own version of
8733          --  Input constructed by the expander. The test for Comes_From_Source
8734          --  is needed to distinguish inherited operations from renamings
8735          --  (which also have Alias set). We exclude internal entities with
8736          --  Interface_Alias to avoid generating duplicated wrappers since
8737          --  the primitive which covers the interface is also available in
8738          --  the list of primitive operations.
8739
8740          --  The function may be abstract, or require_Overriding may be set
8741          --  for it, because tests for null extensions may already have reset
8742          --  the Is_Abstract_Subprogram_Flag. If Requires_Overriding is not
8743          --  set, functions that need wrappers are recognized by having an
8744          --  alias that returns the parent type.
8745
8746          if Comes_From_Source (Subp)
8747            or else No (Alias (Subp))
8748            or else Present (Interface_Alias (Subp))
8749            or else Ekind (Subp) /= E_Function
8750            or else not Has_Controlling_Result (Subp)
8751            or else Is_Access_Type (Etype (Subp))
8752            or else Is_Abstract_Subprogram (Alias (Subp))
8753            or else Is_TSS (Subp, TSS_Stream_Input)
8754          then
8755             goto Next_Prim;
8756
8757          elsif Is_Abstract_Subprogram (Subp)
8758            or else Requires_Overriding (Subp)
8759            or else
8760              (Is_Null_Extension (Etype (Subp))
8761                and then Etype (Alias (Subp)) /= Etype (Subp))
8762          then
8763             Formal_List := No_List;
8764             Formal := First_Formal (Subp);
8765
8766             if Present (Formal) then
8767                Formal_List := New_List;
8768
8769                while Present (Formal) loop
8770                   Append
8771                     (Make_Parameter_Specification
8772                        (Loc,
8773                         Defining_Identifier =>
8774                           Make_Defining_Identifier (Sloc (Formal),
8775                             Chars => Chars (Formal)),
8776                         In_Present  => In_Present (Parent (Formal)),
8777                         Out_Present => Out_Present (Parent (Formal)),
8778                         Null_Exclusion_Present =>
8779                           Null_Exclusion_Present (Parent (Formal)),
8780                         Parameter_Type =>
8781                           New_Occurrence_Of (Etype (Formal), Loc),
8782                         Expression =>
8783                           New_Copy_Tree (Expression (Parent (Formal)))),
8784                      Formal_List);
8785
8786                   Next_Formal (Formal);
8787                end loop;
8788             end if;
8789
8790             Func_Spec :=
8791               Make_Function_Specification (Loc,
8792                 Defining_Unit_Name       =>
8793                   Make_Defining_Identifier (Loc,
8794                     Chars => Chars (Subp)),
8795                 Parameter_Specifications => Formal_List,
8796                 Result_Definition        =>
8797                   New_Occurrence_Of (Etype (Subp), Loc));
8798
8799             Func_Decl := Make_Subprogram_Declaration (Loc, Func_Spec);
8800             Append_To (Decl_List, Func_Decl);
8801
8802             --  Build a wrapper body that calls the parent function. The body
8803             --  contains a single return statement that returns an extension
8804             --  aggregate whose ancestor part is a call to the parent function,
8805             --  passing the formals as actuals (with any controlling arguments
8806             --  converted to the types of the corresponding formals of the
8807             --  parent function, which might be anonymous access types), and
8808             --  having a null extension.
8809
8810             Formal      := First_Formal (Subp);
8811             Par_Formal  := First_Formal (Alias (Subp));
8812             Formal_Node := First (Formal_List);
8813
8814             if Present (Formal) then
8815                Actual_List := New_List;
8816             else
8817                Actual_List := No_List;
8818             end if;
8819
8820             while Present (Formal) loop
8821                if Is_Controlling_Formal (Formal) then
8822                   Append_To (Actual_List,
8823                     Make_Type_Conversion (Loc,
8824                       Subtype_Mark =>
8825                         New_Occurrence_Of (Etype (Par_Formal), Loc),
8826                       Expression   =>
8827                         New_Occurrence_Of
8828                           (Defining_Identifier (Formal_Node), Loc)));
8829                else
8830                   Append_To
8831                     (Actual_List,
8832                      New_Occurrence_Of
8833                        (Defining_Identifier (Formal_Node), Loc));
8834                end if;
8835
8836                Next_Formal (Formal);
8837                Next_Formal (Par_Formal);
8838                Next (Formal_Node);
8839             end loop;
8840
8841             Return_Stmt :=
8842               Make_Simple_Return_Statement (Loc,
8843                 Expression =>
8844                   Make_Extension_Aggregate (Loc,
8845                     Ancestor_Part       =>
8846                       Make_Function_Call (Loc,
8847                         Name                   =>
8848                           New_Occurrence_Of (Alias (Subp), Loc),
8849                         Parameter_Associations => Actual_List),
8850                     Null_Record_Present => True));
8851
8852             Func_Body :=
8853               Make_Subprogram_Body (Loc,
8854                 Specification              => New_Copy_Tree (Func_Spec),
8855                 Declarations               => Empty_List,
8856                 Handled_Statement_Sequence =>
8857                   Make_Handled_Sequence_Of_Statements (Loc,
8858                     Statements => New_List (Return_Stmt)));
8859
8860             Set_Defining_Unit_Name
8861               (Specification (Func_Body),
8862                 Make_Defining_Identifier (Loc, Chars (Subp)));
8863
8864             Append_To (Body_List, Func_Body);
8865
8866             --  Replace the inherited function with the wrapper function in the
8867             --  primitive operations list. We add the minimum decoration needed
8868             --  to override interface primitives.
8869
8870             Set_Ekind (Defining_Unit_Name (Func_Spec), E_Function);
8871
8872             Override_Dispatching_Operation
8873               (Tag_Typ, Subp, New_Op => Defining_Unit_Name (Func_Spec),
8874                Is_Wrapper => True);
8875          end if;
8876
8877       <<Next_Prim>>
8878          Next_Elmt (Prim_Elmt);
8879       end loop;
8880    end Make_Controlling_Function_Wrappers;
8881
8882    -------------------
8883    --  Make_Eq_Body --
8884    -------------------
8885
8886    function Make_Eq_Body
8887      (Typ     : Entity_Id;
8888       Eq_Name : Name_Id) return Node_Id
8889    is
8890       Loc          : constant Source_Ptr := Sloc (Parent (Typ));
8891       Decl         : Node_Id;
8892       Def          : constant Node_Id := Parent (Typ);
8893       Stmts        : constant List_Id := New_List;
8894       Variant_Case : Boolean := Has_Discriminants (Typ);
8895       Comps        : Node_Id := Empty;
8896       Typ_Def      : Node_Id := Type_Definition (Def);
8897
8898    begin
8899       Decl :=
8900         Predef_Spec_Or_Body (Loc,
8901           Tag_Typ => Typ,
8902           Name    => Eq_Name,
8903           Profile => New_List (
8904             Make_Parameter_Specification (Loc,
8905               Defining_Identifier =>
8906                 Make_Defining_Identifier (Loc, Name_X),
8907               Parameter_Type      => New_Occurrence_Of (Typ, Loc)),
8908
8909             Make_Parameter_Specification (Loc,
8910               Defining_Identifier =>
8911                 Make_Defining_Identifier (Loc, Name_Y),
8912               Parameter_Type      => New_Occurrence_Of (Typ, Loc))),
8913
8914           Ret_Type => Standard_Boolean,
8915           For_Body => True);
8916
8917       if Variant_Case then
8918          if Nkind (Typ_Def) = N_Derived_Type_Definition then
8919             Typ_Def := Record_Extension_Part (Typ_Def);
8920          end if;
8921
8922          if Present (Typ_Def) then
8923             Comps := Component_List (Typ_Def);
8924          end if;
8925
8926          Variant_Case :=
8927            Present (Comps) and then Present (Variant_Part (Comps));
8928       end if;
8929
8930       if Variant_Case then
8931          Append_To (Stmts,
8932            Make_Eq_If (Typ, Discriminant_Specifications (Def)));
8933          Append_List_To (Stmts, Make_Eq_Case (Typ, Comps));
8934          Append_To (Stmts,
8935            Make_Simple_Return_Statement (Loc,
8936              Expression => New_Occurrence_Of (Standard_True, Loc)));
8937
8938       else
8939          Append_To (Stmts,
8940            Make_Simple_Return_Statement (Loc,
8941              Expression =>
8942                Expand_Record_Equality
8943                  (Typ,
8944                   Typ    => Typ,
8945                   Lhs    => Make_Identifier (Loc, Name_X),
8946                   Rhs    => Make_Identifier (Loc, Name_Y),
8947                   Bodies => Declarations (Decl))));
8948       end if;
8949
8950       Set_Handled_Statement_Sequence
8951         (Decl, Make_Handled_Sequence_Of_Statements (Loc, Stmts));
8952       return Decl;
8953    end Make_Eq_Body;
8954
8955    ------------------
8956    -- Make_Eq_Case --
8957    ------------------
8958
8959    --  <Make_Eq_If shared components>
8960
8961    --  case X.D1 is
8962    --     when V1 => <Make_Eq_Case> on subcomponents
8963    --     ...
8964    --     when Vn => <Make_Eq_Case> on subcomponents
8965    --  end case;
8966
8967    function Make_Eq_Case
8968      (E      : Entity_Id;
8969       CL     : Node_Id;
8970       Discrs : Elist_Id := New_Elmt_List) return List_Id
8971    is
8972       Loc      : constant Source_Ptr := Sloc (E);
8973       Result   : constant List_Id    := New_List;
8974       Variant  : Node_Id;
8975       Alt_List : List_Id;
8976
8977       function Corresponding_Formal (C : Node_Id) return Entity_Id;
8978       --  Given the discriminant that controls a given variant of an unchecked
8979       --  union, find the formal of the equality function that carries the
8980       --  inferred value of the discriminant.
8981
8982       function External_Name (E : Entity_Id) return Name_Id;
8983       --  The value of a given discriminant is conveyed in the corresponding
8984       --  formal parameter of the equality routine. The name of this formal
8985       --  parameter carries a one-character suffix which is removed here.
8986
8987       --------------------------
8988       -- Corresponding_Formal --
8989       --------------------------
8990
8991       function Corresponding_Formal (C : Node_Id) return Entity_Id is
8992          Discr : constant Entity_Id := Entity (Name (Variant_Part (C)));
8993          Elm   : Elmt_Id;
8994
8995       begin
8996          Elm := First_Elmt (Discrs);
8997          while Present (Elm) loop
8998             if Chars (Discr) = External_Name (Node (Elm)) then
8999                return Node (Elm);
9000             end if;
9001
9002             Next_Elmt (Elm);
9003          end loop;
9004
9005          --  A formal of the proper name must be found
9006
9007          raise Program_Error;
9008       end Corresponding_Formal;
9009
9010       -------------------
9011       -- External_Name --
9012       -------------------
9013
9014       function External_Name (E : Entity_Id) return Name_Id is
9015       begin
9016          Get_Name_String (Chars (E));
9017          Name_Len := Name_Len - 1;
9018          return Name_Find;
9019       end External_Name;
9020
9021    --  Start of processing for Make_Eq_Case
9022
9023    begin
9024       Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
9025
9026       if No (Variant_Part (CL)) then
9027          return Result;
9028       end if;
9029
9030       Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
9031
9032       if No (Variant) then
9033          return Result;
9034       end if;
9035
9036       Alt_List := New_List;
9037       while Present (Variant) loop
9038          Append_To (Alt_List,
9039            Make_Case_Statement_Alternative (Loc,
9040              Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
9041              Statements =>
9042                Make_Eq_Case (E, Component_List (Variant), Discrs)));
9043          Next_Non_Pragma (Variant);
9044       end loop;
9045
9046       --  If we have an Unchecked_Union, use one of the parameters of the
9047       --  enclosing equality routine that captures the discriminant, to use
9048       --  as the expression in the generated case statement.
9049
9050       if Is_Unchecked_Union (E) then
9051          Append_To (Result,
9052            Make_Case_Statement (Loc,
9053              Expression =>
9054                New_Occurrence_Of (Corresponding_Formal (CL), Loc),
9055              Alternatives => Alt_List));
9056
9057       else
9058          Append_To (Result,
9059            Make_Case_Statement (Loc,
9060              Expression =>
9061                Make_Selected_Component (Loc,
9062                  Prefix        => Make_Identifier (Loc, Name_X),
9063                  Selector_Name => New_Copy (Name (Variant_Part (CL)))),
9064              Alternatives => Alt_List));
9065       end if;
9066
9067       return Result;
9068    end Make_Eq_Case;
9069
9070    ----------------
9071    -- Make_Eq_If --
9072    ----------------
9073
9074    --  Generates:
9075
9076    --    if
9077    --      X.C1 /= Y.C1
9078    --        or else
9079    --      X.C2 /= Y.C2
9080    --        ...
9081    --    then
9082    --       return False;
9083    --    end if;
9084
9085    --  or a null statement if the list L is empty
9086
9087    function Make_Eq_If
9088      (E : Entity_Id;
9089       L : List_Id) return Node_Id
9090    is
9091       Loc        : constant Source_Ptr := Sloc (E);
9092       C          : Node_Id;
9093       Field_Name : Name_Id;
9094       Cond       : Node_Id;
9095
9096    begin
9097       if No (L) then
9098          return Make_Null_Statement (Loc);
9099
9100       else
9101          Cond := Empty;
9102
9103          C := First_Non_Pragma (L);
9104          while Present (C) loop
9105             Field_Name := Chars (Defining_Identifier (C));
9106
9107             --  The tags must not be compared: they are not part of the value.
9108             --  Ditto for parent interfaces because their equality operator is
9109             --  abstract.
9110
9111             --  Note also that in the following, we use Make_Identifier for
9112             --  the component names. Use of New_Occurrence_Of to identify the
9113             --  components would be incorrect because the wrong entities for
9114             --  discriminants could be picked up in the private type case.
9115
9116             if Field_Name = Name_uParent
9117               and then Is_Interface (Etype (Defining_Identifier (C)))
9118             then
9119                null;
9120
9121             elsif Field_Name /= Name_uTag then
9122                Evolve_Or_Else (Cond,
9123                  Make_Op_Ne (Loc,
9124                    Left_Opnd =>
9125                      Make_Selected_Component (Loc,
9126                        Prefix        => Make_Identifier (Loc, Name_X),
9127                        Selector_Name => Make_Identifier (Loc, Field_Name)),
9128
9129                    Right_Opnd =>
9130                      Make_Selected_Component (Loc,
9131                        Prefix        => Make_Identifier (Loc, Name_Y),
9132                        Selector_Name => Make_Identifier (Loc, Field_Name))));
9133             end if;
9134
9135             Next_Non_Pragma (C);
9136          end loop;
9137
9138          if No (Cond) then
9139             return Make_Null_Statement (Loc);
9140
9141          else
9142             return
9143               Make_Implicit_If_Statement (E,
9144                 Condition       => Cond,
9145                 Then_Statements => New_List (
9146                   Make_Simple_Return_Statement (Loc,
9147                     Expression => New_Occurrence_Of (Standard_False, Loc))));
9148          end if;
9149       end if;
9150    end Make_Eq_If;
9151
9152    -------------------
9153    -- Make_Neq_Body --
9154    -------------------
9155
9156    function Make_Neq_Body (Tag_Typ : Entity_Id) return Node_Id is
9157
9158       function Is_Predefined_Neq_Renaming (Prim : Node_Id) return Boolean;
9159       --  Returns true if Prim is a renaming of an unresolved predefined
9160       --  inequality operation.
9161
9162       --------------------------------
9163       -- Is_Predefined_Neq_Renaming --
9164       --------------------------------
9165
9166       function Is_Predefined_Neq_Renaming (Prim : Node_Id) return Boolean is
9167       begin
9168          return Chars (Prim) /= Name_Op_Ne
9169            and then Present (Alias (Prim))
9170            and then Comes_From_Source (Prim)
9171            and then Is_Intrinsic_Subprogram (Alias (Prim))
9172            and then Chars (Alias (Prim)) = Name_Op_Ne;
9173       end Is_Predefined_Neq_Renaming;
9174
9175       --  Local variables
9176
9177       Loc           : constant Source_Ptr := Sloc (Parent (Tag_Typ));
9178       Stmts         : constant List_Id    := New_List;
9179       Decl          : Node_Id;
9180       Eq_Prim       : Entity_Id;
9181       Left_Op       : Entity_Id;
9182       Renaming_Prim : Entity_Id;
9183       Right_Op      : Entity_Id;
9184       Target        : Entity_Id;
9185
9186    --  Start of processing for Make_Neq_Body
9187
9188    begin
9189       --  For a call on a renaming of a dispatching subprogram that is
9190       --  overridden, if the overriding occurred before the renaming, then
9191       --  the body executed is that of the overriding declaration, even if the
9192       --  overriding declaration is not visible at the place of the renaming;
9193       --  otherwise, the inherited or predefined subprogram is called, see
9194       --  (RM 8.5.4(8))
9195
9196       --  Stage 1: Search for a renaming of the inequality primitive and also
9197       --  search for an overriding of the equality primitive located before the
9198       --  renaming declaration.
9199
9200       declare
9201          Elmt : Elmt_Id;
9202          Prim : Node_Id;
9203
9204       begin
9205          Eq_Prim       := Empty;
9206          Renaming_Prim := Empty;
9207
9208          Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
9209          while Present (Elmt) loop
9210             Prim := Node (Elmt);
9211
9212             if Is_User_Defined_Equality (Prim) and then No (Alias (Prim)) then
9213                if No (Renaming_Prim) then
9214                   pragma Assert (No (Eq_Prim));
9215                   Eq_Prim := Prim;
9216                end if;
9217
9218             elsif Is_Predefined_Neq_Renaming (Prim) then
9219                Renaming_Prim := Prim;
9220             end if;
9221
9222             Next_Elmt (Elmt);
9223          end loop;
9224       end;
9225
9226       --  No further action needed if no renaming was found
9227
9228       if No (Renaming_Prim) then
9229          return Empty;
9230       end if;
9231
9232       --  Stage 2: Replace the renaming declaration by a subprogram declaration
9233       --  (required to add its body)
9234
9235       Decl := Parent (Parent (Renaming_Prim));
9236       Rewrite (Decl,
9237         Make_Subprogram_Declaration (Loc,
9238           Specification => Specification (Decl)));
9239       Set_Analyzed (Decl);
9240
9241       --  Remove the decoration of intrinsic renaming subprogram
9242
9243       Set_Is_Intrinsic_Subprogram (Renaming_Prim, False);
9244       Set_Convention (Renaming_Prim, Convention_Ada);
9245       Set_Alias (Renaming_Prim, Empty);
9246       Set_Has_Completion (Renaming_Prim, False);
9247
9248       --  Stage 3: Build the corresponding body
9249
9250       Left_Op  := First_Formal (Renaming_Prim);
9251       Right_Op := Next_Formal (Left_Op);
9252
9253       Decl :=
9254         Predef_Spec_Or_Body (Loc,
9255           Tag_Typ => Tag_Typ,
9256           Name    => Chars (Renaming_Prim),
9257           Profile => New_List (
9258             Make_Parameter_Specification (Loc,
9259               Defining_Identifier =>
9260                 Make_Defining_Identifier (Loc, Chars (Left_Op)),
9261               Parameter_Type      => New_Occurrence_Of (Tag_Typ, Loc)),
9262
9263             Make_Parameter_Specification (Loc,
9264               Defining_Identifier =>
9265                 Make_Defining_Identifier (Loc, Chars (Right_Op)),
9266               Parameter_Type      => New_Occurrence_Of (Tag_Typ, Loc))),
9267
9268           Ret_Type => Standard_Boolean,
9269           For_Body => True);
9270
9271       --  If the overriding of the equality primitive occurred before the
9272       --  renaming, then generate:
9273
9274       --    function <Neq_Name> (X : Y : Typ) return Boolean is
9275       --    begin
9276       --       return not Oeq (X, Y);
9277       --    end;
9278
9279       if Present (Eq_Prim) then
9280          Target := Eq_Prim;
9281
9282       --  Otherwise build a nested subprogram which performs the predefined
9283       --  evaluation of the equality operator. That is, generate:
9284
9285       --    function <Neq_Name> (X : Y : Typ) return Boolean is
9286       --       function Oeq (X : Y) return Boolean is
9287       --       begin
9288       --          <<body of default implementation>>
9289       --       end;
9290       --    begin
9291       --       return not Oeq (X, Y);
9292       --    end;
9293
9294       else
9295          declare
9296             Local_Subp : Node_Id;
9297          begin
9298             Local_Subp := Make_Eq_Body (Tag_Typ, Name_Op_Eq);
9299             Set_Declarations (Decl, New_List (Local_Subp));
9300             Target := Defining_Entity (Local_Subp);
9301          end;
9302       end if;
9303
9304       Append_To (Stmts,
9305         Make_Simple_Return_Statement (Loc,
9306           Expression =>
9307             Make_Op_Not (Loc,
9308               Make_Function_Call (Loc,
9309                 Name                   => New_Occurrence_Of (Target, Loc),
9310                 Parameter_Associations => New_List (
9311                   Make_Identifier (Loc, Chars (Left_Op)),
9312                   Make_Identifier (Loc, Chars (Right_Op)))))));
9313
9314       Set_Handled_Statement_Sequence
9315         (Decl, Make_Handled_Sequence_Of_Statements (Loc, Stmts));
9316       return Decl;
9317    end Make_Neq_Body;
9318
9319    -------------------------------
9320    -- Make_Null_Procedure_Specs --
9321    -------------------------------
9322
9323    function Make_Null_Procedure_Specs (Tag_Typ : Entity_Id) return List_Id is
9324       Decl_List      : constant List_Id    := New_List;
9325       Loc            : constant Source_Ptr := Sloc (Tag_Typ);
9326       Formal         : Entity_Id;
9327       Formal_List    : List_Id;
9328       New_Param_Spec : Node_Id;
9329       Parent_Subp    : Entity_Id;
9330       Prim_Elmt      : Elmt_Id;
9331       Subp           : Entity_Id;
9332
9333    begin
9334       Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
9335       while Present (Prim_Elmt) loop
9336          Subp := Node (Prim_Elmt);
9337
9338          --  If a null procedure inherited from an interface has not been
9339          --  overridden, then we build a null procedure declaration to
9340          --  override the inherited procedure.
9341
9342          Parent_Subp := Alias (Subp);
9343
9344          if Present (Parent_Subp)
9345            and then Is_Null_Interface_Primitive (Parent_Subp)
9346          then
9347             Formal_List := No_List;
9348             Formal := First_Formal (Subp);
9349
9350             if Present (Formal) then
9351                Formal_List := New_List;
9352
9353                while Present (Formal) loop
9354
9355                   --  Copy the parameter spec including default expressions
9356
9357                   New_Param_Spec :=
9358                     New_Copy_Tree (Parent (Formal), New_Sloc => Loc);
9359
9360                   --  Generate a new defining identifier for the new formal.
9361                   --  required because New_Copy_Tree does not duplicate
9362                   --  semantic fields (except itypes).
9363
9364                   Set_Defining_Identifier (New_Param_Spec,
9365                     Make_Defining_Identifier (Sloc (Formal),
9366                       Chars => Chars (Formal)));
9367
9368                   --  For controlling arguments we must change their
9369                   --  parameter type to reference the tagged type (instead
9370                   --  of the interface type)
9371
9372                   if Is_Controlling_Formal (Formal) then
9373                      if Nkind (Parameter_Type (Parent (Formal))) = N_Identifier
9374                      then
9375                         Set_Parameter_Type (New_Param_Spec,
9376                           New_Occurrence_Of (Tag_Typ, Loc));
9377
9378                      else pragma Assert
9379                             (Nkind (Parameter_Type (Parent (Formal))) =
9380                                                         N_Access_Definition);
9381                         Set_Subtype_Mark (Parameter_Type (New_Param_Spec),
9382                           New_Occurrence_Of (Tag_Typ, Loc));
9383                      end if;
9384                   end if;
9385
9386                   Append (New_Param_Spec, Formal_List);
9387
9388                   Next_Formal (Formal);
9389                end loop;
9390             end if;
9391
9392             Append_To (Decl_List,
9393               Make_Subprogram_Declaration (Loc,
9394                 Make_Procedure_Specification (Loc,
9395                   Defining_Unit_Name       =>
9396                     Make_Defining_Identifier (Loc, Chars (Subp)),
9397                   Parameter_Specifications => Formal_List,
9398                   Null_Present             => True)));
9399          end if;
9400
9401          Next_Elmt (Prim_Elmt);
9402       end loop;
9403
9404       return Decl_List;
9405    end Make_Null_Procedure_Specs;
9406
9407    -------------------------------------
9408    -- Make_Predefined_Primitive_Specs --
9409    -------------------------------------
9410
9411    procedure Make_Predefined_Primitive_Specs
9412      (Tag_Typ     : Entity_Id;
9413       Predef_List : out List_Id;
9414       Renamed_Eq  : out Entity_Id)
9415    is
9416       function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
9417       --  Returns true if Prim is a renaming of an unresolved predefined
9418       --  equality operation.
9419
9420       -------------------------------
9421       -- Is_Predefined_Eq_Renaming --
9422       -------------------------------
9423
9424       function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
9425       begin
9426          return Chars (Prim) /= Name_Op_Eq
9427            and then Present (Alias (Prim))
9428            and then Comes_From_Source (Prim)
9429            and then Is_Intrinsic_Subprogram (Alias (Prim))
9430            and then Chars (Alias (Prim)) = Name_Op_Eq;
9431       end Is_Predefined_Eq_Renaming;
9432
9433       --  Local variables
9434
9435       Loc       : constant Source_Ptr := Sloc (Tag_Typ);
9436       Res       : constant List_Id    := New_List;
9437       Eq_Name   : Name_Id             := Name_Op_Eq;
9438       Eq_Needed : Boolean;
9439       Eq_Spec   : Node_Id;
9440       Prim      : Elmt_Id;
9441
9442       Has_Predef_Eq_Renaming : Boolean := False;
9443       --  Set to True if Tag_Typ has a primitive that renames the predefined
9444       --  equality operator. Used to implement (RM 8-5-4(8)).
9445
9446    --  Start of processing for Make_Predefined_Primitive_Specs
9447
9448    begin
9449       Renamed_Eq := Empty;
9450
9451       --  Spec of _Size
9452
9453       Append_To (Res, Predef_Spec_Or_Body (Loc,
9454         Tag_Typ => Tag_Typ,
9455         Name    => Name_uSize,
9456         Profile => New_List (
9457           Make_Parameter_Specification (Loc,
9458             Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
9459             Parameter_Type      => New_Occurrence_Of (Tag_Typ, Loc))),
9460
9461         Ret_Type => Standard_Long_Long_Integer));
9462
9463       --  Specs for dispatching stream attributes
9464
9465       declare
9466          Stream_Op_TSS_Names :
9467            constant array (Integer range <>) of TSS_Name_Type :=
9468              (TSS_Stream_Read,
9469               TSS_Stream_Write,
9470               TSS_Stream_Input,
9471               TSS_Stream_Output);
9472
9473       begin
9474          for Op in Stream_Op_TSS_Names'Range loop
9475             if Stream_Operation_OK (Tag_Typ, Stream_Op_TSS_Names (Op)) then
9476                Append_To (Res,
9477                  Predef_Stream_Attr_Spec (Loc, Tag_Typ,
9478                   Stream_Op_TSS_Names (Op)));
9479             end if;
9480          end loop;
9481       end;
9482
9483       --  Spec of "=" is expanded if the type is not limited and if a user
9484       --  defined "=" was not already declared for the non-full view of a
9485       --  private extension
9486
9487       if not Is_Limited_Type (Tag_Typ) then
9488          Eq_Needed := True;
9489          Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9490          while Present (Prim) loop
9491
9492             --  If a primitive is encountered that renames the predefined
9493             --  equality operator before reaching any explicit equality
9494             --  primitive, then we still need to create a predefined equality
9495             --  function, because calls to it can occur via the renaming. A
9496             --  new name is created for the equality to avoid conflicting with
9497             --  any user-defined equality. (Note that this doesn't account for
9498             --  renamings of equality nested within subpackages???)
9499
9500             if Is_Predefined_Eq_Renaming (Node (Prim)) then
9501                Has_Predef_Eq_Renaming := True;
9502                Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
9503
9504             --  User-defined equality
9505
9506             elsif Is_User_Defined_Equality (Node (Prim)) then
9507                if No (Alias (Node (Prim)))
9508                  or else Nkind (Unit_Declaration_Node (Node (Prim))) =
9509                            N_Subprogram_Renaming_Declaration
9510                then
9511                   Eq_Needed := False;
9512                   exit;
9513
9514                --  If the parent is not an interface type and has an abstract
9515                --  equality function explicitly defined in the sources, then
9516                --  the inherited equality is abstract as well, and no body can
9517                --  be created for it.
9518
9519                elsif not Is_Interface (Etype (Tag_Typ))
9520                  and then Present (Alias (Node (Prim)))
9521                  and then Comes_From_Source (Alias (Node (Prim)))
9522                  and then Is_Abstract_Subprogram (Alias (Node (Prim)))
9523                then
9524                   Eq_Needed := False;
9525                   exit;
9526
9527                --  If the type has an equality function corresponding with
9528                --  a primitive defined in an interface type, the inherited
9529                --  equality is abstract as well, and no body can be created
9530                --  for it.
9531
9532                elsif Present (Alias (Node (Prim)))
9533                  and then Comes_From_Source (Ultimate_Alias (Node (Prim)))
9534                  and then
9535                    Is_Interface
9536                      (Find_Dispatching_Type (Ultimate_Alias (Node (Prim))))
9537                then
9538                   Eq_Needed := False;
9539                   exit;
9540                end if;
9541             end if;
9542
9543             Next_Elmt (Prim);
9544          end loop;
9545
9546          --  If a renaming of predefined equality was found but there was no
9547          --  user-defined equality (so Eq_Needed is still true), then set the
9548          --  name back to Name_Op_Eq. But in the case where a user-defined
9549          --  equality was located after such a renaming, then the predefined
9550          --  equality function is still needed, so Eq_Needed must be set back
9551          --  to True.
9552
9553          if Eq_Name /= Name_Op_Eq then
9554             if Eq_Needed then
9555                Eq_Name := Name_Op_Eq;
9556             else
9557                Eq_Needed := True;
9558             end if;
9559          end if;
9560
9561          if Eq_Needed then
9562             Eq_Spec := Predef_Spec_Or_Body (Loc,
9563               Tag_Typ => Tag_Typ,
9564               Name    => Eq_Name,
9565               Profile => New_List (
9566                 Make_Parameter_Specification (Loc,
9567                   Defining_Identifier =>
9568                     Make_Defining_Identifier (Loc, Name_X),
9569                   Parameter_Type      => New_Occurrence_Of (Tag_Typ, Loc)),
9570
9571                 Make_Parameter_Specification (Loc,
9572                   Defining_Identifier =>
9573                     Make_Defining_Identifier (Loc, Name_Y),
9574                   Parameter_Type      => New_Occurrence_Of (Tag_Typ, Loc))),
9575                 Ret_Type => Standard_Boolean);
9576             Append_To (Res, Eq_Spec);
9577
9578             if Has_Predef_Eq_Renaming then
9579                Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
9580
9581                Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9582                while Present (Prim) loop
9583
9584                   --  Any renamings of equality that appeared before an
9585                   --  overriding equality must be updated to refer to the
9586                   --  entity for the predefined equality, otherwise calls via
9587                   --  the renaming would get incorrectly resolved to call the
9588                   --  user-defined equality function.
9589
9590                   if Is_Predefined_Eq_Renaming (Node (Prim)) then
9591                      Set_Alias (Node (Prim), Renamed_Eq);
9592
9593                   --  Exit upon encountering a user-defined equality
9594
9595                   elsif Chars (Node (Prim)) = Name_Op_Eq
9596                     and then No (Alias (Node (Prim)))
9597                   then
9598                      exit;
9599                   end if;
9600
9601                   Next_Elmt (Prim);
9602                end loop;
9603             end if;
9604          end if;
9605
9606          --  Spec for dispatching assignment
9607
9608          Append_To (Res, Predef_Spec_Or_Body (Loc,
9609            Tag_Typ => Tag_Typ,
9610            Name    => Name_uAssign,
9611            Profile => New_List (
9612              Make_Parameter_Specification (Loc,
9613                Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
9614                Out_Present         => True,
9615                Parameter_Type      => New_Occurrence_Of (Tag_Typ, Loc)),
9616
9617              Make_Parameter_Specification (Loc,
9618                Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
9619                Parameter_Type      => New_Occurrence_Of (Tag_Typ, Loc)))));
9620       end if;
9621
9622       --  Ada 2005: Generate declarations for the following primitive
9623       --  operations for limited interfaces and synchronized types that
9624       --  implement a limited interface.
9625
9626       --    Disp_Asynchronous_Select
9627       --    Disp_Conditional_Select
9628       --    Disp_Get_Prim_Op_Kind
9629       --    Disp_Get_Task_Id
9630       --    Disp_Requeue
9631       --    Disp_Timed_Select
9632
9633       --  Disable the generation of these bodies if No_Dispatching_Calls,
9634       --  Ravenscar or ZFP is active.
9635
9636       if Ada_Version >= Ada_2005
9637         and then not Restriction_Active (No_Dispatching_Calls)
9638         and then not Restriction_Active (No_Select_Statements)
9639         and then RTE_Available (RE_Select_Specific_Data)
9640       then
9641          --  These primitives are defined abstract in interface types
9642
9643          if Is_Interface (Tag_Typ)
9644            and then Is_Limited_Record (Tag_Typ)
9645          then
9646             Append_To (Res,
9647               Make_Abstract_Subprogram_Declaration (Loc,
9648                 Specification =>
9649                   Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
9650
9651             Append_To (Res,
9652               Make_Abstract_Subprogram_Declaration (Loc,
9653                 Specification =>
9654                   Make_Disp_Conditional_Select_Spec (Tag_Typ)));
9655
9656             Append_To (Res,
9657               Make_Abstract_Subprogram_Declaration (Loc,
9658                 Specification =>
9659                   Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
9660
9661             Append_To (Res,
9662               Make_Abstract_Subprogram_Declaration (Loc,
9663                 Specification =>
9664                   Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
9665
9666             Append_To (Res,
9667               Make_Abstract_Subprogram_Declaration (Loc,
9668                 Specification =>
9669                   Make_Disp_Requeue_Spec (Tag_Typ)));
9670
9671             Append_To (Res,
9672               Make_Abstract_Subprogram_Declaration (Loc,
9673                 Specification =>
9674                   Make_Disp_Timed_Select_Spec (Tag_Typ)));
9675
9676          --  If ancestor is an interface type, declare non-abstract primitives
9677          --  to override the abstract primitives of the interface type.
9678
9679          --  In VM targets we define these primitives in all root tagged types
9680          --  that are not interface types. Done because in VM targets we don't
9681          --  have secondary dispatch tables and any derivation of Tag_Typ may
9682          --  cover limited interfaces (which always have these primitives since
9683          --  they may be ancestors of synchronized interface types).
9684
9685          elsif (not Is_Interface (Tag_Typ)
9686                  and then Is_Interface (Etype (Tag_Typ))
9687                  and then Is_Limited_Record (Etype (Tag_Typ)))
9688              or else
9689                (Is_Concurrent_Record_Type (Tag_Typ)
9690                  and then Has_Interfaces (Tag_Typ))
9691              or else
9692                (not Tagged_Type_Expansion
9693                  and then not Is_Interface (Tag_Typ)
9694                  and then Tag_Typ = Root_Type (Tag_Typ))
9695          then
9696             Append_To (Res,
9697               Make_Subprogram_Declaration (Loc,
9698                 Specification =>
9699                   Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
9700
9701             Append_To (Res,
9702               Make_Subprogram_Declaration (Loc,
9703                 Specification =>
9704                   Make_Disp_Conditional_Select_Spec (Tag_Typ)));
9705
9706             Append_To (Res,
9707               Make_Subprogram_Declaration (Loc,
9708                 Specification =>
9709                   Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
9710
9711             Append_To (Res,
9712               Make_Subprogram_Declaration (Loc,
9713                 Specification =>
9714                   Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
9715
9716             Append_To (Res,
9717               Make_Subprogram_Declaration (Loc,
9718                 Specification =>
9719                   Make_Disp_Requeue_Spec (Tag_Typ)));
9720
9721             Append_To (Res,
9722               Make_Subprogram_Declaration (Loc,
9723                 Specification =>
9724                   Make_Disp_Timed_Select_Spec (Tag_Typ)));
9725          end if;
9726       end if;
9727
9728       --  All tagged types receive their own Deep_Adjust and Deep_Finalize
9729       --  regardless of whether they are controlled or may contain controlled
9730       --  components.
9731
9732       --  Do not generate the routines if finalization is disabled
9733
9734       if Restriction_Active (No_Finalization) then
9735          null;
9736
9737       else
9738          if not Is_Limited_Type (Tag_Typ) then
9739             Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
9740          end if;
9741
9742          Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
9743       end if;
9744
9745       Predef_List := Res;
9746    end Make_Predefined_Primitive_Specs;
9747
9748    -------------------------
9749    -- Make_Tag_Assignment --
9750    -------------------------
9751
9752    function Make_Tag_Assignment (N : Node_Id) return Node_Id is
9753       Loc      : constant Source_Ptr := Sloc (N);
9754       Def_If   : constant Entity_Id := Defining_Identifier (N);
9755       Expr     : constant Node_Id := Expression (N);
9756       Typ      : constant Entity_Id := Etype (Def_If);
9757       Full_Typ : constant Entity_Id := Underlying_Type (Typ);
9758       New_Ref  : Node_Id;
9759
9760    begin
9761       --  This expansion activity is called during analysis, but cannot
9762       --  be applied in ASIS mode when other expansion is disabled.
9763
9764       if Is_Tagged_Type (Typ)
9765        and then not Is_Class_Wide_Type (Typ)
9766        and then not Is_CPP_Class (Typ)
9767        and then Tagged_Type_Expansion
9768        and then Nkind (Expr) /= N_Aggregate
9769        and then not ASIS_Mode
9770        and then (Nkind (Expr) /= N_Qualified_Expression
9771                   or else Nkind (Expression (Expr)) /= N_Aggregate)
9772       then
9773          New_Ref :=
9774            Make_Selected_Component (Loc,
9775               Prefix        => New_Occurrence_Of (Def_If, Loc),
9776               Selector_Name =>
9777                 New_Occurrence_Of (First_Tag_Component (Full_Typ), Loc));
9778          Set_Assignment_OK (New_Ref);
9779
9780          return
9781            Make_Assignment_Statement (Loc,
9782               Name       => New_Ref,
9783               Expression =>
9784                 Unchecked_Convert_To (RTE (RE_Tag),
9785                   New_Occurrence_Of (Node
9786                       (First_Elmt (Access_Disp_Table (Full_Typ))), Loc)));
9787       else
9788          return Empty;
9789       end if;
9790    end Make_Tag_Assignment;
9791
9792    ---------------------------------
9793    -- Needs_Simple_Initialization --
9794    ---------------------------------
9795
9796    function Needs_Simple_Initialization
9797      (T           : Entity_Id;
9798       Consider_IS : Boolean := True) return Boolean
9799    is
9800       Consider_IS_NS : constant Boolean :=
9801         Normalize_Scalars or (Initialize_Scalars and Consider_IS);
9802
9803    begin
9804       --  Never need initialization if it is suppressed
9805
9806       if Initialization_Suppressed (T) then
9807          return False;
9808       end if;
9809
9810       --  Check for private type, in which case test applies to the underlying
9811       --  type of the private type.
9812
9813       if Is_Private_Type (T) then
9814          declare
9815             RT : constant Entity_Id := Underlying_Type (T);
9816          begin
9817             if Present (RT) then
9818                return Needs_Simple_Initialization (RT);
9819             else
9820                return False;
9821             end if;
9822          end;
9823
9824       --  Scalar type with Default_Value aspect requires initialization
9825
9826       elsif Is_Scalar_Type (T) and then Has_Default_Aspect (T) then
9827          return True;
9828
9829       --  Cases needing simple initialization are access types, and, if pragma
9830       --  Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
9831       --  types.
9832
9833       elsif Is_Access_Type (T)
9834         or else (Consider_IS_NS and then (Is_Scalar_Type (T)))
9835       then
9836          return True;
9837
9838       --  If Initialize/Normalize_Scalars is in effect, string objects also
9839       --  need initialization, unless they are created in the course of
9840       --  expanding an aggregate (since in the latter case they will be
9841       --  filled with appropriate initializing values before they are used).
9842
9843       elsif Consider_IS_NS
9844         and then Is_Standard_String_Type (T)
9845         and then
9846           (not Is_Itype (T)
9847             or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
9848       then
9849          return True;
9850
9851       else
9852          return False;
9853       end if;
9854    end Needs_Simple_Initialization;
9855
9856    ----------------------
9857    -- Predef_Deep_Spec --
9858    ----------------------
9859
9860    function Predef_Deep_Spec
9861      (Loc      : Source_Ptr;
9862       Tag_Typ  : Entity_Id;
9863       Name     : TSS_Name_Type;
9864       For_Body : Boolean := False) return Node_Id
9865    is
9866       Formals : List_Id;
9867
9868    begin
9869       --  V : in out Tag_Typ
9870
9871       Formals := New_List (
9872         Make_Parameter_Specification (Loc,
9873           Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
9874           In_Present          => True,
9875           Out_Present         => True,
9876           Parameter_Type      => New_Occurrence_Of (Tag_Typ, Loc)));
9877
9878       --  F : Boolean := True
9879
9880       if Name = TSS_Deep_Adjust
9881         or else Name = TSS_Deep_Finalize
9882       then
9883          Append_To (Formals,
9884            Make_Parameter_Specification (Loc,
9885              Defining_Identifier => Make_Defining_Identifier (Loc, Name_F),
9886              Parameter_Type      => New_Occurrence_Of (Standard_Boolean, Loc),
9887              Expression          => New_Occurrence_Of (Standard_True, Loc)));
9888       end if;
9889
9890       return
9891         Predef_Spec_Or_Body (Loc,
9892           Name     => Make_TSS_Name (Tag_Typ, Name),
9893           Tag_Typ  => Tag_Typ,
9894           Profile  => Formals,
9895           For_Body => For_Body);
9896
9897    exception
9898       when RE_Not_Available =>
9899          return Empty;
9900    end Predef_Deep_Spec;
9901
9902    -------------------------
9903    -- Predef_Spec_Or_Body --
9904    -------------------------
9905
9906    function Predef_Spec_Or_Body
9907      (Loc      : Source_Ptr;
9908       Tag_Typ  : Entity_Id;
9909       Name     : Name_Id;
9910       Profile  : List_Id;
9911       Ret_Type : Entity_Id := Empty;
9912       For_Body : Boolean := False) return Node_Id
9913    is
9914       Id   : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
9915       Spec : Node_Id;
9916
9917    begin
9918       Set_Is_Public (Id, Is_Public (Tag_Typ));
9919
9920       --  The internal flag is set to mark these declarations because they have
9921       --  specific properties. First, they are primitives even if they are not
9922       --  defined in the type scope (the freezing point is not necessarily in
9923       --  the same scope). Second, the predefined equality can be overridden by
9924       --  a user-defined equality, no body will be generated in this case.
9925
9926       Set_Is_Internal (Id);
9927
9928       if not Debug_Generated_Code then
9929          Set_Debug_Info_Off (Id);
9930       end if;
9931
9932       if No (Ret_Type) then
9933          Spec :=
9934            Make_Procedure_Specification (Loc,
9935              Defining_Unit_Name       => Id,
9936              Parameter_Specifications => Profile);
9937       else
9938          Spec :=
9939            Make_Function_Specification (Loc,
9940              Defining_Unit_Name       => Id,
9941              Parameter_Specifications => Profile,
9942              Result_Definition        => New_Occurrence_Of (Ret_Type, Loc));
9943       end if;
9944
9945       if Is_Interface (Tag_Typ) then
9946          return Make_Abstract_Subprogram_Declaration (Loc, Spec);
9947
9948       --  If body case, return empty subprogram body. Note that this is ill-
9949       --  formed, because there is not even a null statement, and certainly not
9950       --  a return in the function case. The caller is expected to do surgery
9951       --  on the body to add the appropriate stuff.
9952
9953       elsif For_Body then
9954          return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
9955
9956       --  For the case of an Input attribute predefined for an abstract type,
9957       --  generate an abstract specification. This will never be called, but we
9958       --  need the slot allocated in the dispatching table so that attributes
9959       --  typ'Class'Input and typ'Class'Output will work properly.
9960
9961       elsif Is_TSS (Name, TSS_Stream_Input)
9962         and then Is_Abstract_Type (Tag_Typ)
9963       then
9964          return Make_Abstract_Subprogram_Declaration (Loc, Spec);
9965
9966       --  Normal spec case, where we return a subprogram declaration
9967
9968       else
9969          return Make_Subprogram_Declaration (Loc, Spec);
9970       end if;
9971    end Predef_Spec_Or_Body;
9972
9973    -----------------------------
9974    -- Predef_Stream_Attr_Spec --
9975    -----------------------------
9976
9977    function Predef_Stream_Attr_Spec
9978      (Loc      : Source_Ptr;
9979       Tag_Typ  : Entity_Id;
9980       Name     : TSS_Name_Type;
9981       For_Body : Boolean := False) return Node_Id
9982    is
9983       Ret_Type : Entity_Id;
9984
9985    begin
9986       if Name = TSS_Stream_Input then
9987          Ret_Type := Tag_Typ;
9988       else
9989          Ret_Type := Empty;
9990       end if;
9991
9992       return
9993         Predef_Spec_Or_Body
9994           (Loc,
9995            Name     => Make_TSS_Name (Tag_Typ, Name),
9996            Tag_Typ  => Tag_Typ,
9997            Profile  => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
9998            Ret_Type => Ret_Type,
9999            For_Body => For_Body);
10000    end Predef_Stream_Attr_Spec;
10001
10002    ---------------------------------
10003    -- Predefined_Primitive_Bodies --
10004    ---------------------------------
10005
10006    function Predefined_Primitive_Bodies
10007      (Tag_Typ    : Entity_Id;
10008       Renamed_Eq : Entity_Id) return List_Id
10009    is
10010       Loc       : constant Source_Ptr := Sloc (Tag_Typ);
10011       Res       : constant List_Id    := New_List;
10012       Decl      : Node_Id;
10013       Prim      : Elmt_Id;
10014       Eq_Needed : Boolean;
10015       Eq_Name   : Name_Id;
10016       Ent       : Entity_Id;
10017
10018       pragma Warnings (Off, Ent);
10019
10020    begin
10021       pragma Assert (not Is_Interface (Tag_Typ));
10022
10023       --  See if we have a predefined "=" operator
10024
10025       if Present (Renamed_Eq) then
10026          Eq_Needed := True;
10027          Eq_Name   := Chars (Renamed_Eq);
10028
10029       --  If the parent is an interface type then it has defined all the
10030       --  predefined primitives abstract and we need to check if the type
10031       --  has some user defined "=" function which matches the profile of
10032       --  the Ada predefined equality operator to avoid generating it.
10033
10034       elsif Is_Interface (Etype (Tag_Typ)) then
10035          Eq_Needed := True;
10036          Eq_Name := Name_Op_Eq;
10037
10038          Prim := First_Elmt (Primitive_Operations (Tag_Typ));
10039          while Present (Prim) loop
10040             if Chars (Node (Prim)) = Name_Op_Eq
10041               and then not Is_Internal (Node (Prim))
10042               and then Present (First_Entity (Node (Prim)))
10043
10044               --  The predefined equality primitive must have exactly two
10045               --  formals whose type is this tagged type
10046
10047               and then Present (Last_Entity (Node (Prim)))
10048               and then Next_Entity (First_Entity (Node (Prim)))
10049                          = Last_Entity (Node (Prim))
10050               and then Etype (First_Entity (Node (Prim))) = Tag_Typ
10051               and then Etype (Last_Entity (Node (Prim))) = Tag_Typ
10052             then
10053                Eq_Needed := False;
10054                Eq_Name := No_Name;
10055                exit;
10056             end if;
10057
10058             Next_Elmt (Prim);
10059          end loop;
10060
10061       else
10062          Eq_Needed := False;
10063          Eq_Name   := No_Name;
10064
10065          Prim := First_Elmt (Primitive_Operations (Tag_Typ));
10066          while Present (Prim) loop
10067             if Chars (Node (Prim)) = Name_Op_Eq
10068               and then Is_Internal (Node (Prim))
10069             then
10070                Eq_Needed := True;
10071                Eq_Name := Name_Op_Eq;
10072                exit;
10073             end if;
10074
10075             Next_Elmt (Prim);
10076          end loop;
10077       end if;
10078
10079       --  Body of _Size
10080
10081       Decl := Predef_Spec_Or_Body (Loc,
10082         Tag_Typ => Tag_Typ,
10083         Name    => Name_uSize,
10084         Profile => New_List (
10085           Make_Parameter_Specification (Loc,
10086             Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
10087             Parameter_Type      => New_Occurrence_Of (Tag_Typ, Loc))),
10088
10089         Ret_Type => Standard_Long_Long_Integer,
10090         For_Body => True);
10091
10092       Set_Handled_Statement_Sequence (Decl,
10093         Make_Handled_Sequence_Of_Statements (Loc, New_List (
10094           Make_Simple_Return_Statement (Loc,
10095             Expression =>
10096               Make_Attribute_Reference (Loc,
10097                 Prefix          => Make_Identifier (Loc, Name_X),
10098                 Attribute_Name  => Name_Size)))));
10099
10100       Append_To (Res, Decl);
10101
10102       --  Bodies for Dispatching stream IO routines. We need these only for
10103       --  non-limited types (in the limited case there is no dispatching).
10104       --  We also skip them if dispatching or finalization are not available
10105       --  or if stream operations are prohibited by restriction No_Streams or
10106       --  from use of pragma/aspect No_Tagged_Streams.
10107
10108       if Stream_Operation_OK (Tag_Typ, TSS_Stream_Read)
10109         and then No (TSS (Tag_Typ, TSS_Stream_Read))
10110       then
10111          Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
10112          Append_To (Res, Decl);
10113       end if;
10114
10115       if Stream_Operation_OK (Tag_Typ, TSS_Stream_Write)
10116         and then No (TSS (Tag_Typ, TSS_Stream_Write))
10117       then
10118          Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
10119          Append_To (Res, Decl);
10120       end if;
10121
10122       --  Skip body of _Input for the abstract case, since the corresponding
10123       --  spec is abstract (see Predef_Spec_Or_Body).
10124
10125       if not Is_Abstract_Type (Tag_Typ)
10126         and then Stream_Operation_OK (Tag_Typ, TSS_Stream_Input)
10127         and then No (TSS (Tag_Typ, TSS_Stream_Input))
10128       then
10129          Build_Record_Or_Elementary_Input_Function
10130            (Loc, Tag_Typ, Decl, Ent);
10131          Append_To (Res, Decl);
10132       end if;
10133
10134       if Stream_Operation_OK (Tag_Typ, TSS_Stream_Output)
10135         and then No (TSS (Tag_Typ, TSS_Stream_Output))
10136       then
10137          Build_Record_Or_Elementary_Output_Procedure (Loc, Tag_Typ, Decl, Ent);
10138          Append_To (Res, Decl);
10139       end if;
10140
10141       --  Ada 2005: Generate bodies for the following primitive operations for
10142       --  limited interfaces and synchronized types that implement a limited
10143       --  interface.
10144
10145       --    disp_asynchronous_select
10146       --    disp_conditional_select
10147       --    disp_get_prim_op_kind
10148       --    disp_get_task_id
10149       --    disp_timed_select
10150
10151       --  The interface versions will have null bodies
10152
10153       --  Disable the generation of these bodies if No_Dispatching_Calls,
10154       --  Ravenscar or ZFP is active.
10155
10156       --  In VM targets we define these primitives in all root tagged types
10157       --  that are not interface types. Done because in VM targets we don't
10158       --  have secondary dispatch tables and any derivation of Tag_Typ may
10159       --  cover limited interfaces (which always have these primitives since
10160       --  they may be ancestors of synchronized interface types).
10161
10162       if Ada_Version >= Ada_2005
10163         and then not Is_Interface (Tag_Typ)
10164         and then
10165           ((Is_Interface (Etype (Tag_Typ))
10166              and then Is_Limited_Record (Etype (Tag_Typ)))
10167            or else
10168              (Is_Concurrent_Record_Type (Tag_Typ)
10169                and then Has_Interfaces (Tag_Typ))
10170            or else
10171              (not Tagged_Type_Expansion
10172                and then Tag_Typ = Root_Type (Tag_Typ)))
10173         and then not Restriction_Active (No_Dispatching_Calls)
10174         and then not Restriction_Active (No_Select_Statements)
10175         and then RTE_Available (RE_Select_Specific_Data)
10176       then
10177          Append_To (Res, Make_Disp_Asynchronous_Select_Body (Tag_Typ));
10178          Append_To (Res, Make_Disp_Conditional_Select_Body  (Tag_Typ));
10179          Append_To (Res, Make_Disp_Get_Prim_Op_Kind_Body    (Tag_Typ));
10180          Append_To (Res, Make_Disp_Get_Task_Id_Body         (Tag_Typ));
10181          Append_To (Res, Make_Disp_Requeue_Body             (Tag_Typ));
10182          Append_To (Res, Make_Disp_Timed_Select_Body        (Tag_Typ));
10183       end if;
10184
10185       if not Is_Limited_Type (Tag_Typ) and then not Is_Interface (Tag_Typ) then
10186
10187          --  Body for equality
10188
10189          if Eq_Needed then
10190             Decl := Make_Eq_Body (Tag_Typ, Eq_Name);
10191             Append_To (Res, Decl);
10192          end if;
10193
10194          --  Body for inequality (if required)
10195
10196          Decl := Make_Neq_Body (Tag_Typ);
10197
10198          if Present (Decl) then
10199             Append_To (Res, Decl);
10200          end if;
10201
10202          --  Body for dispatching assignment
10203
10204          Decl :=
10205            Predef_Spec_Or_Body (Loc,
10206              Tag_Typ => Tag_Typ,
10207              Name    => Name_uAssign,
10208              Profile => New_List (
10209                Make_Parameter_Specification (Loc,
10210                  Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
10211                  Out_Present         => True,
10212                  Parameter_Type      => New_Occurrence_Of (Tag_Typ, Loc)),
10213
10214                Make_Parameter_Specification (Loc,
10215                  Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
10216                  Parameter_Type      => New_Occurrence_Of (Tag_Typ, Loc))),
10217              For_Body => True);
10218
10219          Set_Handled_Statement_Sequence (Decl,
10220            Make_Handled_Sequence_Of_Statements (Loc, New_List (
10221              Make_Assignment_Statement (Loc,
10222                Name       => Make_Identifier (Loc, Name_X),
10223                Expression => Make_Identifier (Loc, Name_Y)))));
10224
10225          Append_To (Res, Decl);
10226       end if;
10227
10228       --  Generate empty bodies of routines Deep_Adjust and Deep_Finalize for
10229       --  tagged types which do not contain controlled components.
10230
10231       --  Do not generate the routines if finalization is disabled
10232
10233       if Restriction_Active (No_Finalization) then
10234          null;
10235
10236       elsif not Has_Controlled_Component (Tag_Typ) then
10237          if not Is_Limited_Type (Tag_Typ) then
10238             Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
10239
10240             if Is_Controlled (Tag_Typ) then
10241                Set_Handled_Statement_Sequence (Decl,
10242                  Make_Handled_Sequence_Of_Statements (Loc,
10243                    Statements => New_List (
10244                      Make_Adjust_Call (
10245                        Obj_Ref => Make_Identifier (Loc, Name_V),
10246                        Typ     => Tag_Typ))));
10247
10248             else
10249                Set_Handled_Statement_Sequence (Decl,
10250                  Make_Handled_Sequence_Of_Statements (Loc,
10251                    Statements => New_List (
10252                      Make_Null_Statement (Loc))));
10253             end if;
10254
10255             Append_To (Res, Decl);
10256          end if;
10257
10258          Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
10259
10260          if Is_Controlled (Tag_Typ) then
10261             Set_Handled_Statement_Sequence (Decl,
10262               Make_Handled_Sequence_Of_Statements (Loc,
10263                 Statements => New_List (
10264                   Make_Final_Call
10265                     (Obj_Ref => Make_Identifier (Loc, Name_V),
10266                      Typ     => Tag_Typ))));
10267
10268          else
10269             Set_Handled_Statement_Sequence (Decl,
10270               Make_Handled_Sequence_Of_Statements (Loc,
10271                 Statements => New_List (Make_Null_Statement (Loc))));
10272          end if;
10273
10274          Append_To (Res, Decl);
10275       end if;
10276
10277       return Res;
10278    end Predefined_Primitive_Bodies;
10279
10280    ---------------------------------
10281    -- Predefined_Primitive_Freeze --
10282    ---------------------------------
10283
10284    function Predefined_Primitive_Freeze
10285      (Tag_Typ : Entity_Id) return List_Id
10286    is
10287       Res     : constant List_Id := New_List;
10288       Prim    : Elmt_Id;
10289       Frnodes : List_Id;
10290
10291    begin
10292       Prim := First_Elmt (Primitive_Operations (Tag_Typ));
10293       while Present (Prim) loop
10294          if Is_Predefined_Dispatching_Operation (Node (Prim)) then
10295             Frnodes := Freeze_Entity (Node (Prim), Tag_Typ);
10296
10297             if Present (Frnodes) then
10298                Append_List_To (Res, Frnodes);
10299             end if;
10300          end if;
10301
10302          Next_Elmt (Prim);
10303       end loop;
10304
10305       return Res;
10306    end Predefined_Primitive_Freeze;
10307
10308    -------------------------
10309    -- Stream_Operation_OK --
10310    -------------------------
10311
10312    function Stream_Operation_OK
10313      (Typ       : Entity_Id;
10314       Operation : TSS_Name_Type) return Boolean
10315    is
10316       Has_Predefined_Or_Specified_Stream_Attribute : Boolean := False;
10317
10318    begin
10319       --  Special case of a limited type extension: a default implementation
10320       --  of the stream attributes Read or Write exists if that attribute
10321       --  has been specified or is available for an ancestor type; a default
10322       --  implementation of the attribute Output (resp. Input) exists if the
10323       --  attribute has been specified or Write (resp. Read) is available for
10324       --  an ancestor type. The last condition only applies under Ada 2005.
10325
10326       if Is_Limited_Type (Typ) and then Is_Tagged_Type (Typ) then
10327          if Operation = TSS_Stream_Read then
10328             Has_Predefined_Or_Specified_Stream_Attribute :=
10329               Has_Specified_Stream_Read (Typ);
10330
10331          elsif Operation = TSS_Stream_Write then
10332             Has_Predefined_Or_Specified_Stream_Attribute :=
10333               Has_Specified_Stream_Write (Typ);
10334
10335          elsif Operation = TSS_Stream_Input then
10336             Has_Predefined_Or_Specified_Stream_Attribute :=
10337               Has_Specified_Stream_Input (Typ)
10338                 or else
10339                   (Ada_Version >= Ada_2005
10340                     and then Stream_Operation_OK (Typ, TSS_Stream_Read));
10341
10342          elsif Operation = TSS_Stream_Output then
10343             Has_Predefined_Or_Specified_Stream_Attribute :=
10344               Has_Specified_Stream_Output (Typ)
10345                 or else
10346                   (Ada_Version >= Ada_2005
10347                     and then Stream_Operation_OK (Typ, TSS_Stream_Write));
10348          end if;
10349
10350          --  Case of inherited TSS_Stream_Read or TSS_Stream_Write
10351
10352          if not Has_Predefined_Or_Specified_Stream_Attribute
10353            and then Is_Derived_Type (Typ)
10354            and then (Operation = TSS_Stream_Read
10355                       or else Operation = TSS_Stream_Write)
10356          then
10357             Has_Predefined_Or_Specified_Stream_Attribute :=
10358               Present
10359                 (Find_Inherited_TSS (Base_Type (Etype (Typ)), Operation));
10360          end if;
10361       end if;
10362
10363       --  If the type is not limited, or else is limited but the attribute is
10364       --  explicitly specified or is predefined for the type, then return True,
10365       --  unless other conditions prevail, such as restrictions prohibiting
10366       --  streams or dispatching operations. We also return True for limited
10367       --  interfaces, because they may be extended by nonlimited types and
10368       --  permit inheritance in this case (addresses cases where an abstract
10369       --  extension doesn't get 'Input declared, as per comments below, but
10370       --  'Class'Input must still be allowed). Note that attempts to apply
10371       --  stream attributes to a limited interface or its class-wide type
10372       --  (or limited extensions thereof) will still get properly rejected
10373       --  by Check_Stream_Attribute.
10374
10375       --  We exclude the Input operation from being a predefined subprogram in
10376       --  the case where the associated type is an abstract extension, because
10377       --  the attribute is not callable in that case, per 13.13.2(49/2). Also,
10378       --  we don't want an abstract version created because types derived from
10379       --  the abstract type may not even have Input available (for example if
10380       --  derived from a private view of the abstract type that doesn't have
10381       --  a visible Input).
10382
10383       --  Do not generate stream routines for type Finalization_Master because
10384       --  a master may never appear in types and therefore cannot be read or
10385       --  written.
10386
10387       return
10388           (not Is_Limited_Type (Typ)
10389             or else Is_Interface (Typ)
10390             or else Has_Predefined_Or_Specified_Stream_Attribute)
10391         and then
10392           (Operation /= TSS_Stream_Input
10393             or else not Is_Abstract_Type (Typ)
10394             or else not Is_Derived_Type (Typ))
10395         and then not Has_Unknown_Discriminants (Typ)
10396         and then not
10397           (Is_Interface (Typ)
10398             and then
10399               (Is_Task_Interface (Typ)
10400                 or else Is_Protected_Interface (Typ)
10401                 or else Is_Synchronized_Interface (Typ)))
10402         and then not Restriction_Active (No_Streams)
10403         and then not Restriction_Active (No_Dispatch)
10404         and then No (No_Tagged_Streams_Pragma (Typ))
10405         and then not No_Run_Time_Mode
10406         and then RTE_Available (RE_Tag)
10407         and then No (Type_Without_Stream_Operation (Typ))
10408         and then RTE_Available (RE_Root_Stream_Type)
10409         and then not Is_RTE (Typ, RE_Finalization_Master);
10410    end Stream_Operation_OK;
10411
10412 end Exp_Ch3;