OSDN Git Service

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