OSDN Git Service

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