OSDN Git Service

2004-09-09 Vincent Celier <celier@gnat.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / exp_ch3.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                              E X P _ C H 3                               --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-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 difference: the types Tag and Vtable_Ptr, which
1404       --  are access types which would normally require simple initialization
1405       --  to null, do not require initialization as components, since they
1406       --  are explicitly initialized by other means.
1407
1408       procedure Constrain_Array
1409         (SI         : Node_Id;
1410          Check_List : List_Id);
1411       --  Called from Build_Record_Checks.
1412       --  Apply a list of index constraints to an unconstrained array type.
1413       --  The first parameter is the entity for the resulting subtype.
1414       --  Check_List is a list to which the check actions are appended.
1415
1416       procedure Constrain_Index
1417         (Index      : Node_Id;
1418          S          : Node_Id;
1419          Check_List : List_Id);
1420       --  Called from Build_Record_Checks.
1421       --  Process an index constraint in a constrained array declaration.
1422       --  The constraint can be a subtype name, or a range with or without
1423       --  an explicit subtype mark. The index is the corresponding index of the
1424       --  unconstrained array. S is the range expression. Check_List is a list
1425       --  to which the check actions are appended.
1426
1427       function Parent_Subtype_Renaming_Discrims return Boolean;
1428       --  Returns True for base types N that rename discriminants, else False
1429
1430       function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean;
1431       --  Determines whether a record initialization procedure needs to be
1432       --  generated for the given record type.
1433
1434       ----------------------
1435       -- Build_Assignment --
1436       ----------------------
1437
1438       function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id is
1439          Exp  : Node_Id := N;
1440          Lhs  : Node_Id;
1441          Typ  : constant Entity_Id := Underlying_Type (Etype (Id));
1442          Kind : Node_Kind := Nkind (N);
1443          Res  : List_Id;
1444
1445       begin
1446          Loc := Sloc (N);
1447          Lhs :=
1448            Make_Selected_Component (Loc,
1449              Prefix => Make_Identifier (Loc, Name_uInit),
1450              Selector_Name => New_Occurrence_Of (Id, Loc));
1451          Set_Assignment_OK (Lhs);
1452
1453          --  Case of an access attribute applied to the current instance.
1454          --  Replace the reference to the type by a reference to the actual
1455          --  object. (Note that this handles the case of the top level of
1456          --  the expression being given by such an attribute, but does not
1457          --  cover uses nested within an initial value expression. Nested
1458          --  uses are unlikely to occur in practice, but are theoretically
1459          --  possible. It is not clear how to handle them without fully
1460          --  traversing the expression. ???
1461
1462          if Kind = N_Attribute_Reference
1463            and then (Attribute_Name (N) = Name_Unchecked_Access
1464                        or else
1465                      Attribute_Name (N) = Name_Unrestricted_Access)
1466            and then Is_Entity_Name (Prefix (N))
1467            and then Is_Type (Entity (Prefix (N)))
1468            and then Entity (Prefix (N)) = Rec_Type
1469          then
1470             Exp :=
1471               Make_Attribute_Reference (Loc,
1472                 Prefix         => Make_Identifier (Loc, Name_uInit),
1473                 Attribute_Name => Name_Unrestricted_Access);
1474          end if;
1475
1476          --  Ada 2005 (AI-231): Generate conversion to the null-excluding
1477          --  type to force the corresponding run-time check.
1478
1479          if Ada_Version >= Ada_05
1480            and then Can_Never_Be_Null (Etype (Id))  -- Lhs
1481            and then Present (Etype (Exp))
1482            and then not Can_Never_Be_Null (Etype (Exp))
1483          then
1484             Rewrite (Exp, Convert_To (Etype (Id), Relocate_Node (Exp)));
1485             Analyze_And_Resolve (Exp, Etype (Id));
1486          end if;
1487
1488          --  Take a copy of Exp to ensure that later copies of this
1489          --  component_declaration in derived types see the original tree,
1490          --  not a node rewritten during expansion of the init_proc.
1491
1492          Exp := New_Copy_Tree (Exp);
1493
1494          Res := New_List (
1495            Make_Assignment_Statement (Loc,
1496              Name       => Lhs,
1497              Expression => Exp));
1498
1499          Set_No_Ctrl_Actions (First (Res));
1500
1501          --  Adjust the tag if tagged (because of possible view conversions).
1502          --  Suppress the tag adjustment when Java_VM because JVM tags are
1503          --  represented implicitly in objects.
1504
1505          if Is_Tagged_Type (Typ) and then not Java_VM then
1506             Append_To (Res,
1507               Make_Assignment_Statement (Loc,
1508                 Name =>
1509                   Make_Selected_Component (Loc,
1510                     Prefix =>  New_Copy_Tree (Lhs),
1511                     Selector_Name =>
1512                       New_Reference_To (Tag_Component (Typ), Loc)),
1513
1514                 Expression =>
1515                   Unchecked_Convert_To (RTE (RE_Tag),
1516                     New_Reference_To (Access_Disp_Table (Typ), Loc))));
1517          end if;
1518
1519          --  Adjust the component if controlled except if it is an
1520          --  aggregate that will be expanded inline
1521
1522          if Kind = N_Qualified_Expression then
1523             Kind := Nkind (Expression (N));
1524          end if;
1525
1526          if Controlled_Type (Typ)
1527          and then not (Kind = N_Aggregate or else Kind = N_Extension_Aggregate)
1528          then
1529             Append_List_To (Res,
1530               Make_Adjust_Call (
1531                Ref          => New_Copy_Tree (Lhs),
1532                Typ          => Etype (Id),
1533                Flist_Ref    =>
1534                  Find_Final_List (Etype (Id), New_Copy_Tree (Lhs)),
1535                With_Attach  => Make_Integer_Literal (Loc, 1)));
1536          end if;
1537
1538          return Res;
1539
1540       exception
1541          when RE_Not_Available =>
1542             return Empty_List;
1543       end Build_Assignment;
1544
1545       ------------------------------------
1546       -- Build_Discriminant_Assignments --
1547       ------------------------------------
1548
1549       procedure Build_Discriminant_Assignments (Statement_List : List_Id) is
1550          D         : Entity_Id;
1551          Is_Tagged : constant Boolean := Is_Tagged_Type (Rec_Type);
1552
1553       begin
1554          if Has_Discriminants (Rec_Type)
1555            and then not Is_Unchecked_Union (Rec_Type)
1556          then
1557             D := First_Discriminant (Rec_Type);
1558
1559             while Present (D) loop
1560                --  Don't generate the assignment for discriminants in derived
1561                --  tagged types if the discriminant is a renaming of some
1562                --  ancestor discriminant.  This initialization will be done
1563                --  when initializing the _parent field of the derived record.
1564
1565                if Is_Tagged and then
1566                  Present (Corresponding_Discriminant (D))
1567                then
1568                   null;
1569
1570                else
1571                   Loc := Sloc (D);
1572                   Append_List_To (Statement_List,
1573                     Build_Assignment (D,
1574                       New_Reference_To (Discriminal (D), Loc)));
1575                end if;
1576
1577                Next_Discriminant (D);
1578             end loop;
1579          end if;
1580       end Build_Discriminant_Assignments;
1581
1582       --------------------------
1583       -- Build_Init_Call_Thru --
1584       --------------------------
1585
1586       function Build_Init_Call_Thru (Parameters : List_Id) return List_Id is
1587          Parent_Proc : constant Entity_Id :=
1588                          Base_Init_Proc (Etype (Rec_Type));
1589
1590          Parent_Type : constant Entity_Id :=
1591                          Etype (First_Formal (Parent_Proc));
1592
1593          Uparent_Type : constant Entity_Id :=
1594                           Underlying_Type (Parent_Type);
1595
1596          First_Discr_Param : Node_Id;
1597
1598          Parent_Discr : Entity_Id;
1599          First_Arg    : Node_Id;
1600          Args         : List_Id;
1601          Arg          : Node_Id;
1602          Res          : List_Id;
1603
1604       begin
1605          --  First argument (_Init) is the object to be initialized.
1606          --  ??? not sure where to get a reasonable Loc for First_Arg
1607
1608          First_Arg :=
1609            OK_Convert_To (Parent_Type,
1610              New_Reference_To (Defining_Identifier (First (Parameters)), Loc));
1611
1612          Set_Etype (First_Arg, Parent_Type);
1613
1614          Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
1615
1616          --  In the tasks case,
1617          --    add _Master as the value of the _Master parameter
1618          --    add _Chain as the value of the _Chain parameter.
1619          --    add _Task_Name as the value of the _Task_Name parameter.
1620          --  At the outer level, these will be variables holding the
1621          --  corresponding values obtained from GNARL or the expander.
1622          --
1623          --  At inner levels, they will be the parameters passed down through
1624          --  the outer routines.
1625
1626          First_Discr_Param := Next (First (Parameters));
1627
1628          if Has_Task (Rec_Type) then
1629             if Restriction_Active (No_Task_Hierarchy) then
1630
1631                --  See comments in System.Tasking.Initialization.Init_RTS
1632                --  for the value 3.
1633
1634                Append_To (Args, Make_Integer_Literal (Loc, 3));
1635             else
1636                Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1637             end if;
1638
1639             Append_To (Args, Make_Identifier (Loc, Name_uChain));
1640             Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
1641             First_Discr_Param := Next (Next (Next (First_Discr_Param)));
1642          end if;
1643
1644          --  Append discriminant values
1645
1646          if Has_Discriminants (Uparent_Type) then
1647             pragma Assert (not Is_Tagged_Type (Uparent_Type));
1648
1649             Parent_Discr := First_Discriminant (Uparent_Type);
1650             while Present (Parent_Discr) loop
1651
1652                --  Get the initial value for this discriminant
1653                --  ??? needs to be cleaned up to use parent_Discr_Constr
1654                --  directly.
1655
1656                declare
1657                   Discr_Value : Elmt_Id :=
1658                                   First_Elmt
1659                                     (Stored_Constraint (Rec_Type));
1660
1661                   Discr       : Entity_Id :=
1662                                   First_Stored_Discriminant (Uparent_Type);
1663                begin
1664                   while Original_Record_Component (Parent_Discr) /= Discr loop
1665                      Next_Stored_Discriminant (Discr);
1666                      Next_Elmt (Discr_Value);
1667                   end loop;
1668
1669                   Arg := Node (Discr_Value);
1670                end;
1671
1672                --  Append it to the list
1673
1674                if Nkind (Arg) = N_Identifier
1675                   and then Ekind (Entity (Arg)) = E_Discriminant
1676                then
1677                   Append_To (Args,
1678                     New_Reference_To (Discriminal (Entity (Arg)), Loc));
1679
1680                --  Case of access discriminants. We replace the reference
1681                --  to the type by a reference to the actual object
1682
1683 --     ??? why is this code deleted without comment
1684
1685 --               elsif Nkind (Arg) = N_Attribute_Reference
1686 --                 and then Is_Entity_Name (Prefix (Arg))
1687 --                 and then Is_Type (Entity (Prefix (Arg)))
1688 --               then
1689 --                  Append_To (Args,
1690 --                    Make_Attribute_Reference (Loc,
1691 --                      Prefix         => New_Copy (Prefix (Id_Ref)),
1692 --                      Attribute_Name => Name_Unrestricted_Access));
1693
1694                else
1695                   Append_To (Args, New_Copy (Arg));
1696                end if;
1697
1698                Next_Discriminant (Parent_Discr);
1699             end loop;
1700          end if;
1701
1702          Res :=
1703             New_List (
1704               Make_Procedure_Call_Statement (Loc,
1705                 Name => New_Occurrence_Of (Parent_Proc, Loc),
1706                 Parameter_Associations => Args));
1707
1708          return Res;
1709       end Build_Init_Call_Thru;
1710
1711       --------------------------
1712       -- Build_Init_Procedure --
1713       --------------------------
1714
1715       procedure Build_Init_Procedure is
1716          Body_Node             : Node_Id;
1717          Handled_Stmt_Node     : Node_Id;
1718          Parameters            : List_Id;
1719          Proc_Spec_Node        : Node_Id;
1720          Body_Stmts            : List_Id;
1721          Record_Extension_Node : Node_Id;
1722          Init_Tag              : Node_Id;
1723
1724       begin
1725          Body_Stmts := New_List;
1726          Body_Node := New_Node (N_Subprogram_Body, Loc);
1727
1728          Proc_Id :=
1729            Make_Defining_Identifier (Loc,
1730              Chars => Make_Init_Proc_Name (Rec_Type));
1731          Set_Ekind (Proc_Id, E_Procedure);
1732
1733          Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
1734          Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
1735
1736          Parameters := Init_Formals (Rec_Type);
1737          Append_List_To (Parameters,
1738            Build_Discriminant_Formals (Rec_Type, True));
1739
1740          --  For tagged types, we add a flag to indicate whether the routine
1741          --  is called to initialize a parent component in the init_proc of
1742          --  a type extension. If the flag is false, we do not set the tag
1743          --  because it has been set already in the extension.
1744
1745          if Is_Tagged_Type (Rec_Type)
1746            and then not Is_CPP_Class (Rec_Type)
1747          then
1748             Set_Tag :=
1749                   Make_Defining_Identifier (Loc, New_Internal_Name ('P'));
1750
1751             Append_To (Parameters,
1752               Make_Parameter_Specification (Loc,
1753                 Defining_Identifier => Set_Tag,
1754                 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
1755                 Expression => New_Occurrence_Of (Standard_True, Loc)));
1756          end if;
1757
1758          Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
1759          Set_Specification (Body_Node, Proc_Spec_Node);
1760          Set_Declarations (Body_Node, New_List);
1761
1762          if Parent_Subtype_Renaming_Discrims then
1763
1764             --  N is a Derived_Type_Definition that renames the parameters
1765             --  of the ancestor type.  We init it by expanding our discrims
1766             --  and call the ancestor _init_proc with a type-converted object
1767
1768             Append_List_To (Body_Stmts,
1769               Build_Init_Call_Thru (Parameters));
1770
1771          elsif Nkind (Type_Definition (N)) = N_Record_Definition then
1772             Build_Discriminant_Assignments (Body_Stmts);
1773
1774             if not Null_Present (Type_Definition (N)) then
1775                Append_List_To (Body_Stmts,
1776                  Build_Init_Statements (
1777                    Component_List (Type_Definition (N))));
1778             end if;
1779
1780          else
1781             --  N is a Derived_Type_Definition with a possible non-empty
1782             --  extension. The initialization of a type extension consists
1783             --  in the initialization of the components in the extension.
1784
1785             Build_Discriminant_Assignments (Body_Stmts);
1786
1787             Record_Extension_Node :=
1788               Record_Extension_Part (Type_Definition (N));
1789
1790             if not Null_Present (Record_Extension_Node) then
1791                declare
1792                   Stmts : constant List_Id :=
1793                             Build_Init_Statements (
1794                               Component_List (Record_Extension_Node));
1795
1796                begin
1797                   --  The parent field must be initialized first because
1798                   --  the offset of the new discriminants may depend on it
1799
1800                   Prepend_To (Body_Stmts, Remove_Head (Stmts));
1801                   Append_List_To (Body_Stmts, Stmts);
1802                end;
1803             end if;
1804          end if;
1805
1806          --  Add here the assignment to instantiate the Tag
1807
1808          --  The assignement corresponds to the code:
1809
1810          --     _Init._Tag := Typ'Tag;
1811
1812          --  Suppress the tag assignment when Java_VM because JVM tags are
1813          --  represented implicitly in objects.
1814
1815          if Is_Tagged_Type (Rec_Type)
1816            and then not Is_CPP_Class (Rec_Type)
1817            and then not Java_VM
1818          then
1819             Init_Tag :=
1820               Make_Assignment_Statement (Loc,
1821                 Name =>
1822                   Make_Selected_Component (Loc,
1823                     Prefix => Make_Identifier (Loc, Name_uInit),
1824                     Selector_Name =>
1825                       New_Reference_To (Tag_Component (Rec_Type), Loc)),
1826
1827                 Expression =>
1828                   New_Reference_To (Access_Disp_Table (Rec_Type), Loc));
1829
1830             --  The tag must be inserted before the assignments to other
1831             --  components,  because the initial value of the component may
1832             --  depend ot the tag (eg. through a dispatching operation on
1833             --  an access to the current type). The tag assignment is not done
1834             --  when initializing the parent component of a type extension,
1835             --  because in that case the tag is set in the extension.
1836             --  Extensions of imported C++ classes add a final complication,
1837             --  because we cannot inhibit tag setting in the constructor for
1838             --  the parent. In that case we insert the tag initialization
1839             --  after the calls to initialize the parent.
1840
1841             Init_Tag :=
1842               Make_If_Statement (Loc,
1843                 Condition => New_Occurrence_Of (Set_Tag, Loc),
1844                 Then_Statements => New_List (Init_Tag));
1845
1846             if not Is_CPP_Class (Etype (Rec_Type)) then
1847                Prepend_To (Body_Stmts, Init_Tag);
1848
1849             else
1850                declare
1851                   Nod : Node_Id := First (Body_Stmts);
1852
1853                begin
1854                   --  We assume the first init_proc call is for the parent
1855
1856                   while Present (Next (Nod))
1857                     and then (Nkind (Nod) /= N_Procedure_Call_Statement
1858                                or else not Is_Init_Proc (Name (Nod)))
1859                   loop
1860                      Nod := Next (Nod);
1861                   end loop;
1862
1863                   Insert_After (Nod, Init_Tag);
1864                end;
1865             end if;
1866          end if;
1867
1868          Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
1869          Set_Statements (Handled_Stmt_Node, Body_Stmts);
1870          Set_Exception_Handlers (Handled_Stmt_Node, No_List);
1871          Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
1872
1873          if not Debug_Generated_Code then
1874             Set_Debug_Info_Off (Proc_Id);
1875          end if;
1876
1877          --  Associate Init_Proc with type, and determine if the procedure
1878          --  is null (happens because of the Initialize_Scalars pragma case,
1879          --  where we have to generate a null procedure in case it is called
1880          --  by a client with Initialize_Scalars set). Such procedures have
1881          --  to be generated, but do not have to be called, so we mark them
1882          --  as null to suppress the call.
1883
1884          Set_Init_Proc (Rec_Type, Proc_Id);
1885
1886          if List_Length (Body_Stmts) = 1
1887            and then Nkind (First (Body_Stmts)) = N_Null_Statement
1888          then
1889             Set_Is_Null_Init_Proc (Proc_Id);
1890          end if;
1891       end Build_Init_Procedure;
1892
1893       ---------------------------
1894       -- Build_Init_Statements --
1895       ---------------------------
1896
1897       function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
1898          Check_List     : constant List_Id := New_List;
1899          Alt_List       : List_Id;
1900          Statement_List : List_Id;
1901          Stmts          : List_Id;
1902
1903          Per_Object_Constraint_Components : Boolean;
1904
1905          Decl     : Node_Id;
1906          Variant  : Node_Id;
1907
1908          Id  : Entity_Id;
1909          Typ : Entity_Id;
1910
1911          function Has_Access_Constraint (E : Entity_Id) return Boolean;
1912          --  Components with access discriminants that depend on the current
1913          --  instance must be initialized after all other components.
1914
1915          ---------------------------
1916          -- Has_Access_Constraint --
1917          ---------------------------
1918
1919          function Has_Access_Constraint (E : Entity_Id) return Boolean is
1920             Disc : Entity_Id;
1921             T    : constant Entity_Id := Etype (E);
1922
1923          begin
1924             if Has_Per_Object_Constraint (E)
1925               and then Has_Discriminants (T)
1926             then
1927                Disc := First_Discriminant (T);
1928                while Present (Disc) loop
1929                   if Is_Access_Type (Etype (Disc)) then
1930                      return True;
1931                   end if;
1932
1933                   Next_Discriminant (Disc);
1934                end loop;
1935
1936                return False;
1937             else
1938                return False;
1939             end if;
1940          end Has_Access_Constraint;
1941
1942       --  Start of processing for Build_Init_Statements
1943
1944       begin
1945          if Null_Present (Comp_List) then
1946             return New_List (Make_Null_Statement (Loc));
1947          end if;
1948
1949          Statement_List := New_List;
1950
1951          --  Loop through components, skipping pragmas, in 2 steps. The first
1952          --  step deals with regular components. The second step deals with
1953          --  components have per object constraints, and no explicit initia-
1954          --  lization.
1955
1956          Per_Object_Constraint_Components := False;
1957
1958          --  First step : regular components
1959
1960          Decl := First_Non_Pragma (Component_Items (Comp_List));
1961          while Present (Decl) loop
1962             Loc := Sloc (Decl);
1963             Build_Record_Checks
1964               (Subtype_Indication (Component_Definition (Decl)), Check_List);
1965
1966             Id := Defining_Identifier (Decl);
1967             Typ := Etype (Id);
1968
1969             if Has_Access_Constraint (Id)
1970               and then No (Expression (Decl))
1971             then
1972                --  Skip processing for now and ask for a second pass
1973
1974                Per_Object_Constraint_Components := True;
1975
1976             else
1977                --  Case of explicit initialization
1978
1979                if Present (Expression (Decl)) then
1980                   Stmts := Build_Assignment (Id, Expression (Decl));
1981
1982                --  Case of composite component with its own Init_Proc
1983
1984                elsif Has_Non_Null_Base_Init_Proc (Typ) then
1985                   Stmts :=
1986                     Build_Initialization_Call
1987                       (Loc,
1988                        Make_Selected_Component (Loc,
1989                          Prefix => Make_Identifier (Loc, Name_uInit),
1990                          Selector_Name => New_Occurrence_Of (Id, Loc)),
1991                        Typ,
1992                        True,
1993                        Rec_Type,
1994                        Discr_Map => Discr_Map);
1995
1996                --  Case of component needing simple initialization
1997
1998                elsif Component_Needs_Simple_Initialization (Typ) then
1999                   Stmts :=
2000                     Build_Assignment (Id, Get_Simple_Init_Val (Typ, Loc));
2001
2002                --  Nothing needed for this case
2003
2004                else
2005                   Stmts := No_List;
2006                end if;
2007
2008                if Present (Check_List) then
2009                   Append_List_To (Statement_List, Check_List);
2010                end if;
2011
2012                if Present (Stmts) then
2013
2014                   --  Add the initialization of the record controller before
2015                   --  the _Parent field is attached to it when the attachment
2016                   --  can occur. It does not work to simply initialize the
2017                   --  controller first: it must be initialized after the parent
2018                   --  if the parent holds discriminants that can be used
2019                   --  to compute the offset of the controller. We assume here
2020                   --  that the last statement of the initialization call is the
2021                   --  attachement of the parent (see Build_Initialization_Call)
2022
2023                   if Chars (Id) = Name_uController
2024                     and then Rec_Type /= Etype (Rec_Type)
2025                     and then Has_Controlled_Component (Etype (Rec_Type))
2026                     and then Has_New_Controlled_Component (Rec_Type)
2027                   then
2028                      Insert_List_Before (Last (Statement_List), Stmts);
2029                   else
2030                      Append_List_To (Statement_List, Stmts);
2031                   end if;
2032                end if;
2033             end if;
2034
2035             Next_Non_Pragma (Decl);
2036          end loop;
2037
2038          if Per_Object_Constraint_Components then
2039
2040             --  Second pass: components with per-object constraints
2041
2042             Decl := First_Non_Pragma (Component_Items (Comp_List));
2043
2044             while Present (Decl) loop
2045                Loc := Sloc (Decl);
2046                Id := Defining_Identifier (Decl);
2047                Typ := Etype (Id);
2048
2049                if Has_Access_Constraint (Id)
2050                  and then No (Expression (Decl))
2051                then
2052                   if Has_Non_Null_Base_Init_Proc (Typ) then
2053                      Append_List_To (Statement_List,
2054                        Build_Initialization_Call (Loc,
2055                          Make_Selected_Component (Loc,
2056                            Prefix => Make_Identifier (Loc, Name_uInit),
2057                            Selector_Name => New_Occurrence_Of (Id, Loc)),
2058                          Typ, True, Rec_Type, Discr_Map => Discr_Map));
2059
2060                   elsif Component_Needs_Simple_Initialization (Typ) then
2061                      Append_List_To (Statement_List,
2062                        Build_Assignment (Id, Get_Simple_Init_Val (Typ, Loc)));
2063                   end if;
2064                end if;
2065
2066                Next_Non_Pragma (Decl);
2067             end loop;
2068          end if;
2069
2070          --  Process the variant part
2071
2072          if Present (Variant_Part (Comp_List)) then
2073             Alt_List := New_List;
2074             Variant := First_Non_Pragma (Variants (Variant_Part (Comp_List)));
2075
2076             while Present (Variant) loop
2077                Loc := Sloc (Variant);
2078                Append_To (Alt_List,
2079                  Make_Case_Statement_Alternative (Loc,
2080                    Discrete_Choices =>
2081                      New_Copy_List (Discrete_Choices (Variant)),
2082                    Statements =>
2083                      Build_Init_Statements (Component_List (Variant))));
2084
2085                Next_Non_Pragma (Variant);
2086             end loop;
2087
2088             --  The expression of the case statement which is a reference
2089             --  to one of the discriminants is replaced by the appropriate
2090             --  formal parameter of the initialization procedure.
2091
2092             Append_To (Statement_List,
2093               Make_Case_Statement (Loc,
2094                 Expression =>
2095                   New_Reference_To (Discriminal (
2096                     Entity (Name (Variant_Part (Comp_List)))), Loc),
2097                 Alternatives => Alt_List));
2098          end if;
2099
2100          --  For a task record type, add the task create call and calls
2101          --  to bind any interrupt (signal) entries.
2102
2103          if Is_Task_Record_Type (Rec_Type) then
2104
2105             --  In the case of the restricted run time the ATCB has already
2106             --  been preallocated.
2107
2108             if Restricted_Profile then
2109                Append_To (Statement_List,
2110                  Make_Assignment_Statement (Loc,
2111                    Name => Make_Selected_Component (Loc,
2112                      Prefix => Make_Identifier (Loc, Name_uInit),
2113                      Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
2114                    Expression => Make_Attribute_Reference (Loc,
2115                      Prefix =>
2116                        Make_Selected_Component (Loc,
2117                          Prefix => Make_Identifier (Loc, Name_uInit),
2118                          Selector_Name =>
2119                            Make_Identifier (Loc, Name_uATCB)),
2120                      Attribute_Name => Name_Unchecked_Access)));
2121             end if;
2122
2123             Append_To (Statement_List, Make_Task_Create_Call (Rec_Type));
2124
2125             declare
2126                Task_Type : constant Entity_Id :=
2127                              Corresponding_Concurrent_Type (Rec_Type);
2128                Task_Decl : constant Node_Id := Parent (Task_Type);
2129                Task_Def  : constant Node_Id := Task_Definition (Task_Decl);
2130                Vis_Decl  : Node_Id;
2131                Ent       : Entity_Id;
2132
2133             begin
2134                if Present (Task_Def) then
2135                   Vis_Decl := First (Visible_Declarations (Task_Def));
2136                   while Present (Vis_Decl) loop
2137                      Loc := Sloc (Vis_Decl);
2138
2139                      if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
2140                         if Get_Attribute_Id (Chars (Vis_Decl)) =
2141                                                        Attribute_Address
2142                         then
2143                            Ent := Entity (Name (Vis_Decl));
2144
2145                            if Ekind (Ent) = E_Entry then
2146                               Append_To (Statement_List,
2147                                 Make_Procedure_Call_Statement (Loc,
2148                                   Name => New_Reference_To (
2149                                     RTE (RE_Bind_Interrupt_To_Entry), Loc),
2150                                   Parameter_Associations => New_List (
2151                                     Make_Selected_Component (Loc,
2152                                       Prefix =>
2153                                         Make_Identifier (Loc, Name_uInit),
2154                                       Selector_Name =>
2155                                         Make_Identifier (Loc, Name_uTask_Id)),
2156                                     Entry_Index_Expression (
2157                                       Loc, Ent, Empty, Task_Type),
2158                                     Expression (Vis_Decl))));
2159                            end if;
2160                         end if;
2161                      end if;
2162
2163                      Next (Vis_Decl);
2164                   end loop;
2165                end if;
2166             end;
2167          end if;
2168
2169          --  For a protected type, add statements generated by
2170          --  Make_Initialize_Protection.
2171
2172          if Is_Protected_Record_Type (Rec_Type) then
2173             Append_List_To (Statement_List,
2174               Make_Initialize_Protection (Rec_Type));
2175          end if;
2176
2177          --  If no initializations when generated for component declarations
2178          --  corresponding to this Statement_List, append a null statement
2179          --  to the Statement_List to make it a valid Ada tree.
2180
2181          if Is_Empty_List (Statement_List) then
2182             Append (New_Node (N_Null_Statement, Loc), Statement_List);
2183          end if;
2184
2185          return Statement_List;
2186
2187       exception
2188          when RE_Not_Available =>
2189          return Empty_List;
2190       end Build_Init_Statements;
2191
2192       -------------------------
2193       -- Build_Record_Checks --
2194       -------------------------
2195
2196       procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
2197          Subtype_Mark_Id : Entity_Id;
2198
2199       begin
2200          if Nkind (S) = N_Subtype_Indication then
2201             Find_Type (Subtype_Mark (S));
2202             Subtype_Mark_Id := Entity (Subtype_Mark (S));
2203
2204             --  Remaining processing depends on type
2205
2206             case Ekind (Subtype_Mark_Id) is
2207
2208                when Array_Kind =>
2209                   Constrain_Array (S, Check_List);
2210
2211                when others =>
2212                   null;
2213             end case;
2214          end if;
2215       end Build_Record_Checks;
2216
2217       -------------------------------------------
2218       -- Component_Needs_Simple_Initialization --
2219       -------------------------------------------
2220
2221       function Component_Needs_Simple_Initialization
2222         (T : Entity_Id) return Boolean
2223       is
2224       begin
2225          return
2226            Needs_Simple_Initialization (T)
2227              and then not Is_RTE (T, RE_Tag)
2228              and then not Is_RTE (T, RE_Vtable_Ptr);
2229       end Component_Needs_Simple_Initialization;
2230
2231       ---------------------
2232       -- Constrain_Array --
2233       ---------------------
2234
2235       procedure Constrain_Array
2236         (SI          : Node_Id;
2237          Check_List  : List_Id)
2238       is
2239          C                     : constant Node_Id := Constraint (SI);
2240          Number_Of_Constraints : Nat := 0;
2241          Index                 : Node_Id;
2242          S, T                  : Entity_Id;
2243
2244       begin
2245          T := Entity (Subtype_Mark (SI));
2246
2247          if Ekind (T) in Access_Kind then
2248             T := Designated_Type (T);
2249          end if;
2250
2251          S := First (Constraints (C));
2252
2253          while Present (S) loop
2254             Number_Of_Constraints := Number_Of_Constraints + 1;
2255             Next (S);
2256          end loop;
2257
2258          --  In either case, the index constraint must provide a discrete
2259          --  range for each index of the array type and the type of each
2260          --  discrete range must be the same as that of the corresponding
2261          --  index. (RM 3.6.1)
2262
2263          S := First (Constraints (C));
2264          Index := First_Index (T);
2265          Analyze (Index);
2266
2267          --  Apply constraints to each index type
2268
2269          for J in 1 .. Number_Of_Constraints loop
2270             Constrain_Index (Index, S, Check_List);
2271             Next (Index);
2272             Next (S);
2273          end loop;
2274
2275       end Constrain_Array;
2276
2277       ---------------------
2278       -- Constrain_Index --
2279       ---------------------
2280
2281       procedure Constrain_Index
2282         (Index        : Node_Id;
2283          S            : Node_Id;
2284          Check_List   : List_Id)
2285       is
2286          T : constant Entity_Id := Etype (Index);
2287
2288       begin
2289          if Nkind (S) = N_Range then
2290             Process_Range_Expr_In_Decl (S, T, Check_List);
2291          end if;
2292       end Constrain_Index;
2293
2294       --------------------------------------
2295       -- Parent_Subtype_Renaming_Discrims --
2296       --------------------------------------
2297
2298       function Parent_Subtype_Renaming_Discrims return Boolean is
2299          De : Entity_Id;
2300          Dp : Entity_Id;
2301
2302       begin
2303          if Base_Type (Pe) /= Pe then
2304             return False;
2305          end if;
2306
2307          if Etype (Pe) = Pe
2308            or else not Has_Discriminants (Pe)
2309            or else Is_Constrained (Pe)
2310            or else Is_Tagged_Type (Pe)
2311          then
2312             return False;
2313          end if;
2314
2315          --  If there are no explicit stored discriminants we have inherited
2316          --  the root type discriminants so far, so no renamings occurred.
2317
2318          if First_Discriminant (Pe) = First_Stored_Discriminant (Pe) then
2319             return False;
2320          end if;
2321
2322          --  Check if we have done some trivial renaming of the parent
2323          --  discriminants, i.e. someting like
2324          --
2325          --    type DT (X1,X2: int) is new PT (X1,X2);
2326
2327          De := First_Discriminant (Pe);
2328          Dp := First_Discriminant (Etype (Pe));
2329
2330          while Present (De) loop
2331             pragma Assert (Present (Dp));
2332
2333             if Corresponding_Discriminant (De) /= Dp then
2334                return True;
2335             end if;
2336
2337             Next_Discriminant (De);
2338             Next_Discriminant (Dp);
2339          end loop;
2340
2341          return Present (Dp);
2342       end Parent_Subtype_Renaming_Discrims;
2343
2344       ------------------------
2345       -- Requires_Init_Proc --
2346       ------------------------
2347
2348       function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
2349          Comp_Decl : Node_Id;
2350          Id        : Entity_Id;
2351          Typ       : Entity_Id;
2352
2353       begin
2354          --  Definitely do not need one if specifically suppressed
2355
2356          if Suppress_Init_Proc (Rec_Id) then
2357             return False;
2358          end if;
2359
2360          --  Otherwise we need to generate an initialization procedure if
2361          --  Is_CPP_Class is False and at least one of the following applies:
2362
2363          --  1. Discriminants are present, since they need to be initialized
2364          --     with the appropriate discriminant constraint expressions.
2365          --     However, the discriminant of an unchecked union does not
2366          --     count, since the discriminant is not present.
2367
2368          --  2. The type is a tagged type, since the implicit Tag component
2369          --     needs to be initialized with a pointer to the dispatch table.
2370
2371          --  3. The type contains tasks
2372
2373          --  4. One or more components has an initial value
2374
2375          --  5. One or more components is for a type which itself requires
2376          --     an initialization procedure.
2377
2378          --  6. One or more components is a type that requires simple
2379          --     initialization (see Needs_Simple_Initialization), except
2380          --     that types Tag and Vtable_Ptr are excluded, since fields
2381          --     of these types are initialized by other means.
2382
2383          --  7. The type is the record type built for a task type (since at
2384          --     the very least, Create_Task must be called)
2385
2386          --  8. The type is the record type built for a protected type (since
2387          --     at least Initialize_Protection must be called)
2388
2389          --  9. The type is marked as a public entity. The reason we add this
2390          --     case (even if none of the above apply) is to properly handle
2391          --     Initialize_Scalars. If a package is compiled without an IS
2392          --     pragma, and the client is compiled with an IS pragma, then
2393          --     the client will think an initialization procedure is present
2394          --     and call it, when in fact no such procedure is required, but
2395          --     since the call is generated, there had better be a routine
2396          --     at the other end of the call, even if it does nothing!)
2397
2398          --  Note: the reason we exclude the CPP_Class case is ???
2399
2400          if Is_CPP_Class (Rec_Id) then
2401             return False;
2402
2403          elsif not Restriction_Active (No_Initialize_Scalars)
2404            and then Is_Public (Rec_Id)
2405          then
2406             return True;
2407
2408          elsif (Has_Discriminants (Rec_Id)
2409                   and then not Is_Unchecked_Union (Rec_Id))
2410            or else Is_Tagged_Type (Rec_Id)
2411            or else Is_Concurrent_Record_Type (Rec_Id)
2412            or else Has_Task (Rec_Id)
2413          then
2414             return True;
2415          end if;
2416
2417          Id := First_Component (Rec_Id);
2418
2419          while Present (Id) loop
2420             Comp_Decl := Parent (Id);
2421             Typ := Etype (Id);
2422
2423             if Present (Expression (Comp_Decl))
2424               or else Has_Non_Null_Base_Init_Proc (Typ)
2425               or else Component_Needs_Simple_Initialization (Typ)
2426             then
2427                return True;
2428             end if;
2429
2430             Next_Component (Id);
2431          end loop;
2432
2433          return False;
2434       end Requires_Init_Proc;
2435
2436    --  Start of processing for Build_Record_Init_Proc
2437
2438    begin
2439       Rec_Type := Defining_Identifier (N);
2440
2441       --  This may be full declaration of a private type, in which case
2442       --  the visible entity is a record, and the private entity has been
2443       --  exchanged with it in the private part of the current package.
2444       --  The initialization procedure is built for the record type, which
2445       --  is retrievable from the private entity.
2446
2447       if Is_Incomplete_Or_Private_Type (Rec_Type) then
2448          Rec_Type := Underlying_Type (Rec_Type);
2449       end if;
2450
2451       --  If there are discriminants, build the discriminant map to replace
2452       --  discriminants by their discriminals in complex bound expressions.
2453       --  These only arise for the corresponding records of protected types.
2454
2455       if Is_Concurrent_Record_Type (Rec_Type)
2456         and then Has_Discriminants (Rec_Type)
2457       then
2458          declare
2459             Disc : Entity_Id;
2460
2461          begin
2462             Disc := First_Discriminant (Rec_Type);
2463
2464             while Present (Disc) loop
2465                Append_Elmt (Disc, Discr_Map);
2466                Append_Elmt (Discriminal (Disc), Discr_Map);
2467                Next_Discriminant (Disc);
2468             end loop;
2469          end;
2470       end if;
2471
2472       --  Derived types that have no type extension can use the initialization
2473       --  procedure of their parent and do not need a procedure of their own.
2474       --  This is only correct if there are no representation clauses for the
2475       --  type or its parent, and if the parent has in fact been frozen so
2476       --  that its initialization procedure exists.
2477
2478       if Is_Derived_Type (Rec_Type)
2479         and then not Is_Tagged_Type (Rec_Type)
2480         and then not Is_Unchecked_Union (Rec_Type)
2481         and then not Has_New_Non_Standard_Rep (Rec_Type)
2482         and then not Parent_Subtype_Renaming_Discrims
2483         and then Has_Non_Null_Base_Init_Proc (Etype (Rec_Type))
2484       then
2485          Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
2486
2487       --  Otherwise if we need an initialization procedure, then build one,
2488       --  mark it as public and inlinable and as having a completion.
2489
2490       elsif Requires_Init_Proc (Rec_Type)
2491         or else Is_Unchecked_Union (Rec_Type)
2492       then
2493          Build_Init_Procedure;
2494          Set_Is_Public (Proc_Id, Is_Public (Pe));
2495
2496          --  The initialization of protected records is not worth inlining.
2497          --  In addition, when compiled for another unit for inlining purposes,
2498          --  it may make reference to entities that have not been elaborated
2499          --  yet. The initialization of controlled records contains a nested
2500          --  clean-up procedure that makes it impractical to inline as well,
2501          --  and leads to undefined symbols if inlined in a different unit.
2502          --  Similar considerations apply to task types.
2503
2504          if not Is_Concurrent_Type (Rec_Type)
2505            and then not Has_Task (Rec_Type)
2506            and then not Controlled_Type (Rec_Type)
2507          then
2508             Set_Is_Inlined  (Proc_Id);
2509          end if;
2510
2511          Set_Is_Internal    (Proc_Id);
2512          Set_Has_Completion (Proc_Id);
2513
2514          if not Debug_Generated_Code then
2515             Set_Debug_Info_Off (Proc_Id);
2516          end if;
2517       end if;
2518    end Build_Record_Init_Proc;
2519
2520    ----------------------------
2521    -- Build_Slice_Assignment --
2522    ----------------------------
2523
2524    --  Generates the following subprogram:
2525
2526    --    procedure Assign
2527    --     (Source,   Target   : Array_Type,
2528    --      Left_Lo,  Left_Hi, Right_Lo, Right_Hi : Index;
2529    --      Rev :     Boolean)
2530    --    is
2531    --       Li1 : Index;
2532    --       Ri1 : Index;
2533
2534    --    begin
2535    --       if Rev  then
2536    --          Li1 := Left_Hi;
2537    --          Ri1 := Right_Hi;
2538    --       else
2539    --          Li1 := Left_Lo;
2540    --          Ri1 := Right_Lo;
2541    --       end if;
2542
2543    --       loop
2544    --             if Rev then
2545    --                exit when Li1 < Left_Lo;
2546    --             else
2547    --                exit when Li1 > Left_Hi;
2548    --             end if;
2549
2550    --             Target (Li1) := Source (Ri1);
2551
2552    --             if Rev then
2553    --                Li1 := Index'pred (Li1);
2554    --                Ri1 := Index'pred (Ri1);
2555    --             else
2556    --                Li1 := Index'succ (Li1);
2557    --                Ri1 := Index'succ (Ri1);
2558    --             end if;
2559    --       end loop;
2560    --    end Assign;
2561
2562    procedure Build_Slice_Assignment (Typ : Entity_Id) is
2563       Loc   : constant Source_Ptr := Sloc (Typ);
2564       Index : constant Entity_Id  := Base_Type (Etype (First_Index (Typ)));
2565
2566       --  Build formal parameters of procedure
2567
2568       Larray   : constant Entity_Id :=
2569                    Make_Defining_Identifier
2570                      (Loc, Chars => New_Internal_Name ('A'));
2571       Rarray   : constant Entity_Id :=
2572                    Make_Defining_Identifier
2573                      (Loc, Chars => New_Internal_Name ('R'));
2574       Left_Lo  : constant Entity_Id :=
2575                    Make_Defining_Identifier
2576                      (Loc, Chars => New_Internal_Name ('L'));
2577       Left_Hi  : constant Entity_Id :=
2578                    Make_Defining_Identifier
2579                      (Loc, Chars => New_Internal_Name ('L'));
2580       Right_Lo : constant Entity_Id :=
2581                    Make_Defining_Identifier
2582                      (Loc, Chars => New_Internal_Name ('R'));
2583       Right_Hi : constant Entity_Id :=
2584                    Make_Defining_Identifier
2585                      (Loc, Chars => New_Internal_Name ('R'));
2586       Rev      : constant Entity_Id :=
2587                    Make_Defining_Identifier
2588                      (Loc, Chars => New_Internal_Name ('D'));
2589       Proc_Name : constant Entity_Id :=
2590                     Make_Defining_Identifier (Loc,
2591                       Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
2592
2593       Lnn : constant Entity_Id :=
2594               Make_Defining_Identifier (Loc, New_Internal_Name ('L'));
2595       Rnn : constant Entity_Id :=
2596               Make_Defining_Identifier (Loc, New_Internal_Name ('R'));
2597       --  Subscripts for left and right sides
2598
2599       Decls : List_Id;
2600       Loops : Node_Id;
2601       Stats : List_Id;
2602
2603    begin
2604       --  Build declarations for indices
2605
2606       Decls := New_List;
2607
2608       Append_To (Decls,
2609          Make_Object_Declaration (Loc,
2610            Defining_Identifier => Lnn,
2611            Object_Definition  =>
2612              New_Occurrence_Of (Index, Loc)));
2613
2614       Append_To (Decls,
2615         Make_Object_Declaration (Loc,
2616           Defining_Identifier => Rnn,
2617           Object_Definition  =>
2618             New_Occurrence_Of (Index, Loc)));
2619
2620       Stats := New_List;
2621
2622       --  Build initializations for indices
2623
2624       declare
2625          F_Init : constant List_Id := New_List;
2626          B_Init : constant List_Id := New_List;
2627
2628       begin
2629          Append_To (F_Init,
2630            Make_Assignment_Statement (Loc,
2631              Name => New_Occurrence_Of (Lnn, Loc),
2632              Expression => New_Occurrence_Of (Left_Lo, Loc)));
2633
2634          Append_To (F_Init,
2635            Make_Assignment_Statement (Loc,
2636              Name => New_Occurrence_Of (Rnn, Loc),
2637              Expression => New_Occurrence_Of (Right_Lo, Loc)));
2638
2639          Append_To (B_Init,
2640            Make_Assignment_Statement (Loc,
2641              Name => New_Occurrence_Of (Lnn, Loc),
2642              Expression => New_Occurrence_Of (Left_Hi, Loc)));
2643
2644          Append_To (B_Init,
2645            Make_Assignment_Statement (Loc,
2646              Name => New_Occurrence_Of (Rnn, Loc),
2647              Expression => New_Occurrence_Of (Right_Hi, Loc)));
2648
2649          Append_To (Stats,
2650            Make_If_Statement (Loc,
2651              Condition => New_Occurrence_Of (Rev, Loc),
2652              Then_Statements => B_Init,
2653              Else_Statements => F_Init));
2654       end;
2655
2656       --  Now construct the assignment statement
2657
2658       Loops :=
2659         Make_Loop_Statement (Loc,
2660           Statements => New_List (
2661             Make_Assignment_Statement (Loc,
2662               Name =>
2663                 Make_Indexed_Component (Loc,
2664                   Prefix => New_Occurrence_Of (Larray, Loc),
2665                   Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
2666               Expression =>
2667                 Make_Indexed_Component (Loc,
2668                   Prefix => New_Occurrence_Of (Rarray, Loc),
2669                   Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
2670           End_Label  => Empty);
2671
2672       --  Build exit condition.
2673
2674       declare
2675          F_Ass : constant List_Id := New_List;
2676          B_Ass : constant List_Id := New_List;
2677
2678       begin
2679          Append_To (F_Ass,
2680            Make_Exit_Statement (Loc,
2681              Condition =>
2682                Make_Op_Gt (Loc,
2683                  Left_Opnd  => New_Occurrence_Of (Lnn, Loc),
2684                  Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
2685
2686          Append_To (B_Ass,
2687            Make_Exit_Statement (Loc,
2688              Condition =>
2689                Make_Op_Lt (Loc,
2690                  Left_Opnd  => New_Occurrence_Of (Lnn, Loc),
2691                  Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
2692
2693          Prepend_To (Statements (Loops),
2694            Make_If_Statement (Loc,
2695              Condition       => New_Occurrence_Of (Rev, Loc),
2696              Then_Statements => B_Ass,
2697              Else_Statements => F_Ass));
2698       end;
2699
2700       --  Build the increment/decrement statements
2701
2702       declare
2703          F_Ass : constant List_Id := New_List;
2704          B_Ass : constant List_Id := New_List;
2705
2706       begin
2707          Append_To (F_Ass,
2708            Make_Assignment_Statement (Loc,
2709              Name => New_Occurrence_Of (Lnn, Loc),
2710              Expression =>
2711                Make_Attribute_Reference (Loc,
2712                  Prefix =>
2713                    New_Occurrence_Of (Index, Loc),
2714                  Attribute_Name => Name_Succ,
2715                  Expressions => New_List (
2716                    New_Occurrence_Of (Lnn, Loc)))));
2717
2718          Append_To (F_Ass,
2719            Make_Assignment_Statement (Loc,
2720              Name => New_Occurrence_Of (Rnn, Loc),
2721              Expression =>
2722                Make_Attribute_Reference (Loc,
2723                  Prefix =>
2724                    New_Occurrence_Of (Index, Loc),
2725                  Attribute_Name => Name_Succ,
2726                  Expressions => New_List (
2727                    New_Occurrence_Of (Rnn, Loc)))));
2728
2729          Append_To (B_Ass,
2730            Make_Assignment_Statement (Loc,
2731              Name => New_Occurrence_Of (Lnn, Loc),
2732              Expression =>
2733                Make_Attribute_Reference (Loc,
2734                  Prefix =>
2735                    New_Occurrence_Of (Index, Loc),
2736                  Attribute_Name => Name_Pred,
2737                    Expressions => New_List (
2738                      New_Occurrence_Of (Lnn, Loc)))));
2739
2740          Append_To (B_Ass,
2741            Make_Assignment_Statement (Loc,
2742              Name => New_Occurrence_Of (Rnn, Loc),
2743              Expression =>
2744                Make_Attribute_Reference (Loc,
2745                  Prefix =>
2746                    New_Occurrence_Of (Index, Loc),
2747                  Attribute_Name => Name_Pred,
2748                  Expressions => New_List (
2749                    New_Occurrence_Of (Rnn, Loc)))));
2750
2751          Append_To (Statements (Loops),
2752            Make_If_Statement (Loc,
2753              Condition => New_Occurrence_Of (Rev, Loc),
2754              Then_Statements => B_Ass,
2755              Else_Statements => F_Ass));
2756       end;
2757
2758       Append_To (Stats, Loops);
2759
2760       declare
2761          Spec    : Node_Id;
2762          Formals : List_Id := New_List;
2763
2764       begin
2765          Formals := New_List (
2766            Make_Parameter_Specification (Loc,
2767              Defining_Identifier => Larray,
2768              Out_Present => True,
2769              Parameter_Type =>
2770                New_Reference_To (Base_Type (Typ), Loc)),
2771
2772            Make_Parameter_Specification (Loc,
2773              Defining_Identifier => Rarray,
2774              Parameter_Type =>
2775                New_Reference_To (Base_Type (Typ), Loc)),
2776
2777            Make_Parameter_Specification (Loc,
2778              Defining_Identifier => Left_Lo,
2779              Parameter_Type =>
2780                New_Reference_To (Index, Loc)),
2781
2782            Make_Parameter_Specification (Loc,
2783              Defining_Identifier => Left_Hi,
2784              Parameter_Type =>
2785                New_Reference_To (Index, Loc)),
2786
2787            Make_Parameter_Specification (Loc,
2788              Defining_Identifier => Right_Lo,
2789              Parameter_Type =>
2790                New_Reference_To (Index, Loc)),
2791
2792            Make_Parameter_Specification (Loc,
2793              Defining_Identifier => Right_Hi,
2794              Parameter_Type =>
2795                New_Reference_To (Index, Loc)));
2796
2797          Append_To (Formals,
2798            Make_Parameter_Specification (Loc,
2799              Defining_Identifier => Rev,
2800              Parameter_Type =>
2801                New_Reference_To (Standard_Boolean, Loc)));
2802
2803          Spec :=
2804            Make_Procedure_Specification (Loc,
2805              Defining_Unit_Name       => Proc_Name,
2806              Parameter_Specifications => Formals);
2807
2808          Discard_Node (
2809            Make_Subprogram_Body (Loc,
2810              Specification              => Spec,
2811              Declarations               => Decls,
2812              Handled_Statement_Sequence =>
2813                Make_Handled_Sequence_Of_Statements (Loc,
2814                  Statements => Stats)));
2815       end;
2816
2817       Set_TSS (Typ, Proc_Name);
2818       Set_Is_Pure (Proc_Name);
2819    end Build_Slice_Assignment;
2820
2821    ------------------------------------
2822    -- Build_Variant_Record_Equality --
2823    ------------------------------------
2824
2825    --  Generates:
2826
2827    --    function _Equality (X, Y : T) return Boolean is
2828    --    begin
2829    --       --  Compare discriminants
2830
2831    --       if False or else X.D1 /= Y.D1 or else X.D2 /= Y.D2 then
2832    --          return False;
2833    --       end if;
2834
2835    --       --  Compare components
2836
2837    --       if False or else X.C1 /= Y.C1 or else X.C2 /= Y.C2 then
2838    --          return False;
2839    --       end if;
2840
2841    --       --  Compare variant part
2842
2843    --       case X.D1 is
2844    --          when V1 =>
2845    --             if False or else X.C2 /= Y.C2 or else X.C3 /= Y.C3 then
2846    --                return False;
2847    --             end if;
2848    --          ...
2849    --          when Vn =>
2850    --             if False or else X.Cn /= Y.Cn then
2851    --                return False;
2852    --             end if;
2853    --       end case;
2854    --       return True;
2855    --    end _Equality;
2856
2857    procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
2858       Loc   : constant Source_Ptr := Sloc (Typ);
2859
2860       F : constant Entity_Id :=
2861             Make_Defining_Identifier (Loc,
2862               Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
2863
2864       X : constant Entity_Id :=
2865            Make_Defining_Identifier (Loc,
2866              Chars => Name_X);
2867
2868       Y : constant Entity_Id :=
2869             Make_Defining_Identifier (Loc,
2870               Chars => Name_Y);
2871
2872       Def   : constant Node_Id := Parent (Typ);
2873       Comps : constant Node_Id := Component_List (Type_Definition (Def));
2874       Stmts : constant List_Id := New_List;
2875       Pspecs : constant List_Id := New_List;
2876
2877    begin
2878       --  Derived Unchecked_Union types no longer inherit the equality function
2879       --  of their parent.
2880
2881       if Is_Derived_Type (Typ)
2882         and then not Is_Unchecked_Union (Typ)
2883         and then not Has_New_Non_Standard_Rep (Typ)
2884       then
2885          declare
2886             Parent_Eq : constant Entity_Id :=
2887                           TSS (Root_Type (Typ), TSS_Composite_Equality);
2888
2889          begin
2890             if Present (Parent_Eq) then
2891                Copy_TSS (Parent_Eq, Typ);
2892                return;
2893             end if;
2894          end;
2895       end if;
2896
2897       Discard_Node (
2898         Make_Subprogram_Body (Loc,
2899           Specification =>
2900             Make_Function_Specification (Loc,
2901               Defining_Unit_Name       => F,
2902               Parameter_Specifications => Pspecs,
2903               Subtype_Mark => New_Reference_To (Standard_Boolean, Loc)),
2904           Declarations               => New_List,
2905           Handled_Statement_Sequence =>
2906             Make_Handled_Sequence_Of_Statements (Loc,
2907               Statements => Stmts)));
2908
2909       Append_To (Pspecs,
2910         Make_Parameter_Specification (Loc,
2911           Defining_Identifier => X,
2912           Parameter_Type      => New_Reference_To (Typ, Loc)));
2913
2914       Append_To (Pspecs,
2915         Make_Parameter_Specification (Loc,
2916           Defining_Identifier => Y,
2917           Parameter_Type      => New_Reference_To (Typ, Loc)));
2918
2919       --  Unchecked_Unions require additional machinery to support equality.
2920       --  Two extra parameters (A and B) are added to the equality function
2921       --  parameter list in order to capture the inferred values of the
2922       --  discriminants in later calls.
2923
2924       if Is_Unchecked_Union (Typ) then
2925          declare
2926             Discr_Type : constant Node_Id := Etype (First_Discriminant (Typ));
2927
2928             A : constant Node_Id :=
2929                   Make_Defining_Identifier (Loc,
2930                     Chars => Name_A);
2931
2932             B : constant Node_Id :=
2933                   Make_Defining_Identifier (Loc,
2934                     Chars => Name_B);
2935
2936          begin
2937             --  Add A and B to the parameter list
2938
2939             Append_To (Pspecs,
2940               Make_Parameter_Specification (Loc,
2941                 Defining_Identifier => A,
2942                 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
2943
2944             Append_To (Pspecs,
2945               Make_Parameter_Specification (Loc,
2946                 Defining_Identifier => B,
2947                 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
2948
2949             --  Generate the following header code to compare the inferred
2950             --  discriminants:
2951
2952             --  if a /= b then
2953             --     return False;
2954             --  end if;
2955
2956             Append_To (Stmts,
2957               Make_If_Statement (Loc,
2958                 Condition =>
2959                   Make_Op_Ne (Loc,
2960                     Left_Opnd => New_Reference_To (A, Loc),
2961                     Right_Opnd => New_Reference_To (B, Loc)),
2962                 Then_Statements => New_List (
2963                   Make_Return_Statement (Loc,
2964                     Expression => New_Occurrence_Of (Standard_False, Loc)))));
2965
2966             --  Generate component-by-component comparison. Note that we must
2967             --  propagate one of the inferred discriminant formals to act as
2968             --  the case statement switch.
2969
2970             Append_List_To (Stmts,
2971               Make_Eq_Case (Typ, Comps, A));
2972
2973          end;
2974
2975       --  Normal case (not unchecked union)
2976
2977       else
2978          Append_To (Stmts,
2979            Make_Eq_If (Typ,
2980              Discriminant_Specifications (Def)));
2981
2982          Append_List_To (Stmts,
2983            Make_Eq_Case (Typ, Comps));
2984       end if;
2985
2986       Append_To (Stmts,
2987         Make_Return_Statement (Loc,
2988           Expression => New_Reference_To (Standard_True, Loc)));
2989
2990       Set_TSS (Typ, F);
2991       Set_Is_Pure (F);
2992
2993       if not Debug_Generated_Code then
2994          Set_Debug_Info_Off (F);
2995       end if;
2996    end Build_Variant_Record_Equality;
2997
2998    -----------------------------
2999    -- Check_Stream_Attributes --
3000    -----------------------------
3001
3002    procedure Check_Stream_Attributes (Typ : Entity_Id) is
3003       Comp      : Entity_Id;
3004       Par       : constant Entity_Id := Root_Type (Base_Type (Typ));
3005       Par_Read  : constant Boolean   := Present (TSS (Par, TSS_Stream_Read));
3006       Par_Write : constant Boolean   := Present (TSS (Par, TSS_Stream_Write));
3007
3008    begin
3009       if Par_Read or else Par_Write then
3010          Comp := First_Component (Typ);
3011          while Present (Comp) loop
3012             if Comes_From_Source (Comp)
3013               and then  Original_Record_Component (Comp) = Comp
3014               and then Is_Limited_Type (Etype (Comp))
3015             then
3016                if (Par_Read and then
3017                      No (TSS (Base_Type (Etype (Comp)), TSS_Stream_Read)))
3018                  or else
3019                   (Par_Write and then
3020                      No (TSS (Base_Type (Etype (Comp)), TSS_Stream_Write)))
3021                then
3022                   Error_Msg_N
3023                     ("|component must have Stream attribute",
3024                        Parent (Comp));
3025                end if;
3026             end if;
3027
3028             Next_Component (Comp);
3029          end loop;
3030       end if;
3031    end Check_Stream_Attributes;
3032
3033    -----------------------------
3034    -- Expand_Record_Extension --
3035    -----------------------------
3036
3037    --  Add a field _parent at the beginning of the record extension. This is
3038    --  used to implement inheritance. Here are some examples of expansion:
3039
3040    --  1. no discriminants
3041    --      type T2 is new T1 with null record;
3042    --   gives
3043    --      type T2 is new T1 with record
3044    --        _Parent : T1;
3045    --      end record;
3046
3047    --  2. renamed discriminants
3048    --    type T2 (B, C : Int) is new T1 (A => B) with record
3049    --       _Parent : T1 (A => B);
3050    --       D : Int;
3051    --    end;
3052
3053    --  3. inherited discriminants
3054    --    type T2 is new T1 with record -- discriminant A inherited
3055    --       _Parent : T1 (A);
3056    --       D : Int;
3057    --    end;
3058
3059    procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
3060       Indic        : constant Node_Id    := Subtype_Indication (Def);
3061       Loc          : constant Source_Ptr := Sloc (Def);
3062       Rec_Ext_Part : Node_Id             := Record_Extension_Part (Def);
3063       Par_Subtype  : Entity_Id;
3064       Comp_List    : Node_Id;
3065       Comp_Decl    : Node_Id;
3066       Parent_N     : Node_Id;
3067       D            : Entity_Id;
3068       List_Constr  : constant List_Id    := New_List;
3069
3070    begin
3071       --  Expand_Record_Extension is called directly from the semantics, so
3072       --  we must check to see whether expansion is active before proceeding
3073
3074       if not Expander_Active then
3075          return;
3076       end if;
3077
3078       --  This may be a derivation of an untagged private type whose full
3079       --  view is tagged, in which case the Derived_Type_Definition has no
3080       --  extension part. Build an empty one now.
3081
3082       if No (Rec_Ext_Part) then
3083          Rec_Ext_Part :=
3084            Make_Record_Definition (Loc,
3085              End_Label      => Empty,
3086              Component_List => Empty,
3087              Null_Present   => True);
3088
3089          Set_Record_Extension_Part (Def, Rec_Ext_Part);
3090          Mark_Rewrite_Insertion (Rec_Ext_Part);
3091       end if;
3092
3093       Comp_List := Component_List (Rec_Ext_Part);
3094
3095       Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
3096
3097       --  If the derived type inherits its discriminants the type of the
3098       --  _parent field must be constrained by the inherited discriminants
3099
3100       if Has_Discriminants (T)
3101         and then Nkind (Indic) /= N_Subtype_Indication
3102         and then not Is_Constrained (Entity (Indic))
3103       then
3104          D := First_Discriminant (T);
3105          while Present (D) loop
3106             Append_To (List_Constr, New_Occurrence_Of (D, Loc));
3107             Next_Discriminant (D);
3108          end loop;
3109
3110          Par_Subtype :=
3111            Process_Subtype (
3112              Make_Subtype_Indication (Loc,
3113                Subtype_Mark => New_Reference_To (Entity (Indic), Loc),
3114                Constraint   =>
3115                  Make_Index_Or_Discriminant_Constraint (Loc,
3116                    Constraints => List_Constr)),
3117              Def);
3118
3119       --  Otherwise the original subtype_indication is just what is needed
3120
3121       else
3122          Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
3123       end if;
3124
3125       Set_Parent_Subtype (T, Par_Subtype);
3126
3127       Comp_Decl :=
3128         Make_Component_Declaration (Loc,
3129           Defining_Identifier => Parent_N,
3130           Component_Definition =>
3131             Make_Component_Definition (Loc,
3132               Aliased_Present => False,
3133               Subtype_Indication => New_Reference_To (Par_Subtype, Loc)));
3134
3135       if Null_Present (Rec_Ext_Part) then
3136          Set_Component_List (Rec_Ext_Part,
3137            Make_Component_List (Loc,
3138              Component_Items => New_List (Comp_Decl),
3139              Variant_Part => Empty,
3140              Null_Present => False));
3141          Set_Null_Present (Rec_Ext_Part, False);
3142
3143       elsif Null_Present (Comp_List)
3144         or else Is_Empty_List (Component_Items (Comp_List))
3145       then
3146          Set_Component_Items (Comp_List, New_List (Comp_Decl));
3147          Set_Null_Present (Comp_List, False);
3148
3149       else
3150          Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
3151       end if;
3152
3153       Analyze (Comp_Decl);
3154    end Expand_Record_Extension;
3155
3156    ------------------------------------
3157    -- Expand_N_Full_Type_Declaration --
3158    ------------------------------------
3159
3160    procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
3161       Def_Id : constant Entity_Id := Defining_Identifier (N);
3162       B_Id   : constant Entity_Id := Base_Type (Def_Id);
3163       Par_Id : Entity_Id;
3164       FN     : Node_Id;
3165
3166    begin
3167       if Is_Access_Type (Def_Id) then
3168
3169          --  Anonymous access types are created for the components of the
3170          --  record parameter for an entry declaration.  No master is created
3171          --  for such a type.
3172
3173          if Has_Task (Designated_Type (Def_Id))
3174            and then Comes_From_Source (N)
3175          then
3176             Build_Master_Entity (Def_Id);
3177             Build_Master_Renaming (Parent (Def_Id), Def_Id);
3178
3179          --  Create a class-wide master because a Master_Id must be generated
3180          --  for access-to-limited-class-wide types, whose root may be extended
3181          --  with task components.
3182
3183          elsif Is_Class_Wide_Type (Designated_Type (Def_Id))
3184            and then Is_Limited_Type (Designated_Type (Def_Id))
3185            and then Tasking_Allowed
3186
3187             --  Don't create a class-wide master for types whose convention is
3188             --  Java since these types cannot embed Ada tasks anyway. Note that
3189             --  the following test cannot catch the following case:
3190             --
3191             --      package java.lang.Object is
3192             --         type Typ is tagged limited private;
3193             --         type Ref is access all Typ'Class;
3194             --      private
3195             --         type Typ is tagged limited ...;
3196             --         pragma Convention (Typ, Java)
3197             --      end;
3198             --
3199             --  Because the convention appears after we have done the
3200             --  processing for type Ref.
3201
3202            and then Convention (Designated_Type (Def_Id)) /= Convention_Java
3203          then
3204             Build_Class_Wide_Master (Def_Id);
3205
3206          elsif Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
3207             Expand_Access_Protected_Subprogram_Type (N);
3208          end if;
3209
3210       elsif Has_Task (Def_Id) then
3211          Expand_Previous_Access_Type (Def_Id);
3212       end if;
3213
3214       Par_Id := Etype (B_Id);
3215
3216       --  The parent type is private then we need to inherit
3217       --  any TSS operations from the full view.
3218
3219       if Ekind (Par_Id) in Private_Kind
3220         and then Present (Full_View (Par_Id))
3221       then
3222          Par_Id := Base_Type (Full_View (Par_Id));
3223       end if;
3224
3225       if Nkind (Type_Definition (Original_Node (N)))
3226          = N_Derived_Type_Definition
3227         and then not Is_Tagged_Type (Def_Id)
3228         and then Present (Freeze_Node (Par_Id))
3229         and then Present (TSS_Elist (Freeze_Node (Par_Id)))
3230       then
3231          Ensure_Freeze_Node (B_Id);
3232          FN :=  Freeze_Node (B_Id);
3233
3234          if No (TSS_Elist (FN)) then
3235             Set_TSS_Elist (FN, New_Elmt_List);
3236          end if;
3237
3238          declare
3239             T_E   : constant Elist_Id := TSS_Elist (FN);
3240             Elmt  : Elmt_Id;
3241
3242          begin
3243             Elmt  := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
3244
3245             while Present (Elmt) loop
3246                if Chars (Node (Elmt)) /= Name_uInit then
3247                   Append_Elmt (Node (Elmt), T_E);
3248                end if;
3249
3250                Next_Elmt (Elmt);
3251             end loop;
3252
3253             --  If the derived type itself is private with a full view, then
3254             --  associate the full view with the inherited TSS_Elist as well.
3255
3256             if Ekind (B_Id) in Private_Kind
3257               and then Present (Full_View (B_Id))
3258             then
3259                Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
3260                Set_TSS_Elist
3261                  (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
3262             end if;
3263          end;
3264       end if;
3265    end Expand_N_Full_Type_Declaration;
3266
3267    ---------------------------------
3268    -- Expand_N_Object_Declaration --
3269    ---------------------------------
3270
3271    --  First we do special processing for objects of a tagged type where this
3272    --  is the point at which the type is frozen. The creation of the dispatch
3273    --  table and the initialization procedure have to be deferred to this
3274    --  point, since we reference previously declared primitive subprograms.
3275
3276    --  For all types, we call an initialization procedure if there is one
3277
3278    procedure Expand_N_Object_Declaration (N : Node_Id) is
3279       Def_Id  : constant Entity_Id  := Defining_Identifier (N);
3280       Typ     : constant Entity_Id  := Etype (Def_Id);
3281       Loc     : constant Source_Ptr := Sloc (N);
3282       Expr    : constant Node_Id    := Expression (N);
3283       New_Ref : Node_Id;
3284       Id_Ref  : Node_Id;
3285       Expr_Q  : Node_Id;
3286
3287    begin
3288       --  Don't do anything for deferred constants. All proper actions will
3289       --  be expanded during the full declaration.
3290
3291       if No (Expr) and Constant_Present (N) then
3292          return;
3293       end if;
3294
3295       --  Make shared memory routines for shared passive variable
3296
3297       if Is_Shared_Passive (Def_Id) then
3298          Make_Shared_Var_Procs (N);
3299       end if;
3300
3301       --  If tasks being declared, make sure we have an activation chain
3302       --  defined for the tasks (has no effect if we already have one), and
3303       --  also that a Master variable is established and that the appropriate
3304       --  enclosing construct is established as a task master.
3305
3306       if Has_Task (Typ) then
3307          Build_Activation_Chain_Entity (N);
3308          Build_Master_Entity (Def_Id);
3309       end if;
3310
3311       --  Default initialization required, and no expression present
3312
3313       if No (Expr) then
3314
3315          --  Expand Initialize call for controlled objects.  One may wonder why
3316          --  the Initialize Call is not done in the regular Init procedure
3317          --  attached to the record type. That's because the init procedure is
3318          --  recursively called on each component, including _Parent, thus the
3319          --  Init call for a controlled object would generate not only one
3320          --  Initialize call as it is required but one for each ancestor of
3321          --  its type. This processing is suppressed if No_Initialization set.
3322
3323          if not Controlled_Type (Typ)
3324            or else No_Initialization (N)
3325          then
3326             null;
3327
3328          elsif not Abort_Allowed
3329            or else not Comes_From_Source (N)
3330          then
3331             Insert_Actions_After (N,
3332               Make_Init_Call (
3333                 Ref         => New_Occurrence_Of (Def_Id, Loc),
3334                 Typ         => Base_Type (Typ),
3335                 Flist_Ref   => Find_Final_List (Def_Id),
3336                 With_Attach => Make_Integer_Literal (Loc, 1)));
3337
3338          --  Abort allowed
3339
3340          else
3341             --  We need to protect the initialize call
3342
3343             --  begin
3344             --     Defer_Abort.all;
3345             --     Initialize (...);
3346             --  at end
3347             --     Undefer_Abort.all;
3348             --  end;
3349
3350             --  ??? this won't protect the initialize call for controlled
3351             --  components which are part of the init proc, so this block
3352             --  should probably also contain the call to _init_proc but this
3353             --  requires some code reorganization...
3354
3355             declare
3356                L   : constant List_Id :=
3357                       Make_Init_Call (
3358                         Ref         => New_Occurrence_Of (Def_Id, Loc),
3359                         Typ         => Base_Type (Typ),
3360                         Flist_Ref   => Find_Final_List (Def_Id),
3361                         With_Attach => Make_Integer_Literal (Loc, 1));
3362
3363                Blk : constant Node_Id :=
3364                  Make_Block_Statement (Loc,
3365                    Handled_Statement_Sequence =>
3366                      Make_Handled_Sequence_Of_Statements (Loc, L));
3367
3368             begin
3369                Prepend_To (L, Build_Runtime_Call (Loc, RE_Abort_Defer));
3370                Set_At_End_Proc (Handled_Statement_Sequence (Blk),
3371                  New_Occurrence_Of (RTE (RE_Abort_Undefer_Direct), Loc));
3372                Insert_Actions_After (N, New_List (Blk));
3373                Expand_At_End_Handler
3374                  (Handled_Statement_Sequence (Blk), Entity (Identifier (Blk)));
3375             end;
3376          end if;
3377
3378          --  Call type initialization procedure if there is one. We build the
3379          --  call and put it immediately after the object declaration, so that
3380          --  it will be expanded in the usual manner. Note that this will
3381          --  result in proper handling of defaulted discriminants. The call
3382          --  to the Init_Proc is suppressed if No_Initialization is set.
3383
3384          if Has_Non_Null_Base_Init_Proc (Typ)
3385            and then not No_Initialization (N)
3386          then
3387             --  The call to the initialization procedure does NOT freeze
3388             --  the object being initialized. This is because the call is
3389             --  not a source level call. This works fine, because the only
3390             --  possible statements depending on freeze status that can
3391             --  appear after the _Init call are rep clauses which can
3392             --  safely appear after actual references to the object.
3393
3394             Id_Ref := New_Reference_To (Def_Id, Loc);
3395             Set_Must_Not_Freeze (Id_Ref);
3396             Set_Assignment_OK (Id_Ref);
3397
3398             Insert_Actions_After (N,
3399               Build_Initialization_Call (Loc, Id_Ref, Typ));
3400
3401          --  If simple initialization is required, then set an appropriate
3402          --  simple initialization expression in place. This special
3403          --  initialization is required even though No_Init_Flag is present.
3404
3405          elsif Needs_Simple_Initialization (Typ) then
3406             Set_No_Initialization (N, False);
3407             Set_Expression (N, Get_Simple_Init_Val (Typ, Loc));
3408             Analyze_And_Resolve (Expression (N), Typ);
3409          end if;
3410
3411       --  Explicit initialization present
3412
3413       else
3414          --  Obtain actual expression from qualified expression
3415
3416          if Nkind (Expr) = N_Qualified_Expression then
3417             Expr_Q := Expression (Expr);
3418          else
3419             Expr_Q := Expr;
3420          end if;
3421
3422          --  When we have the appropriate type of aggregate in the
3423          --  expression (it has been determined during analysis of the
3424          --  aggregate by setting the delay flag), let's perform in
3425          --  place assignment and thus avoid creating a temporary.
3426
3427          if Is_Delayed_Aggregate (Expr_Q) then
3428             Convert_Aggr_In_Object_Decl (N);
3429
3430          else
3431             --  In most cases, we must check that the initial value meets
3432             --  any constraint imposed by the declared type. However, there
3433             --  is one very important exception to this rule. If the entity
3434             --  has an unconstrained nominal subtype, then it acquired its
3435             --  constraints from the expression in the first place, and not
3436             --  only does this mean that the constraint check is not needed,
3437             --  but an attempt to perform the constraint check can
3438             --  cause order of elaboration problems.
3439
3440             if not Is_Constr_Subt_For_U_Nominal (Typ) then
3441
3442                --  If this is an allocator for an aggregate that has been
3443                --  allocated in place, delay checks until assignments are
3444                --  made, because the discriminants are not initialized.
3445
3446                if Nkind (Expr) = N_Allocator
3447                  and then No_Initialization (Expr)
3448                then
3449                   null;
3450                else
3451                   Apply_Constraint_Check (Expr, Typ);
3452                end if;
3453             end if;
3454
3455             --  If the type is controlled we attach the object to the final
3456             --  list and adjust the target after the copy. This
3457
3458             if Controlled_Type (Typ) then
3459                declare
3460                   Flist : Node_Id;
3461                   F     : Entity_Id;
3462
3463                begin
3464                   --  Attach the result to a dummy final list which will never
3465                   --  be finalized if Delay_Finalize_Attachis set. It is
3466                   --  important to attach to a dummy final list rather than
3467                   --  not attaching at all in order to reset the pointers
3468                   --  coming from the initial value. Equivalent code exists
3469                   --  in the sec-stack case in Exp_Ch4.Expand_N_Allocator.
3470
3471                   if Delay_Finalize_Attach (N) then
3472                      F :=
3473                        Make_Defining_Identifier (Loc, New_Internal_Name ('F'));
3474                      Insert_Action (N,
3475                        Make_Object_Declaration (Loc,
3476                          Defining_Identifier => F,
3477                          Object_Definition   =>
3478                            New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
3479
3480                      Flist := New_Reference_To (F, Loc);
3481
3482                   else
3483                      Flist := Find_Final_List (Def_Id);
3484                   end if;
3485
3486                   Insert_Actions_After (N,
3487                     Make_Adjust_Call (
3488                       Ref          => New_Reference_To (Def_Id, Loc),
3489                       Typ          => Base_Type (Typ),
3490                       Flist_Ref    => Flist,
3491                       With_Attach  => Make_Integer_Literal (Loc, 1)));
3492                end;
3493             end if;
3494
3495             --  For tagged types, when an init value is given, the tag has
3496             --  to be re-initialized separately in order to avoid the
3497             --  propagation of a wrong tag coming from a view conversion
3498             --  unless the type is class wide (in this case the tag comes
3499             --  from the init value). Suppress the tag assignment when
3500             --  Java_VM because JVM tags are represented implicitly
3501             --  in objects. Ditto for types that are CPP_CLASS.
3502
3503             if Is_Tagged_Type (Typ)
3504               and then not Is_Class_Wide_Type (Typ)
3505               and then not Is_CPP_Class (Typ)
3506               and then not Java_VM
3507             then
3508                --  The re-assignment of the tag has to be done even if
3509                --  the object is a constant
3510
3511                New_Ref :=
3512                  Make_Selected_Component (Loc,
3513                     Prefix => New_Reference_To (Def_Id, Loc),
3514                     Selector_Name =>
3515                       New_Reference_To (Tag_Component (Typ), Loc));
3516
3517                Set_Assignment_OK (New_Ref);
3518
3519                Insert_After (N,
3520                  Make_Assignment_Statement (Loc,
3521                    Name => New_Ref,
3522                    Expression =>
3523                      Unchecked_Convert_To (RTE (RE_Tag),
3524                        New_Reference_To
3525                          (Access_Disp_Table (Base_Type (Typ)), Loc))));
3526
3527             --  For discrete types, set the Is_Known_Valid flag if the
3528             --  initializing value is known to be valid.
3529
3530             elsif Is_Discrete_Type (Typ)
3531               and then Expr_Known_Valid (Expr)
3532             then
3533                Set_Is_Known_Valid (Def_Id);
3534
3535             elsif Is_Access_Type (Typ) then
3536
3537                --  Ada 2005 (AI-231): Generate conversion to the null-excluding
3538                --  type to force the corresponding run-time check
3539
3540                if Ada_Version >= Ada_05
3541                  and then (Can_Never_Be_Null (Def_Id)
3542                              or else Can_Never_Be_Null (Typ))
3543                then
3544                   Rewrite
3545                     (Expr_Q,
3546                      Convert_To (Etype (Def_Id), Relocate_Node (Expr_Q)));
3547                   Analyze_And_Resolve (Expr_Q, Etype (Def_Id));
3548                end if;
3549
3550                --  For access types set the Is_Known_Non_Null flag if the
3551                --  initializing value is known to be non-null. We can also
3552                --  set Can_Never_Be_Null if this is a constant.
3553
3554                if Known_Non_Null (Expr) then
3555                   Set_Is_Known_Non_Null (Def_Id);
3556
3557                   if Constant_Present (N) then
3558                      Set_Can_Never_Be_Null (Def_Id);
3559                   end if;
3560                end if;
3561             end if;
3562
3563             --  If validity checking on copies, validate initial expression
3564
3565             if Validity_Checks_On
3566                and then Validity_Check_Copies
3567             then
3568                Ensure_Valid (Expr);
3569                Set_Is_Known_Valid (Def_Id);
3570             end if;
3571          end if;
3572
3573          if Is_Possibly_Unaligned_Slice (Expr) then
3574
3575             --  Make a separate assignment that will be expanded into a
3576             --  loop, to bypass back-end problems with misaligned arrays.
3577
3578             declare
3579                Stat : constant Node_Id :=
3580                        Make_Assignment_Statement (Loc,
3581                          Name => New_Reference_To (Def_Id, Loc),
3582                          Expression => Relocate_Node (Expr));
3583
3584             begin
3585                Set_Expression (N, Empty);
3586                Set_No_Initialization (N);
3587                Set_Assignment_OK (Name (Stat));
3588                Insert_After (N, Stat);
3589                Analyze (Stat);
3590             end;
3591          end if;
3592       end if;
3593
3594       --  For array type, check for size too large
3595       --  We really need this for record types too???
3596
3597       if Is_Array_Type (Typ) then
3598          Apply_Array_Size_Check (N, Typ);
3599       end if;
3600
3601    exception
3602       when RE_Not_Available =>
3603          return;
3604    end Expand_N_Object_Declaration;
3605
3606    ---------------------------------
3607    -- Expand_N_Subtype_Indication --
3608    ---------------------------------
3609
3610    --  Add a check on the range of the subtype. The static case is
3611    --  partially duplicated by Process_Range_Expr_In_Decl in Sem_Ch3,
3612    --  but we still need to check here for the static case in order to
3613    --  avoid generating extraneous expanded code.
3614
3615    procedure Expand_N_Subtype_Indication (N : Node_Id) is
3616       Ran : constant Node_Id   := Range_Expression (Constraint (N));
3617       Typ : constant Entity_Id := Entity (Subtype_Mark (N));
3618
3619    begin
3620       if Nkind (Parent (N)) = N_Constrained_Array_Definition or else
3621          Nkind (Parent (N)) = N_Slice
3622       then
3623          Resolve (Ran, Typ);
3624          Apply_Range_Check (Ran, Typ);
3625       end if;
3626    end Expand_N_Subtype_Indication;
3627
3628    ---------------------------
3629    -- Expand_N_Variant_Part --
3630    ---------------------------
3631
3632    --  If the last variant does not contain the Others choice, replace
3633    --  it with an N_Others_Choice node since Gigi always wants an Others.
3634    --  Note that we do not bother to call Analyze on the modified variant
3635    --  part, since it's only effect would be to compute the contents of
3636    --  the Others_Discrete_Choices node laboriously, and of course we
3637    --  already know the list of choices that corresponds to the others
3638    --  choice (it's the list we are replacing!)
3639
3640    procedure Expand_N_Variant_Part (N : Node_Id) is
3641       Last_Var    : constant Node_Id := Last_Non_Pragma (Variants (N));
3642       Others_Node : Node_Id;
3643
3644    begin
3645       if Nkind (First (Discrete_Choices (Last_Var))) /= N_Others_Choice then
3646          Others_Node := Make_Others_Choice (Sloc (Last_Var));
3647          Set_Others_Discrete_Choices
3648            (Others_Node, Discrete_Choices (Last_Var));
3649          Set_Discrete_Choices (Last_Var, New_List (Others_Node));
3650       end if;
3651    end Expand_N_Variant_Part;
3652
3653    ---------------------------------
3654    -- Expand_Previous_Access_Type --
3655    ---------------------------------
3656
3657    procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
3658       T : Entity_Id := First_Entity (Current_Scope);
3659
3660    begin
3661       --  Find all access types declared in the current scope, whose
3662       --  designated type is Def_Id.
3663
3664       while Present (T) loop
3665          if Is_Access_Type (T)
3666            and then Designated_Type (T) = Def_Id
3667          then
3668             Build_Master_Entity (Def_Id);
3669             Build_Master_Renaming (Parent (Def_Id), T);
3670          end if;
3671
3672          Next_Entity (T);
3673       end loop;
3674    end Expand_Previous_Access_Type;
3675
3676    ------------------------------
3677    -- Expand_Record_Controller --
3678    ------------------------------
3679
3680    procedure Expand_Record_Controller (T : Entity_Id) is
3681       Def             : Node_Id := Type_Definition (Parent (T));
3682       Comp_List       : Node_Id;
3683       Comp_Decl       : Node_Id;
3684       Loc             : Source_Ptr;
3685       First_Comp      : Node_Id;
3686       Controller_Type : Entity_Id;
3687       Ent             : Entity_Id;
3688
3689    begin
3690       if Nkind (Def) = N_Derived_Type_Definition then
3691          Def := Record_Extension_Part (Def);
3692       end if;
3693
3694       if Null_Present (Def) then
3695          Set_Component_List (Def,
3696            Make_Component_List (Sloc (Def),
3697              Component_Items => Empty_List,
3698              Variant_Part => Empty,
3699              Null_Present => True));
3700       end if;
3701
3702       Comp_List := Component_List (Def);
3703
3704       if Null_Present (Comp_List)
3705         or else Is_Empty_List (Component_Items (Comp_List))
3706       then
3707          Loc := Sloc (Comp_List);
3708       else
3709          Loc := Sloc (First (Component_Items (Comp_List)));
3710       end if;
3711
3712       if Is_Return_By_Reference_Type (T) then
3713          Controller_Type := RTE (RE_Limited_Record_Controller);
3714       else
3715          Controller_Type := RTE (RE_Record_Controller);
3716       end if;
3717
3718       Ent := Make_Defining_Identifier (Loc, Name_uController);
3719
3720       Comp_Decl :=
3721         Make_Component_Declaration (Loc,
3722           Defining_Identifier =>  Ent,
3723           Component_Definition =>
3724             Make_Component_Definition (Loc,
3725               Aliased_Present => False,
3726               Subtype_Indication => New_Reference_To (Controller_Type, Loc)));
3727
3728       if Null_Present (Comp_List)
3729         or else Is_Empty_List (Component_Items (Comp_List))
3730       then
3731          Set_Component_Items (Comp_List, New_List (Comp_Decl));
3732          Set_Null_Present (Comp_List, False);
3733
3734       else
3735          --  The controller cannot be placed before the _Parent field
3736          --  since gigi lays out field in order and _parent must be
3737          --  first to preserve the polymorphism of tagged types.
3738
3739          First_Comp := First (Component_Items (Comp_List));
3740
3741          if Chars (Defining_Identifier (First_Comp)) /= Name_uParent
3742            and then Chars (Defining_Identifier (First_Comp)) /= Name_uTag
3743          then
3744             Insert_Before (First_Comp, Comp_Decl);
3745          else
3746             Insert_After (First_Comp, Comp_Decl);
3747          end if;
3748       end if;
3749
3750       New_Scope (T);
3751       Analyze (Comp_Decl);
3752       Set_Ekind (Ent, E_Component);
3753       Init_Component_Location (Ent);
3754
3755       --  Move the _controller entity ahead in the list of internal
3756       --  entities of the enclosing record so that it is selected
3757       --  instead of a potentially inherited one.
3758
3759       declare
3760          E    : constant Entity_Id := Last_Entity (T);
3761          Comp : Entity_Id;
3762
3763       begin
3764          pragma Assert (Chars (E) = Name_uController);
3765
3766          Set_Next_Entity (E, First_Entity (T));
3767          Set_First_Entity (T, E);
3768
3769          Comp := Next_Entity (E);
3770          while Next_Entity (Comp) /= E loop
3771             Next_Entity (Comp);
3772          end loop;
3773
3774          Set_Next_Entity (Comp, Empty);
3775          Set_Last_Entity (T, Comp);
3776       end;
3777
3778       End_Scope;
3779
3780    exception
3781       when RE_Not_Available =>
3782          return;
3783    end Expand_Record_Controller;
3784
3785    ------------------------
3786    -- Expand_Tagged_Root --
3787    ------------------------
3788
3789    procedure Expand_Tagged_Root (T : Entity_Id) is
3790       Def       : constant Node_Id := Type_Definition (Parent (T));
3791       Comp_List : Node_Id;
3792       Comp_Decl : Node_Id;
3793       Sloc_N    : Source_Ptr;
3794
3795    begin
3796       if Null_Present (Def) then
3797          Set_Component_List (Def,
3798            Make_Component_List (Sloc (Def),
3799              Component_Items => Empty_List,
3800              Variant_Part => Empty,
3801              Null_Present => True));
3802       end if;
3803
3804       Comp_List := Component_List (Def);
3805
3806       if Null_Present (Comp_List)
3807         or else Is_Empty_List (Component_Items (Comp_List))
3808       then
3809          Sloc_N := Sloc (Comp_List);
3810       else
3811          Sloc_N := Sloc (First (Component_Items (Comp_List)));
3812       end if;
3813
3814       Comp_Decl :=
3815         Make_Component_Declaration (Sloc_N,
3816           Defining_Identifier => Tag_Component (T),
3817           Component_Definition =>
3818             Make_Component_Definition (Sloc_N,
3819               Aliased_Present => False,
3820               Subtype_Indication => New_Reference_To (RTE (RE_Tag), Sloc_N)));
3821
3822       if Null_Present (Comp_List)
3823         or else Is_Empty_List (Component_Items (Comp_List))
3824       then
3825          Set_Component_Items (Comp_List, New_List (Comp_Decl));
3826          Set_Null_Present (Comp_List, False);
3827
3828       else
3829          Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
3830       end if;
3831
3832       --  We don't Analyze the whole expansion because the tag component has
3833       --  already been analyzed previously. Here we just insure that the
3834       --  tree is coherent with the semantic decoration
3835
3836       Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
3837
3838    exception
3839       when RE_Not_Available =>
3840          return;
3841    end Expand_Tagged_Root;
3842
3843    -----------------------
3844    -- Freeze_Array_Type --
3845    -----------------------
3846
3847    procedure Freeze_Array_Type (N : Node_Id) is
3848       Typ  : constant Entity_Id  := Entity (N);
3849       Base : constant Entity_Id  := Base_Type (Typ);
3850
3851    begin
3852       if not Is_Bit_Packed_Array (Typ) then
3853
3854          --  If the component contains tasks, so does the array type.
3855          --  This may not be indicated in the array type because the
3856          --  component may have been a private type at the point of
3857          --  definition. Same if component type is controlled.
3858
3859          Set_Has_Task (Base, Has_Task (Component_Type (Typ)));
3860          Set_Has_Controlled_Component (Base,
3861            Has_Controlled_Component (Component_Type (Typ))
3862              or else Is_Controlled (Component_Type (Typ)));
3863
3864          if No (Init_Proc (Base)) then
3865
3866             --  If this is an anonymous array created for a declaration
3867             --  with an initial value, its init_proc will never be called.
3868             --  The initial value itself may have been expanded into assign-
3869             --  ments, in which case the object declaration is carries the
3870             --  No_Initialization flag.
3871
3872             if Is_Itype (Base)
3873               and then Nkind (Associated_Node_For_Itype (Base)) =
3874                                                     N_Object_Declaration
3875               and then (Present (Expression (Associated_Node_For_Itype (Base)))
3876                           or else
3877                         No_Initialization (Associated_Node_For_Itype (Base)))
3878             then
3879                null;
3880
3881             --  We do not need an init proc for string or wide string, since
3882             --  the only time these need initialization in normalize or
3883             --  initialize scalars mode, and these types are treated specially
3884             --  and do not need initialization procedures.
3885
3886             elsif Root_Type (Base) = Standard_String
3887               or else Root_Type (Base) = Standard_Wide_String
3888             then
3889                null;
3890
3891             --  Otherwise we have to build an init proc for the subtype
3892
3893             else
3894                Build_Array_Init_Proc (Base, N);
3895             end if;
3896          end if;
3897
3898          if Typ = Base and then Has_Controlled_Component (Base) then
3899             Build_Controlling_Procs (Base);
3900
3901             if not Is_Limited_Type (Component_Type (Typ))
3902               and then Number_Dimensions (Typ) = 1
3903             then
3904                Build_Slice_Assignment (Typ);
3905             end if;
3906          end if;
3907
3908       --  For packed case, there is a default initialization, except
3909       --  if the component type is itself a packed structure with an
3910       --  initialization procedure.
3911
3912       elsif Present (Init_Proc (Component_Type (Base)))
3913         and then No (Base_Init_Proc (Base))
3914       then
3915          Build_Array_Init_Proc (Base, N);
3916       end if;
3917    end Freeze_Array_Type;
3918
3919    -----------------------------
3920    -- Freeze_Enumeration_Type --
3921    -----------------------------
3922
3923    procedure Freeze_Enumeration_Type (N : Node_Id) is
3924       Typ           : constant Entity_Id  := Entity (N);
3925       Loc           : constant Source_Ptr := Sloc (Typ);
3926       Ent           : Entity_Id;
3927       Lst           : List_Id;
3928       Num           : Nat;
3929       Arr           : Entity_Id;
3930       Fent          : Entity_Id;
3931       Ityp          : Entity_Id;
3932       Is_Contiguous : Boolean;
3933       Pos_Expr      : Node_Id;
3934       Last_Repval   : Uint;
3935
3936       Func : Entity_Id;
3937       pragma Warnings (Off, Func);
3938
3939    begin
3940       --  Various optimization are possible if the given representation
3941       --  is contiguous.
3942
3943       Is_Contiguous := True;
3944       Ent := First_Literal (Typ);
3945       Last_Repval := Enumeration_Rep (Ent);
3946       Next_Literal (Ent);
3947
3948       while Present (Ent) loop
3949          if Enumeration_Rep (Ent) - Last_Repval /= 1 then
3950             Is_Contiguous := False;
3951             exit;
3952          else
3953             Last_Repval := Enumeration_Rep (Ent);
3954          end if;
3955
3956          Next_Literal (Ent);
3957       end loop;
3958
3959       if Is_Contiguous then
3960          Set_Has_Contiguous_Rep (Typ);
3961          Ent := First_Literal (Typ);
3962          Num := 1;
3963          Lst := New_List (New_Reference_To (Ent, Sloc (Ent)));
3964
3965       else
3966          --  Build list of literal references
3967
3968          Lst := New_List;
3969          Num := 0;
3970
3971          Ent := First_Literal (Typ);
3972          while Present (Ent) loop
3973             Append_To (Lst, New_Reference_To (Ent, Sloc (Ent)));
3974             Num := Num + 1;
3975             Next_Literal (Ent);
3976          end loop;
3977       end if;
3978
3979       --  Now build an array declaration.
3980
3981       --    typA : array (Natural range 0 .. num - 1) of ctype :=
3982       --             (v, v, v, v, v, ....)
3983
3984       --  where ctype is the corresponding integer type. If the
3985       --  representation is contiguous, we only keep the first literal,
3986       --  which provides the offset for Pos_To_Rep computations.
3987
3988       Arr :=
3989         Make_Defining_Identifier (Loc,
3990           Chars => New_External_Name (Chars (Typ), 'A'));
3991
3992       Append_Freeze_Action (Typ,
3993         Make_Object_Declaration (Loc,
3994           Defining_Identifier => Arr,
3995           Constant_Present    => True,
3996
3997           Object_Definition   =>
3998             Make_Constrained_Array_Definition (Loc,
3999               Discrete_Subtype_Definitions => New_List (
4000                 Make_Subtype_Indication (Loc,
4001                   Subtype_Mark => New_Reference_To (Standard_Natural, Loc),
4002                   Constraint =>
4003                     Make_Range_Constraint (Loc,
4004                       Range_Expression =>
4005                         Make_Range (Loc,
4006                           Low_Bound  =>
4007                             Make_Integer_Literal (Loc, 0),
4008                           High_Bound =>
4009                             Make_Integer_Literal (Loc, Num - 1))))),
4010
4011               Component_Definition =>
4012                 Make_Component_Definition (Loc,
4013                   Aliased_Present => False,
4014                   Subtype_Indication => New_Reference_To (Typ, Loc))),
4015
4016           Expression =>
4017             Make_Aggregate (Loc,
4018               Expressions => Lst)));
4019
4020       Set_Enum_Pos_To_Rep (Typ, Arr);
4021
4022       --  Now we build the function that converts representation values to
4023       --  position values. This function has the form:
4024
4025       --    function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
4026       --    begin
4027       --       case ityp!(A) is
4028       --         when enum-lit'Enum_Rep => return posval;
4029       --         when enum-lit'Enum_Rep => return posval;
4030       --         ...
4031       --         when others   =>
4032       --           [raise Constraint_Error when F "invalid data"]
4033       --           return -1;
4034       --       end case;
4035       --    end;
4036
4037       --  Note: the F parameter determines whether the others case (no valid
4038       --  representation) raises Constraint_Error or returns a unique value
4039       --  of minus one. The latter case is used, e.g. in 'Valid code.
4040
4041       --  Note: the reason we use Enum_Rep values in the case here is to
4042       --  avoid the code generator making inappropriate assumptions about
4043       --  the range of the values in the case where the value is invalid.
4044       --  ityp is a signed or unsigned integer type of appropriate width.
4045
4046       --  Note: if exceptions are not supported, then we suppress the raise
4047       --  and return -1 unconditionally (this is an erroneous program in any
4048       --  case and there is no obligation to raise Constraint_Error here!)
4049       --  We also do this if pragma Restrictions (No_Exceptions) is active.
4050
4051       --  Representations are signed
4052
4053       if Enumeration_Rep (First_Literal (Typ)) < 0 then
4054
4055          --  The underlying type is signed. Reset the Is_Unsigned_Type
4056          --  explicitly, because it might have been inherited from a
4057          --  parent type.
4058
4059          Set_Is_Unsigned_Type (Typ, False);
4060
4061          if Esize (Typ) <= Standard_Integer_Size then
4062             Ityp := Standard_Integer;
4063          else
4064             Ityp := Universal_Integer;
4065          end if;
4066
4067       --  Representations are unsigned
4068
4069       else
4070          if Esize (Typ) <= Standard_Integer_Size then
4071             Ityp := RTE (RE_Unsigned);
4072          else
4073             Ityp := RTE (RE_Long_Long_Unsigned);
4074          end if;
4075       end if;
4076
4077       --  The body of the function is a case statement. First collect
4078       --  case alternatives, or optimize the contiguous case.
4079
4080       Lst := New_List;
4081
4082       --  If representation is contiguous, Pos is computed by subtracting
4083       --  the representation of the first literal.
4084
4085       if Is_Contiguous then
4086          Ent := First_Literal (Typ);
4087
4088          if Enumeration_Rep (Ent) = Last_Repval then
4089
4090             --  Another special case: for a single literal, Pos is zero.
4091
4092             Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
4093
4094          else
4095             Pos_Expr :=
4096               Convert_To (Standard_Integer,
4097                 Make_Op_Subtract (Loc,
4098                   Left_Opnd =>
4099                      Unchecked_Convert_To (Ityp,
4100                        Make_Identifier (Loc, Name_uA)),
4101                    Right_Opnd =>
4102                      Make_Integer_Literal (Loc,
4103                         Intval =>
4104                           Enumeration_Rep (First_Literal (Typ)))));
4105          end if;
4106
4107          Append_To (Lst,
4108               Make_Case_Statement_Alternative (Loc,
4109                 Discrete_Choices => New_List (
4110                   Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
4111                     Low_Bound =>
4112                       Make_Integer_Literal (Loc,
4113                        Intval =>  Enumeration_Rep (Ent)),
4114                     High_Bound =>
4115                       Make_Integer_Literal (Loc, Intval => Last_Repval))),
4116
4117                 Statements => New_List (
4118                   Make_Return_Statement (Loc,
4119                     Expression => Pos_Expr))));
4120
4121       else
4122          Ent := First_Literal (Typ);
4123
4124          while Present (Ent) loop
4125             Append_To (Lst,
4126               Make_Case_Statement_Alternative (Loc,
4127                 Discrete_Choices => New_List (
4128                   Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
4129                     Intval => Enumeration_Rep (Ent))),
4130
4131                 Statements => New_List (
4132                   Make_Return_Statement (Loc,
4133                     Expression =>
4134                       Make_Integer_Literal (Loc,
4135                         Intval => Enumeration_Pos (Ent))))));
4136
4137             Next_Literal (Ent);
4138          end loop;
4139       end if;
4140
4141       --  In normal mode, add the others clause with the test
4142
4143       if not Restriction_Active (No_Exception_Handlers) then
4144          Append_To (Lst,
4145            Make_Case_Statement_Alternative (Loc,
4146              Discrete_Choices => New_List (Make_Others_Choice (Loc)),
4147              Statements => New_List (
4148                Make_Raise_Constraint_Error (Loc,
4149                  Condition => Make_Identifier (Loc, Name_uF),
4150                  Reason    => CE_Invalid_Data),
4151                Make_Return_Statement (Loc,
4152                  Expression =>
4153                    Make_Integer_Literal (Loc, -1)))));
4154
4155       --  If Restriction (No_Exceptions_Handlers) is active then we always
4156       --  return -1 (since we cannot usefully raise Constraint_Error in
4157       --  this case). See description above for further details.
4158
4159       else
4160          Append_To (Lst,
4161            Make_Case_Statement_Alternative (Loc,
4162              Discrete_Choices => New_List (Make_Others_Choice (Loc)),
4163              Statements => New_List (
4164                Make_Return_Statement (Loc,
4165                  Expression =>
4166                    Make_Integer_Literal (Loc, -1)))));
4167       end if;
4168
4169       --  Now we can build the function body
4170
4171       Fent :=
4172         Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
4173
4174       Func :=
4175         Make_Subprogram_Body (Loc,
4176           Specification =>
4177             Make_Function_Specification (Loc,
4178               Defining_Unit_Name       => Fent,
4179               Parameter_Specifications => New_List (
4180                 Make_Parameter_Specification (Loc,
4181                   Defining_Identifier =>
4182                     Make_Defining_Identifier (Loc, Name_uA),
4183                   Parameter_Type => New_Reference_To (Typ, Loc)),
4184                 Make_Parameter_Specification (Loc,
4185                   Defining_Identifier =>
4186                     Make_Defining_Identifier (Loc, Name_uF),
4187                   Parameter_Type => New_Reference_To (Standard_Boolean, Loc))),
4188
4189               Subtype_Mark => New_Reference_To (Standard_Integer, Loc)),
4190
4191             Declarations => Empty_List,
4192
4193             Handled_Statement_Sequence =>
4194               Make_Handled_Sequence_Of_Statements (Loc,
4195                 Statements => New_List (
4196                   Make_Case_Statement (Loc,
4197                     Expression =>
4198                       Unchecked_Convert_To (Ityp,
4199                         Make_Identifier (Loc, Name_uA)),
4200                     Alternatives => Lst))));
4201
4202       Set_TSS (Typ, Fent);
4203       Set_Is_Pure (Fent);
4204
4205       if not Debug_Generated_Code then
4206          Set_Debug_Info_Off (Fent);
4207       end if;
4208
4209    exception
4210       when RE_Not_Available =>
4211          return;
4212    end Freeze_Enumeration_Type;
4213
4214    ------------------------
4215    -- Freeze_Record_Type --
4216    ------------------------
4217
4218    procedure Freeze_Record_Type (N : Node_Id) is
4219       Def_Id      : constant Node_Id := Entity (N);
4220       Comp        : Entity_Id;
4221       Type_Decl   : constant Node_Id := Parent (Def_Id);
4222       Predef_List : List_Id;
4223
4224       Renamed_Eq  : Node_Id := Empty;
4225       --  Could use some comments ???
4226
4227    begin
4228       --  Build discriminant checking functions if not a derived type (for
4229       --  derived types that are not tagged types, we always use the
4230       --  discriminant checking functions of the parent type). However, for
4231       --  untagged types the derivation may have taken place before the
4232       --  parent was frozen, so we copy explicitly the discriminant checking
4233       --  functions from the parent into the components of the derived type.
4234
4235       if not Is_Derived_Type (Def_Id)
4236         or else Has_New_Non_Standard_Rep (Def_Id)
4237         or else Is_Tagged_Type (Def_Id)
4238       then
4239          Build_Discr_Checking_Funcs (Type_Decl);
4240
4241       elsif Is_Derived_Type (Def_Id)
4242         and then not Is_Tagged_Type (Def_Id)
4243
4244          --  If we have a derived Unchecked_Union, we do not inherit the
4245          --  discriminant checking functions from the parent type since the
4246          --  discriminants are non existent.
4247
4248         and then not Is_Unchecked_Union (Def_Id)
4249         and then Has_Discriminants (Def_Id)
4250       then
4251          declare
4252             Old_Comp : Entity_Id;
4253
4254          begin
4255             Old_Comp :=
4256               First_Component (Base_Type (Underlying_Type (Etype (Def_Id))));
4257             Comp := First_Component (Def_Id);
4258             while Present (Comp) loop
4259                if Ekind (Comp) = E_Component
4260                  and then Chars (Comp) = Chars (Old_Comp)
4261                then
4262                   Set_Discriminant_Checking_Func (Comp,
4263                      Discriminant_Checking_Func (Old_Comp));
4264                end if;
4265
4266                Next_Component (Old_Comp);
4267                Next_Component (Comp);
4268             end loop;
4269          end;
4270       end if;
4271
4272       if Is_Derived_Type (Def_Id)
4273         and then Is_Limited_Type (Def_Id)
4274         and then Is_Tagged_Type (Def_Id)
4275       then
4276          Check_Stream_Attributes (Def_Id);
4277       end if;
4278
4279       --  Update task and controlled component flags, because some of the
4280       --  component types may have been private at the point of the record
4281       --  declaration.
4282
4283       Comp := First_Component (Def_Id);
4284
4285       while Present (Comp) loop
4286          if Has_Task (Etype (Comp)) then
4287             Set_Has_Task (Def_Id);
4288
4289          elsif Has_Controlled_Component (Etype (Comp))
4290            or else (Chars (Comp) /= Name_uParent
4291                      and then Is_Controlled (Etype (Comp)))
4292          then
4293             Set_Has_Controlled_Component (Def_Id);
4294          end if;
4295
4296          Next_Component (Comp);
4297       end loop;
4298
4299       --  Creation of the Dispatch Table. Note that a Dispatch Table is
4300       --  created for regular tagged types as well as for Ada types
4301       --  deriving from a C++ Class, but not for tagged types directly
4302       --  corresponding to the C++ classes. In the later case we assume
4303       --  that the Vtable is created in the C++ side and we just use it.
4304
4305       if Is_Tagged_Type (Def_Id) then
4306          if Is_CPP_Class (Def_Id) then
4307             Set_All_DT_Position (Def_Id);
4308             Set_Default_Constructor (Def_Id);
4309
4310          else
4311             --  Usually inherited primitives are not delayed but the first
4312             --  Ada extension of a CPP_Class is an exception since the
4313             --  address of the inherited subprogram has to be inserted in
4314             --  the new Ada Dispatch Table and this is a freezing action
4315             --  (usually the inherited primitive address is inserted in the
4316             --  DT by Inherit_DT)
4317
4318             --  Similarly, if this is an inherited operation whose parent
4319             --  is not frozen yet, it is not in the DT of the parent, and
4320             --  we generate an explicit freeze node for the inherited
4321             --  operation, so that it is properly inserted in the DT of the
4322             --  current type.
4323
4324             declare
4325                Elmt : Elmt_Id := First_Elmt (Primitive_Operations (Def_Id));
4326                Subp : Entity_Id;
4327
4328             begin
4329                while Present (Elmt) loop
4330                   Subp := Node (Elmt);
4331
4332                   if Present (Alias (Subp)) then
4333                      if Is_CPP_Class (Etype (Def_Id)) then
4334                         Set_Has_Delayed_Freeze (Subp);
4335
4336                      elsif Has_Delayed_Freeze (Alias (Subp))
4337                        and then not Is_Frozen (Alias (Subp))
4338                      then
4339                         Set_Is_Frozen (Subp, False);
4340                         Set_Has_Delayed_Freeze (Subp);
4341                      end if;
4342                   end if;
4343
4344                   Next_Elmt (Elmt);
4345                end loop;
4346             end;
4347
4348             if Underlying_Type (Etype (Def_Id)) = Def_Id then
4349                Expand_Tagged_Root (Def_Id);
4350             end if;
4351
4352             --  Unfreeze momentarily the type to add the predefined
4353             --  primitives operations. The reason we unfreeze is so
4354             --  that these predefined operations will indeed end up
4355             --  as primitive operations (which must be before the
4356             --  freeze point).
4357
4358             Set_Is_Frozen (Def_Id, False);
4359             Make_Predefined_Primitive_Specs
4360               (Def_Id, Predef_List, Renamed_Eq);
4361             Insert_List_Before_And_Analyze (N, Predef_List);
4362             Set_Is_Frozen (Def_Id, True);
4363             Set_All_DT_Position (Def_Id);
4364
4365             --  Add the controlled component before the freezing actions
4366             --  it is referenced in those actions.
4367
4368             if Has_New_Controlled_Component (Def_Id) then
4369                Expand_Record_Controller (Def_Id);
4370             end if;
4371
4372             --  Suppress creation of a dispatch table when Java_VM because
4373             --  the dispatching mechanism is handled internally by the JVM.
4374
4375             if not Java_VM then
4376                Append_Freeze_Actions (Def_Id, Make_DT (Def_Id));
4377             end if;
4378
4379             --  Make sure that the primitives Initialize, Adjust and
4380             --  Finalize are Frozen before other TSS subprograms. We
4381             --  don't want them Frozen inside.
4382
4383             if Is_Controlled (Def_Id) then
4384                if not Is_Limited_Type (Def_Id) then
4385                   Append_Freeze_Actions (Def_Id,
4386                     Freeze_Entity
4387                       (Find_Prim_Op (Def_Id, Name_Adjust), Sloc (Def_Id)));
4388                end if;
4389
4390                Append_Freeze_Actions (Def_Id,
4391                  Freeze_Entity
4392                    (Find_Prim_Op (Def_Id, Name_Initialize), Sloc (Def_Id)));
4393
4394                Append_Freeze_Actions (Def_Id,
4395                  Freeze_Entity
4396                    (Find_Prim_Op (Def_Id, Name_Finalize), Sloc (Def_Id)));
4397             end if;
4398
4399             --  Freeze rest of primitive operations
4400
4401             Append_Freeze_Actions
4402               (Def_Id, Predefined_Primitive_Freeze (Def_Id));
4403          end if;
4404
4405       --  In the non-tagged case, an equality function is provided only
4406       --  for variant records (that are not unchecked unions).
4407
4408       elsif Has_Discriminants (Def_Id)
4409         and then not Is_Limited_Type (Def_Id)
4410       then
4411          declare
4412             Comps : constant Node_Id :=
4413                       Component_List (Type_Definition (Type_Decl));
4414
4415          begin
4416             if Present (Comps)
4417               and then Present (Variant_Part (Comps))
4418             then
4419                Build_Variant_Record_Equality (Def_Id);
4420             end if;
4421          end;
4422       end if;
4423
4424       --  Before building the record initialization procedure, if we are
4425       --  dealing with a concurrent record value type, then we must go
4426       --  through the discriminants, exchanging discriminals between the
4427       --  concurrent type and the concurrent record value type. See the
4428       --  section "Handling of Discriminants" in the Einfo spec for details.
4429
4430       if Is_Concurrent_Record_Type (Def_Id)
4431         and then Has_Discriminants (Def_Id)
4432       then
4433          declare
4434             Ctyp : constant Entity_Id :=
4435                      Corresponding_Concurrent_Type (Def_Id);
4436             Conc_Discr : Entity_Id;
4437             Rec_Discr  : Entity_Id;
4438             Temp       : Entity_Id;
4439
4440          begin
4441             Conc_Discr := First_Discriminant (Ctyp);
4442             Rec_Discr  := First_Discriminant (Def_Id);
4443
4444             while Present (Conc_Discr) loop
4445                Temp := Discriminal (Conc_Discr);
4446                Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
4447                Set_Discriminal (Rec_Discr, Temp);
4448
4449                Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
4450                Set_Discriminal_Link (Discriminal (Rec_Discr),  Rec_Discr);
4451
4452                Next_Discriminant (Conc_Discr);
4453                Next_Discriminant (Rec_Discr);
4454             end loop;
4455          end;
4456       end if;
4457
4458       if Has_Controlled_Component (Def_Id) then
4459          if No (Controller_Component (Def_Id)) then
4460             Expand_Record_Controller (Def_Id);
4461          end if;
4462
4463          Build_Controlling_Procs (Def_Id);
4464       end if;
4465
4466       Adjust_Discriminants (Def_Id);
4467       Build_Record_Init_Proc (Type_Decl, Def_Id);
4468
4469       --  For tagged type, build bodies of primitive operations. Note
4470       --  that we do this after building the record initialization
4471       --  experiment, since the primitive operations may need the
4472       --  initialization routine
4473
4474       if Is_Tagged_Type (Def_Id) then
4475          Predef_List := Predefined_Primitive_Bodies (Def_Id, Renamed_Eq);
4476          Append_Freeze_Actions (Def_Id, Predef_List);
4477       end if;
4478
4479    end Freeze_Record_Type;
4480
4481    ------------------------------
4482    -- Freeze_Stream_Operations --
4483    ------------------------------
4484
4485    procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
4486       Names     : constant array (1 .. 4) of TSS_Name_Type :=
4487                     (TSS_Stream_Input,
4488                      TSS_Stream_Output,
4489                      TSS_Stream_Read,
4490                      TSS_Stream_Write);
4491       Stream_Op : Entity_Id;
4492
4493    begin
4494       --  Primitive operations of tagged types are frozen when the dispatch
4495       --  table is constructed.
4496
4497       if not Comes_From_Source (Typ)
4498         or else Is_Tagged_Type (Typ)
4499       then
4500          return;
4501       end if;
4502
4503       for J in Names'Range loop
4504          Stream_Op := TSS (Typ, Names (J));
4505
4506          if Present (Stream_Op)
4507            and then Is_Subprogram (Stream_Op)
4508            and then Nkind (Unit_Declaration_Node (Stream_Op)) =
4509                       N_Subprogram_Declaration
4510            and then not Is_Frozen (Stream_Op)
4511          then
4512             Append_Freeze_Actions
4513                (Typ, Freeze_Entity (Stream_Op, Sloc (N)));
4514          end if;
4515       end loop;
4516    end Freeze_Stream_Operations;
4517
4518    -----------------
4519    -- Freeze_Type --
4520    -----------------
4521
4522    --  Full type declarations are expanded at the point at which the type
4523    --  is frozen. The formal N is the Freeze_Node for the type. Any statements
4524    --  or declarations generated by the freezing (e.g. the procedure generated
4525    --  for initialization) are chained in the Acions field list of the freeze
4526    --  node using Append_Freeze_Actions.
4527
4528    procedure Freeze_Type (N : Node_Id) is
4529       Def_Id    : constant Entity_Id := Entity (N);
4530       RACW_Seen : Boolean := False;
4531
4532    begin
4533       --  Process associated access types needing special processing
4534
4535       if Present (Access_Types_To_Process (N)) then
4536          declare
4537             E : Elmt_Id := First_Elmt (Access_Types_To_Process (N));
4538          begin
4539             while Present (E) loop
4540
4541                if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
4542                   RACW_Seen := True;
4543                end if;
4544
4545                E := Next_Elmt (E);
4546             end loop;
4547          end;
4548
4549          if RACW_Seen then
4550
4551             --  If there are RACWs designating this type, make stubs now.
4552
4553             Remote_Types_Tagged_Full_View_Encountered (Def_Id);
4554          end if;
4555       end if;
4556
4557       --  Freeze processing for record types
4558
4559       if Is_Record_Type (Def_Id) then
4560          if Ekind (Def_Id) = E_Record_Type then
4561             Freeze_Record_Type (N);
4562
4563          --  The subtype may have been declared before the type was frozen.
4564          --  If the type has controlled components it is necessary to create
4565          --  the entity for the controller explicitly because it did not
4566          --  exist at the point of the subtype declaration. Only the entity is
4567          --  needed, the back-end will obtain the layout from the type.
4568          --  This is only necessary if this is constrained subtype whose
4569          --  component list is not shared with the base type.
4570
4571          elsif Ekind (Def_Id) = E_Record_Subtype
4572            and then Has_Discriminants (Def_Id)
4573            and then Last_Entity (Def_Id) /= Last_Entity (Base_Type (Def_Id))
4574            and then Present (Controller_Component (Def_Id))
4575          then
4576             declare
4577                Old_C : constant Entity_Id := Controller_Component (Def_Id);
4578                New_C : Entity_Id;
4579
4580             begin
4581                if Scope (Old_C) = Base_Type (Def_Id) then
4582
4583                   --  The entity is the one in the parent. Create new one.
4584
4585                   New_C := New_Copy (Old_C);
4586                   Set_Parent (New_C, Parent (Old_C));
4587                   New_Scope (Def_Id);
4588                   Enter_Name (New_C);
4589                   End_Scope;
4590                end if;
4591             end;
4592
4593          --  Similar process if the controller of the subtype is not
4594          --  present but the parent has it. This can happen with constrained
4595          --  record components where the subtype is an itype.
4596
4597          elsif Ekind (Def_Id) = E_Record_Subtype
4598            and then Is_Itype (Def_Id)
4599            and then No (Controller_Component (Def_Id))
4600            and then Present (Controller_Component (Etype (Def_Id)))
4601          then
4602             declare
4603                Old_C : constant Entity_Id :=
4604                          Controller_Component (Etype (Def_Id));
4605                New_C : constant Entity_Id := New_Copy (Old_C);
4606
4607             begin
4608                Set_Next_Entity  (New_C, First_Entity (Def_Id));
4609                Set_First_Entity (Def_Id, New_C);
4610
4611                --  The freeze node is only used to introduce the controller,
4612                --  the back-end has no use for it for a discriminated
4613                --   component.
4614
4615                Set_Freeze_Node (Def_Id, Empty);
4616                Set_Has_Delayed_Freeze (Def_Id, False);
4617                Remove (N);
4618             end;
4619          end if;
4620
4621       --  Freeze processing for array types
4622
4623       elsif Is_Array_Type (Def_Id) then
4624          Freeze_Array_Type (N);
4625
4626       --  Freeze processing for access types
4627
4628       --  For pool-specific access types, find out the pool object used for
4629       --  this type, needs actual expansion of it in some cases. Here are the
4630       --  different cases :
4631
4632       --  1. Rep Clause "for Def_Id'Storage_Size use 0;"
4633       --      ---> don't use any storage pool
4634
4635       --  2. Rep Clause : for Def_Id'Storage_Size use Expr.
4636       --     Expand:
4637       --      Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
4638
4639       --  3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
4640       --      ---> Storage Pool is the specified one
4641
4642       --  See GNAT Pool packages in the Run-Time for more details
4643
4644       elsif Ekind (Def_Id) = E_Access_Type
4645         or else Ekind (Def_Id) = E_General_Access_Type
4646       then
4647          declare
4648             Loc         : constant Source_Ptr := Sloc (N);
4649             Desig_Type  : constant Entity_Id := Designated_Type (Def_Id);
4650             Pool_Object : Entity_Id;
4651             Siz_Exp     : Node_Id;
4652
4653             Freeze_Action_Typ : Entity_Id;
4654
4655          begin
4656             if Has_Storage_Size_Clause (Def_Id) then
4657                Siz_Exp := Expression (Parent (Storage_Size_Variable (Def_Id)));
4658             else
4659                Siz_Exp := Empty;
4660             end if;
4661
4662             --  Case 1
4663
4664             --    Rep Clause "for Def_Id'Storage_Size use 0;"
4665             --    ---> don't use any storage pool
4666
4667             if Has_Storage_Size_Clause (Def_Id)
4668               and then Compile_Time_Known_Value (Siz_Exp)
4669               and then Expr_Value (Siz_Exp) = 0
4670             then
4671                null;
4672
4673             --  Case 2
4674
4675             --    Rep Clause : for Def_Id'Storage_Size use Expr.
4676             --    ---> Expand:
4677             --           Def_Id__Pool : Stack_Bounded_Pool
4678             --                            (Expr, DT'Size, DT'Alignment);
4679
4680             elsif Has_Storage_Size_Clause (Def_Id) then
4681                declare
4682                   DT_Size  : Node_Id;
4683                   DT_Align : Node_Id;
4684
4685                begin
4686                   --  For unconstrained composite types we give a size of
4687                   --  zero so that the pool knows that it needs a special
4688                   --  algorithm for variable size object allocation.
4689
4690                   if Is_Composite_Type (Desig_Type)
4691                     and then not Is_Constrained (Desig_Type)
4692                   then
4693                      DT_Size :=
4694                        Make_Integer_Literal (Loc, 0);
4695
4696                      DT_Align :=
4697                        Make_Integer_Literal (Loc, Maximum_Alignment);
4698
4699                   else
4700                      DT_Size :=
4701                        Make_Attribute_Reference (Loc,
4702                          Prefix => New_Reference_To (Desig_Type, Loc),
4703                          Attribute_Name => Name_Max_Size_In_Storage_Elements);
4704
4705                      DT_Align :=
4706                        Make_Attribute_Reference (Loc,
4707                          Prefix => New_Reference_To (Desig_Type, Loc),
4708                          Attribute_Name => Name_Alignment);
4709                   end if;
4710
4711                   Pool_Object :=
4712                     Make_Defining_Identifier (Loc,
4713                       Chars => New_External_Name (Chars (Def_Id), 'P'));
4714
4715                   --  We put the code associated with the pools in the
4716                   --  entity that has the later freeze node, usually the
4717                   --  acces type but it can also be the designated_type;
4718                   --  because the pool code requires both those types to be
4719                   --  frozen
4720
4721                   if Is_Frozen (Desig_Type)
4722                     and then (not Present (Freeze_Node (Desig_Type))
4723                                or else Analyzed (Freeze_Node (Desig_Type)))
4724                   then
4725                      Freeze_Action_Typ := Def_Id;
4726
4727                   --  A Taft amendment type cannot get the freeze actions
4728                   --  since the full view is not there.
4729
4730                   elsif Is_Incomplete_Or_Private_Type (Desig_Type)
4731                     and then No (Full_View (Desig_Type))
4732                   then
4733                      Freeze_Action_Typ := Def_Id;
4734
4735                   else
4736                      Freeze_Action_Typ := Desig_Type;
4737                   end if;
4738
4739                   Append_Freeze_Action (Freeze_Action_Typ,
4740                     Make_Object_Declaration (Loc,
4741                       Defining_Identifier => Pool_Object,
4742                       Object_Definition =>
4743                         Make_Subtype_Indication (Loc,
4744                           Subtype_Mark =>
4745                             New_Reference_To
4746                               (RTE (RE_Stack_Bounded_Pool), Loc),
4747
4748                           Constraint =>
4749                             Make_Index_Or_Discriminant_Constraint (Loc,
4750                               Constraints => New_List (
4751
4752                               --  First discriminant is the Pool Size
4753
4754                                 New_Reference_To (
4755                                   Storage_Size_Variable (Def_Id), Loc),
4756
4757                               --  Second discriminant is the element size
4758
4759                                 DT_Size,
4760
4761                               --  Third discriminant is the alignment
4762
4763                                 DT_Align)))));
4764                end;
4765
4766                Set_Associated_Storage_Pool (Def_Id, Pool_Object);
4767
4768             --  Case 3
4769
4770             --    Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
4771             --    ---> Storage Pool is the specified one
4772
4773             elsif Present (Associated_Storage_Pool (Def_Id)) then
4774
4775                --  Nothing to do the associated storage pool has been attached
4776                --  when analyzing the rep. clause
4777
4778                null;
4779             end if;
4780
4781             --  For access-to-controlled types (including class-wide types
4782             --  and Taft-amendment types which potentially have controlled
4783             --  components), expand the list controller object that will
4784             --  store the dynamically allocated objects. Do not do this
4785             --  transformation for expander-generated access types, but do it
4786             --  for types that are the full view of types derived from other
4787             --  private types. Also suppress the list controller in the case
4788             --  of a designated type with convention Java, since this is used
4789             --  when binding to Java API specs, where there's no equivalent
4790             --  of a finalization list and we don't want to pull in the
4791             --  finalization support if not needed.
4792
4793             if not Comes_From_Source (Def_Id)
4794                and then not Has_Private_Declaration (Def_Id)
4795             then
4796                null;
4797
4798             elsif (Controlled_Type (Desig_Type)
4799                     and then Convention (Desig_Type) /= Convention_Java)
4800               or else
4801                 (Is_Incomplete_Or_Private_Type (Desig_Type)
4802                    and then No (Full_View (Desig_Type))
4803
4804                   --  An exception is made for types defined in the run-time
4805                   --  because Ada.Tags.Tag itself is such a type and cannot
4806                   --  afford this unnecessary overhead that would generates a
4807                   --  loop in the expansion scheme...
4808
4809                   and then not In_Runtime (Def_Id)
4810
4811                   --  Another exception is if Restrictions (No_Finalization)
4812                   --  is active, since then we know nothing is controlled.
4813
4814                   and then not Restriction_Active (No_Finalization))
4815
4816                --  If the designated type is not frozen yet, its controlled
4817                --  status must be retrieved explicitly.
4818
4819               or else (Is_Array_Type (Desig_Type)
4820                 and then not Is_Frozen (Desig_Type)
4821                 and then Controlled_Type (Component_Type (Desig_Type)))
4822             then
4823                Set_Associated_Final_Chain (Def_Id,
4824                  Make_Defining_Identifier (Loc,
4825                    New_External_Name (Chars (Def_Id), 'L')));
4826
4827                Append_Freeze_Action (Def_Id,
4828                  Make_Object_Declaration (Loc,
4829                    Defining_Identifier => Associated_Final_Chain (Def_Id),
4830                    Object_Definition   =>
4831                      New_Reference_To (RTE (RE_List_Controller), Loc)));
4832             end if;
4833          end;
4834
4835       --  Freeze processing for enumeration types
4836
4837       elsif Ekind (Def_Id) = E_Enumeration_Type then
4838
4839          --  We only have something to do if we have a non-standard
4840          --  representation (i.e. at least one literal whose pos value
4841          --  is not the same as its representation)
4842
4843          if Has_Non_Standard_Rep (Def_Id) then
4844             Freeze_Enumeration_Type (N);
4845          end if;
4846
4847       --  Private types that are completed by a derivation from a private
4848       --  type have an internally generated full view, that needs to be
4849       --  frozen. This must be done explicitly because the two views share
4850       --  the freeze node, and the underlying full view is not visible when
4851       --  the freeze node is analyzed.
4852
4853       elsif Is_Private_Type (Def_Id)
4854         and then Is_Derived_Type (Def_Id)
4855         and then Present (Full_View (Def_Id))
4856         and then Is_Itype (Full_View (Def_Id))
4857         and then Has_Private_Declaration (Full_View (Def_Id))
4858         and then Freeze_Node (Full_View (Def_Id)) = N
4859       then
4860          Set_Entity (N, Full_View (Def_Id));
4861          Freeze_Type (N);
4862          Set_Entity (N, Def_Id);
4863
4864       --  All other types require no expander action. There are such
4865       --  cases (e.g. task types and protected types). In such cases,
4866       --  the freeze nodes are there for use by Gigi.
4867
4868       end if;
4869
4870       Freeze_Stream_Operations (N, Def_Id);
4871
4872    exception
4873       when RE_Not_Available =>
4874          return;
4875    end Freeze_Type;
4876
4877    -------------------------
4878    -- Get_Simple_Init_Val --
4879    -------------------------
4880
4881    function Get_Simple_Init_Val
4882      (T   : Entity_Id;
4883       Loc : Source_Ptr) return Node_Id
4884    is
4885       Val    : Node_Id;
4886       Typ    : Node_Id;
4887       Result : Node_Id;
4888       Val_RE : RE_Id;
4889
4890    begin
4891       --  For a private type, we should always have an underlying type
4892       --  (because this was already checked in Needs_Simple_Initialization).
4893       --  What we do is to get the value for the underlying type and then
4894       --  do an Unchecked_Convert to the private type.
4895
4896       if Is_Private_Type (T) then
4897          Val := Get_Simple_Init_Val (Underlying_Type (T), Loc);
4898
4899          --  A special case, if the underlying value is null, then qualify
4900          --  it with the underlying type, so that the null is properly typed
4901          --  Similarly, if it is an aggregate it must be qualified, because
4902          --  an unchecked conversion does not provide a context for it.
4903
4904          if Nkind (Val) = N_Null
4905            or else Nkind (Val) = N_Aggregate
4906          then
4907             Val :=
4908               Make_Qualified_Expression (Loc,
4909                 Subtype_Mark =>
4910                   New_Occurrence_Of (Underlying_Type (T), Loc),
4911                 Expression => Val);
4912          end if;
4913
4914          Result := Unchecked_Convert_To (T, Val);
4915
4916          --  Don't truncate result (important for Initialize/Normalize_Scalars)
4917
4918          if Nkind (Result) = N_Unchecked_Type_Conversion
4919            and then Is_Scalar_Type (Underlying_Type (T))
4920          then
4921             Set_No_Truncation (Result);
4922          end if;
4923
4924          return Result;
4925
4926       --  For scalars, we must have normalize/initialize scalars case
4927
4928       elsif Is_Scalar_Type (T) then
4929          pragma Assert (Init_Or_Norm_Scalars);
4930
4931          --  Processing for Normalize_Scalars case
4932
4933          if Normalize_Scalars then
4934
4935             --  First prepare a value (out of subtype range if possible)
4936
4937             if Is_Real_Type (T) or else Is_Integer_Type (T) then
4938                Val :=
4939                  Make_Attribute_Reference (Loc,
4940                    Prefix => New_Occurrence_Of (Base_Type (T), Loc),
4941                    Attribute_Name => Name_First);
4942
4943             elsif Is_Modular_Integer_Type (T) then
4944                Val :=
4945                  Make_Attribute_Reference (Loc,
4946                    Prefix => New_Occurrence_Of (Base_Type (T), Loc),
4947                    Attribute_Name => Name_Last);
4948
4949             else
4950                pragma Assert (Is_Enumeration_Type (T));
4951
4952                if Esize (T) <= 8 then
4953                   Typ := RTE (RE_Unsigned_8);
4954                elsif Esize (T) <= 16 then
4955                   Typ := RTE (RE_Unsigned_16);
4956                elsif Esize (T) <= 32 then
4957                   Typ := RTE (RE_Unsigned_32);
4958                else
4959                   Typ := RTE (RE_Unsigned_64);
4960                end if;
4961
4962                Val :=
4963                  Make_Attribute_Reference (Loc,
4964                    Prefix => New_Occurrence_Of (Typ, Loc),
4965                    Attribute_Name => Name_Last);
4966             end if;
4967
4968          --  Here for Initialize_Scalars case
4969
4970          else
4971             if Is_Floating_Point_Type (T) then
4972                if Root_Type (T) = Standard_Short_Float then
4973                   Val_RE := RE_IS_Isf;
4974                elsif Root_Type (T) = Standard_Float then
4975                   Val_RE := RE_IS_Ifl;
4976                elsif Root_Type (T) = Standard_Long_Float then
4977                   Val_RE := RE_IS_Ilf;
4978                else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
4979                   Val_RE := RE_IS_Ill;
4980                end if;
4981
4982             elsif Is_Unsigned_Type (Base_Type (T)) then
4983                if Esize (T) = 8 then
4984                   Val_RE := RE_IS_Iu1;
4985                elsif Esize (T) = 16 then
4986                   Val_RE := RE_IS_Iu2;
4987                elsif Esize (T) = 32 then
4988                   Val_RE := RE_IS_Iu4;
4989                else pragma Assert (Esize (T) = 64);
4990                   Val_RE := RE_IS_Iu8;
4991                end if;
4992
4993             else -- signed type
4994                if Esize (T) = 8 then
4995                   Val_RE := RE_IS_Is1;
4996                elsif Esize (T) = 16 then
4997                   Val_RE := RE_IS_Is2;
4998                elsif Esize (T) = 32 then
4999                   Val_RE := RE_IS_Is4;
5000                else pragma Assert (Esize (T) = 64);
5001                   Val_RE := RE_IS_Is8;
5002                end if;
5003             end if;
5004
5005             Val := New_Occurrence_Of (RTE (Val_RE), Loc);
5006          end if;
5007
5008          --  The final expression is obtained by doing an unchecked
5009          --  conversion of this result to the base type of the
5010          --  required subtype. We use the base type to avoid the
5011          --  unchecked conversion from chopping bits, and then we
5012          --  set Kill_Range_Check to preserve the "bad" value.
5013
5014          Result := Unchecked_Convert_To (Base_Type (T), Val);
5015
5016          --  Ensure result is not truncated, since we want the "bad" bits
5017          --  and also kill range check on result.
5018
5019          if Nkind (Result) = N_Unchecked_Type_Conversion then
5020             Set_No_Truncation (Result);
5021             Set_Kill_Range_Check (Result, True);
5022          end if;
5023
5024          return Result;
5025
5026       --  String or Wide_String (must have Initialize_Scalars set)
5027
5028       elsif Root_Type (T) = Standard_String
5029               or else
5030             Root_Type (T) = Standard_Wide_String
5031       then
5032          pragma Assert (Init_Or_Norm_Scalars);
5033
5034          return
5035            Make_Aggregate (Loc,
5036              Component_Associations => New_List (
5037                Make_Component_Association (Loc,
5038                  Choices => New_List (
5039                    Make_Others_Choice (Loc)),
5040                  Expression =>
5041                    Get_Simple_Init_Val (Component_Type (T), Loc))));
5042
5043       --  Access type is initialized to null
5044
5045       elsif Is_Access_Type (T) then
5046          return
5047            Make_Null (Loc);
5048
5049       --  We initialize modular packed bit arrays to zero, to make sure that
5050       --  unused bits are zero, as required (see spec of Exp_Pakd). Also note
5051       --  that this improves gigi code, since the value tracing knows that
5052       --  all bits of the variable start out at zero. The value of zero has
5053       --  to be unchecked converted to the proper array type.
5054
5055       elsif Is_Bit_Packed_Array (T) then
5056          declare
5057             PAT : constant Entity_Id := Packed_Array_Type (T);
5058             Nod : Node_Id;
5059
5060          begin
5061             pragma Assert (Is_Modular_Integer_Type (PAT));
5062
5063             Nod :=
5064               Make_Unchecked_Type_Conversion (Loc,
5065                 Subtype_Mark => New_Occurrence_Of (T, Loc),
5066                 Expression   => Make_Integer_Literal (Loc, 0));
5067
5068             Set_Etype (Expression (Nod), PAT);
5069             return Nod;
5070          end;
5071
5072       --  No other possibilities should arise, since we should only be
5073       --  calling Get_Simple_Init_Val if Needs_Simple_Initialization
5074       --  returned True, indicating one of the above cases held.
5075
5076       else
5077          raise Program_Error;
5078       end if;
5079
5080    exception
5081       when RE_Not_Available =>
5082          return Empty;
5083    end Get_Simple_Init_Val;
5084
5085    ------------------------------
5086    -- Has_New_Non_Standard_Rep --
5087    ------------------------------
5088
5089    function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
5090    begin
5091       if not Is_Derived_Type (T) then
5092          return Has_Non_Standard_Rep (T)
5093            or else Has_Non_Standard_Rep (Root_Type (T));
5094
5095       --  If Has_Non_Standard_Rep is not set on the derived type, the
5096       --  representation is fully inherited.
5097
5098       elsif not Has_Non_Standard_Rep (T) then
5099          return False;
5100
5101       else
5102          return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
5103
5104          --  May need a more precise check here: the First_Rep_Item may
5105          --  be a stream attribute, which does not affect the representation
5106          --  of the type ???
5107       end if;
5108    end Has_New_Non_Standard_Rep;
5109
5110    ----------------
5111    -- In_Runtime --
5112    ----------------
5113
5114    function In_Runtime (E : Entity_Id) return Boolean is
5115       S1 : Entity_Id := Scope (E);
5116
5117    begin
5118       while Scope (S1) /= Standard_Standard loop
5119          S1 := Scope (S1);
5120       end loop;
5121
5122       return Chars (S1) = Name_System or else Chars (S1) = Name_Ada;
5123    end In_Runtime;
5124
5125    ------------------
5126    -- Init_Formals --
5127    ------------------
5128
5129    function Init_Formals (Typ : Entity_Id) return List_Id is
5130       Loc     : constant Source_Ptr := Sloc (Typ);
5131       Formals : List_Id;
5132
5133    begin
5134       --  First parameter is always _Init : in out typ. Note that we need
5135       --  this to be in/out because in the case of the task record value,
5136       --  there are default record fields (_Priority, _Size, -Task_Info)
5137       --  that may be referenced in the generated initialization routine.
5138
5139       Formals := New_List (
5140         Make_Parameter_Specification (Loc,
5141           Defining_Identifier =>
5142             Make_Defining_Identifier (Loc, Name_uInit),
5143           In_Present  => True,
5144           Out_Present => True,
5145           Parameter_Type => New_Reference_To (Typ, Loc)));
5146
5147       --  For task record value, or type that contains tasks, add two more
5148       --  formals, _Master : Master_Id and _Chain : in out Activation_Chain
5149       --  We also add these parameters for the task record type case.
5150
5151       if Has_Task (Typ)
5152         or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
5153       then
5154          Append_To (Formals,
5155            Make_Parameter_Specification (Loc,
5156              Defining_Identifier =>
5157                Make_Defining_Identifier (Loc, Name_uMaster),
5158              Parameter_Type => New_Reference_To (RTE (RE_Master_Id), Loc)));
5159
5160          Append_To (Formals,
5161            Make_Parameter_Specification (Loc,
5162              Defining_Identifier =>
5163                Make_Defining_Identifier (Loc, Name_uChain),
5164              In_Present => True,
5165              Out_Present => True,
5166              Parameter_Type =>
5167                New_Reference_To (RTE (RE_Activation_Chain), Loc)));
5168
5169          Append_To (Formals,
5170            Make_Parameter_Specification (Loc,
5171              Defining_Identifier =>
5172                Make_Defining_Identifier (Loc, Name_uTask_Name),
5173              In_Present => True,
5174              Parameter_Type =>
5175                New_Reference_To (Standard_String, Loc)));
5176       end if;
5177
5178       return Formals;
5179
5180    exception
5181       when RE_Not_Available =>
5182          return Empty_List;
5183    end Init_Formals;
5184
5185    ------------------
5186    -- Make_Eq_Case --
5187    ------------------
5188
5189    --  <Make_Eq_if shared components>
5190    --  case X.D1 is
5191    --     when V1 => <Make_Eq_Case> on subcomponents
5192    --     ...
5193    --     when Vn => <Make_Eq_Case> on subcomponents
5194    --  end case;
5195
5196    function Make_Eq_Case
5197      (E     : Entity_Id;
5198       CL    : Node_Id;
5199       Discr : Entity_Id := Empty) return List_Id
5200    is
5201       Loc      : constant Source_Ptr := Sloc (E);
5202       Result   : constant List_Id    := New_List;
5203       Variant  : Node_Id;
5204       Alt_List : List_Id;
5205
5206    begin
5207       Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
5208
5209       if No (Variant_Part (CL)) then
5210          return Result;
5211       end if;
5212
5213       Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
5214
5215       if No (Variant) then
5216          return Result;
5217       end if;
5218
5219       Alt_List := New_List;
5220
5221       while Present (Variant) loop
5222          Append_To (Alt_List,
5223            Make_Case_Statement_Alternative (Loc,
5224              Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
5225              Statements => Make_Eq_Case (E, Component_List (Variant))));
5226
5227          Next_Non_Pragma (Variant);
5228       end loop;
5229
5230       --  If we have an Unchecked_Union, use one of the parameters that
5231       --  captures the discriminants.
5232
5233       if Is_Unchecked_Union (E) then
5234          Append_To (Result,
5235            Make_Case_Statement (Loc,
5236              Expression => New_Reference_To (Discr, Loc),
5237              Alternatives => Alt_List));
5238
5239       else
5240          Append_To (Result,
5241            Make_Case_Statement (Loc,
5242              Expression =>
5243                Make_Selected_Component (Loc,
5244                  Prefix => Make_Identifier (Loc, Name_X),
5245                  Selector_Name => New_Copy (Name (Variant_Part (CL)))),
5246              Alternatives => Alt_List));
5247       end if;
5248
5249       return Result;
5250    end Make_Eq_Case;
5251
5252    ----------------
5253    -- Make_Eq_If --
5254    ----------------
5255
5256    --  Generates:
5257
5258    --    if
5259    --      X.C1 /= Y.C1
5260    --        or else
5261    --      X.C2 /= Y.C2
5262    --        ...
5263    --    then
5264    --       return False;
5265    --    end if;
5266
5267    --  or a null statement if the list L is empty
5268
5269    function Make_Eq_If
5270      (E : Entity_Id;
5271       L : List_Id) return Node_Id
5272    is
5273       Loc        : constant Source_Ptr := Sloc (E);
5274       C          : Node_Id;
5275       Field_Name : Name_Id;
5276       Cond       : Node_Id;
5277
5278    begin
5279       if No (L) then
5280          return Make_Null_Statement (Loc);
5281
5282       else
5283          Cond := Empty;
5284
5285          C := First_Non_Pragma (L);
5286          while Present (C) loop
5287             Field_Name := Chars (Defining_Identifier (C));
5288
5289             --  The tags must not be compared they are not part of the value.
5290             --  Note also that in the following, we use Make_Identifier for
5291             --  the component names. Use of New_Reference_To to identify the
5292             --  components would be incorrect because the wrong entities for
5293             --  discriminants could be picked up in the private type case.
5294
5295             if Field_Name /= Name_uTag then
5296                Evolve_Or_Else (Cond,
5297                  Make_Op_Ne (Loc,
5298                    Left_Opnd =>
5299                      Make_Selected_Component (Loc,
5300                        Prefix        => Make_Identifier (Loc, Name_X),
5301                        Selector_Name =>
5302                          Make_Identifier (Loc, Field_Name)),
5303
5304                    Right_Opnd =>
5305                      Make_Selected_Component (Loc,
5306                        Prefix        => Make_Identifier (Loc, Name_Y),
5307                        Selector_Name =>
5308                          Make_Identifier (Loc, Field_Name))));
5309             end if;
5310
5311             Next_Non_Pragma (C);
5312          end loop;
5313
5314          if No (Cond) then
5315             return Make_Null_Statement (Loc);
5316
5317          else
5318             return
5319               Make_Implicit_If_Statement (E,
5320                 Condition => Cond,
5321                 Then_Statements => New_List (
5322                   Make_Return_Statement (Loc,
5323                     Expression => New_Occurrence_Of (Standard_False, Loc))));
5324          end if;
5325       end if;
5326    end Make_Eq_If;
5327
5328    -------------------------------------
5329    -- Make_Predefined_Primitive_Specs --
5330    -------------------------------------
5331
5332    procedure Make_Predefined_Primitive_Specs
5333      (Tag_Typ     : Entity_Id;
5334       Predef_List : out List_Id;
5335       Renamed_Eq  : out Node_Id)
5336    is
5337       Loc       : constant Source_Ptr := Sloc (Tag_Typ);
5338       Res       : constant List_Id    := New_List;
5339       Prim      : Elmt_Id;
5340       Eq_Needed : Boolean;
5341       Eq_Spec   : Node_Id;
5342       Eq_Name   : Name_Id := Name_Op_Eq;
5343
5344       function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
5345       --  Returns true if Prim is a renaming of an unresolved predefined
5346       --  equality operation.
5347
5348       -------------------------------
5349       -- Is_Predefined_Eq_Renaming --
5350       -------------------------------
5351
5352       function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
5353       begin
5354          return Chars (Prim) /= Name_Op_Eq
5355            and then Present (Alias (Prim))
5356            and then Comes_From_Source (Prim)
5357            and then Is_Intrinsic_Subprogram (Alias (Prim))
5358            and then Chars (Alias (Prim)) = Name_Op_Eq;
5359       end Is_Predefined_Eq_Renaming;
5360
5361    --  Start of processing for Make_Predefined_Primitive_Specs
5362
5363    begin
5364       Renamed_Eq := Empty;
5365
5366       --  Spec of _Alignment
5367
5368       Append_To (Res, Predef_Spec_Or_Body (Loc,
5369         Tag_Typ => Tag_Typ,
5370         Name    => Name_uAlignment,
5371         Profile => New_List (
5372           Make_Parameter_Specification (Loc,
5373             Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5374             Parameter_Type      => New_Reference_To (Tag_Typ, Loc))),
5375
5376         Ret_Type => Standard_Integer));
5377
5378       --  Spec of _Size
5379
5380       Append_To (Res, Predef_Spec_Or_Body (Loc,
5381         Tag_Typ => Tag_Typ,
5382         Name    => Name_uSize,
5383         Profile => New_List (
5384           Make_Parameter_Specification (Loc,
5385             Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5386             Parameter_Type      => New_Reference_To (Tag_Typ, Loc))),
5387
5388         Ret_Type => Standard_Long_Long_Integer));
5389
5390       --  Specs for dispatching stream attributes. We skip these for limited
5391       --  types, since there is no question of dispatching in the limited case.
5392
5393       --  We also skip these operations if dispatching is not available
5394       --  or if streams are not available (since what's the point?)
5395
5396       if not Is_Limited_Type (Tag_Typ)
5397         and then RTE_Available (RE_Tag)
5398         and then RTE_Available (RE_Root_Stream_Type)
5399       then
5400          Append_To (Res,
5401            Predef_Stream_Attr_Spec (Loc, Tag_Typ, TSS_Stream_Read));
5402          Append_To (Res,
5403            Predef_Stream_Attr_Spec (Loc, Tag_Typ, TSS_Stream_Write));
5404          Append_To (Res,
5405            Predef_Stream_Attr_Spec (Loc, Tag_Typ, TSS_Stream_Input));
5406          Append_To (Res,
5407            Predef_Stream_Attr_Spec (Loc, Tag_Typ, TSS_Stream_Output));
5408       end if;
5409
5410       --  Spec of "=" if expanded if the type is not limited and if a
5411       --  user defined "=" was not already declared for the non-full
5412       --  view of a private extension
5413
5414       if not Is_Limited_Type (Tag_Typ) then
5415          Eq_Needed := True;
5416
5417          Prim := First_Elmt (Primitive_Operations (Tag_Typ));
5418          while Present (Prim) loop
5419
5420             --  If a primitive is encountered that renames the predefined
5421             --  equality operator before reaching any explicit equality
5422             --  primitive, then we still need to create a predefined
5423             --  equality function, because calls to it can occur via
5424             --  the renaming. A new name is created for the equality
5425             --  to avoid conflicting with any user-defined equality.
5426             --  (Note that this doesn't account for renamings of
5427             --  equality nested within subpackages???)
5428
5429             if Is_Predefined_Eq_Renaming (Node (Prim)) then
5430                Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
5431
5432             elsif Chars (Node (Prim)) = Name_Op_Eq
5433               and then (No (Alias (Node (Prim)))
5434                          or else Nkind (Unit_Declaration_Node (Node (Prim))) =
5435                                             N_Subprogram_Renaming_Declaration)
5436               and then Etype (First_Formal (Node (Prim))) =
5437                          Etype (Next_Formal (First_Formal (Node (Prim))))
5438               and then Base_Type (Etype (Node (Prim))) = Standard_Boolean
5439
5440             then
5441                Eq_Needed := False;
5442                exit;
5443
5444             --  If the parent equality is abstract, the inherited equality is
5445             --  abstract as well, and no body can be created for for it.
5446
5447             elsif Chars (Node (Prim)) = Name_Op_Eq
5448               and then Present (Alias (Node (Prim)))
5449               and then Is_Abstract (Alias (Node (Prim)))
5450             then
5451                Eq_Needed := False;
5452                exit;
5453             end if;
5454
5455             Next_Elmt (Prim);
5456          end loop;
5457
5458          --  If a renaming of predefined equality was found
5459          --  but there was no user-defined equality (so Eq_Needed
5460          --  is still true), then set the name back to Name_Op_Eq.
5461          --  But in the case where a user-defined equality was
5462          --  located after such a renaming, then the predefined
5463          --  equality function is still needed, so Eq_Needed must
5464          --  be set back to True.
5465
5466          if Eq_Name /= Name_Op_Eq then
5467             if Eq_Needed then
5468                Eq_Name := Name_Op_Eq;
5469             else
5470                Eq_Needed := True;
5471             end if;
5472          end if;
5473
5474          if Eq_Needed then
5475             Eq_Spec := Predef_Spec_Or_Body (Loc,
5476               Tag_Typ => Tag_Typ,
5477               Name    => Eq_Name,
5478               Profile => New_List (
5479                 Make_Parameter_Specification (Loc,
5480                   Defining_Identifier =>
5481                     Make_Defining_Identifier (Loc, Name_X),
5482                     Parameter_Type      => New_Reference_To (Tag_Typ, Loc)),
5483                 Make_Parameter_Specification (Loc,
5484                   Defining_Identifier =>
5485                     Make_Defining_Identifier (Loc, Name_Y),
5486                     Parameter_Type      => New_Reference_To (Tag_Typ, Loc))),
5487                 Ret_Type => Standard_Boolean);
5488             Append_To (Res, Eq_Spec);
5489
5490             if Eq_Name /= Name_Op_Eq then
5491                Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
5492
5493                Prim := First_Elmt (Primitive_Operations (Tag_Typ));
5494                while Present (Prim) loop
5495
5496                   --  Any renamings of equality that appeared before an
5497                   --  overriding equality must be updated to refer to
5498                   --  the entity for the predefined equality, otherwise
5499                   --  calls via the renaming would get incorrectly
5500                   --  resolved to call the user-defined equality function.
5501
5502                   if Is_Predefined_Eq_Renaming (Node (Prim)) then
5503                      Set_Alias (Node (Prim), Renamed_Eq);
5504
5505                   --  Exit upon encountering a user-defined equality
5506
5507                   elsif Chars (Node (Prim)) = Name_Op_Eq
5508                     and then No (Alias (Node (Prim)))
5509                   then
5510                      exit;
5511                   end if;
5512
5513                   Next_Elmt (Prim);
5514                end loop;
5515             end if;
5516          end if;
5517
5518          --  Spec for dispatching assignment
5519
5520          Append_To (Res, Predef_Spec_Or_Body (Loc,
5521            Tag_Typ => Tag_Typ,
5522            Name    => Name_uAssign,
5523            Profile => New_List (
5524              Make_Parameter_Specification (Loc,
5525                Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5526                Out_Present         => True,
5527                Parameter_Type      => New_Reference_To (Tag_Typ, Loc)),
5528
5529              Make_Parameter_Specification (Loc,
5530                Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
5531                Parameter_Type      => New_Reference_To (Tag_Typ, Loc)))));
5532       end if;
5533
5534       --  Specs for finalization actions that may be required in case a
5535       --  future extension contain a controlled element. We generate those
5536       --  only for root tagged types where they will get dummy bodies or
5537       --  when the type has controlled components and their body must be
5538       --  generated. It is also impossible to provide those for tagged
5539       --  types defined within s-finimp since it would involve circularity
5540       --  problems
5541
5542       if In_Finalization_Root (Tag_Typ) then
5543          null;
5544
5545       --  We also skip these if finalization is not available
5546
5547       elsif Restriction_Active (No_Finalization) then
5548          null;
5549
5550       elsif Etype (Tag_Typ) = Tag_Typ or else Controlled_Type (Tag_Typ) then
5551          if not Is_Limited_Type (Tag_Typ) then
5552             Append_To (Res,
5553               Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
5554          end if;
5555
5556          Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
5557       end if;
5558
5559       Predef_List := Res;
5560    end Make_Predefined_Primitive_Specs;
5561
5562    ---------------------------------
5563    -- Needs_Simple_Initialization --
5564    ---------------------------------
5565
5566    function Needs_Simple_Initialization (T : Entity_Id) return Boolean is
5567    begin
5568       --  Check for private type, in which case test applies to the
5569       --  underlying type of the private type.
5570
5571       if Is_Private_Type (T) then
5572          declare
5573             RT : constant Entity_Id := Underlying_Type (T);
5574
5575          begin
5576             if Present (RT) then
5577                return Needs_Simple_Initialization (RT);
5578             else
5579                return False;
5580             end if;
5581          end;
5582
5583       --  Cases needing simple initialization are access types, and, if pragma
5584       --  Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
5585       --  types.
5586
5587       elsif Is_Access_Type (T)
5588         or else (Init_Or_Norm_Scalars and then (Is_Scalar_Type (T)))
5589         or else (Is_Bit_Packed_Array (T)
5590                    and then Is_Modular_Integer_Type (Packed_Array_Type (T)))
5591       then
5592          return True;
5593
5594       --  If Initialize/Normalize_Scalars is in effect, string objects also
5595       --  need initialization, unless they are created in the course of
5596       --  expanding an aggregate (since in the latter case they will be
5597       --  filled with appropriate initializing values before they are used).
5598
5599       elsif Init_Or_Norm_Scalars
5600         and then
5601           (Root_Type (T) = Standard_String
5602             or else Root_Type (T) = Standard_Wide_String)
5603         and then
5604           (not Is_Itype (T)
5605             or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
5606       then
5607          return True;
5608
5609       else
5610          return False;
5611       end if;
5612    end Needs_Simple_Initialization;
5613
5614    ----------------------
5615    -- Predef_Deep_Spec --
5616    ----------------------
5617
5618    function Predef_Deep_Spec
5619      (Loc      : Source_Ptr;
5620       Tag_Typ  : Entity_Id;
5621       Name     : TSS_Name_Type;
5622       For_Body : Boolean := False) return Node_Id
5623    is
5624       Prof   : List_Id;
5625       Type_B : Entity_Id;
5626
5627    begin
5628       if Name = TSS_Deep_Finalize then
5629          Prof := New_List;
5630          Type_B := Standard_Boolean;
5631
5632       else
5633          Prof := New_List (
5634            Make_Parameter_Specification (Loc,
5635              Defining_Identifier => Make_Defining_Identifier (Loc, Name_L),
5636              In_Present          => True,
5637              Out_Present         => True,
5638              Parameter_Type      =>
5639                New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
5640          Type_B := Standard_Short_Short_Integer;
5641       end if;
5642
5643       Append_To (Prof,
5644            Make_Parameter_Specification (Loc,
5645              Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
5646              In_Present          => True,
5647              Out_Present         => True,
5648              Parameter_Type      => New_Reference_To (Tag_Typ, Loc)));
5649
5650       Append_To (Prof,
5651            Make_Parameter_Specification (Loc,
5652              Defining_Identifier => Make_Defining_Identifier (Loc, Name_B),
5653              Parameter_Type      => New_Reference_To (Type_B, Loc)));
5654
5655       return Predef_Spec_Or_Body (Loc,
5656         Name     => Make_TSS_Name (Tag_Typ, Name),
5657         Tag_Typ  => Tag_Typ,
5658         Profile  => Prof,
5659         For_Body => For_Body);
5660
5661    exception
5662       when RE_Not_Available =>
5663          return Empty;
5664    end Predef_Deep_Spec;
5665
5666    -------------------------
5667    -- Predef_Spec_Or_Body --
5668    -------------------------
5669
5670    function Predef_Spec_Or_Body
5671      (Loc      : Source_Ptr;
5672       Tag_Typ  : Entity_Id;
5673       Name     : Name_Id;
5674       Profile  : List_Id;
5675       Ret_Type : Entity_Id := Empty;
5676       For_Body : Boolean := False) return Node_Id
5677    is
5678       Id   : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
5679       Spec : Node_Id;
5680
5681    begin
5682       Set_Is_Public (Id, Is_Public (Tag_Typ));
5683
5684       --  The internal flag is set to mark these declarations because
5685       --  they have specific properties. First they are primitives even
5686       --  if they are not defined in the type scope (the freezing point
5687       --  is not necessarily in the same scope), furthermore the
5688       --  predefined equality can be overridden by a user-defined
5689       --  equality, no body will be generated in this case.
5690
5691       Set_Is_Internal (Id);
5692
5693       if not Debug_Generated_Code then
5694          Set_Debug_Info_Off (Id);
5695       end if;
5696
5697       if No (Ret_Type) then
5698          Spec :=
5699            Make_Procedure_Specification (Loc,
5700              Defining_Unit_Name       => Id,
5701              Parameter_Specifications => Profile);
5702       else
5703          Spec :=
5704            Make_Function_Specification (Loc,
5705              Defining_Unit_Name       => Id,
5706              Parameter_Specifications => Profile,
5707              Subtype_Mark             =>
5708                New_Reference_To (Ret_Type, Loc));
5709       end if;
5710
5711       --  If body case, return empty subprogram body. Note that this is
5712       --  ill-formed, because there is not even a null statement, and
5713       --  certainly not a return in the function case. The caller is
5714       --  expected to do surgery on the body to add the appropriate stuff.
5715
5716       if For_Body then
5717          return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
5718
5719       --  For the case of Input/Output attributes applied to an abstract type,
5720       --  generate abstract specifications. These will never be called,
5721       --  but we need the slots allocated in the dispatching table so
5722       --  that typ'Class'Input and typ'Class'Output will work properly.
5723
5724       elsif (Is_TSS (Name, TSS_Stream_Input)
5725               or else
5726              Is_TSS (Name, TSS_Stream_Output))
5727         and then Is_Abstract (Tag_Typ)
5728       then
5729          return Make_Abstract_Subprogram_Declaration (Loc, Spec);
5730
5731       --  Normal spec case, where we return a subprogram declaration
5732
5733       else
5734          return Make_Subprogram_Declaration (Loc, Spec);
5735       end if;
5736    end Predef_Spec_Or_Body;
5737
5738    -----------------------------
5739    -- Predef_Stream_Attr_Spec --
5740    -----------------------------
5741
5742    function Predef_Stream_Attr_Spec
5743      (Loc      : Source_Ptr;
5744       Tag_Typ  : Entity_Id;
5745       Name     : TSS_Name_Type;
5746       For_Body : Boolean := False) return Node_Id
5747    is
5748       Ret_Type : Entity_Id;
5749
5750    begin
5751       if Name = TSS_Stream_Input then
5752          Ret_Type := Tag_Typ;
5753       else
5754          Ret_Type := Empty;
5755       end if;
5756
5757       return Predef_Spec_Or_Body (Loc,
5758         Name     => Make_TSS_Name (Tag_Typ, Name),
5759         Tag_Typ  => Tag_Typ,
5760         Profile  => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
5761         Ret_Type => Ret_Type,
5762         For_Body => For_Body);
5763    end Predef_Stream_Attr_Spec;
5764
5765    ---------------------------------
5766    -- Predefined_Primitive_Bodies --
5767    ---------------------------------
5768
5769    function Predefined_Primitive_Bodies
5770      (Tag_Typ    : Entity_Id;
5771       Renamed_Eq : Node_Id) return List_Id
5772    is
5773       Loc       : constant Source_Ptr := Sloc (Tag_Typ);
5774       Res       : constant List_Id    := New_List;
5775       Decl      : Node_Id;
5776       Prim      : Elmt_Id;
5777       Eq_Needed : Boolean;
5778       Eq_Name   : Name_Id;
5779       Ent       : Entity_Id;
5780
5781    begin
5782       --  See if we have a predefined "=" operator
5783
5784       if Present (Renamed_Eq) then
5785          Eq_Needed := True;
5786          Eq_Name   := Chars (Renamed_Eq);
5787
5788       else
5789          Eq_Needed := False;
5790          Eq_Name   := No_Name;
5791
5792          Prim := First_Elmt (Primitive_Operations (Tag_Typ));
5793          while Present (Prim) loop
5794             if Chars (Node (Prim)) = Name_Op_Eq
5795               and then Is_Internal (Node (Prim))
5796             then
5797                Eq_Needed := True;
5798                Eq_Name := Name_Op_Eq;
5799             end if;
5800
5801             Next_Elmt (Prim);
5802          end loop;
5803       end if;
5804
5805       --  Body of _Alignment
5806
5807       Decl := Predef_Spec_Or_Body (Loc,
5808         Tag_Typ => Tag_Typ,
5809         Name    => Name_uAlignment,
5810         Profile => New_List (
5811           Make_Parameter_Specification (Loc,
5812             Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5813             Parameter_Type      => New_Reference_To (Tag_Typ, Loc))),
5814
5815         Ret_Type => Standard_Integer,
5816         For_Body => True);
5817
5818       Set_Handled_Statement_Sequence (Decl,
5819         Make_Handled_Sequence_Of_Statements (Loc, New_List (
5820           Make_Return_Statement (Loc,
5821             Expression =>
5822               Make_Attribute_Reference (Loc,
5823                 Prefix => Make_Identifier (Loc, Name_X),
5824                 Attribute_Name  => Name_Alignment)))));
5825
5826       Append_To (Res, Decl);
5827
5828       --  Body of _Size
5829
5830       Decl := Predef_Spec_Or_Body (Loc,
5831         Tag_Typ => Tag_Typ,
5832         Name    => Name_uSize,
5833         Profile => New_List (
5834           Make_Parameter_Specification (Loc,
5835             Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5836             Parameter_Type      => New_Reference_To (Tag_Typ, Loc))),
5837
5838         Ret_Type => Standard_Long_Long_Integer,
5839         For_Body => True);
5840
5841       Set_Handled_Statement_Sequence (Decl,
5842         Make_Handled_Sequence_Of_Statements (Loc, New_List (
5843           Make_Return_Statement (Loc,
5844             Expression =>
5845               Make_Attribute_Reference (Loc,
5846                 Prefix => Make_Identifier (Loc, Name_X),
5847                 Attribute_Name  => Name_Size)))));
5848
5849       Append_To (Res, Decl);
5850
5851       --  Bodies for Dispatching stream IO routines. We need these only for
5852       --  non-limited types (in the limited case there is no dispatching).
5853       --  We also skip them if dispatching is not available.
5854
5855       if not Is_Limited_Type (Tag_Typ)
5856         and then not Restriction_Active (No_Finalization)
5857       then
5858          if No (TSS (Tag_Typ, TSS_Stream_Read)) then
5859             Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
5860             Append_To (Res, Decl);
5861          end if;
5862
5863          if No (TSS (Tag_Typ, TSS_Stream_Write)) then
5864             Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
5865             Append_To (Res, Decl);
5866          end if;
5867
5868          --  Skip bodies of _Input and _Output for the abstract case, since
5869          --  the corresponding specs are abstract (see Predef_Spec_Or_Body)
5870
5871          if not Is_Abstract (Tag_Typ) then
5872             if No (TSS (Tag_Typ, TSS_Stream_Input)) then
5873                Build_Record_Or_Elementary_Input_Function
5874                  (Loc, Tag_Typ, Decl, Ent);
5875                Append_To (Res, Decl);
5876             end if;
5877
5878             if No (TSS (Tag_Typ, TSS_Stream_Output)) then
5879                Build_Record_Or_Elementary_Output_Procedure
5880                  (Loc, Tag_Typ, Decl, Ent);
5881                Append_To (Res, Decl);
5882             end if;
5883          end if;
5884       end if;
5885
5886       if not Is_Limited_Type (Tag_Typ) then
5887
5888          --  Body for equality
5889
5890          if Eq_Needed then
5891
5892             Decl := Predef_Spec_Or_Body (Loc,
5893               Tag_Typ => Tag_Typ,
5894               Name    => Eq_Name,
5895               Profile => New_List (
5896                 Make_Parameter_Specification (Loc,
5897                   Defining_Identifier =>
5898                     Make_Defining_Identifier (Loc, Name_X),
5899                   Parameter_Type      => New_Reference_To (Tag_Typ, Loc)),
5900
5901                 Make_Parameter_Specification (Loc,
5902                   Defining_Identifier =>
5903                     Make_Defining_Identifier (Loc, Name_Y),
5904                   Parameter_Type      => New_Reference_To (Tag_Typ, Loc))),
5905
5906               Ret_Type => Standard_Boolean,
5907               For_Body => True);
5908
5909             declare
5910                Def          : constant Node_Id := Parent (Tag_Typ);
5911                Stmts        : constant List_Id := New_List;
5912                Variant_Case : Boolean := Has_Discriminants (Tag_Typ);
5913                Comps        : Node_Id := Empty;
5914                Typ_Def      : Node_Id := Type_Definition (Def);
5915
5916             begin
5917                if Variant_Case then
5918                   if Nkind (Typ_Def) = N_Derived_Type_Definition then
5919                      Typ_Def := Record_Extension_Part (Typ_Def);
5920                   end if;
5921
5922                   if Present (Typ_Def) then
5923                      Comps := Component_List (Typ_Def);
5924                   end if;
5925
5926                   Variant_Case := Present (Comps)
5927                     and then Present (Variant_Part (Comps));
5928                end if;
5929
5930                if Variant_Case then
5931                   Append_To (Stmts,
5932                     Make_Eq_If (Tag_Typ, Discriminant_Specifications (Def)));
5933                   Append_List_To (Stmts, Make_Eq_Case (Tag_Typ, Comps));
5934                   Append_To (Stmts,
5935                     Make_Return_Statement (Loc,
5936                       Expression => New_Reference_To (Standard_True, Loc)));
5937
5938                else
5939                   Append_To (Stmts,
5940                     Make_Return_Statement (Loc,
5941                       Expression =>
5942                         Expand_Record_Equality (Tag_Typ,
5943                           Typ => Tag_Typ,
5944                           Lhs => Make_Identifier (Loc, Name_X),
5945                           Rhs => Make_Identifier (Loc, Name_Y),
5946                           Bodies => Declarations (Decl))));
5947                end if;
5948
5949                Set_Handled_Statement_Sequence (Decl,
5950                  Make_Handled_Sequence_Of_Statements (Loc, Stmts));
5951             end;
5952             Append_To (Res, Decl);
5953          end if;
5954
5955          --  Body for dispatching assignment
5956
5957          Decl := Predef_Spec_Or_Body (Loc,
5958            Tag_Typ => Tag_Typ,
5959            Name    => Name_uAssign,
5960            Profile => New_List (
5961              Make_Parameter_Specification (Loc,
5962                Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
5963                Out_Present         => True,
5964                Parameter_Type      => New_Reference_To (Tag_Typ, Loc)),
5965
5966              Make_Parameter_Specification (Loc,
5967                Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
5968                Parameter_Type      => New_Reference_To (Tag_Typ, Loc))),
5969            For_Body => True);
5970
5971          Set_Handled_Statement_Sequence (Decl,
5972            Make_Handled_Sequence_Of_Statements (Loc, New_List (
5973              Make_Assignment_Statement (Loc,
5974                Name       => Make_Identifier (Loc, Name_X),
5975                Expression => Make_Identifier (Loc, Name_Y)))));
5976
5977          Append_To (Res, Decl);
5978       end if;
5979
5980       --  Generate dummy bodies for finalization actions of types that have
5981       --  no controlled components.
5982
5983       --  Skip this processing if we are in the finalization routine in the
5984       --  runtime itself, otherwise we get hopelessly circularly confused!
5985
5986       if In_Finalization_Root (Tag_Typ) then
5987          null;
5988
5989       --  Skip this if finalization is not available
5990
5991       elsif Restriction_Active (No_Finalization) then
5992          null;
5993
5994       elsif (Etype (Tag_Typ) = Tag_Typ or else Is_Controlled (Tag_Typ))
5995         and then not Has_Controlled_Component (Tag_Typ)
5996       then
5997          if not Is_Limited_Type (Tag_Typ) then
5998             Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
5999
6000             if Is_Controlled (Tag_Typ) then
6001                Set_Handled_Statement_Sequence (Decl,
6002                  Make_Handled_Sequence_Of_Statements (Loc,
6003                    Make_Adjust_Call (
6004                      Ref          => Make_Identifier (Loc, Name_V),
6005                      Typ          => Tag_Typ,
6006                      Flist_Ref    => Make_Identifier (Loc, Name_L),
6007                      With_Attach  => Make_Identifier (Loc, Name_B))));
6008
6009             else
6010                Set_Handled_Statement_Sequence (Decl,
6011                  Make_Handled_Sequence_Of_Statements (Loc, New_List (
6012                    Make_Null_Statement (Loc))));
6013             end if;
6014
6015             Append_To (Res, Decl);
6016          end if;
6017
6018          Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
6019
6020          if Is_Controlled (Tag_Typ) then
6021             Set_Handled_Statement_Sequence (Decl,
6022               Make_Handled_Sequence_Of_Statements (Loc,
6023                 Make_Final_Call (
6024                   Ref         => Make_Identifier (Loc, Name_V),
6025                   Typ         => Tag_Typ,
6026                   With_Detach => Make_Identifier (Loc, Name_B))));
6027
6028          else
6029             Set_Handled_Statement_Sequence (Decl,
6030               Make_Handled_Sequence_Of_Statements (Loc, New_List (
6031                 Make_Null_Statement (Loc))));
6032          end if;
6033
6034          Append_To (Res, Decl);
6035       end if;
6036
6037       return Res;
6038    end Predefined_Primitive_Bodies;
6039
6040    ---------------------------------
6041    -- Predefined_Primitive_Freeze --
6042    ---------------------------------
6043
6044    function Predefined_Primitive_Freeze
6045      (Tag_Typ : Entity_Id) return List_Id
6046    is
6047       Loc     : constant Source_Ptr := Sloc (Tag_Typ);
6048       Res     : constant List_Id    := New_List;
6049       Prim    : Elmt_Id;
6050       Frnodes : List_Id;
6051
6052    begin
6053       Prim := First_Elmt (Primitive_Operations (Tag_Typ));
6054       while Present (Prim) loop
6055          if Is_Internal (Node (Prim)) then
6056             Frnodes := Freeze_Entity (Node (Prim), Loc);
6057
6058             if Present (Frnodes) then
6059                Append_List_To (Res, Frnodes);
6060             end if;
6061          end if;
6062
6063          Next_Elmt (Prim);
6064       end loop;
6065
6066       return Res;
6067    end Predefined_Primitive_Freeze;
6068 end Exp_Ch3;