OSDN Git Service

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