OSDN Git Service

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