OSDN Git Service

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