OSDN Git Service

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