OSDN Git Service

* utils.c (gnat_init_decl_processing): Ada has a signed sizetype.
[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-2004 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 2,  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 COPYING.  If not, write --
19 -- to  the Free Software Foundation,  59 Temple Place - Suite 330,  Boston, --
20 -- MA 02111-1307, USA.                                                      --
21 --                                                                          --
22 -- GNAT was originally developed  by the GNAT team at  New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
24 --                                                                          --
25 ------------------------------------------------------------------------------
26
27 with Atree;    use Atree;
28 with Checks;   use Checks;
29 with Einfo;    use Einfo;
30 with Elists;   use Elists;
31 with Errout;   use Errout;
32 with Exp_Aggr; use Exp_Aggr;
33 with Exp_Ch4;  use Exp_Ch4;
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 Hostparm; use Hostparm;
45 with Nlists;   use Nlists;
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_Ch3;  use Sem_Ch3;
53 with Sem_Ch8;  use Sem_Ch8;
54 with Sem_Eval; use Sem_Eval;
55 with Sem_Mech; use Sem_Mech;
56 with Sem_Res;  use Sem_Res;
57 with Sem_Util; use Sem_Util;
58 with Sinfo;    use Sinfo;
59 with Stand;    use Stand;
60 with Stringt;  use Stringt;
61 with Snames;   use Snames;
62 with Tbuild;   use Tbuild;
63 with Ttypes;   use Ttypes;
64 with Uintp;    use Uintp;
65 with Validsw;  use Validsw;
66
67 package body Exp_Ch3 is
68
69    -----------------------
70    -- Local Subprograms --
71    -----------------------
72
73    procedure Adjust_Discriminants (Rtype : Entity_Id);
74    --  This is used when freezing a record type. It attempts to construct
75    --  more restrictive subtypes for discriminants so that the max size of
76    --  the record can be calculated more accurately. See the body of this
77    --  procedure for details.
78
79    procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id);
80    --  Build initialization procedure for given array type. Nod is a node
81    --  used for attachment of any actions required in its construction.
82    --  It also supplies the source location used for the procedure.
83
84    procedure Build_Class_Wide_Master (T : Entity_Id);
85    --  for access to class-wide limited types we must build a task master
86    --  because some subsequent extension may add a task component. To avoid
87    --  bringing in the tasking run-time whenever an access-to-class-wide
88    --  limited type is used, we use the soft-link mechanism and add a level
89    --  of indirection to calls to routines that manipulate Master_Ids.
90
91    function Build_Discriminant_Formals
92      (Rec_Id : Entity_Id;
93       Use_Dl : Boolean) return List_Id;
94    --  This function uses the discriminants of a type to build a list of
95    --  formal parameters, used in the following function. If the flag Use_Dl
96    --  is set, the list is built using the already defined discriminals
97    --  of the type. Otherwise new identifiers are created, with the source
98    --  names of the discriminants.
99
100    procedure Build_Master_Renaming (N : Node_Id; T : Entity_Id);
101    --  If the designated type of an access type is a task type or contains
102    --  tasks, we make sure that a _Master variable is declared in the current
103    --  scope, and then declare a renaming for it:
104    --
105    --    atypeM : Master_Id renames _Master;
106    --
107    --  where atyp is the name of the access type. This declaration is
108    --  used when an allocator for the access type is expanded. The node N
109    --  is the full declaration of the designated type that contains tasks.
110    --  The renaming declaration is inserted before N, and after the Master
111    --  declaration.
112
113    procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id);
114    --  Build record initialization procedure. N is the type declaration
115    --  node, and Pe is the corresponding entity for the record type.
116
117    procedure Build_Slice_Assignment (Typ : Entity_Id);
118    --  Build assignment procedure for one-dimensional arrays of controlled
119    --  types. Other array and slice assignments are expanded in-line, but
120    --  the code expansion for controlled components (when control actions
121    --  are active) can lead to very large blocks that GCC3 handles poorly.
122
123    procedure Build_Variant_Record_Equality (Typ  : Entity_Id);
124    --  Create An Equality function for the non-tagged variant record 'Typ'
125    --  and attach it to the TSS list
126
127    procedure Check_Stream_Attributes (Typ : Entity_Id);
128    --  Check that if a limited extension has a parent with user-defined
129    --  stream attributes, any limited component of the extension also has
130    --  the corresponding user-defined stream attributes.
131
132    procedure Expand_Tagged_Root (T : Entity_Id);
133    --  Add a field _Tag at the beginning of the record. This field carries
134    --  the value of the access to the Dispatch table. This procedure is only
135    --  called on root (non CPP_Class) types, the _Tag field being inherited
136    --  by the descendants.
137
138    procedure Expand_Record_Controller (T : Entity_Id);
139    --  T must be a record type that Has_Controlled_Component. Add a field
140    --  _controller of type Record_Controller or Limited_Record_Controller
141    --  in the record T.
142
143    procedure Freeze_Array_Type (N : Node_Id);
144    --  Freeze an array type. Deals with building the initialization procedure,
145    --  creating the packed array type for a packed array and also with the
146    --  creation of the controlling procedures for the controlled case. The
147    --  argument N is the N_Freeze_Entity node for the type.
148
149    procedure Freeze_Enumeration_Type (N : Node_Id);
150    --  Freeze enumeration type with non-standard representation. Builds the
151    --  array and function needed to convert between enumeration pos and
152    --  enumeration representation values. N is the N_Freeze_Entity node
153    --  for the type.
154
155    procedure Freeze_Record_Type (N : Node_Id);
156    --  Freeze record type. Builds all necessary discriminant checking
157    --  and other ancillary functions, and builds dispatch tables where
158    --  needed. The argument N is the N_Freeze_Entity node. This processing
159    --  applies only to E_Record_Type entities, not to class wide types,
160    --  record subtypes, or private types.
161
162    procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id);
163    --  Treat user-defined stream operations as renaming_as_body if the
164    --  subprogram they rename is not frozen when the type is frozen.
165
166    function Init_Formals (Typ : Entity_Id) return List_Id;
167    --  This function builds the list of formals for an initialization routine.
168    --  The first formal is always _Init with the given type. For task value
169    --  record types and types containing tasks, three additional formals are
170    --  added:
171    --
172    --    _Master    : Master_Id
173    --    _Chain     : in out Activation_Chain
174    --    _Task_Name : String
175    --
176    --  The caller must append additional entries for discriminants if required.
177
178    function In_Runtime (E : Entity_Id) return Boolean;
179    --  Check if E is defined in the RTL (in a child of Ada or System). Used
180    --  to avoid to bring in the overhead of _Input, _Output for tagged types.
181
182    function Make_Eq_Case
183      (E     : Entity_Id;
184       CL    : Node_Id;
185       Discr : Entity_Id := Empty) return List_Id;
186    --  Building block for variant record equality. Defined to share the
187    --  code between the tagged and non-tagged case. Given a Component_List
188    --  node CL, it generates an 'if' followed by a 'case' statement that
189    --  compares all components of local temporaries named X and Y (that
190    --  are declared as formals at some upper level). E provides the Sloc to be
191    --  used for the generated code. Discr is used as the case statement switch
192    --  in the case of Unchecked_Union equality.
193
194    function Make_Eq_If
195      (E : Entity_Id;
196       L : List_Id) return Node_Id;
197    --  Building block for variant record equality. Defined to share the
198    --  code between the tagged and non-tagged case. Given the list of
199    --  components (or discriminants) L, it generates a return statement
200    --  that compares all components of local temporaries named X and Y
201    --  (that are declared as formals at some upper level). E provides the Sloc
202    --  to be used for the generated code.
203
204    procedure Make_Predefined_Primitive_Specs
205      (Tag_Typ     : Entity_Id;
206       Predef_List : out List_Id;
207       Renamed_Eq  : out Node_Id);
208    --  Create a list with the specs of the predefined primitive operations.
209    --  The following entries are present for all tagged types, and provide
210    --  the results of the corresponding attribute applied to the object.
211    --  Dispatching is required in general, since the result of the attribute
212    --  will vary with the actual object subtype.
213    --
214    --     _alignment     provides result of 'Alignment attribute
215    --     _size          provides result of 'Size attribute
216    --     typSR          provides result of 'Read attribute
217    --     typSW          provides result of 'Write attribute
218    --     typSI          provides result of 'Input attribute
219    --     typSO          provides result of 'Output attribute
220    --
221    --  The following entries are additionally present for non-limited
222    --  tagged types, and implement additional dispatching operations
223    --  for predefined operations:
224    --
225    --     _equality      implements "=" operator
226    --     _assign        implements assignment operation
227    --     typDF          implements deep finalization
228    --     typDA          implements deep adust
229    --
230    --  The latter two are empty procedures unless the type contains some
231    --  controlled components that require finalization actions (the deep
232    --  in the name refers to the fact that the action applies to components).
233    --
234    --  The list is returned in Predef_List. The Parameter Renamed_Eq
235    --  either returns the value Empty, or else the defining unit name
236    --  for the predefined equality function in the case where the type
237    --  has a primitive operation that is a renaming of predefined equality
238    --  (but only if there is also an overriding user-defined equality
239    --  function). The returned Renamed_Eq will be passed to the
240    --  corresponding parameter of Predefined_Primitive_Bodies.
241
242    function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean;
243    --  returns True if there are representation clauses for type T that
244    --  are not inherited. If the result is false, the init_proc and the
245    --  discriminant_checking functions of the parent can be reused by
246    --  a derived type.
247
248    function Predef_Spec_Or_Body
249      (Loc      : Source_Ptr;
250       Tag_Typ  : Entity_Id;
251       Name     : Name_Id;
252       Profile  : List_Id;
253       Ret_Type : Entity_Id := Empty;
254       For_Body : Boolean   := False) return Node_Id;
255    --  This function generates the appropriate expansion for a predefined
256    --  primitive operation specified by its name, parameter profile and
257    --  return type (Empty means this is a procedure). If For_Body is false,
258    --  then the returned node is a subprogram declaration. If For_Body is
259    --  true, then the returned node is a empty subprogram body containing
260    --  no declarations and no statements.
261
262    function Predef_Stream_Attr_Spec
263      (Loc      : Source_Ptr;
264       Tag_Typ  : Entity_Id;
265       Name     : TSS_Name_Type;
266       For_Body : Boolean := False) return Node_Id;
267    --  Specialized version of Predef_Spec_Or_Body that apply to read, write,
268    --  input and output attribute whose specs are constructed in Exp_Strm.
269
270    function Predef_Deep_Spec
271      (Loc      : Source_Ptr;
272       Tag_Typ  : Entity_Id;
273       Name     : TSS_Name_Type;
274       For_Body : Boolean := False) return Node_Id;
275    --  Specialized version of Predef_Spec_Or_Body that apply to _deep_adjust
276    --  and _deep_finalize
277
278    function Predefined_Primitive_Bodies
279      (Tag_Typ    : Entity_Id;
280       Renamed_Eq : Node_Id) return List_Id;
281    --  Create the bodies of the predefined primitives that are described in
282    --  Predefined_Primitive_Specs. When not empty, Renamed_Eq must denote
283    --  the defining unit name of the type's predefined equality as returned
284    --  by Make_Predefined_Primitive_Specs.
285
286    function Predefined_Primitive_Freeze (Tag_Typ : Entity_Id) return List_Id;
287    --  Freeze entities of all predefined primitive operations. This is needed
288    --  because the bodies of these operations do not normally do any freezeing.
289
290    --------------------------
291    -- Adjust_Discriminants --
292    --------------------------
293
294    --  This procedure attempts to define subtypes for discriminants that
295    --  are more restrictive than those declared. Such a replacement is
296    --  possible if we can demonstrate that values outside the restricted
297    --  range would cause constraint errors in any case. The advantage of
298    --  restricting the discriminant types in this way is tha the maximum
299    --  size of the variant record can be calculated more conservatively.
300
301    --  An example of a situation in which we can perform this type of
302    --  restriction is the following:
303
304    --    subtype B is range 1 .. 10;
305    --    type Q is array (B range <>) of Integer;
306
307    --    type V (N : Natural) is record
308    --       C : Q (1 .. N);
309    --    end record;
310
311    --  In this situation, we can restrict the upper bound of N to 10, since
312    --  any larger value would cause a constraint error in any case.
313
314    --  There are many situations in which such restriction is possible, but
315    --  for now, we just look for cases like the above, where the component
316    --  in question is a one dimensional array whose upper bound is one of
317    --  the record discriminants. Also the component must not be part of
318    --  any variant part, since then the component does not always exist.
319
320    procedure Adjust_Discriminants (Rtype : Entity_Id) is
321       Loc   : constant Source_Ptr := Sloc (Rtype);
322       Comp  : Entity_Id;
323       Ctyp  : Entity_Id;
324       Ityp  : Entity_Id;
325       Lo    : Node_Id;
326       Hi    : Node_Id;
327       P     : Node_Id;
328       Loval : Uint;
329       Discr : Entity_Id;
330       Dtyp  : Entity_Id;
331       Dhi   : Node_Id;
332       Dhiv  : Uint;
333       Ahi   : Node_Id;
334       Ahiv  : Uint;
335       Tnn   : Entity_Id;
336
337    begin
338       Comp := First_Component (Rtype);
339       while Present (Comp) loop
340
341          --  If our parent is a variant, quit, we do not look at components
342          --  that are in variant parts, because they may not always exist.
343
344          P := Parent (Comp);   -- component declaration
345          P := Parent (P);      -- component list
346
347          exit when Nkind (Parent (P)) = N_Variant;
348
349          --  We are looking for a one dimensional array type
350
351          Ctyp := Etype (Comp);
352
353          if not Is_Array_Type (Ctyp)
354            or else Number_Dimensions (Ctyp) > 1
355          then
356             goto Continue;
357          end if;
358
359          --  The lower bound must be constant, and the upper bound is a
360          --  discriminant (which is a discriminant of the current record).
361
362          Ityp := Etype (First_Index (Ctyp));
363          Lo := Type_Low_Bound (Ityp);
364          Hi := Type_High_Bound (Ityp);
365
366          if not Compile_Time_Known_Value (Lo)
367            or else Nkind (Hi) /= N_Identifier
368            or else No (Entity (Hi))
369            or else Ekind (Entity (Hi)) /= E_Discriminant
370          then
371             goto Continue;
372          end if;
373
374          --  We have an array with appropriate bounds
375
376          Loval := Expr_Value (Lo);
377          Discr := Entity (Hi);
378          Dtyp  := Etype (Discr);
379
380          --  See if the discriminant has a known upper bound
381
382          Dhi := Type_High_Bound (Dtyp);
383
384          if not Compile_Time_Known_Value (Dhi) then
385             goto Continue;
386          end if;
387
388          Dhiv := Expr_Value (Dhi);
389
390          --  See if base type of component array has known upper bound
391
392          Ahi := Type_High_Bound (Etype (First_Index (Base_Type (Ctyp))));
393
394          if not Compile_Time_Known_Value (Ahi) then
395             goto Continue;
396          end if;
397
398          Ahiv := Expr_Value (Ahi);
399
400          --  The condition for doing the restriction is that the high bound
401          --  of the discriminant is greater than the low bound of the array,
402          --  and is also greater than the high bound of the base type index.
403
404          if Dhiv > Loval and then Dhiv > Ahiv then
405
406             --  We can reset the upper bound of the discriminant type to
407             --  whichever is larger, the low bound of the component, or
408             --  the high bound of the base type array index.
409
410             --  We build a subtype that is declared as
411
412             --     subtype Tnn is discr_type range discr_type'First .. max;
413
414             --  And insert this declaration into the tree. The type of the
415             --  discriminant is then reset to this more restricted subtype.
416
417             Tnn := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
418
419             Insert_Action (Declaration_Node (Rtype),
420               Make_Subtype_Declaration (Loc,
421                 Defining_Identifier => Tnn,
422                 Subtype_Indication =>
423                   Make_Subtype_Indication (Loc,
424                     Subtype_Mark => New_Occurrence_Of (Dtyp, Loc),
425                     Constraint   =>
426                       Make_Range_Constraint (Loc,
427                         Range_Expression =>
428                           Make_Range (Loc,
429                             Low_Bound =>
430                               Make_Attribute_Reference (Loc,
431                                 Attribute_Name => Name_First,
432                                 Prefix => New_Occurrence_Of (Dtyp, Loc)),
433                             High_Bound =>
434                               Make_Integer_Literal (Loc,
435                                 Intval => UI_Max (Loval, Ahiv)))))));
436
437             Set_Etype (Discr, Tnn);
438          end if;
439
440       <<Continue>>
441          Next_Component (Comp);
442       end loop;
443    end Adjust_Discriminants;
444
445    ---------------------------
446    -- Build_Array_Init_Proc --
447    ---------------------------
448
449    procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id) is
450       Loc        : constant Source_Ptr := Sloc (Nod);
451       Comp_Type  : constant Entity_Id  := Component_Type (A_Type);
452       Index_List : List_Id;
453       Proc_Id    : Entity_Id;
454       Body_Stmts : List_Id;
455
456       function Init_Component return List_Id;
457       --  Create one statement to initialize one array component, designated
458       --  by a full set of indices.
459
460       function Init_One_Dimension (N : Int) return List_Id;
461       --  Create loop to initialize one dimension of the array. The single
462       --  statement in the loop body initializes the inner dimensions if any,
463       --  or else the single component. Note that this procedure is called
464       --  recursively, with N being the dimension to be initialized. A call
465       --  with N greater than the number of dimensions simply generates the
466       --  component initialization, terminating the recursion.
467
468       --------------------
469       -- Init_Component --
470       --------------------
471
472       function Init_Component return List_Id is
473          Comp : Node_Id;
474
475       begin
476          Comp :=
477            Make_Indexed_Component (Loc,
478              Prefix => Make_Identifier (Loc, Name_uInit),
479              Expressions => Index_List);
480
481          if Needs_Simple_Initialization (Comp_Type) then
482             Set_Assignment_OK (Comp);
483             return New_List (
484               Make_Assignment_Statement (Loc,
485                 Name => Comp,
486                 Expression => Get_Simple_Init_Val (Comp_Type, Loc)));
487
488          else
489             return
490               Build_Initialization_Call (Loc, Comp, Comp_Type, True, A_Type);
491          end if;
492       end Init_Component;
493
494       ------------------------
495       -- Init_One_Dimension --
496       ------------------------
497
498       function Init_One_Dimension (N : Int) return List_Id is
499          Index      : Entity_Id;
500
501       begin
502          --  If the component does not need initializing, then there is nothing
503          --  to do here, so we return a null body. This occurs when generating
504          --  the dummy Init_Proc needed for Initialize_Scalars processing.
505
506          if not Has_Non_Null_Base_Init_Proc (Comp_Type)
507            and then not Needs_Simple_Initialization (Comp_Type)
508            and then not Has_Task (Comp_Type)
509          then
510             return New_List (Make_Null_Statement (Loc));
511
512          --  If all dimensions dealt with, we simply initialize the component
513
514          elsif N > Number_Dimensions (A_Type) then
515             return Init_Component;
516
517          --  Here we generate the required loop
518
519          else
520             Index :=
521               Make_Defining_Identifier (Loc, New_External_Name ('J', N));
522
523             Append (New_Reference_To (Index, Loc), Index_List);
524
525             return New_List (
526               Make_Implicit_Loop_Statement (Nod,
527                 Identifier => Empty,
528                 Iteration_Scheme =>
529                   Make_Iteration_Scheme (Loc,
530                     Loop_Parameter_Specification =>
531                       Make_Loop_Parameter_Specification (Loc,
532                         Defining_Identifier => Index,
533                         Discrete_Subtype_Definition =>
534                           Make_Attribute_Reference (Loc,
535                             Prefix => Make_Identifier (Loc, Name_uInit),
536                             Attribute_Name  => Name_Range,
537                             Expressions => New_List (
538                               Make_Integer_Literal (Loc, N))))),
539                 Statements =>  Init_One_Dimension (N + 1)));
540          end if;
541       end Init_One_Dimension;
542
543    --  Start of processing for Build_Array_Init_Proc
544
545    begin
546       if Suppress_Init_Proc (A_Type) then
547          return;
548       end if;
549
550       Index_List := New_List;
551
552       --  We need an initialization procedure if any of the following is true:
553
554       --    1. The component type has an initialization procedure
555       --    2. The component type needs simple initialization
556       --    3. Tasks are present
557       --    4. The type is marked as a publc entity
558
559       --  The reason for the public entity test is to deal properly with the
560       --  Initialize_Scalars pragma. This pragma can be set in the client and
561       --  not in the declaring package, this means the client will make a call
562       --  to the initialization procedure (because one of conditions 1-3 must
563       --  apply in this case), and we must generate a procedure (even if it is
564       --  null) to satisfy the call in this case.
565
566       --  Exception: do not build an array init_proc for a type whose root type
567       --  is Standard.String or Standard.Wide_String, since there is no place
568       --  to put the code, and in any case we handle initialization of such
569       --  types (in the Initialize_Scalars case, that's the only time the issue
570       --  arises) in a special manner anyway which does not need an init_proc.
571
572       if Has_Non_Null_Base_Init_Proc (Comp_Type)
573         or else Needs_Simple_Initialization (Comp_Type)
574         or else Has_Task (Comp_Type)
575         or else (not Restriction_Active (No_Initialize_Scalars)
576                    and then Is_Public (A_Type)
577                    and then Root_Type (A_Type) /= Standard_String
578                    and then Root_Type (A_Type) /= Standard_Wide_String)
579       then
580          Proc_Id :=
581            Make_Defining_Identifier (Loc, Make_Init_Proc_Name (A_Type));
582
583          Body_Stmts := Init_One_Dimension (1);
584
585          Discard_Node (
586            Make_Subprogram_Body (Loc,
587              Specification =>
588                Make_Procedure_Specification (Loc,
589                  Defining_Unit_Name => Proc_Id,
590                  Parameter_Specifications => Init_Formals (A_Type)),
591              Declarations => New_List,
592              Handled_Statement_Sequence =>
593                Make_Handled_Sequence_Of_Statements (Loc,
594                  Statements => Body_Stmts)));
595
596          Set_Ekind          (Proc_Id, E_Procedure);
597          Set_Is_Public      (Proc_Id, Is_Public (A_Type));
598          Set_Is_Internal    (Proc_Id);
599          Set_Has_Completion (Proc_Id);
600
601          if not Debug_Generated_Code then
602             Set_Debug_Info_Off (Proc_Id);
603          end if;
604
605          --  Set inlined unless controlled stuff or tasks around, in which
606          --  case we do not want to inline, because nested stuff may cause
607          --  difficulties in interunit inlining, and furthermore there is
608          --  in any case no point in inlining such complex init procs.
609
610          if not Has_Task (Proc_Id)
611            and then not Controlled_Type (Proc_Id)
612          then
613             Set_Is_Inlined (Proc_Id);
614          end if;
615
616          --  Associate Init_Proc with type, and determine if the procedure
617          --  is null (happens because of the Initialize_Scalars pragma case,
618          --  where we have to generate a null procedure in case it is called
619          --  by a client with Initialize_Scalars set). Such procedures have
620          --  to be generated, but do not have to be called, so we mark them
621          --  as null to suppress the call.
622
623          Set_Init_Proc (A_Type, Proc_Id);
624
625          if List_Length (Body_Stmts) = 1
626            and then Nkind (First (Body_Stmts)) = N_Null_Statement
627          then
628             Set_Is_Null_Init_Proc (Proc_Id);
629          end if;
630       end if;
631    end Build_Array_Init_Proc;
632
633    -----------------------------
634    -- Build_Class_Wide_Master --
635    -----------------------------
636
637    procedure Build_Class_Wide_Master (T : Entity_Id) is
638       Loc  : constant Source_Ptr := Sloc (T);
639       M_Id : Entity_Id;
640       Decl : Node_Id;
641       P    : Node_Id;
642
643    begin
644       --  Nothing to do if there is no task hierarchy.
645
646       if Restriction_Active (No_Task_Hierarchy) then
647          return;
648       end if;
649
650       --  Nothing to do if we already built a master entity for this scope
651
652       if not Has_Master_Entity (Scope (T)) then
653          --  first build the master entity
654          --    _Master : constant Master_Id := Current_Master.all;
655          --  and insert it just before the current declaration
656
657          Decl :=
658            Make_Object_Declaration (Loc,
659              Defining_Identifier =>
660                Make_Defining_Identifier (Loc, Name_uMaster),
661              Constant_Present => True,
662              Object_Definition => New_Reference_To (Standard_Integer, Loc),
663              Expression =>
664                Make_Explicit_Dereference (Loc,
665                  New_Reference_To (RTE (RE_Current_Master), Loc)));
666
667          P := Parent (T);
668          Insert_Before (P, Decl);
669          Analyze (Decl);
670          Set_Has_Master_Entity (Scope (T));
671
672          --  Now mark the containing scope as a task master
673
674          while Nkind (P) /= N_Compilation_Unit loop
675             P := Parent (P);
676
677             --  If we fall off the top, we are at the outer level, and the
678             --  environment task is our effective master, so nothing to mark.
679
680             if Nkind (P) = N_Task_Body
681               or else Nkind (P) = N_Block_Statement
682               or else Nkind (P) = N_Subprogram_Body
683             then
684                Set_Is_Task_Master (P, True);
685                exit;
686             end if;
687          end loop;
688       end if;
689
690       --  Now define the renaming of the master_id.
691
692       M_Id :=
693         Make_Defining_Identifier (Loc,
694           New_External_Name (Chars (T), 'M'));
695
696       Decl :=
697         Make_Object_Renaming_Declaration (Loc,
698           Defining_Identifier => M_Id,
699           Subtype_Mark => New_Reference_To (Standard_Integer, Loc),
700           Name => Make_Identifier (Loc, Name_uMaster));
701       Insert_Before (Parent (T), Decl);
702       Analyze (Decl);
703
704       Set_Master_Id (T, M_Id);
705
706    exception
707       when RE_Not_Available =>
708          return;
709    end Build_Class_Wide_Master;
710
711    --------------------------------
712    -- Build_Discr_Checking_Funcs --
713    --------------------------------
714
715    procedure Build_Discr_Checking_Funcs (N : Node_Id) is
716       Rec_Id            : Entity_Id;
717       Loc               : Source_Ptr;
718       Enclosing_Func_Id : Entity_Id;
719       Sequence          : Nat     := 1;
720       Type_Def          : Node_Id;
721       V                 : Node_Id;
722
723       function Build_Case_Statement
724         (Case_Id : Entity_Id;
725          Variant : Node_Id) return Node_Id;
726       --  Build a case statement containing only two alternatives. The
727       --  first alternative corresponds exactly to the discrete choices
728       --  given on the variant with contains the components that we are
729       --  generating the checks for. If the discriminant is one of these
730       --  return False. The second alternative is an OTHERS choice that
731       --  will return True indicating the discriminant did not match.
732
733       function Build_Dcheck_Function
734         (Case_Id : Entity_Id;
735          Variant : Node_Id) return Entity_Id;
736       --  Build the discriminant checking function for a given variant
737
738       procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id);
739       --  Builds the discriminant checking function for each variant of the
740       --  given variant part of the record type.
741
742       --------------------------
743       -- Build_Case_Statement --
744       --------------------------
745
746       function Build_Case_Statement
747         (Case_Id : Entity_Id;
748          Variant : Node_Id) return Node_Id
749       is
750          Alt_List       : constant List_Id := New_List;
751          Actuals_List   : List_Id;
752          Case_Node      : Node_Id;
753          Case_Alt_Node  : Node_Id;
754          Choice         : Node_Id;
755          Choice_List    : List_Id;
756          D              : Entity_Id;
757          Return_Node    : Node_Id;
758
759       begin
760          Case_Node := New_Node (N_Case_Statement, Loc);
761
762          --  Replace the discriminant which controls the variant, with the
763          --  name of the formal of the checking function.
764
765          Set_Expression (Case_Node,
766            Make_Identifier (Loc, Chars (Case_Id)));
767
768          Choice := First (Discrete_Choices (Variant));
769
770          if Nkind (Choice) = N_Others_Choice then
771             Choice_List := New_Copy_List (Others_Discrete_Choices (Choice));
772          else
773             Choice_List := New_Copy_List (Discrete_Choices (Variant));
774          end if;
775
776          if not Is_Empty_List (Choice_List) then
777             Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
778             Set_Discrete_Choices (Case_Alt_Node, Choice_List);
779
780             --  In case this is a nested variant, we need to return the result
781             --  of the discriminant checking function for the immediately
782             --  enclosing variant.
783
784             if Present (Enclosing_Func_Id) then
785                Actuals_List := New_List;
786
787                D := First_Discriminant (Rec_Id);
788                while Present (D) loop
789                   Append (Make_Identifier (Loc, Chars (D)), Actuals_List);
790                   Next_Discriminant (D);
791                end loop;
792
793                Return_Node :=
794                  Make_Return_Statement (Loc,
795                    Expression =>
796                      Make_Function_Call (Loc,
797                        Name =>
798                          New_Reference_To (Enclosing_Func_Id,  Loc),
799                        Parameter_Associations =>
800                          Actuals_List));
801
802             else
803                Return_Node :=
804                  Make_Return_Statement (Loc,
805                    Expression =>
806                      New_Reference_To (Standard_False, Loc));
807             end if;
808
809             Set_Statements (Case_Alt_Node, New_List (Return_Node));
810             Append (Case_Alt_Node, Alt_List);
811          end if;
812
813          Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
814          Choice_List := New_List (New_Node (N_Others_Choice, Loc));
815          Set_Discrete_Choices (Case_Alt_Node, Choice_List);
816
817          Return_Node :=
818            Make_Return_Statement (Loc,
819              Expression =>
820                New_Reference_To (Standard_True, Loc));
821
822          Set_Statements (Case_Alt_Node, New_List (Return_Node));
823          Append (Case_Alt_Node, Alt_List);
824
825          Set_Alternatives (Case_Node, Alt_List);
826          return Case_Node;
827       end Build_Case_Statement;
828
829       ---------------------------
830       -- Build_Dcheck_Function --
831       ---------------------------
832
833       function Build_Dcheck_Function
834         (Case_Id : Entity_Id;
835          Variant : Node_Id) return Entity_Id
836       is
837          Body_Node           : Node_Id;
838          Func_Id             : Entity_Id;
839          Parameter_List      : List_Id;
840          Spec_Node           : Node_Id;
841
842       begin
843          Body_Node := New_Node (N_Subprogram_Body, Loc);
844          Sequence := Sequence + 1;
845
846          Func_Id :=
847            Make_Defining_Identifier (Loc,
848              Chars => New_External_Name (Chars (Rec_Id), 'D', Sequence));
849
850          Spec_Node := New_Node (N_Function_Specification, Loc);
851          Set_Defining_Unit_Name (Spec_Node, Func_Id);
852
853          Parameter_List := Build_Discriminant_Formals (Rec_Id, False);
854
855          Set_Parameter_Specifications (Spec_Node, Parameter_List);
856          Set_Subtype_Mark (Spec_Node,
857                            New_Reference_To (Standard_Boolean,  Loc));
858          Set_Specification (Body_Node, Spec_Node);
859          Set_Declarations (Body_Node, New_List);
860
861          Set_Handled_Statement_Sequence (Body_Node,
862            Make_Handled_Sequence_Of_Statements (Loc,
863              Statements => New_List (
864                Build_Case_Statement (Case_Id, Variant))));
865
866          Set_Ekind       (Func_Id, E_Function);
867          Set_Mechanism   (Func_Id, Default_Mechanism);
868          Set_Is_Inlined  (Func_Id, True);
869          Set_Is_Pure     (Func_Id, True);
870          Set_Is_Public   (Func_Id, Is_Public (Rec_Id));
871          Set_Is_Internal (Func_Id, True);
872
873          if not Debug_Generated_Code then
874             Set_Debug_Info_Off (Func_Id);
875          end if;
876
877          Analyze (Body_Node);
878
879          Append_Freeze_Action (Rec_Id, Body_Node);
880          Set_Dcheck_Function (Variant, Func_Id);
881          return Func_Id;
882       end Build_Dcheck_Function;
883
884       ----------------------------
885       -- Build_Dcheck_Functions --
886       ----------------------------
887
888       procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id) is
889          Component_List_Node : Node_Id;
890          Decl                : Entity_Id;
891          Discr_Name          : Entity_Id;
892          Func_Id             : Entity_Id;
893          Variant             : Node_Id;
894          Saved_Enclosing_Func_Id : Entity_Id;
895
896       begin
897          --  Build the discriminant checking function for each variant, label
898          --  all components of that variant with the function's name.
899
900          Discr_Name := Entity (Name (Variant_Part_Node));
901          Variant := First_Non_Pragma (Variants (Variant_Part_Node));
902
903          while Present (Variant) loop
904             Func_Id := Build_Dcheck_Function (Discr_Name, Variant);
905             Component_List_Node := Component_List (Variant);
906
907             if not Null_Present (Component_List_Node) then
908                Decl :=
909                  First_Non_Pragma (Component_Items (Component_List_Node));
910
911                while Present (Decl) loop
912                   Set_Discriminant_Checking_Func
913                     (Defining_Identifier (Decl), Func_Id);
914
915                   Next_Non_Pragma (Decl);
916                end loop;
917
918                if Present (Variant_Part (Component_List_Node)) then
919                   Saved_Enclosing_Func_Id := Enclosing_Func_Id;
920                   Enclosing_Func_Id := Func_Id;
921                   Build_Dcheck_Functions (Variant_Part (Component_List_Node));
922                   Enclosing_Func_Id := Saved_Enclosing_Func_Id;
923                end if;
924             end if;
925
926             Next_Non_Pragma (Variant);
927          end loop;
928       end Build_Dcheck_Functions;
929
930    --  Start of processing for Build_Discr_Checking_Funcs
931
932    begin
933       --  Only build if not done already
934
935       if not Discr_Check_Funcs_Built (N) then
936          Type_Def := Type_Definition (N);
937
938          if Nkind (Type_Def) = N_Record_Definition then
939             if No (Component_List (Type_Def)) then   -- null record.
940                return;
941             else
942                V := Variant_Part (Component_List (Type_Def));
943             end if;
944
945          else pragma Assert (Nkind (Type_Def) = N_Derived_Type_Definition);
946             if No (Component_List (Record_Extension_Part (Type_Def))) then
947                return;
948             else
949                V := Variant_Part
950                       (Component_List (Record_Extension_Part (Type_Def)));
951             end if;
952          end if;
953
954          Rec_Id := Defining_Identifier (N);
955
956          if Present (V) and then not Is_Unchecked_Union (Rec_Id) then
957             Loc := Sloc (N);
958             Enclosing_Func_Id := Empty;
959             Build_Dcheck_Functions (V);
960          end if;
961
962          Set_Discr_Check_Funcs_Built (N);
963       end if;
964    end Build_Discr_Checking_Funcs;
965
966    --------------------------------
967    -- Build_Discriminant_Formals --
968    --------------------------------
969
970    function Build_Discriminant_Formals
971      (Rec_Id : Entity_Id;
972       Use_Dl : Boolean) return List_Id
973    is
974       Loc             : Source_Ptr       := Sloc (Rec_Id);
975       Parameter_List  : constant List_Id := New_List;
976       D               : Entity_Id;
977       Formal          : Entity_Id;
978       Param_Spec_Node : Node_Id;
979
980    begin
981       if Has_Discriminants (Rec_Id) then
982          D := First_Discriminant (Rec_Id);
983          while Present (D) loop
984             Loc := Sloc (D);
985
986             if Use_Dl then
987                Formal := Discriminal (D);
988             else
989                Formal := Make_Defining_Identifier (Loc, Chars (D));
990             end if;
991
992             Param_Spec_Node :=
993               Make_Parameter_Specification (Loc,
994                   Defining_Identifier => Formal,
995                 Parameter_Type =>
996                   New_Reference_To (Etype (D), Loc));
997             Append (Param_Spec_Node, Parameter_List);
998             Next_Discriminant (D);
999          end loop;
1000       end if;
1001
1002       return Parameter_List;
1003    end Build_Discriminant_Formals;
1004
1005    -------------------------------
1006    -- Build_Initialization_Call --
1007    -------------------------------
1008
1009    --  References to a discriminant inside the record type declaration
1010    --  can appear either in the subtype_indication to constrain a
1011    --  record or an array, or as part of a larger expression given for
1012    --  the initial value of a component. In both of these cases N appears
1013    --  in the record initialization procedure and needs to be replaced by
1014    --  the formal parameter of the initialization procedure which
1015    --  corresponds to that discriminant.
1016
1017    --  In the example below, references to discriminants D1 and D2 in proc_1
1018    --  are replaced by references to formals with the same name
1019    --  (discriminals)
1020
1021    --  A similar replacement is done for calls to any record
1022    --  initialization procedure for any components that are themselves
1023    --  of a record type.
1024
1025    --  type R (D1, D2 : Integer) is record
1026    --     X : Integer := F * D1;
1027    --     Y : Integer := F * D2;
1028    --  end record;
1029
1030    --  procedure proc_1 (Out_2 : out R; D1 : Integer; D2 : Integer) is
1031    --  begin
1032    --     Out_2.D1 := D1;
1033    --     Out_2.D2 := D2;
1034    --     Out_2.X := F * D1;
1035    --     Out_2.Y := F * D2;
1036    --  end;
1037
1038    function Build_Initialization_Call
1039      (Loc               : Source_Ptr;
1040       Id_Ref            : Node_Id;
1041       Typ               : Entity_Id;
1042       In_Init_Proc      : Boolean := False;
1043       Enclos_Type       : Entity_Id := Empty;
1044       Discr_Map         : Elist_Id := New_Elmt_List;
1045       With_Default_Init : Boolean := False) return List_Id
1046    is
1047       First_Arg      : Node_Id;
1048       Args           : List_Id;
1049       Decls          : List_Id;
1050       Decl           : Node_Id;
1051       Discr          : Entity_Id;
1052       Arg            : Node_Id;
1053       Proc           : constant Entity_Id := Base_Init_Proc (Typ);
1054       Init_Type      : constant Entity_Id := Etype (First_Formal (Proc));
1055       Full_Init_Type : constant Entity_Id := Underlying_Type (Init_Type);
1056       Res            : constant List_Id   := New_List;
1057       Full_Type      : Entity_Id := Typ;
1058       Controller_Typ : Entity_Id;
1059
1060    begin
1061       --  Nothing to do if the Init_Proc is null, unless Initialize_Scalars
1062       --  is active (in which case we make the call anyway, since in the
1063       --  actual compiled client it may be non null).
1064
1065       if Is_Null_Init_Proc (Proc) and then not Init_Or_Norm_Scalars then
1066          return Empty_List;
1067       end if;
1068
1069       --  Go to full view if private type. In the case of successive
1070       --  private derivations, this can require more than one step.
1071
1072       while Is_Private_Type (Full_Type)
1073         and then Present (Full_View (Full_Type))
1074       loop
1075          Full_Type := Full_View (Full_Type);
1076       end loop;
1077
1078       --  If Typ is derived, the procedure is the initialization procedure for
1079       --  the root type. Wrap the argument in an conversion to make it type
1080       --  honest. Actually it isn't quite type honest, because there can be
1081       --  conflicts of views in the private type case. That is why we set
1082       --  Conversion_OK in the conversion node.
1083       if (Is_Record_Type (Typ)
1084            or else Is_Array_Type (Typ)
1085            or else Is_Private_Type (Typ))
1086         and then Init_Type /= Base_Type (Typ)
1087       then
1088          First_Arg := OK_Convert_To (Etype (Init_Type), Id_Ref);
1089          Set_Etype (First_Arg, Init_Type);
1090
1091       else
1092          First_Arg := Id_Ref;
1093       end if;
1094
1095       Args := New_List (Convert_Concurrent (First_Arg, Typ));
1096
1097       --  In the tasks case, add _Master as the value of the _Master parameter
1098       --  and _Chain as the value of the _Chain parameter. At the outer level,
1099       --  these will be variables holding the corresponding values obtained
1100       --  from GNARL. At inner levels, they will be the parameters passed down
1101       --  through the outer routines.
1102
1103       if Has_Task (Full_Type) then
1104          if Restriction_Active (No_Task_Hierarchy) then
1105
1106             --  See comments in System.Tasking.Initialization.Init_RTS
1107             --  for the value 3 (should be rtsfindable constant ???)
1108
1109             Append_To (Args, Make_Integer_Literal (Loc, 3));
1110          else
1111             Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1112          end if;
1113
1114          Append_To (Args, Make_Identifier (Loc, Name_uChain));
1115
1116          --  Ada 2005 (AI-287): In case of default initialized components
1117          --  with tasks, we generate a null string actual parameter.
1118          --  This is just a workaround that must be improved later???
1119
1120          if With_Default_Init then
1121             declare
1122                S           : String_Id;
1123                Null_String : Node_Id;
1124             begin
1125                Start_String;
1126                S := End_String;
1127                Null_String := Make_String_Literal (Loc, Strval => S);
1128                Append_To (Args, Null_String);
1129             end;
1130          else
1131             Decls := Build_Task_Image_Decls (Loc, Id_Ref, Enclos_Type);
1132             Decl  := Last (Decls);
1133
1134             Append_To (Args,
1135               New_Occurrence_Of (Defining_Identifier (Decl), Loc));
1136             Append_List (Decls, Res);
1137          end if;
1138
1139       else
1140          Decls := No_List;
1141          Decl  := Empty;
1142       end if;
1143
1144       --  Add discriminant values if discriminants are present
1145
1146       if Has_Discriminants (Full_Init_Type) then
1147          Discr := First_Discriminant (Full_Init_Type);
1148
1149          while Present (Discr) loop
1150
1151             --  If this is a discriminated concurrent type, the init_proc
1152             --  for the corresponding record is being called. Use that
1153             --  type directly to find the discriminant value, to handle
1154             --  properly intervening renamed discriminants.
1155
1156             declare
1157                T : Entity_Id := Full_Type;
1158
1159             begin
1160                if Is_Protected_Type (T) then
1161                   T := Corresponding_Record_Type (T);
1162
1163                elsif Is_Private_Type (T)
1164                  and then Present (Underlying_Full_View (T))
1165                  and then Is_Protected_Type (Underlying_Full_View (T))
1166                then
1167                   T := Corresponding_Record_Type (Underlying_Full_View (T));
1168                end if;
1169
1170                Arg :=
1171                  Get_Discriminant_Value (
1172                    Discr,
1173                    T,
1174                    Discriminant_Constraint (Full_Type));
1175             end;
1176
1177             if In_Init_Proc then
1178
1179                --  Replace any possible references to the discriminant in the
1180                --  call to the record initialization procedure with references
1181                --  to the appropriate formal parameter.
1182
1183                if Nkind (Arg) = N_Identifier
1184                   and then Ekind (Entity (Arg)) = E_Discriminant
1185                then
1186                   Arg := New_Reference_To (Discriminal (Entity (Arg)), Loc);
1187
1188                --  Case of access discriminants. We replace the reference
1189                --  to the type by a reference to the actual object
1190
1191                elsif Nkind (Arg) = N_Attribute_Reference
1192                  and then Is_Access_Type (Etype (Arg))
1193                  and then Is_Entity_Name (Prefix (Arg))
1194                  and then Is_Type (Entity (Prefix (Arg)))
1195                then
1196                   Arg :=
1197                     Make_Attribute_Reference (Loc,
1198                       Prefix         => New_Copy (Prefix (Id_Ref)),
1199                       Attribute_Name => Name_Unrestricted_Access);
1200
1201                --  Otherwise make a copy of the default expression. Note
1202                --  that we use the current Sloc for this, because we do not
1203                --  want the call to appear to be at the declaration point.
1204                --  Within the expression, replace discriminants with their
1205                --  discriminals.
1206
1207                else
1208                   Arg :=
1209                     New_Copy_Tree (Arg, Map => Discr_Map, New_Sloc => Loc);
1210                end if;
1211
1212             else
1213                if Is_Constrained (Full_Type) then
1214                   Arg := Duplicate_Subexpr_No_Checks (Arg);
1215                else
1216                   --  The constraints come from the discriminant default
1217                   --  exps, they must be reevaluated, so we use New_Copy_Tree
1218                   --  but we ensure the proper Sloc (for any embedded calls).
1219
1220                   Arg := New_Copy_Tree (Arg, New_Sloc => Loc);
1221                end if;
1222             end if;
1223
1224             --  Ada 2005 (AI-287) In case of default initialized components,
1225             --  we need to generate the corresponding selected component node
1226             --  to access the discriminant value. In other cases this is not
1227             --  required because we are inside the init proc and we use the
1228             --  corresponding formal.
1229
1230             if With_Default_Init
1231               and then Nkind (Id_Ref) = N_Selected_Component
1232             then
1233                Append_To (Args,
1234                  Make_Selected_Component (Loc,
1235                    Prefix => New_Copy_Tree (Prefix (Id_Ref)),
1236                    Selector_Name => Arg));
1237             else
1238                Append_To (Args, Arg);
1239             end if;
1240
1241             Next_Discriminant (Discr);
1242          end loop;
1243       end if;
1244
1245       --  If this is a call to initialize the parent component of a derived
1246       --  tagged type, indicate that the tag should not be set in the parent.
1247
1248       if Is_Tagged_Type (Full_Init_Type)
1249         and then not Is_CPP_Class (Full_Init_Type)
1250         and then Nkind (Id_Ref) = N_Selected_Component
1251         and then Chars (Selector_Name (Id_Ref)) = Name_uParent
1252       then
1253          Append_To (Args, New_Occurrence_Of (Standard_False, Loc));
1254       end if;
1255
1256       Append_To (Res,
1257         Make_Procedure_Call_Statement (Loc,
1258           Name => New_Occurrence_Of (Proc, Loc),
1259           Parameter_Associations => Args));
1260
1261       if Controlled_Type (Typ)
1262         and then Nkind (Id_Ref) = N_Selected_Component
1263       then
1264          if Chars (Selector_Name (Id_Ref)) /= Name_uParent then
1265             Append_List_To (Res,
1266               Make_Init_Call (
1267                 Ref         => New_Copy_Tree (First_Arg),
1268                 Typ         => Typ,
1269                 Flist_Ref   =>
1270                   Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1271                 With_Attach => Make_Integer_Literal (Loc, 1)));
1272
1273          --  If the enclosing type is an extension with new controlled
1274          --  components, it has his own record controller. If the parent
1275          --  also had a record controller, attach it to the new one.
1276          --  Build_Init_Statements relies on the fact that in this specific
1277          --  case the last statement of the result is the attach call to
1278          --  the controller. If this is changed, it must be synchronized.
1279
1280          elsif Present (Enclos_Type)
1281            and then Has_New_Controlled_Component (Enclos_Type)
1282            and then Has_Controlled_Component (Typ)
1283          then
1284             if Is_Return_By_Reference_Type (Typ) then
1285                Controller_Typ := RTE (RE_Limited_Record_Controller);
1286             else
1287                Controller_Typ := RTE (RE_Record_Controller);
1288             end if;
1289
1290             Append_List_To (Res,
1291               Make_Init_Call (
1292                 Ref       =>
1293                   Make_Selected_Component (Loc,
1294                     Prefix        => New_Copy_Tree (First_Arg),
1295                     Selector_Name => Make_Identifier (Loc, Name_uController)),
1296                 Typ       => Controller_Typ,
1297                 Flist_Ref => Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1298                 With_Attach => Make_Integer_Literal (Loc, 1)));
1299          end if;
1300       end if;
1301
1302       return Res;
1303
1304    exception
1305       when RE_Not_Available =>
1306          return Empty_List;
1307    end Build_Initialization_Call;
1308
1309    ---------------------------
1310    -- Build_Master_Renaming --
1311    ---------------------------
1312
1313    procedure Build_Master_Renaming (N : Node_Id; T : Entity_Id) is
1314       Loc  : constant Source_Ptr := Sloc (N);
1315       M_Id : Entity_Id;
1316       Decl : Node_Id;
1317
1318    begin
1319       --  Nothing to do if there is no task hierarchy.
1320
1321       if Restriction_Active (No_Task_Hierarchy) then
1322          return;
1323       end if;
1324
1325       M_Id :=
1326         Make_Defining_Identifier (Loc,
1327           New_External_Name (Chars (T), 'M'));
1328
1329       Decl :=
1330         Make_Object_Renaming_Declaration (Loc,
1331           Defining_Identifier => M_Id,
1332           Subtype_Mark => New_Reference_To (RTE (RE_Master_Id), Loc),
1333           Name => Make_Identifier (Loc, Name_uMaster));
1334       Insert_Before (N, Decl);
1335       Analyze (Decl);
1336
1337       Set_Master_Id (T, M_Id);
1338
1339    exception
1340       when RE_Not_Available =>
1341          return;
1342    end Build_Master_Renaming;
1343
1344    ----------------------------
1345    -- Build_Record_Init_Proc --
1346    ----------------------------
1347
1348    procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id) is
1349       Loc         : Source_Ptr := Sloc (N);
1350       Discr_Map   : constant Elist_Id := New_Elmt_List;
1351       Proc_Id     : Entity_Id;
1352       Rec_Type    : Entity_Id;
1353       Set_Tag     : Entity_Id := Empty;
1354
1355       function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id;
1356       --  Build a assignment statement node which assigns to record
1357       --  component its default expression if defined. The left hand side
1358       --  of the assignment is marked Assignment_OK so that initialization
1359       --  of limited private records works correctly, Return also the
1360       --  adjustment call for controlled objects
1361
1362       procedure Build_Discriminant_Assignments (Statement_List : List_Id);
1363       --  If the record has discriminants, adds assignment statements to
1364       --  statement list to initialize the discriminant values from the
1365       --  arguments of the initialization procedure.
1366
1367       function Build_Init_Statements (Comp_List : Node_Id) return List_Id;
1368       --  Build a list representing a sequence of statements which initialize
1369       --  components of the given component list. This may involve building
1370       --  case statements for the variant parts.
1371
1372       function Build_Init_Call_Thru (Parameters : List_Id) return List_Id;
1373       --  Given a non-tagged type-derivation that declares discriminants,
1374       --  such as
1375       --
1376       --  type R (R1, R2 : Integer) is record ... end record;
1377       --
1378       --  type D (D1 : Integer) is new R (1, D1);
1379       --
1380       --  we make the _init_proc of D be
1381       --
1382       --       procedure _init_proc(X : D; D1 : Integer) is
1383       --       begin
1384       --          _init_proc( R(X), 1, D1);
1385       --       end _init_proc;
1386       --
1387       --  This function builds the call statement in this _init_proc.
1388
1389       procedure Build_Init_Procedure;
1390       --  Build the tree corresponding to the procedure specification and body
1391       --  of the initialization procedure (by calling all the preceding
1392       --  auxiliary routines), and install it as the _init TSS.
1393
1394       procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id);
1395       --  Add range checks to components of disciminated records. S is a
1396       --  subtype indication of a record component. Check_List is a list
1397       --  to which the check actions are appended.
1398
1399       function Component_Needs_Simple_Initialization
1400         (T : Entity_Id) return Boolean;
1401       --  Determines if a component needs simple initialization, given its
1402       --  type T. This is the same as Needs_Simple_Initialization except
1403       --  for the following differences. The types Tag and Vtable_Ptr,
1404       --  which are access types which would normally require simple
1405       --  initialization to null, do not require initialization as
1406       --  components, since they are explicitly initialized by other
1407       --  means. The other relaxation is for packed bit arrays that are
1408       --  associated with a modular type, which in some cases require
1409       --  zero initialization to properly support comparisons, except
1410       --  that comparison of such components always involves an explicit
1411       --  selection of only the component's specific bits (whether or not
1412       --  there are adjacent components or gaps), so zero initialization
1413       --  is never needed for components.
1414
1415       procedure Constrain_Array
1416         (SI         : Node_Id;
1417          Check_List : List_Id);
1418       --  Called from Build_Record_Checks.
1419       --  Apply a list of index constraints to an unconstrained array type.
1420       --  The first parameter is the entity for the resulting subtype.
1421       --  Check_List is a list to which the check actions are appended.
1422
1423       procedure Constrain_Index
1424         (Index      : Node_Id;
1425          S          : Node_Id;
1426          Check_List : List_Id);
1427       --  Called from Build_Record_Checks.
1428       --  Process an index constraint in a constrained array declaration.
1429       --  The constraint can be a subtype name, or a range with or without
1430       --  an explicit subtype mark. The index is the corresponding index of the
1431       --  unconstrained array. S is the range expression. Check_List is a list
1432       --  to which the check actions are appended.
1433
1434       function Parent_Subtype_Renaming_Discrims return Boolean;
1435       --  Returns True for base types N that rename discriminants, else False
1436
1437       function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean;
1438       --  Determines whether a record initialization procedure needs to be
1439       --  generated for the given record type.
1440
1441       ----------------------
1442       -- Build_Assignment --
1443       ----------------------
1444
1445       function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id is
1446          Exp  : Node_Id := N;
1447          Lhs  : Node_Id;
1448          Typ  : constant Entity_Id := Underlying_Type (Etype (Id));
1449          Kind : Node_Kind := Nkind (N);
1450          Res  : List_Id;
1451
1452       begin
1453          Loc := Sloc (N);
1454          Lhs :=
1455            Make_Selected_Component (Loc,
1456              Prefix => Make_Identifier (Loc, Name_uInit),
1457              Selector_Name => New_Occurrence_Of (Id, Loc));
1458          Set_Assignment_OK (Lhs);
1459
1460          --  Case of an access attribute applied to the current
1461          --  instance. Replace the reference to the type by a
1462          --  reference to the actual object. (Note that this
1463          --  handles the case of the top level of the expression
1464          --  being given by such an attribute, but doesn't cover
1465          --  uses nested within an initial value expression.
1466          --  Nested uses are unlikely to occur in practice,
1467          --  but theoretically possible. It's not clear how
1468          --  to handle them without fully traversing the
1469          --  expression. ???)
1470
1471          if Kind = N_Attribute_Reference
1472            and then (Attribute_Name (N) = Name_Unchecked_Access
1473                        or else
1474                      Attribute_Name (N) = Name_Unrestricted_Access)
1475            and then Is_Entity_Name (Prefix (N))
1476            and then Is_Type (Entity (Prefix (N)))
1477            and then Entity (Prefix (N)) = Rec_Type
1478          then
1479             Exp :=
1480               Make_Attribute_Reference (Loc,
1481                 Prefix         => Make_Identifier (Loc, Name_uInit),
1482                 Attribute_Name => Name_Unrestricted_Access);
1483          end if;
1484
1485          --  For a derived type the default value is copied from the component
1486          --  declaration of the parent. In the analysis of the init_proc for
1487          --  the parent the default value may have been expanded into a local
1488          --  variable, which is of course not usable here. We must copy the
1489          --  original expression and reanalyze.
1490
1491          if Nkind (Exp) = N_Identifier
1492            and then not Comes_From_Source (Exp)
1493            and then Analyzed (Exp)
1494            and then not In_Open_Scopes (Scope (Entity (Exp)))
1495            and then Nkind (Original_Node (Exp)) = N_Aggregate
1496          then
1497             Exp := New_Copy_Tree (Original_Node (Exp));
1498          end if;
1499
1500          --  Ada 2005 (AI-231): Generate conversion to the null-excluding
1501          --  type to force the corresponding run-time check
1502
1503          if Ada_Version >= Ada_05
1504            and then Can_Never_Be_Null (Etype (Id))  -- Lhs
1505            and then Present (Etype (Exp))
1506            and then not Can_Never_Be_Null (Etype (Exp))
1507          then
1508             Rewrite (Exp, Convert_To (Etype (Id), Relocate_Node (Exp)));
1509             Analyze_And_Resolve (Exp, Etype (Id));
1510          end if;
1511
1512          Res := New_List (
1513            Make_Assignment_Statement (Loc,
1514              Name       => Lhs,
1515              Expression => Exp));
1516
1517          Set_No_Ctrl_Actions (First (Res));
1518
1519          --  Adjust the tag if tagged (because of possible view conversions).
1520          --  Suppress the tag adjustment when Java_VM because JVM tags are
1521          --  represented implicitly in objects.
1522
1523          if Is_Tagged_Type (Typ) and then not Java_VM then
1524             Append_To (Res,
1525               Make_Assignment_Statement (Loc,
1526                 Name =>
1527                   Make_Selected_Component (Loc,
1528                     Prefix =>  New_Copy_Tree (Lhs),
1529                     Selector_Name =>
1530                       New_Reference_To (Tag_Component (Typ), Loc)),
1531
1532                 Expression =>
1533                   Unchecked_Convert_To (RTE (RE_Tag),
1534                     New_Reference_To (Access_Disp_Table (Typ), Loc))));
1535          end if;
1536
1537          --  Adjust the component if controlled except if it is an
1538          --  aggregate that will be expanded inline
1539
1540          if Kind = N_Qualified_Expression then
1541             Kind := Nkind (Expression (N));
1542          end if;
1543
1544          if Controlled_Type (Typ)
1545          and then not (Kind = N_Aggregate or else Kind = N_Extension_Aggregate)
1546          then
1547             Append_List_To (Res,
1548               Make_Adjust_Call (
1549                Ref          => New_Copy_Tree (Lhs),
1550                Typ          => Etype (Id),
1551                Flist_Ref    =>
1552                  Find_Final_List (Etype (Id), New_Copy_Tree (Lhs)),
1553                With_Attach  => Make_Integer_Literal (Loc, 1)));
1554          end if;
1555
1556          return Res;
1557
1558       exception
1559          when RE_Not_Available =>
1560             return Empty_List;
1561       end Build_Assignment;
1562
1563       ------------------------------------
1564       -- Build_Discriminant_Assignments --
1565       ------------------------------------
1566
1567       procedure Build_Discriminant_Assignments (Statement_List : List_Id) is
1568          D         : Entity_Id;
1569          Is_Tagged : constant Boolean := Is_Tagged_Type (Rec_Type);
1570
1571       begin
1572          if Has_Discriminants (Rec_Type)
1573            and then not Is_Unchecked_Union (Rec_Type)
1574          then
1575             D := First_Discriminant (Rec_Type);
1576
1577             while Present (D) loop
1578                --  Don't generate the assignment for discriminants in derived
1579                --  tagged types if the discriminant is a renaming of some
1580                --  ancestor discriminant.  This initialization will be done
1581                --  when initializing the _parent field of the derived record.
1582
1583                if Is_Tagged and then
1584                  Present (Corresponding_Discriminant (D))
1585                then
1586                   null;
1587
1588                else
1589                   Loc := Sloc (D);
1590                   Append_List_To (Statement_List,
1591                     Build_Assignment (D,
1592                       New_Reference_To (Discriminal (D), Loc)));
1593                end if;
1594
1595                Next_Discriminant (D);
1596             end loop;
1597          end if;
1598       end Build_Discriminant_Assignments;
1599
1600       --------------------------
1601       -- Build_Init_Call_Thru --
1602       --------------------------
1603
1604       function Build_Init_Call_Thru (Parameters : List_Id) return List_Id is
1605          Parent_Proc : constant Entity_Id :=
1606                          Base_Init_Proc (Etype (Rec_Type));
1607
1608          Parent_Type : constant Entity_Id :=
1609                          Etype (First_Formal (Parent_Proc));
1610
1611          Uparent_Type : constant Entity_Id :=
1612                           Underlying_Type (Parent_Type);
1613
1614          First_Discr_Param : Node_Id;
1615
1616          Parent_Discr : Entity_Id;
1617          First_Arg    : Node_Id;
1618          Args         : List_Id;
1619          Arg          : Node_Id;
1620          Res          : List_Id;
1621
1622       begin
1623          --  First argument (_Init) is the object to be initialized.
1624          --  ??? not sure where to get a reasonable Loc for First_Arg
1625
1626          First_Arg :=
1627            OK_Convert_To (Parent_Type,
1628              New_Reference_To (Defining_Identifier (First (Parameters)), Loc));
1629
1630          Set_Etype (First_Arg, Parent_Type);
1631
1632          Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
1633
1634          --  In the tasks case,
1635          --    add _Master as the value of the _Master parameter
1636          --    add _Chain as the value of the _Chain parameter.
1637          --    add _Task_Name as the value of the _Task_Name parameter.
1638          --  At the outer level, these will be variables holding the
1639          --  corresponding values obtained from GNARL or the expander.
1640          --
1641          --  At inner levels, they will be the parameters passed down through
1642          --  the outer routines.
1643
1644          First_Discr_Param := Next (First (Parameters));
1645
1646          if Has_Task (Rec_Type) then
1647             if Restriction_Active (No_Task_Hierarchy) then
1648
1649                --  See comments in System.Tasking.Initialization.Init_RTS
1650                --  for the value 3.
1651
1652                Append_To (Args, Make_Integer_Literal (Loc, 3));
1653             else
1654                Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1655             end if;
1656
1657             Append_To (Args, Make_Identifier (Loc, Name_uChain));
1658             Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
1659             First_Discr_Param := Next (Next (Next (First_Discr_Param)));
1660          end if;
1661
1662          --  Append discriminant values
1663
1664          if Has_Discriminants (Uparent_Type) then
1665             pragma Assert (not Is_Tagged_Type (Uparent_Type));
1666
1667             Parent_Discr := First_Discriminant (Uparent_Type);
1668             while Present (Parent_Discr) loop
1669
1670                --  Get the initial value for this discriminant
1671                --  ??? needs to be cleaned up to use parent_Discr_Constr
1672                --  directly.
1673
1674                declare
1675                   Discr_Value : Elmt_Id :=
1676                                   First_Elmt
1677                                     (Stored_Constraint (Rec_Type));
1678
1679                   Discr       : Entity_Id :=
1680                                   First_Stored_Discriminant (Uparent_Type);
1681                begin
1682                   while Original_Record_Component (Parent_Discr) /= Discr loop
1683                      Next_Stored_Discriminant (Discr);
1684                      Next_Elmt (Discr_Value);
1685                   end loop;
1686
1687                   Arg := Node (Discr_Value);
1688                end;
1689
1690                --  Append it to the list
1691
1692                if Nkind (Arg) = N_Identifier
1693                   and then Ekind (Entity (Arg)) = E_Discriminant
1694                then
1695                   Append_To (Args,
1696                     New_Reference_To (Discriminal (Entity (Arg)), Loc));
1697
1698                --  Case of access discriminants. We replace the reference
1699                --  to the type by a reference to the actual object
1700
1701 --     ??? why is this code deleted without comment
1702
1703 --               elsif Nkind (Arg) = N_Attribute_Reference
1704 --                 and then Is_Entity_Name (Prefix (Arg))
1705 --                 and then Is_Type (Entity (Prefix (Arg)))
1706 --               then
1707 --                  Append_To (Args,
1708 --                    Make_Attribute_Reference (Loc,
1709 --                      Prefix         => New_Copy (Prefix (Id_Ref)),
1710 --                      Attribute_Name => Name_Unrestricted_Access));
1711
1712                else
1713                   Append_To (Args, New_Copy (Arg));
1714                end if;
1715
1716                Next_Discriminant (Parent_Discr);
1717             end loop;
1718          end if;
1719
1720          Res :=
1721             New_List (
1722               Make_Procedure_Call_Statement (Loc,
1723                 Name => New_Occurrence_Of (Parent_Proc, Loc),
1724                 Parameter_Associations => Args));
1725
1726          return Res;
1727       end Build_Init_Call_Thru;
1728
1729       --------------------------
1730       -- Build_Init_Procedure --
1731       --------------------------
1732
1733       procedure Build_Init_Procedure is
1734          Body_Node             : Node_Id;
1735          Handled_Stmt_Node     : Node_Id;
1736          Parameters            : List_Id;
1737          Proc_Spec_Node        : Node_Id;
1738          Body_Stmts            : List_Id;
1739          Record_Extension_Node : Node_Id;
1740          Init_Tag              : Node_Id;
1741
1742       begin
1743          Body_Stmts := New_List;
1744          Body_Node := New_Node (N_Subprogram_Body, Loc);
1745
1746          Proc_Id :=
1747            Make_Defining_Identifier (Loc,
1748              Chars => Make_Init_Proc_Name (Rec_Type));
1749          Set_Ekind (Proc_Id, E_Procedure);
1750
1751          Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
1752          Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
1753
1754          Parameters := Init_Formals (Rec_Type);
1755          Append_List_To (Parameters,
1756            Build_Discriminant_Formals (Rec_Type, True));
1757
1758          --  For tagged types, we add a flag to indicate whether the routine
1759          --  is called to initialize a parent component in the init_proc of
1760          --  a type extension. If the flag is false, we do not set the tag
1761          --  because it has been set already in the extension.
1762
1763          if Is_Tagged_Type (Rec_Type)
1764            and then not Is_CPP_Class (Rec_Type)
1765          then
1766             Set_Tag :=
1767                   Make_Defining_Identifier (Loc, New_Internal_Name ('P'));
1768
1769             Append_To (Parameters,
1770               Make_Parameter_Specification (Loc,
1771                 Defining_Identifier => Set_Tag,
1772                 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
1773                 Expression => New_Occurrence_Of (Standard_True, Loc)));
1774          end if;
1775
1776          Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
1777          Set_Specification (Body_Node, Proc_Spec_Node);
1778          Set_Declarations (Body_Node, New_List);
1779
1780          if Parent_Subtype_Renaming_Discrims then
1781
1782             --  N is a Derived_Type_Definition that renames the parameters
1783             --  of the ancestor type.  We init it by expanding our discrims
1784             --  and call the ancestor _init_proc with a type-converted object
1785
1786             Append_List_To (Body_Stmts,
1787               Build_Init_Call_Thru (Parameters));
1788
1789          elsif Nkind (Type_Definition (N)) = N_Record_Definition then
1790             Build_Discriminant_Assignments (Body_Stmts);
1791
1792             if not Null_Present (Type_Definition (N)) then
1793                Append_List_To (Body_Stmts,
1794                  Build_Init_Statements (
1795                    Component_List (Type_Definition (N))));
1796             end if;
1797
1798          else
1799             --  N is a Derived_Type_Definition with a possible non-empty
1800             --  extension. The initialization of a type extension consists
1801             --  in the initialization of the components in the extension.
1802
1803             Build_Discriminant_Assignments (Body_Stmts);
1804
1805             Record_Extension_Node :=
1806               Record_Extension_Part (Type_Definition (N));
1807
1808             if not Null_Present (Record_Extension_Node) then
1809                declare
1810                   Stmts : constant List_Id :=
1811                             Build_Init_Statements (
1812                               Component_List (Record_Extension_Node));
1813
1814                begin
1815                   --  The parent field must be initialized first because
1816                   --  the offset of the new discriminants may depend on it
1817
1818                   Prepend_To (Body_Stmts, Remove_Head (Stmts));
1819                   Append_List_To (Body_Stmts, Stmts);
1820                end;
1821             end if;
1822          end if;
1823
1824          --  Add here the assignment to instantiate the Tag
1825
1826          --  The assignement corresponds to the code:
1827
1828          --     _Init._Tag := Typ'Tag;
1829
1830          --  Suppress the tag assignment when Java_VM because JVM tags are
1831          --  represented implicitly in objects.
1832
1833          if Is_Tagged_Type (Rec_Type)
1834            and then not Is_CPP_Class (Rec_Type)
1835            and then not Java_VM
1836          then
1837             Init_Tag :=
1838               Make_Assignment_Statement (Loc,
1839                 Name =>
1840                   Make_Selected_Component (Loc,
1841                     Prefix => Make_Identifier (Loc, Name_uInit),
1842                     Selector_Name =>
1843                       New_Reference_To (Tag_Component (Rec_Type), Loc)),
1844
1845                 Expression =>
1846                   New_Reference_To (Access_Disp_Table (Rec_Type), Loc));
1847
1848             --  The tag must be inserted before the assignments to other
1849             --  components,  because the initial value of the component may
1850             --  depend ot the tag (eg. through a dispatching operation on
1851             --  an access to the current type). The tag assignment is not done
1852             --  when initializing the parent component of a type extension,
1853             --  because in that case the tag is set in the extension.
1854             --  Extensions of imported C++ classes add a final complication,
1855             --  because we cannot inhibit tag setting in the constructor for
1856             --  the parent. In that case we insert the tag initialization
1857             --  after the calls to initialize the parent.
1858
1859             Init_Tag :=
1860               Make_If_Statement (Loc,
1861                 Condition => New_Occurrence_Of (Set_Tag, Loc),
1862                 Then_Statements => New_List (Init_Tag));
1863
1864             if not Is_CPP_Class (Etype (Rec_Type)) then
1865                Prepend_To (Body_Stmts, Init_Tag);
1866
1867             else
1868                declare
1869                   Nod : Node_Id := First (Body_Stmts);
1870
1871                begin
1872                   --  We assume the first init_proc call is for the parent
1873
1874                   while Present (Next (Nod))
1875                     and then (Nkind (Nod) /= N_Procedure_Call_Statement
1876                                or else not Is_Init_Proc (Name (Nod)))
1877                   loop
1878                      Nod := Next (Nod);
1879                   end loop;
1880
1881                   Insert_After (Nod, Init_Tag);
1882                end;
1883             end if;
1884          end if;
1885
1886          Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
1887          Set_Statements (Handled_Stmt_Node, Body_Stmts);
1888          Set_Exception_Handlers (Handled_Stmt_Node, No_List);
1889          Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
1890
1891          if not Debug_Generated_Code then
1892             Set_Debug_Info_Off (Proc_Id);
1893          end if;
1894
1895          --  Associate Init_Proc with type, and determine if the procedure
1896          --  is null (happens because of the Initialize_Scalars pragma case,
1897          --  where we have to generate a null procedure in case it is called
1898          --  by a client with Initialize_Scalars set). Such procedures have
1899          --  to be generated, but do not have to be called, so we mark them
1900          --  as null to suppress the call.
1901
1902          Set_Init_Proc (Rec_Type, Proc_Id);
1903
1904          if List_Length (Body_Stmts) = 1
1905            and then Nkind (First (Body_Stmts)) = N_Null_Statement
1906          then
1907             Set_Is_Null_Init_Proc (Proc_Id);
1908          end if;
1909       end Build_Init_Procedure;
1910
1911       ---------------------------
1912       -- Build_Init_Statements --
1913       ---------------------------
1914
1915       function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
1916          Check_List     : constant List_Id := New_List;
1917          Alt_List       : List_Id;
1918          Statement_List : List_Id;
1919          Stmts          : List_Id;
1920
1921          Per_Object_Constraint_Components : Boolean;
1922
1923          Decl     : Node_Id;
1924          Variant  : Node_Id;
1925
1926          Id  : Entity_Id;
1927          Typ : Entity_Id;
1928
1929          function Has_Access_Constraint (E : Entity_Id) return Boolean;
1930          --  Components with access discriminants that depend on the current
1931          --  instance must be initialized after all other components.
1932
1933          ---------------------------
1934          -- Has_Access_Constraint --
1935          ---------------------------
1936
1937          function Has_Access_Constraint (E : Entity_Id) return Boolean is
1938             Disc : Entity_Id;
1939             T    : constant Entity_Id := Etype (E);
1940
1941          begin
1942             if Has_Per_Object_Constraint (E)
1943               and then Has_Discriminants (T)
1944             then
1945                Disc := First_Discriminant (T);
1946                while Present (Disc) loop
1947                   if Is_Access_Type (Etype (Disc)) then
1948                      return True;
1949                   end if;
1950
1951                   Next_Discriminant (Disc);
1952                end loop;
1953
1954                return False;
1955             else
1956                return False;
1957             end if;
1958          end Has_Access_Constraint;
1959
1960       --  Start of processing for Build_Init_Statements
1961
1962       begin
1963          if Null_Present (Comp_List) then
1964             return New_List (Make_Null_Statement (Loc));
1965          end if;
1966
1967          Statement_List := New_List;
1968
1969          --  Loop through components, skipping pragmas, in 2 steps. The first
1970          --  step deals with regular components. The second step deals with
1971          --  components have per object constraints, and no explicit initia-
1972          --  lization.
1973
1974          Per_Object_Constraint_Components := False;
1975
1976          --  First step : regular components
1977
1978          Decl := First_Non_Pragma (Component_Items (Comp_List));
1979          while Present (Decl) loop
1980             Loc := Sloc (Decl);
1981             Build_Record_Checks
1982               (Subtype_Indication (Component_Definition (Decl)), Check_List);
1983
1984             Id := Defining_Identifier (Decl);
1985             Typ := Etype (Id);
1986
1987             if Has_Access_Constraint (Id)
1988               and then No (Expression (Decl))
1989             then
1990                --  Skip processing for now and ask for a second pass
1991
1992                Per_Object_Constraint_Components := True;
1993
1994             else
1995                --  Case of explicit initialization
1996
1997                if Present (Expression (Decl)) then
1998                   Stmts := Build_Assignment (Id, Expression (Decl));
1999
2000                --  Case of composite component with its own Init_Proc
2001
2002                elsif Has_Non_Null_Base_Init_Proc (Typ) then
2003                   Stmts :=
2004                     Build_Initialization_Call
2005                       (Loc,
2006                        Make_Selected_Component (Loc,
2007                          Prefix => Make_Identifier (Loc, Name_uInit),
2008                          Selector_Name => New_Occurrence_Of (Id, Loc)),
2009                        Typ,
2010                        True,
2011                        Rec_Type,
2012                        Discr_Map => Discr_Map);
2013
2014                --  Case of component needing simple initialization
2015
2016                elsif Component_Needs_Simple_Initialization (Typ) then
2017                   Stmts :=
2018                     Build_Assignment (Id, Get_Simple_Init_Val (Typ, Loc));
2019
2020                --  Nothing needed for this case
2021
2022                else
2023                   Stmts := No_List;
2024                end if;
2025
2026                if Present (Check_List) then
2027                   Append_List_To (Statement_List, Check_List);
2028                end if;
2029
2030                if Present (Stmts) then
2031
2032                   --  Add the initialization of the record controller before
2033                   --  the _Parent field is attached to it when the attachment
2034                   --  can occur. It does not work to simply initialize the
2035                   --  controller first: it must be initialized after the parent
2036                   --  if the parent holds discriminants that can be used
2037                   --  to compute the offset of the controller. We assume here
2038                   --  that the last statement of the initialization call is the
2039                   --  attachement of the parent (see Build_Initialization_Call)
2040
2041                   if Chars (Id) = Name_uController
2042                     and then Rec_Type /= Etype (Rec_Type)
2043                     and then Has_Controlled_Component (Etype (Rec_Type))
2044                     and then Has_New_Controlled_Component (Rec_Type)
2045                   then
2046                      Insert_List_Before (Last (Statement_List), Stmts);
2047                   else
2048                      Append_List_To (Statement_List, Stmts);
2049                   end if;
2050                end if;
2051             end if;
2052
2053             Next_Non_Pragma (Decl);
2054          end loop;
2055
2056          if Per_Object_Constraint_Components then
2057
2058             --  Second pass: components with per-object constraints
2059
2060             Decl := First_Non_Pragma (Component_Items (Comp_List));
2061
2062             while Present (Decl) loop
2063                Loc := Sloc (Decl);
2064                Id := Defining_Identifier (Decl);
2065                Typ := Etype (Id);
2066
2067                if Has_Access_Constraint (Id)
2068                  and then No (Expression (Decl))
2069                then
2070                   if Has_Non_Null_Base_Init_Proc (Typ) then
2071                      Append_List_To (Statement_List,
2072                        Build_Initialization_Call (Loc,
2073                          Make_Selected_Component (Loc,
2074                            Prefix => Make_Identifier (Loc, Name_uInit),
2075                            Selector_Name => New_Occurrence_Of (Id, Loc)),
2076                          Typ, True, Rec_Type, Discr_Map => Discr_Map));
2077
2078                   elsif Component_Needs_Simple_Initialization (Typ) then
2079                      Append_List_To (Statement_List,
2080                        Build_Assignment (Id, Get_Simple_Init_Val (Typ, Loc)));
2081                   end if;
2082                end if;
2083
2084                Next_Non_Pragma (Decl);
2085             end loop;
2086          end if;
2087
2088          --  Process the variant part
2089
2090          if Present (Variant_Part (Comp_List)) then
2091             Alt_List := New_List;
2092             Variant := First_Non_Pragma (Variants (Variant_Part (Comp_List)));
2093
2094             while Present (Variant) loop
2095                Loc := Sloc (Variant);
2096                Append_To (Alt_List,
2097                  Make_Case_Statement_Alternative (Loc,
2098                    Discrete_Choices =>
2099                      New_Copy_List (Discrete_Choices (Variant)),
2100                    Statements =>
2101                      Build_Init_Statements (Component_List (Variant))));
2102
2103                Next_Non_Pragma (Variant);
2104             end loop;
2105
2106             --  The expression of the case statement which is a reference
2107             --  to one of the discriminants is replaced by the appropriate
2108             --  formal parameter of the initialization procedure.
2109
2110             Append_To (Statement_List,
2111               Make_Case_Statement (Loc,
2112                 Expression =>
2113                   New_Reference_To (Discriminal (
2114                     Entity (Name (Variant_Part (Comp_List)))), Loc),
2115                 Alternatives => Alt_List));
2116          end if;
2117
2118          --  For a task record type, add the task create call and calls
2119          --  to bind any interrupt (signal) entries.
2120
2121          if Is_Task_Record_Type (Rec_Type) then
2122
2123             --  In the case of the restricted run time the ATCB has already
2124             --  been preallocated.
2125
2126             if Restricted_Profile then
2127                Append_To (Statement_List,
2128                  Make_Assignment_Statement (Loc,
2129                    Name => Make_Selected_Component (Loc,
2130                      Prefix => Make_Identifier (Loc, Name_uInit),
2131                      Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
2132                    Expression => Make_Attribute_Reference (Loc,
2133                      Prefix =>
2134                        Make_Selected_Component (Loc,
2135                          Prefix => Make_Identifier (Loc, Name_uInit),
2136                          Selector_Name =>
2137                            Make_Identifier (Loc, Name_uATCB)),
2138                      Attribute_Name => Name_Unchecked_Access)));
2139             end if;
2140
2141             Append_To (Statement_List, Make_Task_Create_Call (Rec_Type));
2142
2143             declare
2144                Task_Type : constant Entity_Id :=
2145                              Corresponding_Concurrent_Type (Rec_Type);
2146                Task_Decl : constant Node_Id := Parent (Task_Type);
2147                Task_Def  : constant Node_Id := Task_Definition (Task_Decl);
2148                Vis_Decl  : Node_Id;
2149                Ent       : Entity_Id;
2150
2151             begin
2152                if Present (Task_Def) then
2153                   Vis_Decl := First (Visible_Declarations (Task_Def));
2154                   while Present (Vis_Decl) loop
2155                      Loc := Sloc (Vis_Decl);
2156
2157                      if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
2158                         if Get_Attribute_Id (Chars (Vis_Decl)) =
2159                                                        Attribute_Address
2160                         then
2161                            Ent := Entity (Name (Vis_Decl));
2162
2163                            if Ekind (Ent) = E_Entry then
2164                               Append_To (Statement_List,
2165                                 Make_Procedure_Call_Statement (Loc,
2166                                   Name => New_Reference_To (
2167                                     RTE (RE_Bind_Interrupt_To_Entry), Loc),
2168                                   Parameter_Associations => New_List (
2169                                     Make_Selected_Component (Loc,
2170                                       Prefix =>
2171                                         Make_Identifier (Loc, Name_uInit),
2172                                       Selector_Name =>
2173                                         Make_Identifier (Loc, Name_uTask_Id)),
2174                                     Entry_Index_Expression (
2175                                       Loc, Ent, Empty, Task_Type),
2176                                     Expression (Vis_Decl))));
2177                            end if;
2178                         end if;
2179                      end if;
2180
2181                      Next (Vis_Decl);
2182                   end loop;
2183                end if;
2184             end;
2185          end if;
2186
2187          --  For a protected type, add statements generated by
2188          --  Make_Initialize_Protection.
2189
2190          if Is_Protected_Record_Type (Rec_Type) then
2191             Append_List_To (Statement_List,
2192               Make_Initialize_Protection (Rec_Type));
2193          end if;
2194
2195          --  If no initializations when generated for component declarations
2196          --  corresponding to this Statement_List, append a null statement
2197          --  to the Statement_List to make it a valid Ada tree.
2198
2199          if Is_Empty_List (Statement_List) then
2200             Append (New_Node (N_Null_Statement, Loc), Statement_List);
2201          end if;
2202
2203          return Statement_List;
2204
2205       exception
2206          when RE_Not_Available =>
2207          return Empty_List;
2208       end Build_Init_Statements;
2209
2210       -------------------------
2211       -- Build_Record_Checks --
2212       -------------------------
2213
2214       procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
2215          Subtype_Mark_Id : Entity_Id;
2216
2217       begin
2218          if Nkind (S) = N_Subtype_Indication then
2219             Find_Type (Subtype_Mark (S));
2220             Subtype_Mark_Id := Entity (Subtype_Mark (S));
2221
2222             --  Remaining processing depends on type
2223
2224             case Ekind (Subtype_Mark_Id) is
2225
2226                when Array_Kind =>
2227                   Constrain_Array (S, Check_List);
2228
2229                when others =>
2230                   null;
2231             end case;
2232          end if;
2233       end Build_Record_Checks;
2234
2235       -------------------------------------------
2236       -- Component_Needs_Simple_Initialization --
2237       -------------------------------------------
2238
2239       function Component_Needs_Simple_Initialization
2240         (T : Entity_Id) return Boolean
2241       is
2242       begin
2243          return
2244            Needs_Simple_Initialization (T)
2245              and then not Is_RTE (T, RE_Tag)
2246              and then not Is_RTE (T, RE_Vtable_Ptr)
2247              and then not Is_Bit_Packed_Array (T);
2248       end Component_Needs_Simple_Initialization;
2249
2250       ---------------------
2251       -- Constrain_Array --
2252       ---------------------
2253
2254       procedure Constrain_Array
2255         (SI          : Node_Id;
2256          Check_List  : List_Id)
2257       is
2258          C                     : constant Node_Id := Constraint (SI);
2259          Number_Of_Constraints : Nat := 0;
2260          Index                 : Node_Id;
2261          S, T                  : Entity_Id;
2262
2263       begin
2264          T := Entity (Subtype_Mark (SI));
2265
2266          if Ekind (T) in Access_Kind then
2267             T := Designated_Type (T);
2268          end if;
2269
2270          S := First (Constraints (C));
2271
2272          while Present (S) loop
2273             Number_Of_Constraints := Number_Of_Constraints + 1;
2274             Next (S);
2275          end loop;
2276
2277          --  In either case, the index constraint must provide a discrete
2278          --  range for each index of the array type and the type of each
2279          --  discrete range must be the same as that of the corresponding
2280          --  index. (RM 3.6.1)
2281
2282          S := First (Constraints (C));
2283          Index := First_Index (T);
2284          Analyze (Index);
2285
2286          --  Apply constraints to each index type
2287
2288          for J in 1 .. Number_Of_Constraints loop
2289             Constrain_Index (Index, S, Check_List);
2290             Next (Index);
2291             Next (S);
2292          end loop;
2293
2294       end Constrain_Array;
2295
2296       ---------------------
2297       -- Constrain_Index --
2298       ---------------------
2299
2300       procedure Constrain_Index
2301         (Index        : Node_Id;
2302          S            : Node_Id;
2303          Check_List   : List_Id)
2304       is
2305          T : constant Entity_Id := Etype (Index);
2306
2307       begin
2308          if Nkind (S) = N_Range then
2309             Process_Range_Expr_In_Decl (S, T, Check_List);
2310          end if;
2311       end Constrain_Index;
2312
2313       --------------------------------------
2314       -- Parent_Subtype_Renaming_Discrims --
2315       --------------------------------------
2316
2317       function Parent_Subtype_Renaming_Discrims return Boolean is
2318          De : Entity_Id;
2319          Dp : Entity_Id;
2320
2321       begin
2322          if Base_Type (Pe) /= Pe then
2323             return False;
2324          end if;
2325
2326          if Etype (Pe) = Pe
2327            or else not Has_Discriminants (Pe)
2328            or else Is_Constrained (Pe)
2329            or else Is_Tagged_Type (Pe)
2330          then
2331             return False;
2332          end if;
2333
2334          --  If there are no explicit stored discriminants we have inherited
2335          --  the root type discriminants so far, so no renamings occurred.
2336
2337          if First_Discriminant (Pe) = First_Stored_Discriminant (Pe) then
2338             return False;
2339          end if;
2340
2341          --  Check if we have done some trivial renaming of the parent
2342          --  discriminants, i.e. someting like
2343          --
2344          --    type DT (X1,X2: int) is new PT (X1,X2);
2345
2346          De := First_Discriminant (Pe);
2347          Dp := First_Discriminant (Etype (Pe));
2348
2349          while Present (De) loop
2350             pragma Assert (Present (Dp));
2351
2352             if Corresponding_Discriminant (De) /= Dp then
2353                return True;
2354             end if;
2355
2356             Next_Discriminant (De);
2357             Next_Discriminant (Dp);
2358          end loop;
2359
2360          return Present (Dp);
2361       end Parent_Subtype_Renaming_Discrims;
2362
2363       ------------------------
2364       -- Requires_Init_Proc --
2365       ------------------------
2366
2367       function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
2368          Comp_Decl : Node_Id;
2369          Id        : Entity_Id;
2370          Typ       : Entity_Id;
2371
2372       begin
2373          --  Definitely do not need one if specifically suppressed
2374
2375          if Suppress_Init_Proc (Rec_Id) then
2376             return False;
2377          end if;
2378
2379          --  Otherwise we need to generate an initialization procedure if
2380          --  Is_CPP_Class is False and at least one of the following applies:
2381
2382          --  1. Discriminants are present, since they need to be initialized
2383          --     with the appropriate discriminant constraint expressions.
2384          --     However, the discriminant of an unchecked union does not
2385          --     count, since the discriminant is not present.
2386
2387          --  2. The type is a tagged type, since the implicit Tag component
2388          --     needs to be initialized with a pointer to the dispatch table.
2389
2390          --  3. The type contains tasks
2391
2392          --  4. One or more components has an initial value
2393
2394          --  5. One or more components is for a type which itself requires
2395          --     an initialization procedure.
2396
2397          --  6. One or more components is a type that requires simple
2398          --     initialization (see Needs_Simple_Initialization), except
2399          --     that types Tag and Vtable_Ptr are excluded, since fields
2400          --     of these types are initialized by other means.
2401
2402          --  7. The type is the record type built for a task type (since at
2403          --     the very least, Create_Task must be called)
2404
2405          --  8. The type is the record type built for a protected type (since
2406          --     at least Initialize_Protection must be called)
2407
2408          --  9. The type is marked as a public entity. The reason we add this
2409          --     case (even if none of the above apply) is to properly handle
2410          --     Initialize_Scalars. If a package is compiled without an IS
2411          --     pragma, and the client is compiled with an IS pragma, then
2412          --     the client will think an initialization procedure is present
2413          --     and call it, when in fact no such procedure is required, but
2414          --     since the call is generated, there had better be a routine
2415          --     at the other end of the call, even if it does nothing!)
2416
2417          --  Note: the reason we exclude the CPP_Class case is ???
2418
2419          if Is_CPP_Class (Rec_Id) then
2420             return False;
2421
2422          elsif not Restriction_Active (No_Initialize_Scalars)
2423            and then Is_Public (Rec_Id)
2424          then
2425             return True;
2426
2427          elsif (Has_Discriminants (Rec_Id)
2428                   and then not Is_Unchecked_Union (Rec_Id))
2429            or else Is_Tagged_Type (Rec_Id)
2430            or else Is_Concurrent_Record_Type (Rec_Id)
2431            or else Has_Task (Rec_Id)
2432          then
2433             return True;
2434          end if;
2435
2436          Id := First_Component (Rec_Id);
2437
2438          while Present (Id) loop
2439             Comp_Decl := Parent (Id);
2440             Typ := Etype (Id);
2441
2442             if Present (Expression (Comp_Decl))
2443               or else Has_Non_Null_Base_Init_Proc (Typ)
2444               or else Component_Needs_Simple_Initialization (Typ)
2445             then
2446                return True;
2447             end if;
2448
2449             Next_Component (Id);
2450          end loop;
2451
2452          return False;
2453       end Requires_Init_Proc;
2454
2455    --  Start of processing for Build_Record_Init_Proc
2456
2457    begin
2458       Rec_Type := Defining_Identifier (N);
2459
2460       --  This may be full declaration of a private type, in which case
2461       --  the visible entity is a record, and the private entity has been
2462       --  exchanged with it in the private part of the current package.
2463       --  The initialization procedure is built for the record type, which
2464       --  is retrievable from the private entity.
2465
2466       if Is_Incomplete_Or_Private_Type (Rec_Type) then
2467          Rec_Type := Underlying_Type (Rec_Type);
2468       end if;
2469
2470       --  If there are discriminants, build the discriminant map to replace
2471       --  discriminants by their discriminals in complex bound expressions.
2472       --  These only arise for the corresponding records of protected types.
2473
2474       if Is_Concurrent_Record_Type (Rec_Type)
2475         and then Has_Discriminants (Rec_Type)
2476       then
2477          declare
2478             Disc : Entity_Id;
2479
2480          begin
2481             Disc := First_Discriminant (Rec_Type);
2482
2483             while Present (Disc) loop
2484                Append_Elmt (Disc, Discr_Map);
2485                Append_Elmt (Discriminal (Disc), Discr_Map);
2486                Next_Discriminant (Disc);
2487             end loop;
2488          end;
2489       end if;
2490
2491       --  Derived types that have no type extension can use the initialization
2492       --  procedure of their parent and do not need a procedure of their own.
2493       --  This is only correct if there are no representation clauses for the
2494       --  type or its parent, and if the parent has in fact been frozen so
2495       --  that its initialization procedure exists.
2496
2497       if Is_Derived_Type (Rec_Type)
2498         and then not Is_Tagged_Type (Rec_Type)
2499         and then not Is_Unchecked_Union (Rec_Type)
2500         and then not Has_New_Non_Standard_Rep (Rec_Type)
2501         and then not Parent_Subtype_Renaming_Discrims
2502         and then Has_Non_Null_Base_Init_Proc (Etype (Rec_Type))
2503       then
2504          Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
2505
2506       --  Otherwise if we need an initialization procedure, then build one,
2507       --  mark it as public and inlinable and as having a completion.
2508
2509       elsif Requires_Init_Proc (Rec_Type)
2510         or else Is_Unchecked_Union (Rec_Type)
2511       then
2512          Build_Init_Procedure;
2513          Set_Is_Public (Proc_Id, Is_Public (Pe));
2514
2515          --  The initialization of protected records is not worth inlining.
2516          --  In addition, when compiled for another unit for inlining purposes,
2517          --  it may make reference to entities that have not been elaborated
2518          --  yet. The initialization of controlled records contains a nested
2519          --  clean-up procedure that makes it impractical to inline as well,
2520          --  and leads to undefined symbols if inlined in a different unit.
2521          --  Similar considerations apply to task types.
2522
2523          if not Is_Concurrent_Type (Rec_Type)
2524            and then not Has_Task (Rec_Type)
2525            and then not Controlled_Type (Rec_Type)
2526          then
2527             Set_Is_Inlined  (Proc_Id);
2528          end if;
2529
2530          Set_Is_Internal    (Proc_Id);
2531          Set_Has_Completion (Proc_Id);
2532
2533          if not Debug_Generated_Code then
2534             Set_Debug_Info_Off (Proc_Id);
2535          end if;
2536       end if;
2537    end Build_Record_Init_Proc;
2538
2539    ----------------------------
2540    -- Build_Slice_Assignment --
2541    ----------------------------
2542
2543    --  Generates the following subprogram:
2544
2545    --    procedure Assign
2546    --     (Source,   Target   : Array_Type,
2547    --      Left_Lo,  Left_Hi, Right_Lo, Right_Hi : Index;
2548    --      Rev :     Boolean)
2549    --    is
2550    --       Li1 : Index;
2551    --       Ri1 : Index;
2552
2553    --    begin
2554    --       if Rev  then
2555    --          Li1 := Left_Hi;
2556    --          Ri1 := Right_Hi;
2557    --       else
2558    --          Li1 := Left_Lo;
2559    --          Ri1 := Right_Lo;
2560    --       end if;
2561
2562    --       loop
2563    --             if Rev then
2564    --                exit when Li1 < Left_Lo;
2565    --             else
2566    --                exit when Li1 > Left_Hi;
2567    --             end if;
2568
2569    --             Target (Li1) := Source (Ri1);
2570
2571    --             if Rev then
2572    --                Li1 := Index'pred (Li1);
2573    --                Ri1 := Index'pred (Ri1);
2574    --             else
2575    --                Li1 := Index'succ (Li1);
2576    --                Ri1 := Index'succ (Ri1);
2577    --             end if;
2578    --       end loop;
2579    --    end Assign;
2580
2581    procedure Build_Slice_Assignment (Typ : Entity_Id) is
2582       Loc   : constant Source_Ptr := Sloc (Typ);
2583       Index : constant Entity_Id  := Base_Type (Etype (First_Index (Typ)));
2584
2585       --  Build formal parameters of procedure
2586
2587       Larray   : constant Entity_Id :=
2588                    Make_Defining_Identifier
2589                      (Loc, Chars => New_Internal_Name ('A'));
2590       Rarray   : constant Entity_Id :=
2591                    Make_Defining_Identifier
2592                      (Loc, Chars => New_Internal_Name ('R'));
2593       Left_Lo  : constant Entity_Id :=
2594                    Make_Defining_Identifier
2595                      (Loc, Chars => New_Internal_Name ('L'));
2596       Left_Hi  : constant Entity_Id :=
2597                    Make_Defining_Identifier
2598                      (Loc, Chars => New_Internal_Name ('L'));
2599       Right_Lo : constant Entity_Id :=
2600                    Make_Defining_Identifier
2601                      (Loc, Chars => New_Internal_Name ('R'));
2602       Right_Hi : constant Entity_Id :=
2603                    Make_Defining_Identifier
2604                      (Loc, Chars => New_Internal_Name ('R'));
2605       Rev      : constant Entity_Id :=
2606                    Make_Defining_Identifier
2607                      (Loc, Chars => New_Internal_Name ('D'));
2608       Proc_Name : constant Entity_Id :=
2609                     Make_Defining_Identifier (Loc,
2610                       Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
2611
2612       Lnn : constant Entity_Id :=
2613               Make_Defining_Identifier (Loc, New_Internal_Name ('L'));
2614       Rnn : constant Entity_Id :=
2615               Make_Defining_Identifier (Loc, New_Internal_Name ('R'));
2616       --  Subscripts for left and right sides
2617
2618       Decls : List_Id;
2619       Loops : Node_Id;
2620       Stats : List_Id;
2621
2622    begin
2623       --  Build declarations for indices
2624
2625       Decls := New_List;
2626
2627       Append_To (Decls,
2628          Make_Object_Declaration (Loc,
2629            Defining_Identifier => Lnn,
2630            Object_Definition  =>
2631              New_Occurrence_Of (Index, Loc)));
2632
2633       Append_To (Decls,
2634         Make_Object_Declaration (Loc,
2635           Defining_Identifier => Rnn,
2636           Object_Definition  =>
2637             New_Occurrence_Of (Index, Loc)));
2638
2639       Stats := New_List;
2640
2641       --  Build initializations for indices
2642
2643       declare
2644          F_Init : constant List_Id := New_List;
2645          B_Init : constant List_Id := New_List;
2646
2647       begin
2648          Append_To (F_Init,
2649            Make_Assignment_Statement (Loc,
2650              Name => New_Occurrence_Of (Lnn, Loc),
2651              Expression => New_Occurrence_Of (Left_Lo, Loc)));
2652
2653          Append_To (F_Init,
2654            Make_Assignment_Statement (Loc,
2655              Name => New_Occurrence_Of (Rnn, Loc),
2656              Expression => New_Occurrence_Of (Right_Lo, Loc)));
2657
2658          Append_To (B_Init,
2659            Make_Assignment_Statement (Loc,
2660              Name => New_Occurrence_Of (Lnn, Loc),
2661              Expression => New_Occurrence_Of (Left_Hi, Loc)));
2662
2663          Append_To (B_Init,
2664            Make_Assignment_Statement (Loc,
2665              Name => New_Occurrence_Of (Rnn, Loc),
2666              Expression => New_Occurrence_Of (Right_Hi, Loc)));
2667
2668          Append_To (Stats,
2669            Make_If_Statement (Loc,
2670              Condition => New_Occurrence_Of (Rev, Loc),
2671              Then_Statements => B_Init,
2672              Else_Statements => F_Init));
2673       end;
2674
2675       --  Now construct the assignment statement
2676
2677       Loops :=
2678         Make_Loop_Statement (Loc,
2679           Statements => New_List (
2680             Make_Assignment_Statement (Loc,
2681               Name =>
2682                 Make_Indexed_Component (Loc,
2683                   Prefix => New_Occurrence_Of (Larray, Loc),
2684                   Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
2685               Expression =>
2686                 Make_Indexed_Component (Loc,
2687                   Prefix => New_Occurrence_Of (Rarray, Loc),
2688                   Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
2689           End_Label  => Empty);
2690
2691       --  Build exit condition.
2692
2693       declare
2694          F_Ass : constant List_Id := New_List;
2695          B_Ass : constant List_Id := New_List;
2696
2697       begin
2698          Append_To (F_Ass,
2699            Make_Exit_Statement (Loc,
2700              Condition =>
2701                Make_Op_Gt (Loc,
2702                  Left_Opnd  => New_Occurrence_Of (Lnn, Loc),
2703                  Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
2704
2705          Append_To (B_Ass,
2706            Make_Exit_Statement (Loc,
2707              Condition =>
2708                Make_Op_Lt (Loc,
2709                  Left_Opnd  => New_Occurrence_Of (Lnn, Loc),
2710                  Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
2711
2712          Prepend_To (Statements (Loops),
2713            Make_If_Statement (Loc,
2714              Condition       => New_Occurrence_Of (Rev, Loc),
2715              Then_Statements => B_Ass,
2716              Else_Statements => F_Ass));
2717       end;
2718
2719       --  Build the increment/decrement statements
2720
2721       declare
2722          F_Ass : constant List_Id := New_List;
2723          B_Ass : constant List_Id := New_List;
2724
2725       begin
2726          Append_To (F_Ass,
2727            Make_Assignment_Statement (Loc,
2728              Name => New_Occurrence_Of (Lnn, Loc),
2729              Expression =>
2730                Make_Attribute_Reference (Loc,
2731                  Prefix =>
2732                    New_Occurrence_Of (Index, Loc),
2733                  Attribute_Name => Name_Succ,
2734                  Expressions => New_List (
2735                    New_Occurrence_Of (Lnn, Loc)))));
2736
2737          Append_To (F_Ass,
2738            Make_Assignment_Statement (Loc,
2739              Name => New_Occurrence_Of (Rnn, Loc),
2740              Expression =>
2741                Make_Attribute_Reference (Loc,
2742                  Prefix =>
2743                    New_Occurrence_Of (Index, Loc),
2744                  Attribute_Name => Name_Succ,
2745                  Expressions => New_List (
2746                    New_Occurrence_Of (Rnn, Loc)))));
2747
2748          Append_To (B_Ass,
2749            Make_Assignment_Statement (Loc,
2750              Name => New_Occurrence_Of (Lnn, Loc),
2751              Expression =>
2752                Make_Attribute_Reference (Loc,
2753                  Prefix =>
2754                    New_Occurrence_Of (Index, Loc),
2755                  Attribute_Name => Name_Pred,
2756                    Expressions => New_List (
2757                      New_Occurrence_Of (Lnn, Loc)))));
2758
2759          Append_To (B_Ass,
2760            Make_Assignment_Statement (Loc,
2761              Name => New_Occurrence_Of (Rnn, Loc),
2762              Expression =>
2763                Make_Attribute_Reference (Loc,
2764                  Prefix =>
2765                    New_Occurrence_Of (Index, Loc),
2766                  Attribute_Name => Name_Pred,
2767                  Expressions => New_List (
2768                    New_Occurrence_Of (Rnn, Loc)))));
2769
2770          Append_To (Statements (Loops),
2771            Make_If_Statement (Loc,
2772              Condition => New_Occurrence_Of (Rev, Loc),
2773              Then_Statements => B_Ass,
2774              Else_Statements => F_Ass));
2775       end;
2776
2777       Append_To (Stats, Loops);
2778
2779       declare
2780          Spec    : Node_Id;
2781          Formals : List_Id := New_List;
2782
2783       begin
2784          Formals := New_List (
2785            Make_Parameter_Specification (Loc,
2786              Defining_Identifier => Larray,
2787              Out_Present => True,
2788              Parameter_Type =>
2789                New_Reference_To (Base_Type (Typ), Loc)),
2790
2791            Make_Parameter_Specification (Loc,
2792              Defining_Identifier => Rarray,
2793              Parameter_Type =>
2794                New_Reference_To (Base_Type (Typ), Loc)),
2795
2796            Make_Parameter_Specification (Loc,
2797              Defining_Identifier => Left_Lo,
2798              Parameter_Type =>
2799                New_Reference_To (Index, Loc)),
2800
2801            Make_Parameter_Specification (Loc,
2802              Defining_Identifier => Left_Hi,
2803              Parameter_Type =>
2804                New_Reference_To (Index, Loc)),
2805
2806            Make_Parameter_Specification (Loc,
2807              Defining_Identifier => Right_Lo,
2808              Parameter_Type =>
2809                New_Reference_To (Index, Loc)),
2810
2811            Make_Parameter_Specification (Loc,
2812              Defining_Identifier => Right_Hi,
2813              Parameter_Type =>
2814                New_Reference_To (Index, Loc)));
2815
2816          Append_To (Formals,
2817            Make_Parameter_Specification (Loc,
2818              Defining_Identifier => Rev,
2819              Parameter_Type =>
2820                New_Reference_To (Standard_Boolean, Loc)));
2821
2822          Spec :=
2823            Make_Procedure_Specification (Loc,
2824              Defining_Unit_Name       => Proc_Name,
2825              Parameter_Specifications => Formals);
2826
2827          Discard_Node (
2828            Make_Subprogram_Body (Loc,
2829              Specification              => Spec,
2830              Declarations               => Decls,
2831              Handled_Statement_Sequence =>
2832                Make_Handled_Sequence_Of_Statements (Loc,
2833                  Statements => Stats)));
2834       end;
2835
2836       Set_TSS (Typ, Proc_Name);
2837       Set_Is_Pure (Proc_Name);
2838    end Build_Slice_Assignment;
2839
2840    ------------------------------------
2841    -- Build_Variant_Record_Equality --
2842    ------------------------------------
2843
2844    --  Generates:
2845
2846    --    function _Equality (X, Y : T) return Boolean is
2847    --    begin
2848    --       --  Compare discriminants
2849
2850    --       if False or else X.D1 /= Y.D1 or else X.D2 /= Y.D2 then
2851    --          return False;
2852    --       end if;
2853
2854    --       --  Compare components
2855
2856    --       if False or else X.C1 /= Y.C1 or else X.C2 /= Y.C2 then
2857    --          return False;
2858    --       end if;
2859
2860    --       --  Compare variant part
2861
2862    --       case X.D1 is
2863    --          when V1 =>
2864    --             if False or else X.C2 /= Y.C2 or else X.C3 /= Y.C3 then
2865    --                return False;
2866    --             end if;
2867    --          ...
2868    --          when Vn =>
2869    --             if False or else X.Cn /= Y.Cn then
2870    --                return False;
2871    --             end if;
2872    --       end case;
2873    --       return True;
2874    --    end _Equality;
2875
2876    procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
2877       Loc   : constant Source_Ptr := Sloc (Typ);
2878
2879       F : constant Entity_Id :=
2880             Make_Defining_Identifier (Loc,
2881               Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
2882
2883       X : constant Entity_Id :=
2884            Make_Defining_Identifier (Loc,
2885              Chars => Name_X);
2886
2887       Y : constant Entity_Id :=
2888             Make_Defining_Identifier (Loc,
2889               Chars => Name_Y);
2890
2891       Def   : constant Node_Id := Parent (Typ);
2892       Comps : constant Node_Id := Component_List (Type_Definition (Def));
2893       Stmts : constant List_Id := New_List;
2894       Pspecs : constant List_Id := New_List;
2895
2896    begin
2897       --  Derived Unchecked_Union types no longer inherit the equality function
2898       --  of their parent.
2899
2900       if Is_Derived_Type (Typ)
2901         and then not Is_Unchecked_Union (Typ)
2902         and then not Has_New_Non_Standard_Rep (Typ)
2903       then
2904          declare
2905             Parent_Eq : constant Entity_Id :=
2906                           TSS (Root_Type (Typ), TSS_Composite_Equality);
2907
2908          begin
2909             if Present (Parent_Eq) then
2910                Copy_TSS (Parent_Eq, Typ);
2911                return;
2912             end if;
2913          end;
2914       end if;
2915
2916       Discard_Node (
2917         Make_Subprogram_Body (Loc,
2918           Specification =>
2919             Make_Function_Specification (Loc,
2920               Defining_Unit_Name       => F,
2921               Parameter_Specifications => Pspecs,
2922               Subtype_Mark => New_Reference_To (Standard_Boolean, Loc)),
2923           Declarations               => New_List,
2924           Handled_Statement_Sequence =>
2925             Make_Handled_Sequence_Of_Statements (Loc,
2926               Statements => Stmts)));
2927
2928       Append_To (Pspecs,
2929         Make_Parameter_Specification (Loc,
2930           Defining_Identifier => X,
2931           Parameter_Type      => New_Reference_To (Typ, Loc)));
2932
2933       Append_To (Pspecs,
2934         Make_Parameter_Specification (Loc,
2935           Defining_Identifier => Y,
2936           Parameter_Type      => New_Reference_To (Typ, Loc)));
2937
2938       --  Unchecked_Unions require additional machinery to support equality.
2939       --  Two extra parameters (A and B) are added to the equality function
2940       --  parameter list in order to capture the inferred values of the
2941       --  discriminants in later calls.
2942
2943       if Is_Unchecked_Union (Typ) then
2944          declare
2945             Discr_Type : constant Node_Id := Etype (First_Discriminant (Typ));
2946
2947             A : constant Node_Id :=
2948                   Make_Defining_Identifier (Loc,
2949                     Chars => Name_A);
2950
2951             B : constant Node_Id :=
2952                   Make_Defining_Identifier (Loc,
2953                     Chars => Name_B);
2954
2955          begin
2956             --  Add A and B to the parameter list
2957
2958             Append_To (Pspecs,
2959               Make_Parameter_Specification (Loc,
2960                 Defining_Identifier => A,
2961                 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
2962
2963             Append_To (Pspecs,
2964               Make_Parameter_Specification (Loc,
2965                 Defining_Identifier => B,
2966                 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
2967
2968             --  Generate the following header code to compare the inferred
2969             --  discriminants:
2970
2971             --  if a /= b then
2972             --     return False;
2973             --  end if;
2974
2975             Append_To (Stmts,
2976               Make_If_Statement (Loc,
2977                 Condition =>
2978                   Make_Op_Ne (Loc,
2979                     Left_Opnd => New_Reference_To (A, Loc),
2980                     Right_Opnd => New_Reference_To (B, Loc)),
2981                 Then_Statements => New_List (
2982                   Make_Return_Statement (Loc,
2983                     Expression => New_Occurrence_Of (Standard_False, Loc)))));
2984
2985             --  Generate component-by-component comparison. Note that we must
2986             --  propagate one of the inferred discriminant formals to act as
2987             --  the case statement switch.
2988
2989             Append_List_To (Stmts,
2990               Make_Eq_Case (Typ, Comps, A));
2991
2992          end;
2993
2994       --  Normal case (not unchecked union)
2995
2996       else
2997          Append_To (Stmts,
2998            Make_Eq_If (Typ,
2999              Discriminant_Specifications (Def)));
3000
3001          Append_List_To (Stmts,
3002            Make_Eq_Case (Typ, Comps));
3003       end if;
3004
3005       Append_To (Stmts,
3006         Make_Return_Statement (Loc,
3007           Expression => New_Reference_To (Standard_True, Loc)));
3008
3009       Set_TSS (Typ, F);
3010       Set_Is_Pure (F);
3011
3012       if not Debug_Generated_Code then
3013          Set_Debug_Info_Off (F);
3014       end if;
3015    end Build_Variant_Record_Equality;
3016
3017    -----------------------------
3018    -- Check_Stream_Attributes --
3019    -----------------------------
3020
3021    procedure Check_Stream_Attributes (Typ : Entity_Id) is
3022       Comp      : Entity_Id;
3023       Par       : constant Entity_Id := Root_Type (Base_Type (Typ));
3024       Par_Read  : constant Boolean   := Present (TSS (Par, TSS_Stream_Read));
3025       Par_Write : constant Boolean   := Present (TSS (Par, TSS_Stream_Write));
3026
3027    begin
3028       if Par_Read or else Par_Write then
3029          Comp := First_Component (Typ);
3030          while Present (Comp) loop
3031             if Comes_From_Source (Comp)
3032               and then  Original_Record_Component (Comp) = Comp
3033               and then Is_Limited_Type (Etype (Comp))
3034             then
3035                if (Par_Read and then
3036                      No (TSS (Base_Type (Etype (Comp)), TSS_Stream_Read)))
3037                  or else
3038                   (Par_Write and then
3039                      No (TSS (Base_Type (Etype (Comp)), TSS_Stream_Write)))
3040                then
3041                   Error_Msg_N
3042                     ("|component must have Stream attribute",
3043                        Parent (Comp));
3044                end if;
3045             end if;
3046
3047             Next_Component (Comp);
3048          end loop;
3049       end if;
3050    end Check_Stream_Attributes;
3051
3052    ---------------------------
3053    -- Expand_Derived_Record --
3054    ---------------------------
3055
3056    --  Add a field _parent at the beginning of the record extension. This is
3057    --  used to implement inheritance. Here are some examples of expansion:
3058
3059    --  1. no discriminants
3060    --      type T2 is new T1 with null record;
3061    --   gives
3062    --      type T2 is new T1 with record
3063    --        _Parent : T1;
3064    --      end record;
3065
3066    --  2. renamed discriminants
3067    --    type T2 (B, C : Int) is new T1 (A => B) with record
3068    --       _Parent : T1 (A => B);
3069    --       D : Int;
3070    --    end;
3071
3072    --  3. inherited discriminants
3073    --    type T2 is new T1 with record -- discriminant A inherited
3074    --       _Parent : T1 (A);
3075    --       D : Int;
3076    --    end;
3077
3078    procedure Expand_Derived_Record (T : Entity_Id; Def : Node_Id) is
3079       Indic        : constant Node_Id    := Subtype_Indication (Def);
3080       Loc          : constant Source_Ptr := Sloc (Def);
3081       Rec_Ext_Part : Node_Id             := Record_Extension_Part (Def);
3082       Par_Subtype  : Entity_Id;
3083       Comp_List    : Node_Id;
3084       Comp_Decl    : Node_Id;
3085       Parent_N     : Node_Id;
3086       D            : Entity_Id;
3087       List_Constr  : constant List_Id    := New_List;
3088
3089    begin
3090       --  Expand_Tagged_Extension is called directly from the semantics, so
3091       --  we must check to see whether expansion is active before proceeding
3092
3093       if not Expander_Active then
3094          return;
3095       end if;
3096
3097       --  This may be a derivation of an untagged private type whose full
3098       --  view is tagged, in which case the Derived_Type_Definition has no
3099       --  extension part. Build an empty one now.
3100
3101       if No (Rec_Ext_Part) then
3102          Rec_Ext_Part :=
3103            Make_Record_Definition (Loc,
3104              End_Label      => Empty,
3105              Component_List => Empty,
3106              Null_Present   => True);
3107
3108          Set_Record_Extension_Part (Def, Rec_Ext_Part);
3109          Mark_Rewrite_Insertion (Rec_Ext_Part);
3110       end if;
3111
3112       Comp_List := Component_List (Rec_Ext_Part);
3113
3114       Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
3115
3116       --  If the derived type inherits its discriminants the type of the
3117       --  _parent field must be constrained by the inherited discriminants
3118
3119       if Has_Discriminants (T)
3120         and then Nkind (Indic) /= N_Subtype_Indication
3121         and then not Is_Constrained (Entity (Indic))
3122       then
3123          D := First_Discriminant (T);
3124          while Present (D) loop
3125             Append_To (List_Constr, New_Occurrence_Of (D, Loc));
3126             Next_Discriminant (D);
3127          end loop;
3128
3129          Par_Subtype :=
3130            Process_Subtype (
3131              Make_Subtype_Indication (Loc,
3132                Subtype_Mark => New_Reference_To (Entity (Indic), Loc),
3133                Constraint   =>
3134                  Make_Index_Or_Discriminant_Constraint (Loc,
3135                    Constraints => List_Constr)),
3136              Def);
3137
3138       --  Otherwise the original subtype_indication is just what is needed
3139
3140       else
3141          Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
3142       end if;
3143
3144       Set_Parent_Subtype (T, Par_Subtype);
3145
3146       Comp_Decl :=
3147         Make_Component_Declaration (Loc,
3148           Defining_Identifier => Parent_N,
3149           Component_Definition =>
3150             Make_Component_Definition (Loc,
3151               Aliased_Present => False,
3152               Subtype_Indication => New_Reference_To (Par_Subtype, Loc)));
3153
3154       if Null_Present (Rec_Ext_Part) then
3155          Set_Component_List (Rec_Ext_Part,
3156            Make_Component_List (Loc,
3157              Component_Items => New_List (Comp_Decl),
3158              Variant_Part => Empty,
3159              Null_Present => False));
3160          Set_Null_Present (Rec_Ext_Part, False);
3161
3162       elsif Null_Present (Comp_List)
3163         or else Is_Empty_List (Component_Items (Comp_List))
3164       then
3165          Set_Component_Items (Comp_List, New_List (Comp_Decl));
3166          Set_Null_Present (Comp_List, False);
3167
3168       else
3169          Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
3170       end if;
3171
3172       Analyze (Comp_Decl);
3173    end Expand_Derived_Record;
3174
3175    ------------------------------------
3176    -- Expand_N_Full_Type_Declaration --
3177    ------------------------------------
3178
3179    procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
3180       Def_Id : constant Entity_Id := Defining_Identifier (N);
3181       B_Id   : constant Entity_Id := Base_Type (Def_Id);
3182       Par_Id : Entity_Id;
3183       FN     : Node_Id;
3184
3185    begin
3186       if Is_Access_Type (Def_Id) then
3187
3188          --  Anonymous access types are created for the components of the
3189          --  record parameter for an entry declaration.  No master is created
3190          --  for such a type.
3191
3192          if Has_Task (Designated_Type (Def_Id))
3193            and then Comes_From_Source (N)
3194          then
3195             Build_Master_Entity (Def_Id);
3196             Build_Master_Renaming (Parent (Def_Id), Def_Id);
3197
3198          --  Create a class-wide master because a Master_Id must be generated
3199          --  for access-to-limited-class-wide types, whose root may be extended
3200          --  with task components.
3201
3202          elsif Is_Class_Wide_Type (Designated_Type (Def_Id))
3203            and then Is_Limited_Type (Designated_Type (Def_Id))
3204            and then Tasking_Allowed
3205
3206             --  Don't create a class-wide master for types whose convention is
3207             --  Java since these types cannot embed Ada tasks anyway. Note that
3208             --  the following test cannot catch the following case:
3209             --
3210             --      package java.lang.Object is
3211             --         type Typ is tagged limited private;
3212             --         type Ref is access all Typ'Class;
3213             --      private
3214             --         type Typ is tagged limited ...;
3215             --         pragma Convention (Typ, Java)
3216             --      end;
3217             --
3218             --  Because the convention appears after we have done the
3219             --  processing for type Ref.
3220
3221            and then Convention (Designated_Type (Def_Id)) /= Convention_Java
3222          then
3223             Build_Class_Wide_Master (Def_Id);
3224
3225          elsif Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
3226             Expand_Access_Protected_Subprogram_Type (N);
3227          end if;
3228
3229       elsif Has_Task (Def_Id) then
3230          Expand_Previous_Access_Type (Def_Id);
3231       end if;
3232
3233       Par_Id := Etype (B_Id);
3234
3235       --  The parent type is private then we need to inherit
3236       --  any TSS operations from the full view.
3237
3238       if Ekind (Par_Id) in Private_Kind
3239         and then Present (Full_View (Par_Id))
3240       then
3241          Par_Id := Base_Type (Full_View (Par_Id));
3242       end if;
3243
3244       if Nkind (Type_Definition (Original_Node (N)))
3245          = N_Derived_Type_Definition
3246         and then not Is_Tagged_Type (Def_Id)
3247         and then Present (Freeze_Node (Par_Id))
3248         and then Present (TSS_Elist (Freeze_Node (Par_Id)))
3249       then
3250          Ensure_Freeze_Node (B_Id);
3251          FN :=  Freeze_Node (B_Id);
3252
3253          if No (TSS_Elist (FN)) then
3254             Set_TSS_Elist (FN, New_Elmt_List);
3255          end if;
3256
3257          declare
3258             T_E   : constant Elist_Id := TSS_Elist (FN);
3259             Elmt  : Elmt_Id;
3260
3261          begin
3262             Elmt  := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
3263
3264             while Present (Elmt) loop
3265                if Chars (Node (Elmt)) /= Name_uInit then
3266                   Append_Elmt (Node (Elmt), T_E);
3267                end if;
3268
3269                Next_Elmt (Elmt);
3270             end loop;
3271
3272             --  If the derived type itself is private with a full view, then
3273             --  associate the full view with the inherited TSS_Elist as well.
3274
3275             if Ekind (B_Id) in Private_Kind
3276               and then Present (Full_View (B_Id))
3277             then
3278                Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
3279                Set_TSS_Elist
3280                  (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
3281             end if;
3282          end;
3283       end if;
3284    end Expand_N_Full_Type_Declaration;
3285
3286    ---------------------------------
3287    -- Expand_N_Object_Declaration --
3288    ---------------------------------
3289
3290    --  First we do special processing for objects of a tagged type where this
3291    --  is the point at which the type is frozen. The creation of the dispatch
3292    --  table and the initialization procedure have to be deferred to this
3293    --  point, since we reference previously declared primitive subprograms.
3294
3295    --  For all types, we call an initialization procedure if there is one
3296
3297    procedure Expand_N_Object_Declaration (N : Node_Id) is
3298       Def_Id  : constant Entity_Id  := Defining_Identifier (N);
3299       Typ     : constant Entity_Id  := Etype (Def_Id);
3300       Loc     : constant Source_Ptr := Sloc (N);
3301       Expr    : constant Node_Id    := Expression (N);
3302       New_Ref : Node_Id;
3303       Id_Ref  : Node_Id;
3304       Expr_Q  : Node_Id;
3305
3306    begin
3307       --  Don't do anything for deferred constants. All proper actions will
3308       --  be expanded during the full declaration.
3309
3310       if No (Expr) and Constant_Present (N) then
3311          return;
3312       end if;
3313
3314       --  Make shared memory routines for shared passive variable
3315
3316       if Is_Shared_Passive (Def_Id) then
3317          Make_Shared_Var_Procs (N);
3318       end if;
3319
3320       --  If tasks being declared, make sure we have an activation chain
3321       --  defined for the tasks (has no effect if we already have one), and
3322       --  also that a Master variable is established and that the appropriate
3323       --  enclosing construct is established as a task master.
3324
3325       if Has_Task (Typ) then
3326          Build_Activation_Chain_Entity (N);
3327          Build_Master_Entity (Def_Id);
3328       end if;
3329
3330       --  Default initialization required, and no expression present
3331
3332       if No (Expr) then
3333
3334          --  Expand Initialize call for controlled objects.  One may wonder why
3335          --  the Initialize Call is not done in the regular Init procedure
3336          --  attached to the record type. That's because the init procedure is
3337          --  recursively called on each component, including _Parent, thus the
3338          --  Init call for a controlled object would generate not only one
3339          --  Initialize call as it is required but one for each ancestor of
3340          --  its type. This processing is suppressed if No_Initialization set.
3341
3342          if not Controlled_Type (Typ)
3343            or else No_Initialization (N)
3344          then
3345             null;
3346
3347          elsif not Abort_Allowed
3348            or else not Comes_From_Source (N)
3349          then
3350             Insert_Actions_After (N,
3351               Make_Init_Call (
3352                 Ref         => New_Occurrence_Of (Def_Id, Loc),
3353                 Typ         => Base_Type (Typ),
3354                 Flist_Ref   => Find_Final_List (Def_Id),
3355                 With_Attach => Make_Integer_Literal (Loc, 1)));
3356
3357          --  Abort allowed
3358
3359          else
3360             --  We need to protect the initialize call
3361
3362             --  begin
3363             --     Defer_Abort.all;
3364             --     Initialize (...);
3365             --  at end
3366             --     Undefer_Abort.all;
3367             --  end;
3368
3369             --  ??? this won't protect the initialize call for controlled
3370             --  components which are part of the init proc, so this block
3371             --  should probably also contain the call to _init_proc but this
3372             --  requires some code reorganization...
3373
3374             declare
3375                L   : constant List_Id :=
3376                       Make_Init_Call (
3377                         Ref         => New_Occurrence_Of (Def_Id, Loc),
3378                         Typ         => Base_Type (Typ),
3379                         Flist_Ref   => Find_Final_List (Def_Id),
3380                         With_Attach => Make_Integer_Literal (Loc, 1));
3381
3382                Blk : constant Node_Id :=
3383                  Make_Block_Statement (Loc,
3384                    Handled_Statement_Sequence =>
3385                      Make_Handled_Sequence_Of_Statements (Loc, L));
3386
3387             begin
3388                Prepend_To (L, Build_Runtime_Call (Loc, RE_Abort_Defer));
3389                Set_At_End_Proc (Handled_Statement_Sequence (Blk),
3390                  New_Occurrence_Of (RTE (RE_Abort_Undefer_Direct), Loc));
3391                Insert_Actions_After (N, New_List (Blk));
3392                Expand_At_End_Handler
3393                  (Handled_Statement_Sequence (Blk), Entity (Identifier (Blk)));
3394             end;
3395          end if;
3396
3397          --  Call type initialization procedure if there is one. We build the
3398          --  call and put it immediately after the object declaration, so that
3399          --  it will be expanded in the usual manner. Note that this will
3400          --  result in proper handling of defaulted discriminants. The call
3401          --  to the Init_Proc is suppressed if No_Initialization is set.
3402
3403          if Has_Non_Null_Base_Init_Proc (Typ)
3404            and then not No_Initialization (N)
3405          then
3406             --  The call to the initialization procedure does NOT freeze
3407             --  the object being initialized. This is because the call is
3408             --  not a source level call. This works fine, because the only
3409             --  possible statements depending on freeze status that can
3410             --  appear after the _Init call are rep clauses which can
3411             --  safely appear after actual references to the object.
3412
3413             Id_Ref := New_Reference_To (Def_Id, Loc);
3414             Set_Must_Not_Freeze (Id_Ref);
3415             Set_Assignment_OK (Id_Ref);
3416
3417             Insert_Actions_After (N,
3418               Build_Initialization_Call (Loc, Id_Ref, Typ));
3419
3420          --  If simple initialization is required, then set an appropriate
3421          --  simple initialization expression in place. This special
3422          --  initialization is required even though No_Init_Flag is present.
3423
3424          elsif Needs_Simple_Initialization (Typ) then
3425             Set_No_Initialization (N, False);
3426             Set_Expression (N, Get_Simple_Init_Val (Typ, Loc));
3427             Analyze_And_Resolve (Expression (N), Typ);
3428          end if;
3429
3430       --  Explicit initialization present
3431
3432       else
3433          --  Obtain actual expression from qualified expression
3434
3435          if Nkind (Expr) = N_Qualified_Expression then
3436             Expr_Q := Expression (Expr);
3437          else
3438             Expr_Q := Expr;
3439          end if;
3440
3441          --  When we have the appropriate type of aggregate in the
3442          --  expression (it has been determined during analysis of the
3443          --  aggregate by setting the delay flag), let's perform in
3444          --  place assignment and thus avoid creating a temporary.
3445
3446          if Is_Delayed_Aggregate (Expr_Q) then
3447             Convert_Aggr_In_Object_Decl (N);
3448
3449          else
3450             --  In most cases, we must check that the initial value meets
3451             --  any constraint imposed by the declared type. However, there
3452             --  is one very important exception to this rule. If the entity
3453             --  has an unconstrained nominal subtype, then it acquired its
3454             --  constraints from the expression in the first place, and not
3455             --  only does this mean that the constraint check is not needed,
3456             --  but an attempt to perform the constraint check can
3457             --  cause order of elaboration problems.
3458
3459             if not Is_Constr_Subt_For_U_Nominal (Typ) then
3460
3461                --  If this is an allocator for an aggregate that has been
3462                --  allocated in place, delay checks until assignments are
3463                --  made, because the discriminants are not initialized.
3464
3465                if Nkind (Expr) = N_Allocator
3466                  and then No_Initialization (Expr)
3467                then
3468                   null;
3469                else
3470                   Apply_Constraint_Check (Expr, Typ);
3471                end if;
3472             end if;
3473
3474             --  If the type is controlled we attach the object to the final
3475             --  list and adjust the target after the copy. This
3476
3477             if Controlled_Type (Typ) then
3478                declare
3479                   Flist : Node_Id;
3480                   F     : Entity_Id;
3481
3482                begin
3483                   --  Attach the result to a dummy final list which will never
3484                   --  be finalized if Delay_Finalize_Attachis set. It is
3485                   --  important to attach to a dummy final list rather than
3486                   --  not attaching at all in order to reset the pointers
3487                   --  coming from the initial value. Equivalent code exists
3488                   --  in the sec-stack case in Exp_Ch4.Expand_N_Allocator.
3489
3490                   if Delay_Finalize_Attach (N) then
3491                      F :=
3492                        Make_Defining_Identifier (Loc, New_Internal_Name ('F'));
3493                      Insert_Action (N,
3494                        Make_Object_Declaration (Loc,
3495                          Defining_Identifier => F,
3496                          Object_Definition   =>
3497                            New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
3498
3499                      Flist := New_Reference_To (F, Loc);
3500
3501                   else
3502                      Flist := Find_Final_List (Def_Id);
3503                   end if;
3504
3505                   Insert_Actions_After (N,
3506                     Make_Adjust_Call (
3507                       Ref          => New_Reference_To (Def_Id, Loc),
3508                       Typ          => Base_Type (Typ),
3509                       Flist_Ref    => Flist,
3510                       With_Attach  => Make_Integer_Literal (Loc, 1)));
3511                end;
3512             end if;
3513
3514             --  For tagged types, when an init value is given, the tag has
3515             --  to be re-initialized separately in order to avoid the
3516             --  propagation of a wrong tag coming from a view conversion
3517             --  unless the type is class wide (in this case the tag comes
3518             --  from the init value). Suppress the tag assignment when
3519             --  Java_VM because JVM tags are represented implicitly
3520             --  in objects. Ditto for types that are CPP_CLASS.
3521
3522             if Is_Tagged_Type (Typ)
3523               and then not Is_Class_Wide_Type (Typ)
3524               and then not Is_CPP_Class (Typ)
3525               and then not Java_VM
3526             then
3527                --  The re-assignment of the tag has to be done even if
3528                --  the object is a constant
3529
3530                New_Ref :=
3531                  Make_Selected_Component (Loc,
3532                     Prefix => New_Reference_To (Def_Id, Loc),
3533                     Selector_Name =>
3534                       New_Reference_To (Tag_Component (Typ), Loc));
3535
3536                Set_Assignment_OK (New_Ref);
3537
3538                Insert_After (N,
3539                  Make_Assignment_Statement (Loc,
3540                    Name => New_Ref,
3541                    Expression =>
3542                      Unchecked_Convert_To (RTE (RE_Tag),
3543                        New_Reference_To
3544                          (Access_Disp_Table (Base_Type (Typ)), Loc))));
3545
3546             --  For discrete types, set the Is_Known_Valid flag if the
3547             --  initializing value is known to be valid.
3548
3549             elsif Is_Discrete_Type (Typ)
3550               and then Expr_Known_Valid (Expr)
3551             then
3552                Set_Is_Known_Valid (Def_Id);
3553
3554             elsif Is_Access_Type (Typ) then
3555
3556                --  Ada 2005 (AI-231): Generate conversion to the null-excluding
3557                --  type to force the corresponding run-time check
3558
3559                if Ada_Version >= Ada_05
3560                  and then (Can_Never_Be_Null (Def_Id)
3561                              or else Can_Never_Be_Null (Typ))
3562                then
3563                   Rewrite
3564                     (Expr_Q,
3565                      Convert_To (Etype (Def_Id), Relocate_Node (Expr_Q)));
3566                   Analyze_And_Resolve (Expr_Q, Etype (Def_Id));
3567                end if;
3568
3569                --  For access types set the Is_Known_Non_Null flag if the
3570                --  initializing value is known to be non-null. We can also
3571                --  set Can_Never_Be_Null if this is a constant.
3572
3573                if Known_Non_Null (Expr) then
3574                   Set_Is_Known_Non_Null (Def_Id);
3575
3576                   if Constant_Present (N) then
3577                      Set_Can_Never_Be_Null (Def_Id);
3578                   end if;
3579                end if;
3580             end if;
3581
3582             --  If validity checking on copies, validate initial expression
3583
3584             if Validity_Checks_On
3585                and then Validity_Check_Copies
3586             then
3587                Ensure_Valid (Expr);
3588                Set_Is_Known_Valid (Def_Id);
3589             end if;
3590          end if;
3591
3592          if Is_Possibly_Unaligned_Slice (Expr) then
3593
3594             --  Make a separate assignment that will be expanded into a
3595             --  loop, to bypass back-end problems with misaligned arrays.
3596
3597             declare
3598                Stat : constant Node_Id :=
3599                        Make_Assignment_Statement (Loc,
3600                          Name => New_Reference_To (Def_Id, Loc),
3601                          Expression => Relocate_Node (Expr));
3602
3603             begin
3604                Set_Expression (N, Empty);
3605                Set_No_Initialization (N);
3606                Set_Assignment_OK (Name (Stat));
3607                Insert_After (N, Stat);
3608                Analyze (Stat);
3609             end;
3610          end if;
3611       end if;
3612
3613       --  For array type, check for size too large
3614       --  We really need this for record types too???
3615
3616       if Is_Array_Type (Typ) then
3617          Apply_Array_Size_Check (N, Typ);
3618       end if;
3619
3620    exception
3621       when RE_Not_Available =>
3622          return;
3623    end Expand_N_Object_Declaration;
3624
3625    ---------------------------------
3626    -- Expand_N_Subtype_Indication --
3627    ---------------------------------
3628
3629    --  Add a check on the range of the subtype. The static case is
3630    --  partially duplicated by Process_Range_Expr_In_Decl in Sem_Ch3,
3631    --  but we still need to check here for the static case in order to
3632    --  avoid generating extraneous expanded code.
3633
3634    procedure Expand_N_Subtype_Indication (N : Node_Id) is
3635       Ran : constant Node_Id   := Range_Expression (Constraint (N));
3636       Typ : constant Entity_Id := Entity (Subtype_Mark (N));
3637
3638    begin
3639       if Nkind (Parent (N)) = N_Constrained_Array_Definition or else
3640          Nkind (Parent (N)) = N_Slice
3641       then
3642          Resolve (Ran, Typ);
3643          Apply_Range_Check (Ran, Typ);
3644       end if;
3645    end Expand_N_Subtype_Indication;
3646
3647    ---------------------------
3648    -- Expand_N_Variant_Part --
3649    ---------------------------
3650
3651    --  If the last variant does not contain the Others choice, replace
3652    --  it with an N_Others_Choice node since Gigi always wants an Others.
3653    --  Note that we do not bother to call Analyze on the modified variant
3654    --  part, since it's only effect would be to compute the contents of
3655    --  the Others_Discrete_Choices node laboriously, and of course we
3656    --  already know the list of choices that corresponds to the others
3657    --  choice (it's the list we are replacing!)
3658
3659    procedure Expand_N_Variant_Part (N : Node_Id) is
3660       Last_Var    : constant Node_Id := Last_Non_Pragma (Variants (N));
3661       Others_Node : Node_Id;
3662
3663    begin
3664       if Nkind (First (Discrete_Choices (Last_Var))) /= N_Others_Choice then
3665          Others_Node := Make_Others_Choice (Sloc (Last_Var));
3666          Set_Others_Discrete_Choices
3667            (Others_Node, Discrete_Choices (Last_Var));
3668          Set_Discrete_Choices (Last_Var, New_List (Others_Node));
3669       end if;
3670    end Expand_N_Variant_Part;
3671
3672    ---------------------------------
3673    -- Expand_Previous_Access_Type --
3674    ---------------------------------
3675
3676    procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
3677       T : Entity_Id := First_Entity (Current_Scope);
3678
3679    begin
3680       --  Find all access types declared in the current scope, whose
3681       --  designated type is Def_Id.
3682
3683       while Present (T) loop
3684          if Is_Access_Type (T)
3685            and then Designated_Type (T) = Def_Id
3686          then
3687             Build_Master_Entity (Def_Id);
3688             Build_Master_Renaming (Parent (Def_Id), T);
3689          end if;
3690
3691          Next_Entity (T);
3692       end loop;
3693    end Expand_Previous_Access_Type;
3694
3695    ------------------------------
3696    -- Expand_Record_Controller --
3697    ------------------------------
3698
3699    procedure Expand_Record_Controller (T : Entity_Id) is
3700       Def             : Node_Id := Type_Definition (Parent (T));
3701       Comp_List       : Node_Id;
3702       Comp_Decl       : Node_Id;
3703       Loc             : Source_Ptr;
3704       First_Comp      : Node_Id;
3705       Controller_Type : Entity_Id;
3706       Ent             : Entity_Id;
3707
3708    begin
3709       if Nkind (Def) = N_Derived_Type_Definition then
3710          Def := Record_Extension_Part (Def);
3711       end if;
3712
3713       if Null_Present (Def) then
3714          Set_Component_List (Def,
3715            Make_Component_List (Sloc (Def),
3716              Component_Items => Empty_List,
3717              Variant_Part => Empty,
3718              Null_Present => True));
3719       end if;
3720
3721       Comp_List := Component_List (Def);
3722
3723       if Null_Present (Comp_List)
3724         or else Is_Empty_List (Component_Items (Comp_List))
3725       then
3726          Loc := Sloc (Comp_List);
3727       else
3728          Loc := Sloc (First (Component_Items (Comp_List)));
3729       end if;
3730
3731       if Is_Return_By_Reference_Type (T) then
3732          Controller_Type := RTE (RE_Limited_Record_Controller);
3733       else
3734          Controller_Type := RTE (RE_Record_Controller);
3735       end if;
3736
3737       Ent := Make_Defining_Identifier (Loc, Name_uController);
3738
3739       Comp_Decl :=
3740         Make_Component_Declaration (Loc,
3741           Defining_Identifier =>  Ent,
3742           Component_Definition =>
3743             Make_Component_Definition (Loc,
3744               Aliased_Present => False,
3745               Subtype_Indication => New_Reference_To (Controller_Type, Loc)));
3746
3747       if Null_Present (Comp_List)
3748         or else Is_Empty_List (Component_Items (Comp_List))
3749       then
3750          Set_Component_Items (Comp_List, New_List (Comp_Decl));
3751          Set_Null_Present (Comp_List, False);
3752
3753       else
3754          --  The controller cannot be placed before the _Parent field
3755          --  since gigi lays out field in order and _parent must be
3756          --  first to preserve the polymorphism of tagged types.
3757
3758          First_Comp := First (Component_Items (Comp_List));
3759
3760          if Chars (Defining_Identifier (First_Comp)) /= Name_uParent
3761            and then Chars (Defining_Identifier (First_Comp)) /= Name_uTag
3762          then
3763             Insert_Before (First_Comp, Comp_Decl);
3764          else
3765             Insert_After (First_Comp, Comp_Decl);
3766          end if;
3767       end if;
3768
3769       New_Scope (T);
3770       Analyze (Comp_Decl);
3771       Set_Ekind (Ent, E_Component);
3772       Init_Component_Location (Ent);
3773
3774       --  Move the _controller entity ahead in the list of internal
3775       --  entities of the enclosing record so that it is selected
3776       --  instead of a potentially inherited one.
3777
3778       declare
3779          E    : constant Entity_Id := Last_Entity (T);
3780          Comp : Entity_Id;
3781
3782       begin
3783          pragma Assert (Chars (E) = Name_uController);
3784
3785          Set_Next_Entity (E, First_Entity (T));
3786          Set_First_Entity (T, E);
3787
3788          Comp := Next_Entity (E);
3789          while Next_Entity (Comp) /= E loop
3790             Next_Entity (Comp);
3791          end loop;
3792
3793          Set_Next_Entity (Comp, Empty);
3794          Set_Last_Entity (T, Comp);
3795       end;
3796
3797       End_Scope;
3798
3799    exception
3800       when RE_Not_Available =>
3801          return;
3802    end Expand_Record_Controller;
3803
3804    ------------------------
3805    -- Expand_Tagged_Root --
3806    ------------------------
3807
3808    procedure Expand_Tagged_Root (T : Entity_Id) is
3809       Def       : constant Node_Id := Type_Definition (Parent (T));
3810       Comp_List : Node_Id;
3811       Comp_Decl : Node_Id;
3812       Sloc_N    : Source_Ptr;
3813
3814    begin
3815       if Null_Present (Def) then
3816          Set_Component_List (Def,
3817            Make_Component_List (Sloc (Def),
3818              Component_Items => Empty_List,
3819              Variant_Part => Empty,
3820              Null_Present => True));
3821       end if;
3822
3823       Comp_List := Component_List (Def);
3824
3825       if Null_Present (Comp_List)
3826         or else Is_Empty_List (Component_Items (Comp_List))
3827       then
3828          Sloc_N := Sloc (Comp_List);
3829       else
3830          Sloc_N := Sloc (First (Component_Items (Comp_List)));
3831       end if;
3832
3833       Comp_Decl :=
3834         Make_Component_Declaration (Sloc_N,
3835           Defining_Identifier => Tag_Component (T),
3836           Component_Definition =>
3837             Make_Component_Definition (Sloc_N,
3838               Aliased_Present => False,
3839               Subtype_Indication => New_Reference_To (RTE (RE_Tag), Sloc_N)));
3840
3841       if Null_Present (Comp_List)
3842         or else Is_Empty_List (Component_Items (Comp_List))
3843       then
3844          Set_Component_Items (Comp_List, New_List (Comp_Decl));
3845          Set_Null_Present (Comp_List, False);
3846
3847       else
3848          Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
3849       end if;
3850
3851       --  We don't Analyze the whole expansion because the tag component has
3852       --  already been analyzed previously. Here we just insure that the
3853       --  tree is coherent with the semantic decoration
3854
3855       Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
3856
3857    exception
3858       when RE_Not_Available =>
3859          return;
3860    end Expand_Tagged_Root;
3861
3862    -----------------------
3863    -- Freeze_Array_Type --
3864    -----------------------
3865
3866    procedure Freeze_Array_Type (N : Node_Id) is
3867       Typ  : constant Entity_Id  := Entity (N);
3868       Base : constant Entity_Id  := Base_Type (Typ);
3869
3870    begin
3871       if not Is_Bit_Packed_Array (Typ) then
3872
3873          --  If the component contains tasks, so does the array type.
3874          --  This may not be indicated in the array type because the
3875          --  component may have been a private type at the point of
3876          --  definition. Same if component type is controlled.
3877
3878          Set_Has_Task (Base, Has_Task (Component_Type (Typ)));
3879          Set_Has_Controlled_Component (Base,
3880            Has_Controlled_Component (Component_Type (Typ))
3881              or else Is_Controlled (Component_Type (Typ)));
3882
3883          if No (Init_Proc (Base)) then
3884
3885             --  If this is an anonymous array created for a declaration
3886             --  with an initial value, its init_proc will never be called.
3887             --  The initial value itself may have been expanded into assign-
3888             --  ments, in which case the object declaration is carries the
3889             --  No_Initialization flag.
3890
3891             if Is_Itype (Base)
3892               and then Nkind (Associated_Node_For_Itype (Base)) =
3893                                                     N_Object_Declaration
3894               and then (Present (Expression (Associated_Node_For_Itype (Base)))
3895                           or else
3896                         No_Initialization (Associated_Node_For_Itype (Base)))
3897             then
3898                null;
3899
3900             --  We do not need an init proc for string or wide string, since
3901             --  the only time these need initialization in normalize or
3902             --  initialize scalars mode, and these types are treated specially
3903             --  and do not need initialization procedures.
3904
3905             elsif Root_Type (Base) = Standard_String
3906               or else Root_Type (Base) = Standard_Wide_String
3907             then
3908                null;
3909
3910             --  Otherwise we have to build an init proc for the subtype
3911
3912             else
3913                Build_Array_Init_Proc (Base, N);
3914             end if;
3915          end if;
3916
3917          if Typ = Base and then Has_Controlled_Component (Base) then
3918             Build_Controlling_Procs (Base);
3919
3920             if not Is_Limited_Type (Component_Type (Typ))
3921               and then Number_Dimensions (Typ) = 1
3922             then
3923                Build_Slice_Assignment (Typ);
3924             end if;
3925          end if;
3926
3927       --  For packed case, there is a default initialization, except
3928       --  if the component type is itself a packed structure with an
3929       --  initialization procedure.
3930
3931       elsif Present (Init_Proc (Component_Type (Base)))
3932         and then No (Base_Init_Proc (Base))
3933       then
3934          Build_Array_Init_Proc (Base, N);
3935       end if;
3936    end Freeze_Array_Type;
3937
3938    -----------------------------
3939    -- Freeze_Enumeration_Type --
3940    -----------------------------
3941
3942    procedure Freeze_Enumeration_Type (N : Node_Id) is
3943       Typ           : constant Entity_Id  := Entity (N);
3944       Loc           : constant Source_Ptr := Sloc (Typ);
3945       Ent           : Entity_Id;
3946       Lst           : List_Id;
3947       Num           : Nat;
3948       Arr           : Entity_Id;
3949       Fent          : Entity_Id;
3950       Ityp          : Entity_Id;
3951       Is_Contiguous : Boolean;
3952       Pos_Expr      : Node_Id;
3953       Last_Repval   : Uint;
3954
3955       Func : Entity_Id;
3956       pragma Warnings (Off, Func);
3957
3958    begin
3959       --  Various optimization are possible if the given representation
3960       --  is contiguous.
3961
3962       Is_Contiguous := True;
3963       Ent := First_Literal (Typ);
3964       Last_Repval := Enumeration_Rep (Ent);
3965       Next_Literal (Ent);
3966
3967       while Present (Ent) loop
3968          if Enumeration_Rep (Ent) - Last_Repval /= 1 then
3969             Is_Contiguous := False;
3970             exit;
3971          else
3972             Last_Repval := Enumeration_Rep (Ent);
3973          end if;
3974
3975          Next_Literal (Ent);
3976       end loop;
3977
3978       if Is_Contiguous then
3979          Set_Has_Contiguous_Rep (Typ);
3980          Ent := First_Literal (Typ);
3981          Num := 1;
3982          Lst := New_List (New_Reference_To (Ent, Sloc (Ent)));
3983
3984       else
3985          --  Build list of literal references
3986
3987          Lst := New_List;
3988          Num := 0;
3989
3990          Ent := First_Literal (Typ);
3991          while Present (Ent) loop
3992             Append_To (Lst, New_Reference_To (Ent, Sloc (Ent)));
3993             Num := Num + 1;
3994             Next_Literal (Ent);
3995          end loop;
3996       end if;
3997
3998       --  Now build an array declaration.
3999
4000       --    typA : array (Natural range 0 .. num - 1) of ctype :=
4001       --             (v, v, v, v, v, ....)
4002
4003       --  where ctype is the corresponding integer type. If the
4004       --  representation is contiguous, we only keep the first literal,
4005       --  which provides the offset for Pos_To_Rep computations.
4006
4007       Arr :=
4008         Make_Defining_Identifier (Loc,
4009           Chars => New_External_Name (Chars (Typ), 'A'));
4010
4011       Append_Freeze_Action (Typ,
4012         Make_Object_Declaration (Loc,
4013           Defining_Identifier => Arr,
4014           Constant_Present    => True,
4015
4016           Object_Definition   =>
4017             Make_Constrained_Array_Definition (Loc,
4018               Discrete_Subtype_Definitions => New_List (
4019                 Make_Subtype_Indication (Loc,
4020                   Subtype_Mark => New_Reference_To (Standard_Natural, Loc),
4021                   Constraint =>
4022                     Make_Range_Constraint (Loc,
4023                       Range_Expression =>
4024                         Make_Range (Loc,
4025                           Low_Bound  =>
4026                             Make_Integer_Literal (Loc, 0),
4027                           High_Bound =>
4028                             Make_Integer_Literal (Loc, Num - 1))))),
4029
4030               Component_Definition =>
4031                 Make_Component_Definition (Loc,
4032                   Aliased_Present => False,
4033                   Subtype_Indication => New_Reference_To (Typ, Loc))),
4034
4035           Expression =>
4036             Make_Aggregate (Loc,
4037               Expressions => Lst)));
4038
4039       Set_Enum_Pos_To_Rep (Typ, Arr);
4040
4041       --  Now we build the function that converts representation values to
4042       --  position values. This function has the form:
4043
4044       --    function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
4045       --    begin
4046       --       case ityp!(A) is
4047       --         when enum-lit'Enum_Rep => return posval;
4048       --         when enum-lit'Enum_Rep => return posval;
4049       --         ...
4050       --         when others   =>
4051       --           [raise Constraint_Error when F "invalid data"]
4052       --           return -1;
4053       --       end case;
4054       --    end;
4055
4056       --  Note: the F parameter determines whether the others case (no valid
4057       --  representation) raises Constraint_Error or returns a unique value
4058       --  of minus one. The latter case is used, e.g. in 'Valid code.
4059
4060       --  Note: the reason we use Enum_Rep values in the case here is to
4061       --  avoid the code generator making inappropriate assumptions about
4062       --  the range of the values in the case where the value is invalid.
4063       --  ityp is a signed or unsigned integer type of appropriate width.
4064
4065       --  Note: if exceptions are not supported, then we suppress the raise
4066       --  and return -1 unconditionally (this is an erroneous program in any
4067       --  case and there is no obligation to raise Constraint_Error here!)
4068       --  We also do this if pragma Restrictions (No_Exceptions) is active.
4069
4070       --  Representations are signed
4071
4072       if Enumeration_Rep (First_Literal (Typ)) < 0 then
4073
4074          --  The underlying type is signed. Reset the Is_Unsigned_Type
4075          --  explicitly, because it might have been inherited from a
4076          --  parent type.
4077
4078          Set_Is_Unsigned_Type (Typ, False);
4079
4080          if Esize (Typ) <= Standard_Integer_Size then
4081             Ityp := Standard_Integer;
4082          else
4083             Ityp := Universal_Integer;
4084          end if;
4085
4086       --  Representations are unsigned
4087
4088       else
4089          if Esize (Typ) <= Standard_Integer_Size then
4090             Ityp := RTE (RE_Unsigned);
4091          else
4092             Ityp := RTE (RE_Long_Long_Unsigned);
4093          end if;
4094       end if;
4095
4096       --  The body of the function is a case statement. First collect
4097       --  case alternatives, or optimize the contiguous case.
4098
4099       Lst := New_List;
4100
4101       --  If representation is contiguous, Pos is computed by subtracting
4102       --  the representation of the first literal.
4103
4104       if Is_Contiguous then
4105          Ent := First_Literal (Typ);
4106
4107          if Enumeration_Rep (Ent) = Last_Repval then
4108
4109             --  Another special case: for a single literal, Pos is zero.
4110
4111             Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
4112
4113          else
4114             Pos_Expr :=
4115               Convert_To (Standard_Integer,
4116                 Make_Op_Subtract (Loc,
4117                   Left_Opnd =>
4118                      Unchecked_Convert_To (Ityp,
4119                        Make_Identifier (Loc, Name_uA)),
4120                    Right_Opnd =>
4121                      Make_Integer_Literal (Loc,
4122                         Intval =>
4123                           Enumeration_Rep (First_Literal (Typ)))));
4124          end if;
4125
4126          Append_To (Lst,
4127               Make_Case_Statement_Alternative (Loc,
4128                 Discrete_Choices => New_List (
4129                   Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
4130                     Low_Bound =>
4131                       Make_Integer_Literal (Loc,
4132                        Intval =>  Enumeration_Rep (Ent)),
4133                     High_Bound =>
4134                       Make_Integer_Literal (Loc, Intval => Last_Repval))),
4135
4136                 Statements => New_List (
4137                   Make_Return_Statement (Loc,
4138                     Expression => Pos_Expr))));
4139
4140       else
4141          Ent := First_Literal (Typ);
4142
4143          while Present (Ent) loop
4144             Append_To (Lst,
4145               Make_Case_Statement_Alternative (Loc,
4146                 Discrete_Choices => New_List (
4147                   Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
4148                     Intval => Enumeration_Rep (Ent))),
4149
4150                 Statements => New_List (
4151                   Make_Return_Statement (Loc,
4152                     Expression =>
4153                       Make_Integer_Literal (Loc,
4154                         Intval => Enumeration_Pos (Ent))))));
4155
4156             Next_Literal (Ent);
4157          end loop;
4158       end if;
4159
4160       --  In normal mode, add the others clause with the test
4161
4162       if not Restriction_Active (No_Exception_Handlers) then
4163          Append_To (Lst,
4164            Make_Case_Statement_Alternative (Loc,
4165              Discrete_Choices => New_List (Make_Others_Choice (Loc)),
4166              Statements => New_List (
4167                Make_Raise_Constraint_Error (Loc,
4168                  Condition => Make_Identifier (Loc, Name_uF),
4169                  Reason    => CE_Invalid_Data),
4170                Make_Return_Statement (Loc,
4171                  Expression =>
4172                    Make_Integer_Literal (Loc, -1)))));
4173
4174       --  If Restriction (No_Exceptions_Handlers) is active then we always
4175       --  return -1 (since we cannot usefully raise Constraint_Error in
4176       --  this case). See description above for further details.
4177
4178       else
4179          Append_To (Lst,
4180            Make_Case_Statement_Alternative (Loc,
4181              Discrete_Choices => New_List (Make_Others_Choice (Loc)),
4182              Statements => New_List (
4183                Make_Return_Statement (Loc,
4184                  Expression =>
4185                    Make_Integer_Literal (Loc, -1)))));
4186       end if;
4187
4188       --  Now we can build the function body
4189
4190       Fent :=
4191         Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
4192
4193       Func :=
4194         Make_Subprogram_Body (Loc,
4195           Specification =>
4196             Make_Function_Specification (Loc,
4197               Defining_Unit_Name       => Fent,
4198               Parameter_Specifications => New_List (
4199                 Make_Parameter_Specification (Loc,
4200                   Defining_Identifier =>
4201                     Make_Defining_Identifier (Loc, Name_uA),
4202                   Parameter_Type => New_Reference_To (Typ, Loc)),
4203                 Make_Parameter_Specification (Loc,
4204                   Defining_Identifier =>
4205                     Make_Defining_Identifier (Loc, Name_uF),
4206                   Parameter_Type => New_Reference_To (Standard_Boolean, Loc))),
4207
4208               Subtype_Mark => New_Reference_To (Standard_Integer, Loc)),
4209
4210             Declarations => Empty_List,
4211
4212             Handled_Statement_Sequence =>
4213               Make_Handled_Sequence_Of_Statements (Loc,
4214                 Statements => New_List (
4215                   Make_Case_Statement (Loc,
4216                     Expression =>
4217                       Unchecked_Convert_To (Ityp,
4218                         Make_Identifier (Loc, Name_uA)),
4219                     Alternatives => Lst))));
4220
4221       Set_TSS (Typ, Fent);
4222       Set_Is_Pure (Fent);
4223
4224       if not Debug_Generated_Code then
4225          Set_Debug_Info_Off (Fent);
4226       end if;
4227
4228    exception
4229       when RE_Not_Available =>
4230          return;
4231    end Freeze_Enumeration_Type;
4232
4233    ------------------------
4234    -- Freeze_Record_Type --
4235    ------------------------
4236
4237    procedure Freeze_Record_Type (N : Node_Id) is
4238       Def_Id      : constant Node_Id := Entity (N);
4239       Comp        : Entity_Id;
4240       Type_Decl   : constant Node_Id := Parent (Def_Id);
4241       Predef_List : List_Id;
4242
4243       Renamed_Eq  : Node_Id := Empty;
4244       --  Could use some comments ???
4245
4246    begin
4247       --  Build discriminant checking functions if not a derived type (for
4248       --  derived types that are not tagged types, we always use the
4249       --  discriminant checking functions of the parent type). However, for
4250       --  untagged types the derivation may have taken place before the
4251       --  parent was frozen, so we copy explicitly the discriminant checking
4252       --  functions from the parent into the components of the derived type.
4253
4254       if not Is_Derived_Type (Def_Id)
4255         or else Has_New_Non_Standard_Rep (Def_Id)
4256         or else Is_Tagged_Type (Def_Id)
4257       then
4258          Build_Discr_Checking_Funcs (Type_Decl);
4259
4260       elsif Is_Derived_Type (Def_Id)
4261         and then not Is_Tagged_Type (Def_Id)
4262
4263          --  If we have a derived Unchecked_Union, we do not inherit the
4264          --  discriminant checking functions from the parent type since the
4265          --  discriminants are non existent.
4266
4267         and then not Is_Unchecked_Union (Def_Id)
4268         and then Has_Discriminants (Def_Id)
4269       then
4270          declare
4271             Old_Comp : Entity_Id;
4272
4273          begin
4274             Old_Comp :=
4275               First_Component (Base_Type (Underlying_Type (Etype (Def_Id))));
4276             Comp := First_Component (Def_Id);
4277             while Present (Comp) loop
4278                if Ekind (Comp) = E_Component
4279                  and then Chars (Comp) = Chars (Old_Comp)
4280                then
4281                   Set_Discriminant_Checking_Func (Comp,
4282                      Discriminant_Checking_Func (Old_Comp));
4283                end if;
4284
4285                Next_Component (Old_Comp);
4286                Next_Component (Comp);
4287             end loop;
4288          end;
4289       end if;
4290
4291       if Is_Derived_Type (Def_Id)
4292         and then Is_Limited_Type (Def_Id)
4293         and then Is_Tagged_Type (Def_Id)
4294       then
4295          Check_Stream_Attributes (Def_Id);
4296       end if;
4297
4298       --  Update task and controlled component flags, because some of the
4299       --  component types may have been private at the point of the record
4300       --  declaration.
4301
4302       Comp := First_Component (Def_Id);
4303
4304       while Present (Comp) loop
4305          if Has_Task (Etype (Comp)) then
4306             Set_Has_Task (Def_Id);
4307
4308          elsif Has_Controlled_Component (Etype (Comp))
4309            or else (Chars (Comp) /= Name_uParent
4310                      and then Is_Controlled (Etype (Comp)))
4311          then
4312             Set_Has_Controlled_Component (Def_Id);
4313          end if;
4314
4315          Next_Component (Comp);
4316       end loop;
4317
4318       --  Creation of the Dispatch Table. Note that a Dispatch Table is
4319       --  created for regular tagged types as well as for Ada types
4320       --  deriving from a C++ Class, but not for tagged types directly
4321       --  corresponding to the C++ classes. In the later case we assume
4322       --  that the Vtable is created in the C++ side and we just use it.
4323
4324       if Is_Tagged_Type (Def_Id) then
4325          if Is_CPP_Class (Def_Id) then
4326             Set_All_DT_Position (Def_Id);
4327             Set_Default_Constructor (Def_Id);
4328
4329          else
4330             --  Usually inherited primitives are not delayed but the first
4331             --  Ada extension of a CPP_Class is an exception since the
4332             --  address of the inherited subprogram has to be inserted in
4333             --  the new Ada Dispatch Table and this is a freezing action
4334             --  (usually the inherited primitive address is inserted in the
4335             --  DT by Inherit_DT)
4336
4337             --  Similarly, if this is an inherited operation whose parent
4338             --  is not frozen yet, it is not in the DT of the parent, and
4339             --  we generate an explicit freeze node for the inherited
4340             --  operation, so that it is properly inserted in the DT of the
4341             --  current type.
4342
4343             declare
4344                Elmt : Elmt_Id := First_Elmt (Primitive_Operations (Def_Id));
4345                Subp : Entity_Id;
4346
4347             begin
4348                while Present (Elmt) loop
4349                   Subp := Node (Elmt);
4350
4351                   if Present (Alias (Subp)) then
4352                      if Is_CPP_Class (Etype (Def_Id)) then
4353                         Set_Has_Delayed_Freeze (Subp);
4354
4355                      elsif Has_Delayed_Freeze (Alias (Subp))
4356                        and then not Is_Frozen (Alias (Subp))
4357                      then
4358                         Set_Is_Frozen (Subp, False);
4359                         Set_Has_Delayed_Freeze (Subp);
4360                      end if;
4361                   end if;
4362
4363                   Next_Elmt (Elmt);
4364                end loop;
4365             end;
4366
4367             if Underlying_Type (Etype (Def_Id)) = Def_Id then
4368                Expand_Tagged_Root (Def_Id);
4369             end if;
4370
4371             --  Unfreeze momentarily the type to add the predefined
4372             --  primitives operations. The reason we unfreeze is so
4373             --  that these predefined operations will indeed end up
4374             --  as primitive operations (which must be before the
4375             --  freeze point).
4376
4377             Set_Is_Frozen (Def_Id, False);
4378             Make_Predefined_Primitive_Specs
4379               (Def_Id, Predef_List, Renamed_Eq);
4380             Insert_List_Before_And_Analyze (N, Predef_List);
4381             Set_Is_Frozen (Def_Id, True);
4382             Set_All_DT_Position (Def_Id);
4383
4384             --  Add the controlled component before the freezing actions
4385             --  it is referenced in those actions.
4386
4387             if Has_New_Controlled_Component (Def_Id) then
4388                Expand_Record_Controller (Def_Id);
4389             end if;
4390
4391             --  Suppress creation of a dispatch table when Java_VM because
4392             --  the dispatching mechanism is handled internally by the JVM.
4393
4394             if not Java_VM then
4395                Append_Freeze_Actions (Def_Id, Make_DT (Def_Id));
4396             end if;
4397
4398             --  Make sure that the primitives Initialize, Adjust and
4399             --  Finalize are Frozen before other TSS subprograms. We
4400             --  don't want them Frozen inside.
4401
4402             if Is_Controlled (Def_Id) then
4403                if not Is_Limited_Type (Def_Id) then
4404                   Append_Freeze_Actions (Def_Id,
4405                     Freeze_Entity
4406                       (Find_Prim_Op (Def_Id, Name_Adjust), Sloc (Def_Id)));
4407                end if;
4408
4409                Append_Freeze_Actions (Def_Id,
4410                  Freeze_Entity
4411                    (Find_Prim_Op (Def_Id, Name_Initialize), Sloc (Def_Id)));
4412
4413                Append_Freeze_Actions (Def_Id,
4414                  Freeze_Entity
4415                    (Find_Prim_Op (Def_Id, Name_Finalize), Sloc (Def_Id)));
4416             end if;
4417
4418             --  Freeze rest of primitive operations
4419
4420             Append_Freeze_Actions
4421               (Def_Id, Predefined_Primitive_Freeze (Def_Id));
4422          end if;
4423
4424       --  In the non-tagged case, an equality function is provided only
4425       --  for variant records (that are not unchecked unions).
4426
4427       elsif Has_Discriminants (Def_Id)
4428         and then not Is_Limited_Type (Def_Id)
4429       then
4430          declare
4431             Comps : constant Node_Id :=
4432                       Component_List (Type_Definition (Type_Decl));
4433
4434          begin
4435             if Present (Comps)
4436               and then Present (Variant_Part (Comps))
4437             then
4438                Build_Variant_Record_Equality (Def_Id);
4439             end if;
4440          end;
4441       end if;
4442
4443       --  Before building the record initialization procedure, if we are
4444       --  dealing with a concurrent record value type, then we must go
4445       --  through the discriminants, exchanging discriminals between the
4446       --  concurrent type and the concurrent record value type. See the
4447       --  section "Handling of Discriminants" in the Einfo spec for details.
4448
4449       if Is_Concurrent_Record_Type (Def_Id)
4450         and then Has_Discriminants (Def_Id)
4451       then
4452          declare
4453             Ctyp : constant Entity_Id :=
4454                      Corresponding_Concurrent_Type (Def_Id);
4455             Conc_Discr : Entity_Id;
4456             Rec_Discr  : Entity_Id;
4457             Temp       : Entity_Id;
4458
4459          begin
4460             Conc_Discr := First_Discriminant (Ctyp);
4461             Rec_Discr  := First_Discriminant (Def_Id);
4462
4463             while Present (Conc_Discr) loop
4464                Temp := Discriminal (Conc_Discr);
4465                Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
4466                Set_Discriminal (Rec_Discr, Temp);
4467
4468                Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
4469                Set_Discriminal_Link (Discriminal (Rec_Discr),  Rec_Discr);
4470
4471                Next_Discriminant (Conc_Discr);
4472                Next_Discriminant (Rec_Discr);
4473             end loop;
4474          end;
4475       end if;
4476
4477       if Has_Controlled_Component (Def_Id) then
4478          if No (Controller_Component (Def_Id)) then
4479             Expand_Record_Controller (Def_Id);
4480          end if;
4481
4482          Build_Controlling_Procs (Def_Id);
4483       end if;
4484
4485       Adjust_Discriminants (Def_Id);
4486       Build_Record_Init_Proc (Type_Decl, Def_Id);
4487
4488       --  For tagged type, build bodies of primitive operations. Note
4489       --  that we do this after building the record initialization
4490       --  experiment, since the primitive operations may need the
4491       --  initialization routine
4492
4493       if Is_Tagged_Type (Def_Id) then
4494          Predef_List := Predefined_Primitive_Bodies (Def_Id, Renamed_Eq);
4495          Append_Freeze_Actions (Def_Id, Predef_List);
4496       end if;
4497
4498    end Freeze_Record_Type;
4499
4500    ------------------------------
4501    -- Freeze_Stream_Operations --
4502    ------------------------------
4503
4504    procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
4505       Names     : constant array (1 .. 4) of TSS_Name_Type :=
4506                     (TSS_Stream_Input,
4507                      TSS_Stream_Output,
4508                      TSS_Stream_Read,
4509                      TSS_Stream_Write);
4510       Stream_Op : Entity_Id;
4511
4512    begin
4513       --  Primitive operations of tagged types are frozen when the dispatch
4514       --  table is constructed.
4515
4516       if not Comes_From_Source (Typ)
4517         or else Is_Tagged_Type (Typ)
4518       then
4519          return;
4520       end if;
4521
4522       for J in Names'Range loop
4523          Stream_Op := TSS (Typ, Names (J));
4524
4525          if Present (Stream_Op)
4526            and then Is_Subprogram (Stream_Op)
4527            and then Nkind (Unit_Declaration_Node (Stream_Op)) =
4528                       N_Subprogram_Declaration
4529            and then not Is_Frozen (Stream_Op)
4530          then
4531             Append_Freeze_Actions
4532                (Typ, Freeze_Entity (Stream_Op, Sloc (N)));
4533          end if;
4534       end loop;
4535    end Freeze_Stream_Operations;
4536
4537    -----------------
4538    -- Freeze_Type --
4539    -----------------
4540
4541    --  Full type declarations are expanded at the point at which the type
4542    --  is frozen. The formal N is the Freeze_Node for the type. Any statements
4543    --  or declarations generated by the freezing (e.g. the procedure generated
4544    --  for initialization) are chained in the Acions field list of the freeze
4545    --  node using Append_Freeze_Actions.
4546
4547    procedure Freeze_Type (N : Node_Id) is
4548       Def_Id    : constant Entity_Id := Entity (N);
4549       RACW_Seen : Boolean := False;
4550
4551    begin
4552       --  Process associated access types needing special processing
4553
4554       if Present (Access_Types_To_Process (N)) then
4555          declare
4556             E : Elmt_Id := First_Elmt (Access_Types_To_Process (N));
4557          begin
4558             while Present (E) loop
4559
4560                if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
4561                   RACW_Seen := True;
4562                end if;
4563
4564                E := Next_Elmt (E);
4565             end loop;
4566          end;
4567
4568          if RACW_Seen then
4569
4570             --  If there are RACWs designating this type, make stubs now.
4571
4572             Remote_Types_Tagged_Full_View_Encountered (Def_Id);
4573          end if;
4574       end if;
4575
4576       --  Freeze processing for record types
4577
4578       if Is_Record_Type (Def_Id) then
4579          if Ekind (Def_Id) = E_Record_Type then
4580             Freeze_Record_Type (N);
4581
4582          --  The subtype may have been declared before the type was frozen.
4583          --  If the type has controlled components it is necessary to create
4584          --  the entity for the controller explicitly because it did not
4585          --  exist at the point of the subtype declaration. Only the entity is
4586          --  needed, the back-end will obtain the layout from the type.
4587          --  This is only necessary if this is constrained subtype whose
4588          --  component list is not shared with the base type.
4589
4590          elsif Ekind (Def_Id) = E_Record_Subtype
4591            and then Has_Discriminants (Def_Id)
4592            and then Last_Entity (Def_Id) /= Last_Entity (Base_Type (Def_Id))
4593            and then Present (Controller_Component (Def_Id))
4594          then
4595             declare
4596                Old_C : constant Entity_Id := Controller_Component (Def_Id);
4597                New_C : Entity_Id;
4598
4599             begin
4600                if Scope (Old_C) = Base_Type (Def_Id) then
4601
4602                   --  The entity is the one in the parent. Create new one.
4603
4604                   New_C := New_Copy (Old_C);
4605                   Set_Parent (New_C, Parent (Old_C));
4606                   New_Scope (Def_Id);
4607                   Enter_Name (New_C);
4608                   End_Scope;
4609                end if;
4610             end;
4611
4612          --  Similar process if the controller of the subtype is not
4613          --  present but the parent has it. This can happen with constrained
4614          --  record components where the subtype is an itype.
4615
4616          elsif Ekind (Def_Id) = E_Record_Subtype
4617            and then Is_Itype (Def_Id)
4618            and then No (Controller_Component (Def_Id))
4619            and then Present (Controller_Component (Etype (Def_Id)))
4620          then
4621             declare
4622                Old_C : constant Entity_Id :=
4623                          Controller_Component (Etype (Def_Id));
4624                New_C : constant Entity_Id := New_Copy (Old_C);
4625
4626             begin
4627                Set_Next_Entity  (New_C, First_Entity (Def_Id));
4628                Set_First_Entity (Def_Id, New_C);
4629
4630                --  The freeze node is only used to introduce the controller,
4631                --  the back-end has no use for it for a discriminated
4632                --   component.
4633
4634                Set_Freeze_Node (Def_Id, Empty);
4635                Set_Has_Delayed_Freeze (Def_Id, False);
4636                Remove (N);
4637             end;
4638          end if;
4639
4640       --  Freeze processing for array types
4641
4642       elsif Is_Array_Type (Def_Id) then
4643          Freeze_Array_Type (N);
4644
4645       --  Freeze processing for access types
4646
4647       --  For pool-specific access types, find out the pool object used for
4648       --  this type, needs actual expansion of it in some cases. Here are the
4649       --  different cases :
4650
4651       --  1. Rep Clause "for Def_Id'Storage_Size use 0;"
4652       --      ---> don't use any storage pool
4653
4654       --  2. Rep Clause : for Def_Id'Storage_Size use Expr.
4655       --     Expand:
4656       --      Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
4657
4658       --  3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
4659       --      ---> Storage Pool is the specified one
4660
4661       --  See GNAT Pool packages in the Run-Time for more details
4662
4663       elsif Ekind (Def_Id) = E_Access_Type
4664         or else Ekind (Def_Id) = E_General_Access_Type
4665       then
4666          declare
4667             Loc         : constant Source_Ptr := Sloc (N);
4668             Desig_Type  : constant Entity_Id := Designated_Type (Def_Id);
4669             Pool_Object : Entity_Id;
4670             Siz_Exp     : Node_Id;
4671
4672             Freeze_Action_Typ : Entity_Id;
4673
4674          begin
4675             if Has_Storage_Size_Clause (Def_Id) then
4676                Siz_Exp := Expression (Parent (Storage_Size_Variable (Def_Id)));
4677             else
4678                Siz_Exp := Empty;
4679             end if;
4680
4681             --  Case 1
4682
4683             --    Rep Clause "for Def_Id'Storage_Size use 0;"
4684             --    ---> don't use any storage pool
4685
4686             if Has_Storage_Size_Clause (Def_Id)
4687               and then Compile_Time_Known_Value (Siz_Exp)
4688               and then Expr_Value (Siz_Exp) = 0
4689             then
4690                null;
4691
4692             --  Case 2
4693
4694             --    Rep Clause : for Def_Id'Storage_Size use Expr.
4695             --    ---> Expand:
4696             --           Def_Id__Pool : Stack_Bounded_Pool
4697             --                            (Expr, DT'Size, DT'Alignment);
4698
4699             elsif Has_Storage_Size_Clause (Def_Id) then
4700                declare
4701                   DT_Size  : Node_Id;
4702                   DT_Align : Node_Id;
4703
4704                begin
4705                   --  For unconstrained composite types we give a size of
4706                   --  zero so that the pool knows that it needs a special
4707                   --  algorithm for variable size object allocation.
4708
4709                   if Is_Composite_Type (Desig_Type)
4710                     and then not Is_Constrained (Desig_Type)
4711                   then
4712                      DT_Size :=
4713                        Make_Integer_Literal (Loc, 0);
4714
4715                      DT_Align :=
4716                        Make_Integer_Literal (Loc, Maximum_Alignment);
4717
4718                   else
4719                      DT_Size :=
4720                        Make_Attribute_Reference (Loc,
4721                          Prefix => New_Reference_To (Desig_Type, Loc),
4722                          Attribute_Name => Name_Max_Size_In_Storage_Elements);
4723
4724                      DT_Align :=
4725                        Make_Attribute_Reference (Loc,
4726                          Prefix => New_Reference_To (Desig_Type, Loc),
4727                          Attribute_Name => Name_Alignment);
4728                   end if;
4729
4730                   Pool_Object :=
4731                     Make_Defining_Identifier (Loc,
4732                       Chars => New_External_Name (Chars (Def_Id), 'P'));
4733
4734                   --  We put the code associated with the pools in the
4735                   --  entity that has the later freeze node, usually the
4736                   --  acces type but it can also be the designated_type;
4737                   --  because the pool code requires both those types to be
4738                   --  frozen
4739
4740                   if Is_Frozen (Desig_Type)
4741                     and then (not Present (Freeze_Node (Desig_Type))
4742                                or else Analyzed (Freeze_Node (Desig_Type)))
4743                   then
4744                      Freeze_Action_Typ := Def_Id;
4745
4746                   --  A Taft amendment type cannot get the freeze actions
4747                   --  since the full view is not there.
4748
4749                   elsif Is_Incomplete_Or_Private_Type (Desig_Type)
4750                     and then No (Full_View (Desig_Type))
4751                   then
4752                      Freeze_Action_Typ := Def_Id;
4753
4754                   else
4755                      Freeze_Action_Typ := Desig_Type;
4756                   end if;
4757
4758                   Append_Freeze_Action (Freeze_Action_Typ,
4759                     Make_Object_Declaration (Loc,
4760                       Defining_Identifier => Pool_Object,
4761                       Object_Definition =>
4762                         Make_Subtype_Indication (Loc,
4763                           Subtype_Mark =>
4764                             New_Reference_To
4765                               (RTE (RE_Stack_Bounded_Pool), Loc),
4766
4767                           Constraint =>
4768                             Make_Index_Or_Discriminant_Constraint (Loc,
4769                               Constraints => New_List (
4770
4771                               --  First discriminant is the Pool Size
4772
4773                                 New_Reference_To (
4774                                   Storage_Size_Variable (Def_Id), Loc),
4775
4776                               --  Second discriminant is the element size
4777
4778                                 DT_Size,
4779
4780                               --  Third discriminant is the alignment
4781
4782                                 DT_Align)))));
4783                end;
4784
4785                Set_Associated_Storage_Pool (Def_Id, Pool_Object);
4786
4787             --  Case 3
4788
4789             --    Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
4790             --    ---> Storage Pool is the specified one
4791
4792             elsif Present (Associated_Storage_Pool (Def_Id)) then
4793
4794                --  Nothing to do the associated storage pool has been attached
4795                --  when analyzing the rep. clause
4796
4797                null;
4798             end if;
4799
4800             --  For access-to-controlled types (including class-wide types
4801             --  and Taft-amendment types which potentially have controlled
4802             --  components), expand the list controller object that will
4803             --  store the dynamically allocated objects. Do not do this
4804             --  transformation for expander-generated access types, but do it
4805             --  for types that are the full view of types derived from other
4806             --  private types. Also suppress the list controller in the case
4807             --  of a designated type with convention Java, since this is used
4808             --  when binding to Java API specs, where there's no equivalent
4809             --  of a finalization list and we don't want to pull in the
4810             --  finalization support if not needed.
4811
4812             if not Comes_From_Source (Def_Id)
4813                and then not Has_Private_Declaration (Def_Id)
4814             then
4815                null;
4816
4817             elsif (Controlled_Type (Desig_Type)
4818                     and then Convention (Desig_Type) /= Convention_Java)
4819               or else
4820                 (Is_Incomplete_Or_Private_Type (Desig_Type)
4821                    and then No (Full_View (Desig_Type))
4822
4823                   --  An exception is made for types defined in the run-time
4824                   --  because Ada.Tags.Tag itself is such a type and cannot
4825                   --  afford this unnecessary overhead that would generates a
4826                   --  loop in the expansion scheme...
4827
4828                   and then not In_Runtime (Def_Id)
4829
4830                   --  Another exception is if Restrictions (No_Finalization)
4831                   --  is active, since then we know nothing is controlled.
4832
4833                   and then not Restriction_Active (No_Finalization))
4834
4835                --  If the designated type is not frozen yet, its controlled
4836                --  status must be retrieved explicitly.
4837
4838               or else (Is_Array_Type (Desig_Type)
4839                 and then not Is_Frozen (Desig_Type)
4840                 and then Controlled_Type (Component_Type (Desig_Type)))
4841             then
4842                Set_Associated_Final_Chain (Def_Id,
4843                  Make_Defining_Identifier (Loc,
4844                    New_External_Name (Chars (Def_Id), 'L')));
4845
4846                Append_Freeze_Action (Def_Id,
4847                  Make_Object_Declaration (Loc,
4848                    Defining_Identifier => Associated_Final_Chain (Def_Id),
4849                    Object_Definition   =>
4850                      New_Reference_To (RTE (RE_List_Controller), Loc)));
4851             end if;
4852          end;
4853
4854       --  Freeze processing for enumeration types
4855
4856       elsif Ekind (Def_Id) = E_Enumeration_Type then
4857
4858          --  We only have something to do if we have a non-standard
4859          --  representation (i.e. at least one literal whose pos value
4860          --  is not the same as its representation)
4861
4862          if Has_Non_Standard_Rep (Def_Id) then
4863             Freeze_Enumeration_Type (N);
4864          end if;
4865
4866       --  Private types that are completed by a derivation from a private
4867       --  type have an internally generated full view, that needs to be
4868       --  frozen. This must be done explicitly because the two views share
4869       --  the freeze node, and the underlying full view is not visible when
4870       --  the freeze node is analyzed.
4871
4872       elsif Is_Private_Type (Def_Id)
4873         and then Is_Derived_Type (Def_Id)
4874         and then Present (Full_View (Def_Id))
4875         and then Is_Itype (Full_View (Def_Id))
4876         and then Has_Private_Declaration (Full_View (Def_Id))
4877         and then Freeze_Node (Full_View (Def_Id)) = N
4878       then
4879          Set_Entity (N, Full_View (Def_Id));
4880          Freeze_Type (N);
4881          Set_Entity (N, Def_Id);
4882
4883       --  All other types require no expander action. There are such
4884       --  cases (e.g. task types and protected types). In such cases,
4885       --  the freeze nodes are there for use by Gigi.
4886
4887       end if;
4888
4889       Freeze_Stream_Operations (N, Def_Id);
4890
4891    exception
4892       when RE_Not_Available =>
4893          return;
4894    end Freeze_Type;
4895
4896    -------------------------
4897    -- Get_Simple_Init_Val --
4898    -------------------------
4899
4900    function Get_Simple_Init_Val
4901      (T   : Entity_Id;
4902       Loc : Source_Ptr) return Node_Id
4903    is
4904       Val    : Node_Id;
4905       Typ    : Node_Id;
4906       Result : Node_Id;
4907       Val_RE : RE_Id;
4908
4909    begin
4910       --  For a private type, we should always have an underlying type
4911       --  (because this was already checked in Needs_Simple_Initialization).
4912       --  What we do is to get the value for the underlying type and then
4913       --  do an Unchecked_Convert to the private type.
4914
4915       if Is_Private_Type (T) then
4916          Val := Get_Simple_Init_Val (Underlying_Type (T), Loc);
4917
4918          --  A special case, if the underlying value is null, then qualify
4919          --  it with the underlying type, so that the null is properly typed
4920          --  Similarly, if it is an aggregate it must be qualified, because
4921          --  an unchecked conversion does not provide a context for it.
4922
4923          if Nkind (Val) = N_Null
4924            or else Nkind (Val) = N_Aggregate
4925          then
4926             Val :=
4927               Make_Qualified_Expression (Loc,
4928                 Subtype_Mark =>
4929                   New_Occurrence_Of (Underlying_Type (T), Loc),
4930                 Expression => Val);
4931          end if;
4932
4933          Result := Unchecked_Convert_To (T, Val);
4934
4935          --  Don't truncate result (important for Initialize/Normalize_Scalars)
4936
4937          if Nkind (Result) = N_Unchecked_Type_Conversion
4938            and then Is_Scalar_Type (Underlying_Type (T))
4939          then
4940             Set_No_Truncation (Result);
4941          end if;
4942
4943          return Result;
4944
4945       --  For scalars, we must have normalize/initialize scalars case
4946
4947       elsif Is_Scalar_Type (T) then
4948          pragma Assert (Init_Or_Norm_Scalars);
4949
4950          --  Processing for Normalize_Scalars case
4951
4952          if Normalize_Scalars then
4953
4954             --  First prepare a value (out of subtype range if possible)
4955
4956             if Is_Real_Type (T) or else Is_Integer_Type (T) then
4957                Val :=
4958                  Make_Attribute_Reference (Loc,
4959                    Prefix => New_Occurrence_Of (Base_Type (T), Loc),
4960                    Attribute_Name => Name_First);
4961
4962             elsif Is_Modular_Integer_Type (T) then
4963                Val :=
4964                  Make_Attribute_Reference (Loc,
4965                    Prefix => New_Occurrence_Of (Base_Type (T), Loc),
4966                    Attribute_Name => Name_Last);
4967
4968             else
4969                pragma Assert (Is_Enumeration_Type (T));
4970
4971                if Esize (T) <= 8 then
4972                   Typ := RTE (RE_Unsigned_8);
4973                elsif Esize (T) <= 16 then
4974                   Typ := RTE (RE_Unsigned_16);
4975                elsif Esize (T) <= 32 then
4976                   Typ := RTE (RE_Unsigned_32);
4977                else
4978                   Typ := RTE (RE_Unsigned_64);
4979                end if;
4980
4981                Val :=
4982                  Make_Attribute_Reference (Loc,
4983                    Prefix => New_Occurrence_Of (Typ, Loc),
4984                    Attribute_Name => Name_Last);
4985             end if;
4986
4987          --  Here for Initialize_Scalars case
4988
4989          else
4990             if Is_Floating_Point_Type (T) then
4991                if Root_Type (T) = Standard_Short_Float then
4992                   Val_RE := RE_IS_Isf;
4993                elsif Root_Type (T) = Standard_Float then
4994                   Val_RE := RE_IS_Ifl;
4995                elsif Root_Type (T) = Standard_Long_Float then
4996                   Val_RE := RE_IS_Ilf;
4997                else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
4998                   Val_RE := RE_IS_Ill;
4999                end if;
5000
5001             elsif Is_Unsigned_Type (Base_Type (T)) then
5002                if Esize (T) = 8 then
5003                   Val_RE := RE_IS_Iu1;
5004                elsif Esize (T) = 16 then
5005                   Val_RE := RE_IS_Iu2;
5006                elsif Esize (T) = 32 then
5007                   Val_RE := RE_IS_Iu4;
5008                else pragma Assert (Esize (T) = 64);
5009                   Val_RE := RE_IS_Iu8;
5010                end if;
5011
5012             else -- signed type
5013                if Esize (T) = 8 then
5014                   Val_RE := RE_IS_Is1;
5015                elsif Esize (T) = 16 then
5016                   Val_RE := RE_IS_Is2;
5017                elsif Esize (T) = 32 then
5018                   Val_RE := RE_IS_Is4;
5019                else pragma Assert (Esize (T) = 64);
5020                   Val_RE := RE_IS_Is8;
5021                end if;
5022             end if;
5023
5024             Val := New_Occurrence_Of (RTE (Val_RE), Loc);
5025          end if;
5026
5027          --  The final expression is obtained by doing an unchecked
5028          --  conversion of this result to the base type of the
5029          --  required subtype. We use the base type to avoid the
5030          --  unchecked conversion from chopping bits, and then we
5031          --  set Kill_Range_Check to preserve the "bad" value.
5032
5033          Result := Unchecked_Convert_To (Base_Type (T), Val);
5034
5035          --  Ensure result is not truncated, since we want the "bad" bits
5036          --  and also kill range check on result.
5037
5038          if Nkind (Result) = N_Unchecked_Type_Conversion then
5039             Set_No_Truncation (Result);
5040             Set_Kill_Range_Check (Result, True);
5041          end if;
5042
5043          return Result;
5044
5045       --  String or Wide_String (must have Initialize_Scalars set)
5046
5047       elsif Root_Type (T) = Standard_String
5048               or else
5049             Root_Type (T) = Standard_Wide_String
5050       then
5051          pragma Assert (Init_Or_Norm_Scalars);
5052
5053          return
5054            Make_Aggregate (Loc,
5055              Component_Associations => New_List (
5056                Make_Component_Association (Loc,
5057                  Choices => New_List (
5058                    Make_Others_Choice (Loc)),
5059                  Expression =>
5060                    Get_Simple_Init_Val (Component_Type (T), Loc))));
5061
5062       --  Access type is initialized to null
5063
5064       elsif Is_Access_Type (T) then
5065          return
5066            Make_Null (Loc);
5067
5068       --  We initialize modular packed bit arrays to zero, to make sure that
5069       --  unused bits are zero, as required (see spec of Exp_Pakd). Also note
5070       --  that this improves gigi code, since the value tracing knows that
5071       --  all bits of the variable start out at zero. The value of zero has
5072       --  to be unchecked converted to the proper array type.
5073
5074       elsif Is_Bit_Packed_Array (T) then
5075          declare
5076             PAT : constant Entity_Id := Packed_Array_Type (T);
5077             Nod : Node_Id;
5078
5079          begin
5080             pragma Assert (Is_Modular_Integer_Type (PAT));
5081
5082             Nod :=
5083               Make_Unchecked_Type_Conversion (Loc,
5084                 Subtype_Mark => New_Occurrence_Of (T, Loc),
5085                 Expression   => Make_Integer_Literal (Loc, 0));
5086
5087             Set_Etype (Expression (Nod), PAT);
5088             return Nod;
5089          end;
5090
5091       --  No other possibilities should arise, since we should only be
5092       --  calling Get_Simple_Init_Val if Needs_Simple_Initialization
5093       --  returned True, indicating one of the above cases held.
5094
5095       else
5096          raise Program_Error;
5097       end if;
5098
5099    exception
5100       when RE_Not_Available =>
5101          return Empty;
5102    end Get_Simple_Init_Val;
5103
5104    ------------------------------
5105    -- Has_New_Non_Standard_Rep --
5106    ------------------------------
5107
5108    function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
5109    begin
5110       if not Is_Derived_Type (T) then
5111          return Has_Non_Standard_Rep (T)
5112            or else Has_Non_Standard_Rep (Root_Type (T));
5113
5114       --  If Has_Non_Standard_Rep is not set on the derived type, the
5115       --  representation is fully inherited.
5116
5117       elsif not Has_Non_Standard_Rep (T) then
5118          return False;
5119
5120       else
5121          return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
5122
5123          --  May need a more precise check here: the First_Rep_Item may
5124          --  be a stream attribute, which does not affect the representation
5125          --  of the type ???
5126       end if;
5127    end Has_New_Non_Standard_Rep;
5128
5129    ----------------
5130    -- In_Runtime --
5131    ----------------
5132
5133    function In_Runtime (E : Entity_Id) return Boolean is
5134       S1 : Entity_Id := Scope (E);
5135
5136    begin
5137       while Scope (S1) /= Standard_Standard loop
5138          S1 := Scope (S1);
5139       end loop;
5140
5141       return Chars (S1) = Name_System or else Chars (S1) = Name_Ada;
5142    end In_Runtime;
5143
5144    ------------------
5145    -- Init_Formals --
5146    ------------------
5147
5148    function Init_Formals (Typ : Entity_Id) return List_Id is
5149       Loc     : constant Source_Ptr := Sloc (Typ);
5150       Formals : List_Id;
5151
5152    begin
5153       --  First parameter is always _Init : in out typ. Note that we need
5154       --  this to be in/out because in the case of the task record value,
5155       --  there are default record fields (_Priority, _Size, -Task_Info)
5156       --  that may be referenced in the generated initialization routine.
5157
5158       Formals := New_List (
5159         Make_Parameter_Specification (Loc,
5160           Defining_Identifier =>
5161             Make_Defining_Identifier (Loc, Name_uInit),
5162           In_Present  => True,
5163           Out_Present => True,
5164           Parameter_Type => New_Reference_To (Typ, Loc)));
5165
5166       --  For task record value, or type that contains tasks, add two more
5167       --  formals, _Master : Master_Id and _Chain : in out Activation_Chain
5168       --  We also add these parameters for the task record type case.
5169
5170       if Has_Task (Typ)
5171         or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
5172       then
5173          Append_To (Formals,
5174            Make_Parameter_Specification (Loc,
5175              Defining_Identifier =>
5176                Make_Defining_Identifier (Loc, Name_uMaster),
5177              Parameter_Type => New_Reference_To (RTE (RE_Master_Id), Loc)));
5178
5179          Append_To (Formals,
5180            Make_Parameter_Specification (Loc,
5181              Defining_Identifier =>
5182                Make_Defining_Identifier (Loc, Name_uChain),
5183              In_Present => True,
5184              Out_Present => True,
5185              Parameter_Type =>
5186                New_Reference_To (RTE (RE_Activation_Chain), Loc)));
5187
5188          Append_To (Formals,
5189            Make_Parameter_Specification (Loc,
5190              Defining_Identifier =>
5191                Make_Defining_Identifier (Loc, Name_uTask_Name),
5192              In_Present => True,
5193              Parameter_Type =>
5194                New_Reference_To (Standard_String, Loc)));
5195       end if;
5196
5197       return Formals;
5198
5199    exception
5200       when RE_Not_Available =>
5201          return Empty_List;
5202    end Init_Formals;
5203
5204    ------------------
5205    -- Make_Eq_Case --
5206    ------------------
5207
5208    --  <Make_Eq_if shared components>
5209    --  case X.D1 is
5210    --     when V1 => <Make_Eq_Case> on subcomponents
5211    --     ...
5212    --     when Vn => <Make_Eq_Case> on subcomponents
5213    --  end case;
5214
5215    function Make_Eq_Case
5216      (E     : Entity_Id;
5217       CL    : Node_Id;
5218       Discr : Entity_Id := Empty) return List_Id
5219    is
5220       Loc      : constant Source_Ptr := Sloc (E);
5221       Result   : constant List_Id    := New_List;
5222       Variant  : Node_Id;
5223       Alt_List : List_Id;
5224
5225    begin
5226       Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
5227
5228       if No (Variant_Part (CL)) then
5229          return Result;
5230       end if;
5231
5232       Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
5233
5234       if No (Variant) then
5235          return Result;
5236       end if;
5237
5238       Alt_List := New_List;
5239
5240       while Present (Variant) loop
5241          Append_To (Alt_List,
5242            Make_Case_Statement_Alternative (Loc,
5243              Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
5244              Statements => Make_Eq_Case (E, Component_List (Variant))));
5245
5246          Next_Non_Pragma (Variant);
5247       end loop;
5248
5249       --  If we have an Unchecked_Union, use one of the parameters that
5250       --  captures the discriminants.
5251
5252       if Is_Unchecked_Union (E) then
5253          Append_To (Result,
5254            Make_Case_Statement (Loc,
5255              Expression => New_Reference_To (Discr, Loc),
5256              Alternatives => Alt_List));
5257
5258       else
5259          Append_To (Result,
5260            Make_Case_Statement (Loc,
5261              Expression =>
5262                Make_Selected_Component (Loc,
5263                  Prefix => Make_Identifier (Loc, Name_X),
5264                  Selector_Name => New_Copy (Name (Variant_Part (CL)))),
5265              Alternatives => Alt_List));
5266       end if;
5267
5268       return Result;
5269    end Make_Eq_Case;
5270
5271    ----------------
5272    -- Make_Eq_If --
5273    ----------------
5274
5275    --  Generates:
5276
5277    --    if
5278    --      X.C1 /= Y.C1
5279    --        or else
5280    --      X.C2 /= Y.C2
5281    --        ...
5282    --    then
5283    --       return False;
5284    --    end if;
5285
5286    --  or a null statement if the list L is empty
5287
5288    function Make_Eq_If
5289      (E : Entity_Id;
5290       L : List_Id) return Node_Id
5291    is
5292       Loc        : constant Source_Ptr := Sloc (E);
5293       C          : Node_Id;
5294       Field_Name : Name_Id;
5295       Cond       : Node_Id;
5296
5297    begin
5298       if No (L) then
5299          return Make_Null_Statement (Loc);
5300
5301       else
5302          Cond := Empty;
5303
5304          C := First_Non_Pragma (L);
5305          while Present (C) loop
5306             Field_Name := Chars (Defining_Identifier (C));
5307
5308             --  The tags must not be compared they are not part of the value.
5309             --  Note also that in the following, we use Make_Identifier for
5310             --  the component names. Use of New_Reference_To to identify the
5311             --  components would be incorrect because the wrong entities for
5312             --  discriminants could be picked up in the private type case.
5313
5314             if Field_Name /= Name_uTag then
5315                Evolve_Or_Else (Cond,
5316                  Make_Op_Ne (Loc,
5317                    Left_Opnd =>
5318                      Make_Selected_Component (Loc,
5319                        Prefix        => Make_Identifier (Loc, Name_X),
5320                        Selector_Name =>
5321                          Make_Identifier (Loc, Field_Name)),
5322
5323                    Right_Opnd =>
5324                      Make_Selected_Component (Loc,
5325                        Prefix        => Make_Identifier (Loc, Name_Y),
5326                        Selector_Name =>
5327                          Make_Identifier (Loc, Field_Name))));
5328             end if;
5329
5330             Next_Non_Pragma (C);
5331          end loop;
5332
5333          if No (Cond) then
5334             return Make_Null_Statement (Loc);
5335
5336          else
5337             return
5338               Make_Implicit_If_Statement (E,
5339                 Condition => Cond,
5340                 Then_Statements => New_List (
5341                   Make_Return_Statement (Loc,
5342                     Expression => New_Occurrence_Of (Standard_False, Loc))));
5343          end if;
5344       end if;
5345    end Make_Eq_If;
5346
5347    -------------------------------------
5348    -- Make_Predefined_Primitive_Specs --
5349    -------------------------------------
5350
5351    procedure Make_Predefined_Primitive_Specs
5352      (Tag_Typ     : Entity_Id;
5353       Predef_List : out List_Id;
5354       Renamed_Eq  : out Node_Id)
5355    is
5356       Loc       : constant Source_Ptr := Sloc (Tag_Typ);
5357       Res       : constant List_Id    := New_List;
5358       Prim      : Elmt_Id;
5359       Eq_Needed : Boolean;
5360       Eq_Spec   : Node_Id;
5361       Eq_Name   : Name_Id := Name_Op_Eq;
5362
5363       function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
5364       --  Returns true if Prim is a renaming of an unresolved predefined
5365       --  equality operation.
5366
5367       -------------------------------
5368       -- Is_Predefined_Eq_Renaming --
5369       -------------------------------
5370
5371       function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
5372       begin
5373          return Chars (Prim) /= Name_Op_Eq
5374            and then Present (Alias (Prim))
5375            and then Comes_From_Source (Prim)
5376            and then Is_Intrinsic_Subprogram (Alias (Prim))
5377            and then Chars (Alias (Prim)) = Name_Op_Eq;
5378       end Is_Predefined_Eq_Renaming;
5379
5380    --  Start of processing for Make_Predefined_Primitive_Specs
5381
5382    begin
5383       Renamed_Eq := Empty;
5384
5385       --  Spec of _Alignment
5386
5387       Append_To (Res, Predef_Spec_Or_Body (Loc,
5388         Tag_Typ => Tag_Typ,
5389         Name    => Name_uAlignment,
5390         Profile => New_List (
5391           Make_Parameter_Specification (Loc,
5392             Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5393             Parameter_Type      => New_Reference_To (Tag_Typ, Loc))),
5394
5395         Ret_Type => Standard_Integer));
5396
5397       --  Spec of _Size
5398
5399       Append_To (Res, Predef_Spec_Or_Body (Loc,
5400         Tag_Typ => Tag_Typ,
5401         Name    => Name_uSize,
5402         Profile => New_List (
5403           Make_Parameter_Specification (Loc,
5404             Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5405             Parameter_Type      => New_Reference_To (Tag_Typ, Loc))),
5406
5407         Ret_Type => Standard_Long_Long_Integer));
5408
5409       --  Specs for dispatching stream attributes. We skip these for limited
5410       --  types, since there is no question of dispatching in the limited case.
5411
5412       --  We also skip these operations if dispatching is not available
5413       --  or if streams are not available (since what's the point?)
5414
5415       if not Is_Limited_Type (Tag_Typ)
5416         and then RTE_Available (RE_Tag)
5417         and then RTE_Available (RE_Root_Stream_Type)
5418       then
5419          Append_To (Res,
5420            Predef_Stream_Attr_Spec (Loc, Tag_Typ, TSS_Stream_Read));
5421          Append_To (Res,
5422            Predef_Stream_Attr_Spec (Loc, Tag_Typ, TSS_Stream_Write));
5423          Append_To (Res,
5424            Predef_Stream_Attr_Spec (Loc, Tag_Typ, TSS_Stream_Input));
5425          Append_To (Res,
5426            Predef_Stream_Attr_Spec (Loc, Tag_Typ, TSS_Stream_Output));
5427       end if;
5428
5429       --  Spec of "=" if expanded if the type is not limited and if a
5430       --  user defined "=" was not already declared for the non-full
5431       --  view of a private extension
5432
5433       if not Is_Limited_Type (Tag_Typ) then
5434          Eq_Needed := True;
5435
5436          Prim := First_Elmt (Primitive_Operations (Tag_Typ));
5437          while Present (Prim) loop
5438
5439             --  If a primitive is encountered that renames the predefined
5440             --  equality operator before reaching any explicit equality
5441             --  primitive, then we still need to create a predefined
5442             --  equality function, because calls to it can occur via
5443             --  the renaming. A new name is created for the equality
5444             --  to avoid conflicting with any user-defined equality.
5445             --  (Note that this doesn't account for renamings of
5446             --  equality nested within subpackages???)
5447
5448             if Is_Predefined_Eq_Renaming (Node (Prim)) then
5449                Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
5450
5451             elsif Chars (Node (Prim)) = Name_Op_Eq
5452               and then (No (Alias (Node (Prim)))
5453                          or else Nkind (Unit_Declaration_Node (Node (Prim))) =
5454                                             N_Subprogram_Renaming_Declaration)
5455               and then Etype (First_Formal (Node (Prim))) =
5456                          Etype (Next_Formal (First_Formal (Node (Prim))))
5457               and then Base_Type (Etype (Node (Prim))) = Standard_Boolean
5458
5459             then
5460                Eq_Needed := False;
5461                exit;
5462
5463             --  If the parent equality is abstract, the inherited equality is
5464             --  abstract as well, and no body can be created for for it.
5465
5466             elsif Chars (Node (Prim)) = Name_Op_Eq
5467               and then Present (Alias (Node (Prim)))
5468               and then Is_Abstract (Alias (Node (Prim)))
5469             then
5470                Eq_Needed := False;
5471                exit;
5472             end if;
5473
5474             Next_Elmt (Prim);
5475          end loop;
5476
5477          --  If a renaming of predefined equality was found
5478          --  but there was no user-defined equality (so Eq_Needed
5479          --  is still true), then set the name back to Name_Op_Eq.
5480          --  But in the case where a user-defined equality was
5481          --  located after such a renaming, then the predefined
5482          --  equality function is still needed, so Eq_Needed must
5483          --  be set back to True.
5484
5485          if Eq_Name /= Name_Op_Eq then
5486             if Eq_Needed then
5487                Eq_Name := Name_Op_Eq;
5488             else
5489                Eq_Needed := True;
5490             end if;
5491          end if;
5492
5493          if Eq_Needed then
5494             Eq_Spec := Predef_Spec_Or_Body (Loc,
5495               Tag_Typ => Tag_Typ,
5496               Name    => Eq_Name,
5497               Profile => New_List (
5498                 Make_Parameter_Specification (Loc,
5499                   Defining_Identifier =>
5500                     Make_Defining_Identifier (Loc, Name_X),
5501                     Parameter_Type      => New_Reference_To (Tag_Typ, Loc)),
5502                 Make_Parameter_Specification (Loc,
5503                   Defining_Identifier =>
5504                     Make_Defining_Identifier (Loc, Name_Y),
5505                     Parameter_Type      => New_Reference_To (Tag_Typ, Loc))),
5506                 Ret_Type => Standard_Boolean);
5507             Append_To (Res, Eq_Spec);
5508
5509             if Eq_Name /= Name_Op_Eq then
5510                Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
5511
5512                Prim := First_Elmt (Primitive_Operations (Tag_Typ));
5513                while Present (Prim) loop
5514
5515                   --  Any renamings of equality that appeared before an
5516                   --  overriding equality must be updated to refer to
5517                   --  the entity for the predefined equality, otherwise
5518                   --  calls via the renaming would get incorrectly
5519                   --  resolved to call the user-defined equality function.
5520
5521                   if Is_Predefined_Eq_Renaming (Node (Prim)) then
5522                      Set_Alias (Node (Prim), Renamed_Eq);
5523
5524                   --  Exit upon encountering a user-defined equality
5525
5526                   elsif Chars (Node (Prim)) = Name_Op_Eq
5527                     and then No (Alias (Node (Prim)))
5528                   then
5529                      exit;
5530                   end if;
5531
5532                   Next_Elmt (Prim);
5533                end loop;
5534             end if;
5535          end if;
5536
5537          --  Spec for dispatching assignment
5538
5539          Append_To (Res, Predef_Spec_Or_Body (Loc,
5540            Tag_Typ => Tag_Typ,
5541            Name    => Name_uAssign,
5542            Profile => New_List (
5543              Make_Parameter_Specification (Loc,
5544                Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5545                Out_Present         => True,
5546                Parameter_Type      => New_Reference_To (Tag_Typ, Loc)),
5547
5548              Make_Parameter_Specification (Loc,
5549                Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
5550                Parameter_Type      => New_Reference_To (Tag_Typ, Loc)))));
5551       end if;
5552
5553       --  Specs for finalization actions that may be required in case a
5554       --  future extension contain a controlled element. We generate those
5555       --  only for root tagged types where they will get dummy bodies or
5556       --  when the type has controlled components and their body must be
5557       --  generated. It is also impossible to provide those for tagged
5558       --  types defined within s-finimp since it would involve circularity
5559       --  problems
5560
5561       if In_Finalization_Root (Tag_Typ) then
5562          null;
5563
5564       --  We also skip these if finalization is not available
5565
5566       elsif Restriction_Active (No_Finalization) then
5567          null;
5568
5569       elsif Etype (Tag_Typ) = Tag_Typ or else Controlled_Type (Tag_Typ) then
5570          if not Is_Limited_Type (Tag_Typ) then
5571             Append_To (Res,
5572               Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
5573          end if;
5574
5575          Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
5576       end if;
5577
5578       Predef_List := Res;
5579    end Make_Predefined_Primitive_Specs;
5580
5581    ---------------------------------
5582    -- Needs_Simple_Initialization --
5583    ---------------------------------
5584
5585    function Needs_Simple_Initialization (T : Entity_Id) return Boolean is
5586    begin
5587       --  Check for private type, in which case test applies to the
5588       --  underlying type of the private type.
5589
5590       if Is_Private_Type (T) then
5591          declare
5592             RT : constant Entity_Id := Underlying_Type (T);
5593
5594          begin
5595             if Present (RT) then
5596                return Needs_Simple_Initialization (RT);
5597             else
5598                return False;
5599             end if;
5600          end;
5601
5602       --  Cases needing simple initialization are access types, and, if pragma
5603       --  Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
5604       --  types.
5605
5606       elsif Is_Access_Type (T)
5607         or else (Init_Or_Norm_Scalars and then (Is_Scalar_Type (T)))
5608
5609         or else (Is_Bit_Packed_Array (T)
5610                    and then Is_Modular_Integer_Type (Packed_Array_Type (T)))
5611       then
5612          return True;
5613
5614       --  If Initialize/Normalize_Scalars is in effect, string objects also
5615       --  need initialization, unless they are created in the course of
5616       --  expanding an aggregate (since in the latter case they will be
5617       --  filled with appropriate initializing values before they are used).
5618
5619       elsif Init_Or_Norm_Scalars
5620         and then
5621           (Root_Type (T) = Standard_String
5622             or else Root_Type (T) = Standard_Wide_String)
5623         and then
5624           (not Is_Itype (T)
5625             or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
5626       then
5627          return True;
5628
5629       else
5630          return False;
5631       end if;
5632    end Needs_Simple_Initialization;
5633
5634    ----------------------
5635    -- Predef_Deep_Spec --
5636    ----------------------
5637
5638    function Predef_Deep_Spec
5639      (Loc      : Source_Ptr;
5640       Tag_Typ  : Entity_Id;
5641       Name     : TSS_Name_Type;
5642       For_Body : Boolean := False) return Node_Id
5643    is
5644       Prof   : List_Id;
5645       Type_B : Entity_Id;
5646
5647    begin
5648       if Name = TSS_Deep_Finalize then
5649          Prof := New_List;
5650          Type_B := Standard_Boolean;
5651
5652       else
5653          Prof := New_List (
5654            Make_Parameter_Specification (Loc,
5655              Defining_Identifier => Make_Defining_Identifier (Loc, Name_L),
5656              In_Present          => True,
5657              Out_Present         => True,
5658              Parameter_Type      =>
5659                New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
5660          Type_B := Standard_Short_Short_Integer;
5661       end if;
5662
5663       Append_To (Prof,
5664            Make_Parameter_Specification (Loc,
5665              Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
5666              In_Present          => True,
5667              Out_Present         => True,
5668              Parameter_Type      => New_Reference_To (Tag_Typ, Loc)));
5669
5670       Append_To (Prof,
5671            Make_Parameter_Specification (Loc,
5672              Defining_Identifier => Make_Defining_Identifier (Loc, Name_B),
5673              Parameter_Type      => New_Reference_To (Type_B, Loc)));
5674
5675       return Predef_Spec_Or_Body (Loc,
5676         Name     => Make_TSS_Name (Tag_Typ, Name),
5677         Tag_Typ  => Tag_Typ,
5678         Profile  => Prof,
5679         For_Body => For_Body);
5680
5681    exception
5682       when RE_Not_Available =>
5683          return Empty;
5684    end Predef_Deep_Spec;
5685
5686    -------------------------
5687    -- Predef_Spec_Or_Body --
5688    -------------------------
5689
5690    function Predef_Spec_Or_Body
5691      (Loc      : Source_Ptr;
5692       Tag_Typ  : Entity_Id;
5693       Name     : Name_Id;
5694       Profile  : List_Id;
5695       Ret_Type : Entity_Id := Empty;
5696       For_Body : Boolean := False) return Node_Id
5697    is
5698       Id   : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
5699       Spec : Node_Id;
5700
5701    begin
5702       Set_Is_Public (Id, Is_Public (Tag_Typ));
5703
5704       --  The internal flag is set to mark these declarations because
5705       --  they have specific properties. First they are primitives even
5706       --  if they are not defined in the type scope (the freezing point
5707       --  is not necessarily in the same scope), furthermore the
5708       --  predefined equality can be overridden by a user-defined
5709       --  equality, no body will be generated in this case.
5710
5711       Set_Is_Internal (Id);
5712
5713       if not Debug_Generated_Code then
5714          Set_Debug_Info_Off (Id);
5715       end if;
5716
5717       if No (Ret_Type) then
5718          Spec :=
5719            Make_Procedure_Specification (Loc,
5720              Defining_Unit_Name       => Id,
5721              Parameter_Specifications => Profile);
5722       else
5723          Spec :=
5724            Make_Function_Specification (Loc,
5725              Defining_Unit_Name       => Id,
5726              Parameter_Specifications => Profile,
5727              Subtype_Mark             =>
5728                New_Reference_To (Ret_Type, Loc));
5729       end if;
5730
5731       --  If body case, return empty subprogram body. Note that this is
5732       --  ill-formed, because there is not even a null statement, and
5733       --  certainly not a return in the function case. The caller is
5734       --  expected to do surgery on the body to add the appropriate stuff.
5735
5736       if For_Body then
5737          return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
5738
5739       --  For the case of Input/Output attributes applied to an abstract type,
5740       --  generate abstract specifications. These will never be called,
5741       --  but we need the slots allocated in the dispatching table so
5742       --  that typ'Class'Input and typ'Class'Output will work properly.
5743
5744       elsif (Is_TSS (Name, TSS_Stream_Input)
5745               or else
5746              Is_TSS (Name, TSS_Stream_Output))
5747         and then Is_Abstract (Tag_Typ)
5748       then
5749          return Make_Abstract_Subprogram_Declaration (Loc, Spec);
5750
5751       --  Normal spec case, where we return a subprogram declaration
5752
5753       else
5754          return Make_Subprogram_Declaration (Loc, Spec);
5755       end if;
5756    end Predef_Spec_Or_Body;
5757
5758    -----------------------------
5759    -- Predef_Stream_Attr_Spec --
5760    -----------------------------
5761
5762    function Predef_Stream_Attr_Spec
5763      (Loc      : Source_Ptr;
5764       Tag_Typ  : Entity_Id;
5765       Name     : TSS_Name_Type;
5766       For_Body : Boolean := False) return Node_Id
5767    is
5768       Ret_Type : Entity_Id;
5769
5770    begin
5771       if Name = TSS_Stream_Input then
5772          Ret_Type := Tag_Typ;
5773       else
5774          Ret_Type := Empty;
5775       end if;
5776
5777       return Predef_Spec_Or_Body (Loc,
5778         Name     => Make_TSS_Name (Tag_Typ, Name),
5779         Tag_Typ  => Tag_Typ,
5780         Profile  => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
5781         Ret_Type => Ret_Type,
5782         For_Body => For_Body);
5783    end Predef_Stream_Attr_Spec;
5784
5785    ---------------------------------
5786    -- Predefined_Primitive_Bodies --
5787    ---------------------------------
5788
5789    function Predefined_Primitive_Bodies
5790      (Tag_Typ    : Entity_Id;
5791       Renamed_Eq : Node_Id) return List_Id
5792    is
5793       Loc       : constant Source_Ptr := Sloc (Tag_Typ);
5794       Res       : constant List_Id    := New_List;
5795       Decl      : Node_Id;
5796       Prim      : Elmt_Id;
5797       Eq_Needed : Boolean;
5798       Eq_Name   : Name_Id;
5799       Ent       : Entity_Id;
5800
5801    begin
5802       --  See if we have a predefined "=" operator
5803
5804       if Present (Renamed_Eq) then
5805          Eq_Needed := True;
5806          Eq_Name   := Chars (Renamed_Eq);
5807
5808       else
5809          Eq_Needed := False;
5810          Eq_Name   := No_Name;
5811
5812          Prim := First_Elmt (Primitive_Operations (Tag_Typ));
5813          while Present (Prim) loop
5814             if Chars (Node (Prim)) = Name_Op_Eq
5815               and then Is_Internal (Node (Prim))
5816             then
5817                Eq_Needed := True;
5818                Eq_Name := Name_Op_Eq;
5819             end if;
5820
5821             Next_Elmt (Prim);
5822          end loop;
5823       end if;
5824
5825       --  Body of _Alignment
5826
5827       Decl := Predef_Spec_Or_Body (Loc,
5828         Tag_Typ => Tag_Typ,
5829         Name    => Name_uAlignment,
5830         Profile => New_List (
5831           Make_Parameter_Specification (Loc,
5832             Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5833             Parameter_Type      => New_Reference_To (Tag_Typ, Loc))),
5834
5835         Ret_Type => Standard_Integer,
5836         For_Body => True);
5837
5838       Set_Handled_Statement_Sequence (Decl,
5839         Make_Handled_Sequence_Of_Statements (Loc, New_List (
5840           Make_Return_Statement (Loc,
5841             Expression =>
5842               Make_Attribute_Reference (Loc,
5843                 Prefix => Make_Identifier (Loc, Name_X),
5844                 Attribute_Name  => Name_Alignment)))));
5845
5846       Append_To (Res, Decl);
5847
5848       --  Body of _Size
5849
5850       Decl := Predef_Spec_Or_Body (Loc,
5851         Tag_Typ => Tag_Typ,
5852         Name    => Name_uSize,
5853         Profile => New_List (
5854           Make_Parameter_Specification (Loc,
5855             Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5856             Parameter_Type      => New_Reference_To (Tag_Typ, Loc))),
5857
5858         Ret_Type => Standard_Long_Long_Integer,
5859         For_Body => True);
5860
5861       Set_Handled_Statement_Sequence (Decl,
5862         Make_Handled_Sequence_Of_Statements (Loc, New_List (
5863           Make_Return_Statement (Loc,
5864             Expression =>
5865               Make_Attribute_Reference (Loc,
5866                 Prefix => Make_Identifier (Loc, Name_X),
5867                 Attribute_Name  => Name_Size)))));
5868
5869       Append_To (Res, Decl);
5870
5871       --  Bodies for Dispatching stream IO routines. We need these only for
5872       --  non-limited types (in the limited case there is no dispatching).
5873       --  We also skip them if dispatching is not available.
5874
5875       if not Is_Limited_Type (Tag_Typ)
5876         and then not Restriction_Active (No_Finalization)
5877       then
5878          if No (TSS (Tag_Typ, TSS_Stream_Read)) then
5879             Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
5880             Append_To (Res, Decl);
5881          end if;
5882
5883          if No (TSS (Tag_Typ, TSS_Stream_Write)) then
5884             Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
5885             Append_To (Res, Decl);
5886          end if;
5887
5888          --  Skip bodies of _Input and _Output for the abstract case, since
5889          --  the corresponding specs are abstract (see Predef_Spec_Or_Body)
5890
5891          if not Is_Abstract (Tag_Typ) then
5892             if No (TSS (Tag_Typ, TSS_Stream_Input)) then
5893                Build_Record_Or_Elementary_Input_Function
5894                  (Loc, Tag_Typ, Decl, Ent);
5895                Append_To (Res, Decl);
5896             end if;
5897
5898             if No (TSS (Tag_Typ, TSS_Stream_Output)) then
5899                Build_Record_Or_Elementary_Output_Procedure
5900                  (Loc, Tag_Typ, Decl, Ent);
5901                Append_To (Res, Decl);
5902             end if;
5903          end if;
5904       end if;
5905
5906       if not Is_Limited_Type (Tag_Typ) then
5907
5908          --  Body for equality
5909
5910          if Eq_Needed then
5911
5912             Decl := Predef_Spec_Or_Body (Loc,
5913               Tag_Typ => Tag_Typ,
5914               Name    => Eq_Name,
5915               Profile => New_List (
5916                 Make_Parameter_Specification (Loc,
5917                   Defining_Identifier =>
5918                     Make_Defining_Identifier (Loc, Name_X),
5919                   Parameter_Type      => New_Reference_To (Tag_Typ, Loc)),
5920
5921                 Make_Parameter_Specification (Loc,
5922                   Defining_Identifier =>
5923                     Make_Defining_Identifier (Loc, Name_Y),
5924                   Parameter_Type      => New_Reference_To (Tag_Typ, Loc))),
5925
5926               Ret_Type => Standard_Boolean,
5927               For_Body => True);
5928
5929             declare
5930                Def          : constant Node_Id := Parent (Tag_Typ);
5931                Stmts        : constant List_Id := New_List;
5932                Variant_Case : Boolean := Has_Discriminants (Tag_Typ);
5933                Comps        : Node_Id := Empty;
5934                Typ_Def      : Node_Id := Type_Definition (Def);
5935
5936             begin
5937                if Variant_Case then
5938                   if Nkind (Typ_Def) = N_Derived_Type_Definition then
5939                      Typ_Def := Record_Extension_Part (Typ_Def);
5940                   end if;
5941
5942                   if Present (Typ_Def) then
5943                      Comps := Component_List (Typ_Def);
5944                   end if;
5945
5946                   Variant_Case := Present (Comps)
5947                     and then Present (Variant_Part (Comps));
5948                end if;
5949
5950                if Variant_Case then
5951                   Append_To (Stmts,
5952                     Make_Eq_If (Tag_Typ, Discriminant_Specifications (Def)));
5953                   Append_List_To (Stmts, Make_Eq_Case (Tag_Typ, Comps));
5954                   Append_To (Stmts,
5955                     Make_Return_Statement (Loc,
5956                       Expression => New_Reference_To (Standard_True, Loc)));
5957
5958                else
5959                   Append_To (Stmts,
5960                     Make_Return_Statement (Loc,
5961                       Expression =>
5962                         Expand_Record_Equality (Tag_Typ,
5963                           Typ => Tag_Typ,
5964                           Lhs => Make_Identifier (Loc, Name_X),
5965                           Rhs => Make_Identifier (Loc, Name_Y),
5966                           Bodies => Declarations (Decl))));
5967                end if;
5968
5969                Set_Handled_Statement_Sequence (Decl,
5970                  Make_Handled_Sequence_Of_Statements (Loc, Stmts));
5971             end;
5972             Append_To (Res, Decl);
5973          end if;
5974
5975          --  Body for dispatching assignment
5976
5977          Decl := Predef_Spec_Or_Body (Loc,
5978            Tag_Typ => Tag_Typ,
5979            Name    => Name_uAssign,
5980            Profile => New_List (
5981              Make_Parameter_Specification (Loc,
5982                Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5983                Out_Present         => True,
5984                Parameter_Type      => New_Reference_To (Tag_Typ, Loc)),
5985
5986              Make_Parameter_Specification (Loc,
5987                Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
5988                Parameter_Type      => New_Reference_To (Tag_Typ, Loc))),
5989            For_Body => True);
5990
5991          Set_Handled_Statement_Sequence (Decl,
5992            Make_Handled_Sequence_Of_Statements (Loc, New_List (
5993              Make_Assignment_Statement (Loc,
5994                Name       => Make_Identifier (Loc, Name_X),
5995                Expression => Make_Identifier (Loc, Name_Y)))));
5996
5997          Append_To (Res, Decl);
5998       end if;
5999
6000       --  Generate dummy bodies for finalization actions of types that have
6001       --  no controlled components.
6002
6003       --  Skip this processing if we are in the finalization routine in the
6004       --  runtime itself, otherwise we get hopelessly circularly confused!
6005
6006       if In_Finalization_Root (Tag_Typ) then
6007          null;
6008
6009       --  Skip this if finalization is not available
6010
6011       elsif Restriction_Active (No_Finalization) then
6012          null;
6013
6014       elsif (Etype (Tag_Typ) = Tag_Typ or else Is_Controlled (Tag_Typ))
6015         and then not Has_Controlled_Component (Tag_Typ)
6016       then
6017          if not Is_Limited_Type (Tag_Typ) then
6018             Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
6019
6020             if Is_Controlled (Tag_Typ) then
6021                Set_Handled_Statement_Sequence (Decl,
6022                  Make_Handled_Sequence_Of_Statements (Loc,
6023                    Make_Adjust_Call (
6024                      Ref          => Make_Identifier (Loc, Name_V),
6025                      Typ          => Tag_Typ,
6026                      Flist_Ref    => Make_Identifier (Loc, Name_L),
6027                      With_Attach  => Make_Identifier (Loc, Name_B))));
6028
6029             else
6030                Set_Handled_Statement_Sequence (Decl,
6031                  Make_Handled_Sequence_Of_Statements (Loc, New_List (
6032                    Make_Null_Statement (Loc))));
6033             end if;
6034
6035             Append_To (Res, Decl);
6036          end if;
6037
6038          Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
6039
6040          if Is_Controlled (Tag_Typ) then
6041             Set_Handled_Statement_Sequence (Decl,
6042               Make_Handled_Sequence_Of_Statements (Loc,
6043                 Make_Final_Call (
6044                   Ref         => Make_Identifier (Loc, Name_V),
6045                   Typ         => Tag_Typ,
6046                   With_Detach => Make_Identifier (Loc, Name_B))));
6047
6048          else
6049             Set_Handled_Statement_Sequence (Decl,
6050               Make_Handled_Sequence_Of_Statements (Loc, New_List (
6051                 Make_Null_Statement (Loc))));
6052          end if;
6053
6054          Append_To (Res, Decl);
6055       end if;
6056
6057       return Res;
6058    end Predefined_Primitive_Bodies;
6059
6060    ---------------------------------
6061    -- Predefined_Primitive_Freeze --
6062    ---------------------------------
6063
6064    function Predefined_Primitive_Freeze
6065      (Tag_Typ : Entity_Id) return List_Id
6066    is
6067       Loc     : constant Source_Ptr := Sloc (Tag_Typ);
6068       Res     : constant List_Id    := New_List;
6069       Prim    : Elmt_Id;
6070       Frnodes : List_Id;
6071
6072    begin
6073       Prim := First_Elmt (Primitive_Operations (Tag_Typ));
6074       while Present (Prim) loop
6075          if Is_Internal (Node (Prim)) then
6076             Frnodes := Freeze_Entity (Node (Prim), Loc);
6077
6078             if Present (Frnodes) then
6079                Append_List_To (Res, Frnodes);
6080             end if;
6081          end if;
6082
6083          Next_Elmt (Prim);
6084       end loop;
6085
6086       return Res;
6087    end Predefined_Primitive_Freeze;
6088 end Exp_Ch3;