OSDN Git Service

2009-04-08 Thomas Quinot <quinot@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / exp_ch7.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                              E X P _ C H 7                               --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2008, 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 3,  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 COPYING3.  If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license.          --
20 --                                                                          --
21 -- GNAT was originally developed  by the GNAT team at  New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
23 --                                                                          --
24 ------------------------------------------------------------------------------
25
26 --  This package contains virtually all expansion mechanisms related to
27 --    - controlled types
28 --    - transient scopes
29
30 with Atree;    use Atree;
31 with Debug;    use Debug;
32 with Einfo;    use Einfo;
33 with Errout;   use Errout;
34 with Exp_Ch9;  use Exp_Ch9;
35 with Exp_Ch11; use Exp_Ch11;
36 with Exp_Dbug; use Exp_Dbug;
37 with Exp_Dist; use Exp_Dist;
38 with Exp_Disp; use Exp_Disp;
39 with Exp_Tss;  use Exp_Tss;
40 with Exp_Util; use Exp_Util;
41 with Freeze;   use Freeze;
42 with Lib;      use Lib;
43 with Nlists;   use Nlists;
44 with Nmake;    use Nmake;
45 with Opt;      use Opt;
46 with Output;   use Output;
47 with Restrict; use Restrict;
48 with Rident;   use Rident;
49 with Rtsfind;  use Rtsfind;
50 with Sinfo;    use Sinfo;
51 with Sem;      use Sem;
52 with Sem_Ch3;  use Sem_Ch3;
53 with Sem_Ch7;  use Sem_Ch7;
54 with Sem_Ch8;  use Sem_Ch8;
55 with Sem_Res;  use Sem_Res;
56 with Sem_Type; use Sem_Type;
57 with Sem_Util; use Sem_Util;
58 with Snames;   use Snames;
59 with Stand;    use Stand;
60 with Targparm; use Targparm;
61 with Tbuild;   use Tbuild;
62 with Uintp;    use Uintp;
63
64 package body Exp_Ch7 is
65
66    --------------------------------
67    -- Transient Scope Management --
68    --------------------------------
69
70    --  A transient scope is created when temporary objects are created by the
71    --  compiler. These temporary objects are allocated on the secondary stack
72    --  and the transient scope is responsible for finalizing the object when
73    --  appropriate and reclaiming the memory at the right time. The temporary
74    --  objects are generally the objects allocated to store the result of a
75    --  function returning an unconstrained or a tagged value. Expressions
76    --  needing to be wrapped in a transient scope (functions calls returning
77    --  unconstrained or tagged values) may appear in 3 different contexts which
78    --  lead to 3 different kinds of transient scope expansion:
79
80    --   1. In a simple statement (procedure call, assignment, ...). In
81    --      this case the instruction is wrapped into a transient block.
82    --      (See Wrap_Transient_Statement for details)
83
84    --   2. In an expression of a control structure (test in a IF statement,
85    --      expression in a CASE statement, ...).
86    --      (See Wrap_Transient_Expression for details)
87
88    --   3. In a expression of an object_declaration. No wrapping is possible
89    --      here, so the finalization actions, if any are done right after the
90    --      declaration and the secondary stack deallocation is done in the
91    --      proper enclosing scope (see Wrap_Transient_Declaration for details)
92
93    --  Note about functions returning tagged types: It has been decided to
94    --  always allocate their result in the secondary stack, even though is not
95    --  absolutely mandatory when the tagged type is constrained because the
96    --  caller knows the size of the returned object and thus could allocate the
97    --  result in the primary stack. An exception to this is when the function
98    --  builds its result in place, as is done for functions with inherently
99    --  limited result types for Ada 2005. In that case, certain callers may
100    --  pass the address of a constrained object as the target object for the
101    --  function result.
102
103    --  By allocating tagged results in the secondary stack a number of
104    --  implementation difficulties are avoided:
105
106    --    - If it is a dispatching function call, the computation of the size of
107    --      the result is possible but complex from the outside.
108
109    --    - If the returned type is controlled, the assignment of the returned
110    --      value to the anonymous object involves an Adjust, and we have no
111    --      easy way to access the anonymous object created by the back end.
112
113    --    - If the returned type is class-wide, this is an unconstrained type
114    --      anyway.
115
116    --  Furthermore, the small loss in efficiency which is the result of this
117    --  decision is not such a big deal because functions returning tagged types
118    --  are not as common in practice compared to functions returning access to
119    --  a tagged type.
120
121    --------------------------------------------------
122    -- Transient Blocks and Finalization Management --
123    --------------------------------------------------
124
125    function Find_Node_To_Be_Wrapped (N : Node_Id) return Node_Id;
126    --  N is a node which may generate a transient scope. Loop over the
127    --  parent pointers of N until it find the appropriate node to
128    --  wrap. It it returns Empty, it means that no transient scope is
129    --  needed in this context.
130
131    function Make_Clean
132      (N                          : Node_Id;
133       Clean                      : Entity_Id;
134       Mark                       : Entity_Id;
135       Flist                      : Entity_Id;
136       Is_Task                    : Boolean;
137       Is_Master                  : Boolean;
138       Is_Protected_Subprogram    : Boolean;
139       Is_Task_Allocation_Block   : Boolean;
140       Is_Asynchronous_Call_Block : Boolean;
141       Chained_Cleanup_Action     : Node_Id) return Node_Id;
142    --  Expand the clean-up procedure for a controlled and/or transient block,
143    --  and/or task master or task body, or a block used to  implement task
144    --  allocation or asynchronous entry calls, or a procedure used to implement
145    --  protected procedures. Clean is the entity for such a procedure. Mark
146    --  is the entity for the secondary stack mark, if empty only controlled
147    --  block clean-up will be performed. Flist is the entity for the local
148    --  final list, if empty only transient scope clean-up will be performed.
149    --  The flags Is_Task and Is_Master control the calls to the corresponding
150    --  finalization actions for a task body or for an entity that is a task
151    --  master. Finally if Chained_Cleanup_Action is present, it is a reference
152    --  to a previous cleanup procedure, a call to which is appended at the
153    --  end of the generated one.
154
155    procedure Set_Node_To_Be_Wrapped (N : Node_Id);
156    --  Set the field Node_To_Be_Wrapped of the current scope
157
158    procedure Insert_Actions_In_Scope_Around (N : Node_Id);
159    --  Insert the before-actions kept in the scope stack before N, and the
160    --  after after-actions, after N which must be a member of a list.
161
162    function Make_Transient_Block
163      (Loc    : Source_Ptr;
164       Action : Node_Id) return Node_Id;
165    --  Create a transient block whose name is Scope, which is also a
166    --  controlled block if Flist is not empty and whose only code is
167    --  Action (either a single statement or single declaration).
168
169    type Final_Primitives is (Initialize_Case, Adjust_Case, Finalize_Case);
170    --  This enumeration type is defined in order to ease sharing code for
171    --  building finalization procedures for composite types.
172
173    Name_Of      : constant array (Final_Primitives) of Name_Id :=
174                     (Initialize_Case => Name_Initialize,
175                      Adjust_Case     => Name_Adjust,
176                      Finalize_Case   => Name_Finalize);
177
178    Deep_Name_Of : constant array (Final_Primitives) of TSS_Name_Type :=
179                     (Initialize_Case => TSS_Deep_Initialize,
180                      Adjust_Case     => TSS_Deep_Adjust,
181                      Finalize_Case   => TSS_Deep_Finalize);
182
183    procedure Build_Record_Deep_Procs (Typ : Entity_Id);
184    --  Build the deep Initialize/Adjust/Finalize for a record Typ with
185    --  Has_Component_Component set and store them using the TSS mechanism.
186
187    procedure Build_Array_Deep_Procs (Typ : Entity_Id);
188    --  Build the deep Initialize/Adjust/Finalize for a record Typ with
189    --  Has_Controlled_Component set and store them using the TSS mechanism.
190
191    function Make_Deep_Proc
192      (Prim  : Final_Primitives;
193       Typ   : Entity_Id;
194       Stmts : List_Id) return Node_Id;
195    --  This function generates the tree for Deep_Initialize, Deep_Adjust
196    --  or Deep_Finalize procedures according to the first parameter,
197    --  these procedures operate on the type Typ. The Stmts parameter
198    --  gives the body of the procedure.
199
200    function Make_Deep_Array_Body
201      (Prim : Final_Primitives;
202       Typ  : Entity_Id) return List_Id;
203    --  This function generates the list of statements for implementing
204    --  Deep_Initialize, Deep_Adjust or Deep_Finalize procedures
205    --  according to the first parameter, these procedures operate on the
206    --  array type Typ.
207
208    function Make_Deep_Record_Body
209      (Prim : Final_Primitives;
210       Typ  : Entity_Id) return List_Id;
211    --  This function generates the list of statements for implementing
212    --  Deep_Initialize, Deep_Adjust or Deep_Finalize procedures
213    --  according to the first parameter, these procedures operate on the
214    --  record type Typ.
215
216    procedure Check_Visibly_Controlled
217      (Prim : Final_Primitives;
218       Typ  : Entity_Id;
219       E    : in out Entity_Id;
220       Cref : in out Node_Id);
221    --  The controlled operation declared for a derived type may not be
222    --  overriding, if the controlled operations of the parent type are
223    --  hidden, for example when the parent is a private type whose full
224    --  view is controlled. For other primitive operations we modify the
225    --  name of the operation to indicate that it is not overriding, but
226    --  this is not possible for Initialize, etc. because they have to be
227    --  retrievable by name. Before generating the proper call to one of
228    --  these operations we check whether Typ is known to be controlled at
229    --  the point of definition. If it is not then we must retrieve the
230    --  hidden operation of the parent and use it instead.  This is one
231    --  case that might be solved more cleanly once Overriding pragmas or
232    --  declarations are in place.
233
234    function Convert_View
235      (Proc : Entity_Id;
236       Arg  : Node_Id;
237       Ind  : Pos := 1) return Node_Id;
238    --  Proc is one of the Initialize/Adjust/Finalize operations, and
239    --  Arg is the argument being passed to it. Ind indicates which
240    --  formal of procedure Proc we are trying to match. This function
241    --  will, if necessary, generate an conversion between the partial
242    --  and full view of Arg to match the type of the formal of Proc,
243    --  or force a conversion to the class-wide type in the case where
244    --  the operation is abstract.
245
246    -----------------------------
247    -- Finalization Management --
248    -----------------------------
249
250    --  This part describe how Initialization/Adjustment/Finalization procedures
251    --  are generated and called. Two cases must be considered, types that are
252    --  Controlled (Is_Controlled flag set) and composite types that contain
253    --  controlled components (Has_Controlled_Component flag set). In the first
254    --  case the procedures to call are the user-defined primitive operations
255    --  Initialize/Adjust/Finalize. In the second case, GNAT generates
256    --  Deep_Initialize, Deep_Adjust and Deep_Finalize that are in charge
257    --  of calling the former procedures on the controlled components.
258
259    --  For records with Has_Controlled_Component set, a hidden "controller"
260    --  component is inserted. This controller component contains its own
261    --  finalization list on which all controlled components are attached
262    --  creating an indirection on the upper-level Finalization list. This
263    --  technique facilitates the management of objects whose number of
264    --  controlled components changes during execution. This controller
265    --  component is itself controlled and is attached to the upper-level
266    --  finalization chain. Its adjust primitive is in charge of calling adjust
267    --  on the components and adjusting the finalization pointer to match their
268    --  new location (see a-finali.adb).
269
270    --  It is not possible to use a similar technique for arrays that have
271    --  Has_Controlled_Component set. In this case, deep procedures are
272    --  generated that call initialize/adjust/finalize + attachment or
273    --  detachment on the finalization list for all component.
274
275    --  Initialize calls: they are generated for declarations or dynamic
276    --  allocations of Controlled objects with no initial value. They are always
277    --  followed by an attachment to the current Finalization Chain. For the
278    --  dynamic allocation case this the chain attached to the scope of the
279    --  access type definition otherwise, this is the chain of the current
280    --  scope.
281
282    --  Adjust Calls: They are generated on 2 occasions: (1) for
283    --  declarations or dynamic allocations of Controlled objects with an
284    --  initial value. (2) after an assignment. In the first case they are
285    --  followed by an attachment to the final chain, in the second case
286    --  they are not.
287
288    --  Finalization Calls: They are generated on (1) scope exit, (2)
289    --  assignments, (3) unchecked deallocations. In case (3) they have to
290    --  be detached from the final chain, in case (2) they must not and in
291    --  case (1) this is not important since we are exiting the scope anyway.
292
293    --  Other details:
294
295    --    Type extensions will have a new record controller at each derivation
296    --    level containing controlled components. The record controller for
297    --    the parent/ancestor is attached to the finalization list of the
298    --    extension's record controller (i.e. the parent is like a component
299    --    of the extension).
300
301    --    For types that are both Is_Controlled and Has_Controlled_Components,
302    --    the record controller and the object itself are handled separately.
303    --    It could seem simpler to attach the object at the end of its record
304    --    controller but this would not tackle view conversions properly.
305
306    --    A classwide type can always potentially have controlled components
307    --    but the record controller of the corresponding actual type may not
308    --    be known at compile time so the dispatch table contains a special
309    --    field that allows to compute the offset of the record controller
310    --    dynamically. See s-finimp.Deep_Tag_Attach and a-tags.RC_Offset.
311
312    --  Here is a simple example of the expansion of a controlled block :
313
314    --    declare
315    --       X : Controlled;
316    --       Y : Controlled := Init;
317    --
318    --       type R is record
319    --          C : Controlled;
320    --       end record;
321    --       W : R;
322    --       Z : R := (C => X);
323    --    begin
324    --       X := Y;
325    --       W := Z;
326    --    end;
327    --
328    --  is expanded into
329    --
330    --    declare
331    --       _L : System.FI.Finalizable_Ptr;
332
333    --       procedure _Clean is
334    --       begin
335    --          Abort_Defer;
336    --          System.FI.Finalize_List (_L);
337    --          Abort_Undefer;
338    --       end _Clean;
339
340    --       X : Controlled;
341    --       begin
342    --          Abort_Defer;
343    --          Initialize (X);
344    --          Attach_To_Final_List (_L, Finalizable (X), 1);
345    --       at end: Abort_Undefer;
346    --       Y : Controlled := Init;
347    --       Adjust (Y);
348    --       Attach_To_Final_List (_L, Finalizable (Y), 1);
349    --
350    --       type R is record
351    --         _C : Record_Controller;
352    --          C : Controlled;
353    --       end record;
354    --       W : R;
355    --       begin
356    --          Abort_Defer;
357    --          Deep_Initialize (W, _L, 1);
358    --       at end: Abort_Under;
359    --       Z : R := (C => X);
360    --       Deep_Adjust (Z, _L, 1);
361
362    --    begin
363    --       _Assign (X, Y);
364    --       Deep_Finalize (W, False);
365    --       <save W's final pointers>
366    --       W := Z;
367    --       <restore W's final pointers>
368    --       Deep_Adjust (W, _L, 0);
369    --    at end
370    --       _Clean;
371    --    end;
372
373    function Global_Flist_Ref (Flist_Ref : Node_Id) return Boolean;
374    --  Return True if Flist_Ref refers to a global final list, either the
375    --  object Global_Final_List which is used to attach standalone objects,
376    --  or any of the list controllers associated with library-level access
377    --  to controlled objects.
378
379    procedure Clean_Simple_Protected_Objects (N : Node_Id);
380    --  Protected objects without entries are not controlled types, and the
381    --  locks have to be released explicitly when such an object goes out
382    --  of scope. Traverse declarations in scope to determine whether such
383    --  objects are present.
384
385    ----------------------------
386    -- Build_Array_Deep_Procs --
387    ----------------------------
388
389    procedure Build_Array_Deep_Procs (Typ : Entity_Id) is
390    begin
391       Set_TSS (Typ,
392         Make_Deep_Proc (
393           Prim  => Initialize_Case,
394           Typ   => Typ,
395           Stmts => Make_Deep_Array_Body (Initialize_Case, Typ)));
396
397       if not Is_Inherently_Limited_Type (Typ) then
398          Set_TSS (Typ,
399            Make_Deep_Proc (
400              Prim  => Adjust_Case,
401              Typ   => Typ,
402              Stmts => Make_Deep_Array_Body (Adjust_Case, Typ)));
403       end if;
404
405       Set_TSS (Typ,
406         Make_Deep_Proc (
407           Prim  => Finalize_Case,
408           Typ   => Typ,
409           Stmts => Make_Deep_Array_Body (Finalize_Case, Typ)));
410    end Build_Array_Deep_Procs;
411
412    -----------------------------
413    -- Build_Controlling_Procs --
414    -----------------------------
415
416    procedure Build_Controlling_Procs (Typ : Entity_Id) is
417    begin
418       if Is_Array_Type (Typ) then
419          Build_Array_Deep_Procs (Typ);
420
421       else pragma Assert (Is_Record_Type (Typ));
422          Build_Record_Deep_Procs (Typ);
423       end if;
424    end Build_Controlling_Procs;
425
426    ----------------------
427    -- Build_Final_List --
428    ----------------------
429
430    procedure Build_Final_List (N : Node_Id; Typ : Entity_Id) is
431       Loc  : constant Source_Ptr := Sloc (N);
432       Decl : Node_Id;
433
434    begin
435       Set_Associated_Final_Chain (Typ,
436         Make_Defining_Identifier (Loc,
437           New_External_Name (Chars (Typ), 'L')));
438
439       Decl :=
440         Make_Object_Declaration (Loc,
441           Defining_Identifier =>
442              Associated_Final_Chain (Typ),
443           Object_Definition   =>
444             New_Reference_To
445               (RTE (RE_List_Controller), Loc));
446
447       --  The type may have been frozen already, and this is a late freezing
448       --  action, in which case the declaration must be elaborated at once.
449       --  If the call is for an allocator, the chain must also be created now,
450       --  because the freezing of the type does not build one. Otherwise, the
451       --  declaration is one of the freezing actions for a user-defined type.
452
453       if Is_Frozen (Typ)
454         or else (Nkind (N) = N_Allocator
455                   and then Ekind (Etype (N)) = E_Anonymous_Access_Type)
456       then
457          Insert_Action (N, Decl);
458       else
459          Append_Freeze_Action (Typ, Decl);
460       end if;
461    end Build_Final_List;
462
463    ---------------------
464    -- Build_Late_Proc --
465    ---------------------
466
467    procedure Build_Late_Proc (Typ : Entity_Id; Nam : Name_Id) is
468    begin
469       for Final_Prim in Name_Of'Range loop
470          if Name_Of (Final_Prim) = Nam then
471             Set_TSS (Typ,
472               Make_Deep_Proc (
473                 Prim  => Final_Prim,
474                 Typ   => Typ,
475                 Stmts => Make_Deep_Record_Body (Final_Prim, Typ)));
476          end if;
477       end loop;
478    end Build_Late_Proc;
479
480    -----------------------------
481    -- Build_Record_Deep_Procs --
482    -----------------------------
483
484    procedure Build_Record_Deep_Procs (Typ : Entity_Id) is
485    begin
486       Set_TSS (Typ,
487         Make_Deep_Proc (
488           Prim  => Initialize_Case,
489           Typ   => Typ,
490           Stmts => Make_Deep_Record_Body (Initialize_Case, Typ)));
491
492       if not Is_Inherently_Limited_Type (Typ) then
493          Set_TSS (Typ,
494            Make_Deep_Proc (
495              Prim  => Adjust_Case,
496              Typ   => Typ,
497              Stmts => Make_Deep_Record_Body (Adjust_Case, Typ)));
498       end if;
499
500       Set_TSS (Typ,
501         Make_Deep_Proc (
502           Prim  => Finalize_Case,
503           Typ   => Typ,
504           Stmts => Make_Deep_Record_Body (Finalize_Case, Typ)));
505    end Build_Record_Deep_Procs;
506
507    -------------------
508    -- Cleanup_Array --
509    -------------------
510
511    function Cleanup_Array
512      (N    : Node_Id;
513       Obj  : Node_Id;
514       Typ  : Entity_Id) return List_Id
515    is
516       Loc        : constant Source_Ptr := Sloc (N);
517       Index_List : constant List_Id := New_List;
518
519       function Free_Component return List_Id;
520       --  Generate the code to finalize the task or protected  subcomponents
521       --  of a single component of the array.
522
523       function Free_One_Dimension (Dim : Int) return List_Id;
524       --  Generate a loop over one dimension of the array
525
526       --------------------
527       -- Free_Component --
528       --------------------
529
530       function Free_Component return List_Id is
531          Stmts : List_Id := New_List;
532          Tsk   : Node_Id;
533          C_Typ : constant Entity_Id := Component_Type (Typ);
534
535       begin
536          --  Component type is known to contain tasks or protected objects
537
538          Tsk :=
539            Make_Indexed_Component (Loc,
540              Prefix        => Duplicate_Subexpr_No_Checks (Obj),
541              Expressions   => Index_List);
542
543          Set_Etype (Tsk, C_Typ);
544
545          if Is_Task_Type (C_Typ) then
546             Append_To (Stmts, Cleanup_Task (N, Tsk));
547
548          elsif Is_Simple_Protected_Type (C_Typ) then
549             Append_To (Stmts, Cleanup_Protected_Object (N, Tsk));
550
551          elsif Is_Record_Type (C_Typ) then
552             Stmts := Cleanup_Record (N, Tsk, C_Typ);
553
554          elsif Is_Array_Type (C_Typ) then
555             Stmts := Cleanup_Array (N, Tsk, C_Typ);
556          end if;
557
558          return Stmts;
559       end Free_Component;
560
561       ------------------------
562       -- Free_One_Dimension --
563       ------------------------
564
565       function Free_One_Dimension (Dim : Int) return List_Id is
566          Index      : Entity_Id;
567
568       begin
569          if Dim > Number_Dimensions (Typ) then
570             return Free_Component;
571
572          --  Here we generate the required loop
573
574          else
575             Index :=
576               Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
577
578             Append (New_Reference_To (Index, Loc), Index_List);
579
580             return New_List (
581               Make_Implicit_Loop_Statement (N,
582                 Identifier => Empty,
583                 Iteration_Scheme =>
584                   Make_Iteration_Scheme (Loc,
585                     Loop_Parameter_Specification =>
586                       Make_Loop_Parameter_Specification (Loc,
587                         Defining_Identifier => Index,
588                         Discrete_Subtype_Definition =>
589                           Make_Attribute_Reference (Loc,
590                             Prefix => Duplicate_Subexpr (Obj),
591                             Attribute_Name  => Name_Range,
592                             Expressions => New_List (
593                               Make_Integer_Literal (Loc, Dim))))),
594                 Statements =>  Free_One_Dimension (Dim + 1)));
595          end if;
596       end Free_One_Dimension;
597
598    --  Start of processing for Cleanup_Array
599
600    begin
601       return Free_One_Dimension (1);
602    end Cleanup_Array;
603
604    --------------------
605    -- Cleanup_Record --
606    --------------------
607
608    function Cleanup_Record
609      (N    : Node_Id;
610       Obj  : Node_Id;
611       Typ  : Entity_Id) return List_Id
612    is
613       Loc   : constant Source_Ptr := Sloc (N);
614       Tsk   : Node_Id;
615       Comp  : Entity_Id;
616       Stmts : constant List_Id    := New_List;
617       U_Typ : constant Entity_Id  := Underlying_Type (Typ);
618
619    begin
620       if Has_Discriminants (U_Typ)
621         and then Nkind (Parent (U_Typ)) = N_Full_Type_Declaration
622         and then
623           Nkind (Type_Definition (Parent (U_Typ))) = N_Record_Definition
624         and then
625           Present
626             (Variant_Part
627               (Component_List (Type_Definition (Parent (U_Typ)))))
628       then
629          --  For now, do not attempt to free a component that may appear in
630          --  a variant, and instead issue a warning. Doing this "properly"
631          --  would require building a case statement and would be quite a
632          --  mess. Note that the RM only requires that free "work" for the
633          --  case of a task access value, so already we go way beyond this
634          --  in that we deal with the array case and non-discriminated
635          --  record cases.
636
637          Error_Msg_N
638            ("task/protected object in variant record will not be freed?", N);
639          return New_List (Make_Null_Statement (Loc));
640       end if;
641
642       Comp := First_Component (Typ);
643
644       while Present (Comp) loop
645          if Has_Task (Etype (Comp))
646            or else Has_Simple_Protected_Object (Etype (Comp))
647          then
648             Tsk :=
649               Make_Selected_Component (Loc,
650                 Prefix        => Duplicate_Subexpr_No_Checks (Obj),
651                 Selector_Name => New_Occurrence_Of (Comp, Loc));
652             Set_Etype (Tsk, Etype (Comp));
653
654             if Is_Task_Type (Etype (Comp)) then
655                Append_To (Stmts, Cleanup_Task (N, Tsk));
656
657             elsif Is_Simple_Protected_Type (Etype (Comp)) then
658                Append_To (Stmts, Cleanup_Protected_Object (N, Tsk));
659
660             elsif Is_Record_Type (Etype (Comp)) then
661
662                --  Recurse, by generating the prefix of the argument to
663                --  the eventual cleanup call.
664
665                Append_List_To
666                  (Stmts, Cleanup_Record (N, Tsk, Etype (Comp)));
667
668             elsif Is_Array_Type (Etype (Comp)) then
669                Append_List_To
670                  (Stmts, Cleanup_Array (N, Tsk, Etype (Comp)));
671             end if;
672          end if;
673
674          Next_Component (Comp);
675       end loop;
676
677       return Stmts;
678    end Cleanup_Record;
679
680    ------------------------------
681    -- Cleanup_Protected_Object --
682    ------------------------------
683
684    function Cleanup_Protected_Object
685      (N   : Node_Id;
686       Ref : Node_Id) return Node_Id
687    is
688       Loc : constant Source_Ptr := Sloc (N);
689
690    begin
691       return
692         Make_Procedure_Call_Statement (Loc,
693           Name => New_Reference_To (RTE (RE_Finalize_Protection), Loc),
694           Parameter_Associations => New_List (
695             Concurrent_Ref (Ref)));
696    end Cleanup_Protected_Object;
697
698    ------------------------------------
699    -- Clean_Simple_Protected_Objects --
700    ------------------------------------
701
702    procedure Clean_Simple_Protected_Objects (N : Node_Id) is
703       Stmts : constant List_Id := Statements (Handled_Statement_Sequence (N));
704       Stmt  : Node_Id          := Last (Stmts);
705       E     : Entity_Id;
706
707    begin
708       E := First_Entity (Current_Scope);
709       while Present (E) loop
710          if (Ekind (E) = E_Variable
711               or else Ekind (E) = E_Constant)
712            and then Has_Simple_Protected_Object (Etype (E))
713            and then not Has_Task (Etype (E))
714            and then Nkind (Parent (E)) /= N_Object_Renaming_Declaration
715          then
716             declare
717                Typ : constant Entity_Id := Etype (E);
718                Ref : constant Node_Id := New_Occurrence_Of (E, Sloc (Stmt));
719
720             begin
721                if Is_Simple_Protected_Type (Typ) then
722                   Append_To (Stmts, Cleanup_Protected_Object (N, Ref));
723
724                elsif Has_Simple_Protected_Object (Typ) then
725                   if Is_Record_Type (Typ) then
726                      Append_List_To (Stmts, Cleanup_Record (N, Ref, Typ));
727
728                   elsif Is_Array_Type (Typ) then
729                      Append_List_To (Stmts, Cleanup_Array (N, Ref, Typ));
730                   end if;
731                end if;
732             end;
733          end if;
734
735          Next_Entity (E);
736       end loop;
737
738       --   Analyze inserted cleanup statements
739
740       if Present (Stmt) then
741          Stmt := Next (Stmt);
742
743          while Present (Stmt) loop
744             Analyze (Stmt);
745             Next (Stmt);
746          end loop;
747       end if;
748    end Clean_Simple_Protected_Objects;
749
750    ------------------
751    -- Cleanup_Task --
752    ------------------
753
754    function Cleanup_Task
755      (N   : Node_Id;
756       Ref : Node_Id) return Node_Id
757    is
758       Loc  : constant Source_Ptr := Sloc (N);
759    begin
760       return
761         Make_Procedure_Call_Statement (Loc,
762           Name => New_Reference_To (RTE (RE_Free_Task), Loc),
763           Parameter_Associations =>
764             New_List (Concurrent_Ref (Ref)));
765    end Cleanup_Task;
766
767    ---------------------------------
768    -- Has_Simple_Protected_Object --
769    ---------------------------------
770
771    function Has_Simple_Protected_Object (T : Entity_Id) return Boolean is
772       Comp : Entity_Id;
773
774    begin
775       if Is_Simple_Protected_Type (T) then
776          return True;
777
778       elsif Is_Array_Type (T) then
779          return Has_Simple_Protected_Object (Component_Type (T));
780
781       elsif Is_Record_Type (T) then
782          Comp := First_Component (T);
783
784          while Present (Comp) loop
785             if Has_Simple_Protected_Object (Etype (Comp)) then
786                return True;
787             end if;
788
789             Next_Component (Comp);
790          end loop;
791
792          return False;
793
794       else
795          return False;
796       end if;
797    end Has_Simple_Protected_Object;
798
799    ------------------------------
800    -- Is_Simple_Protected_Type --
801    ------------------------------
802
803    function Is_Simple_Protected_Type (T : Entity_Id) return Boolean is
804    begin
805       return Is_Protected_Type (T) and then not Has_Entries (T);
806    end Is_Simple_Protected_Type;
807
808    ------------------------------
809    -- Check_Visibly_Controlled --
810    ------------------------------
811
812    procedure Check_Visibly_Controlled
813      (Prim : Final_Primitives;
814       Typ  : Entity_Id;
815       E    : in out Entity_Id;
816       Cref : in out Node_Id)
817    is
818       Parent_Type : Entity_Id;
819       Op          : Entity_Id;
820
821    begin
822       if Is_Derived_Type (Typ)
823         and then Comes_From_Source (E)
824         and then not Is_Overriding_Operation (E)
825       then
826          --  We know that the explicit operation on the type does not override
827          --  the inherited operation of the parent, and that the derivation
828          --  is from a private type that is not visibly controlled.
829
830          Parent_Type := Etype (Typ);
831          Op := Find_Prim_Op (Parent_Type, Name_Of (Prim));
832
833          if Present (Op) then
834             E := Op;
835
836             --  Wrap the object to be initialized into the proper
837             --  unchecked conversion, to be compatible with the operation
838             --  to be called.
839
840             if Nkind (Cref) = N_Unchecked_Type_Conversion then
841                Cref := Unchecked_Convert_To (Parent_Type, Expression (Cref));
842             else
843                Cref := Unchecked_Convert_To (Parent_Type, Cref);
844             end if;
845          end if;
846       end if;
847    end Check_Visibly_Controlled;
848
849    -------------------------------
850    -- CW_Or_Has_Controlled_Part --
851    -------------------------------
852
853    function CW_Or_Has_Controlled_Part (T : Entity_Id) return Boolean is
854    begin
855       return Is_Class_Wide_Type (T) or else Needs_Finalization (T);
856    end CW_Or_Has_Controlled_Part;
857
858    --------------------------
859    -- Controller_Component --
860    --------------------------
861
862    function Controller_Component (Typ : Entity_Id) return Entity_Id is
863       T         : Entity_Id := Base_Type (Typ);
864       Comp      : Entity_Id;
865       Comp_Scop : Entity_Id;
866       Res       : Entity_Id := Empty;
867       Res_Scop  : Entity_Id := Empty;
868
869    begin
870       if Is_Class_Wide_Type (T) then
871          T := Root_Type (T);
872       end if;
873
874       if Is_Private_Type (T) then
875          T := Underlying_Type (T);
876       end if;
877
878       --  Fetch the outermost controller
879
880       Comp := First_Entity (T);
881       while Present (Comp) loop
882          if Chars (Comp) = Name_uController then
883             Comp_Scop := Scope (Original_Record_Component (Comp));
884
885             --  If this controller is at the outermost level, no need to
886             --  look for another one
887
888             if Comp_Scop = T then
889                return Comp;
890
891             --  Otherwise record the outermost one and continue looking
892
893             elsif Res = Empty or else Is_Ancestor (Res_Scop, Comp_Scop) then
894                Res      := Comp;
895                Res_Scop := Comp_Scop;
896             end if;
897          end if;
898
899          Next_Entity (Comp);
900       end loop;
901
902       --  If we fall through the loop, there is no controller component
903
904       return Res;
905    end Controller_Component;
906
907    ------------------
908    -- Convert_View --
909    ------------------
910
911    function Convert_View
912      (Proc : Entity_Id;
913       Arg  : Node_Id;
914       Ind  : Pos := 1) return Node_Id
915    is
916       Fent : Entity_Id := First_Entity (Proc);
917       Ftyp : Entity_Id;
918       Atyp : Entity_Id;
919
920    begin
921       for J in 2 .. Ind loop
922          Next_Entity (Fent);
923       end loop;
924
925       Ftyp := Etype (Fent);
926
927       if Nkind_In (Arg, N_Type_Conversion, N_Unchecked_Type_Conversion) then
928          Atyp := Entity (Subtype_Mark (Arg));
929       else
930          Atyp := Etype (Arg);
931       end if;
932
933       if Is_Abstract_Subprogram (Proc) and then Is_Tagged_Type (Ftyp) then
934          return Unchecked_Convert_To (Class_Wide_Type (Ftyp), Arg);
935
936       elsif Ftyp /= Atyp
937         and then Present (Atyp)
938         and then
939           (Is_Private_Type (Ftyp) or else Is_Private_Type (Atyp))
940         and then
941            Base_Type (Underlying_Type (Atyp)) =
942              Base_Type (Underlying_Type (Ftyp))
943       then
944          return Unchecked_Convert_To (Ftyp, Arg);
945
946       --  If the argument is already a conversion, as generated by
947       --  Make_Init_Call, set the target type to the type of the formal
948       --  directly, to avoid spurious typing problems.
949
950       elsif Nkind_In (Arg, N_Unchecked_Type_Conversion, N_Type_Conversion)
951         and then not Is_Class_Wide_Type (Atyp)
952       then
953          Set_Subtype_Mark (Arg, New_Occurrence_Of (Ftyp, Sloc (Arg)));
954          Set_Etype (Arg, Ftyp);
955          return Arg;
956
957       else
958          return Arg;
959       end if;
960    end Convert_View;
961
962    -------------------------------
963    -- Establish_Transient_Scope --
964    -------------------------------
965
966    --  This procedure is called each time a transient block has to be inserted
967    --  that is to say for each call to a function with unconstrained or tagged
968    --  result. It creates a new scope on the stack scope in order to enclose
969    --  all transient variables generated
970
971    procedure Establish_Transient_Scope (N : Node_Id; Sec_Stack : Boolean) is
972       Loc       : constant Source_Ptr := Sloc (N);
973       Wrap_Node : Node_Id;
974
975    begin
976       --  Nothing to do for virtual machines where memory is GCed
977
978       if VM_Target /= No_VM then
979          return;
980       end if;
981
982       --  Do not create a transient scope if we are already inside one
983
984       for S in reverse Scope_Stack.First .. Scope_Stack.Last loop
985          if Scope_Stack.Table (S).Is_Transient then
986             if Sec_Stack then
987                Set_Uses_Sec_Stack (Scope_Stack.Table (S).Entity);
988             end if;
989
990             return;
991
992          --  If we have encountered Standard there are no enclosing
993          --  transient scopes.
994
995          elsif Scope_Stack.Table (S).Entity = Standard_Standard then
996             exit;
997
998          end if;
999       end loop;
1000
1001       Wrap_Node := Find_Node_To_Be_Wrapped (N);
1002
1003       --  Case of no wrap node, false alert, no transient scope needed
1004
1005       if No (Wrap_Node) then
1006          null;
1007
1008       --  If the node to wrap is an iteration_scheme, the expression is
1009       --  one of the bounds, and the expansion will make an explicit
1010       --  declaration for it (see Analyze_Iteration_Scheme, sem_ch5.adb),
1011       --  so do not apply any transformations here.
1012
1013       elsif Nkind (Wrap_Node) = N_Iteration_Scheme then
1014          null;
1015
1016       else
1017          Push_Scope (New_Internal_Entity (E_Block, Current_Scope, Loc, 'B'));
1018          Set_Scope_Is_Transient;
1019
1020          if Sec_Stack then
1021             Set_Uses_Sec_Stack (Current_Scope);
1022             Check_Restriction (No_Secondary_Stack, N);
1023          end if;
1024
1025          Set_Etype (Current_Scope, Standard_Void_Type);
1026          Set_Node_To_Be_Wrapped (Wrap_Node);
1027
1028          if Debug_Flag_W then
1029             Write_Str ("    <Transient>");
1030             Write_Eol;
1031          end if;
1032       end if;
1033    end Establish_Transient_Scope;
1034
1035    ----------------------------
1036    -- Expand_Cleanup_Actions --
1037    ----------------------------
1038
1039    procedure Expand_Cleanup_Actions (N : Node_Id) is
1040       S       : constant Entity_Id  := Current_Scope;
1041       Flist   : constant Entity_Id := Finalization_Chain_Entity (S);
1042       Is_Task : constant Boolean := Nkind (Original_Node (N)) = N_Task_Body;
1043
1044       Is_Master            : constant Boolean :=
1045                                Nkind (N) /= N_Entry_Body
1046                                  and then Is_Task_Master (N);
1047       Is_Protected         : constant Boolean :=
1048                                Nkind (N) = N_Subprogram_Body
1049                                  and then Is_Protected_Subprogram_Body (N);
1050       Is_Task_Allocation   : constant Boolean :=
1051                                Nkind (N) = N_Block_Statement
1052                                  and then Is_Task_Allocation_Block (N);
1053       Is_Asynchronous_Call : constant Boolean :=
1054                                Nkind (N) = N_Block_Statement
1055                                  and then Is_Asynchronous_Call_Block (N);
1056
1057       Previous_At_End_Proc : constant Node_Id :=
1058                                At_End_Proc (Handled_Statement_Sequence (N));
1059
1060       Clean     : Entity_Id;
1061       Loc       : Source_Ptr;
1062       Mark      : Entity_Id := Empty;
1063       New_Decls : constant List_Id := New_List;
1064       Blok      : Node_Id;
1065       End_Lab   : Node_Id;
1066       Wrapped   : Boolean;
1067       Chain     : Entity_Id := Empty;
1068       Decl      : Node_Id;
1069       Old_Poll  : Boolean;
1070
1071    begin
1072       --  If we are generating expanded code for debugging purposes, use
1073       --  the Sloc of the point of insertion for the cleanup code. The Sloc
1074       --  will be updated subsequently to reference the proper line in the
1075       --  .dg file.  If we are not debugging generated code, use instead
1076       --  No_Location, so that no debug information is generated for the
1077       --  cleanup code. This makes the behavior of the NEXT command in GDB
1078       --  monotonic, and makes the placement of breakpoints more accurate.
1079
1080       if Debug_Generated_Code then
1081          Loc := Sloc (S);
1082       else
1083          Loc := No_Location;
1084       end if;
1085
1086       --  There are cleanup actions only if the secondary stack needs
1087       --  releasing or some finalizations are needed or in the context
1088       --  of tasking
1089
1090       if Uses_Sec_Stack  (Current_Scope)
1091         and then not Sec_Stack_Needed_For_Return (Current_Scope)
1092       then
1093          null;
1094       elsif No (Flist)
1095         and then not Is_Master
1096         and then not Is_Task
1097         and then not Is_Protected
1098         and then not Is_Task_Allocation
1099         and then not Is_Asynchronous_Call
1100       then
1101          Clean_Simple_Protected_Objects (N);
1102          return;
1103       end if;
1104
1105       --  If the current scope is the subprogram body that is the rewriting
1106       --  of a task body, and the descriptors have not been delayed (due to
1107       --  some nested instantiations) do not generate redundant cleanup
1108       --  actions: the cleanup procedure already exists for this body.
1109
1110       if Nkind (N) = N_Subprogram_Body
1111         and then Nkind (Original_Node (N)) = N_Task_Body
1112         and then not Delay_Subprogram_Descriptors (Corresponding_Spec (N))
1113       then
1114          return;
1115       end if;
1116
1117       --  Set polling off, since we don't need to poll during cleanup
1118       --  actions, and indeed for the cleanup routine, which is executed
1119       --  with aborts deferred, we don't want polling.
1120
1121       Old_Poll := Polling_Required;
1122       Polling_Required := False;
1123
1124       --  Make sure we have a declaration list, since we will add to it
1125
1126       if No (Declarations (N)) then
1127          Set_Declarations (N, New_List);
1128       end if;
1129
1130       --  The task activation call has already been built for task
1131       --  allocation blocks.
1132
1133       if not Is_Task_Allocation then
1134          Build_Task_Activation_Call (N);
1135       end if;
1136
1137       if Is_Master then
1138          Establish_Task_Master (N);
1139       end if;
1140
1141       --  If secondary stack is in use, expand:
1142       --    _Mxx : constant Mark_Id := SS_Mark;
1143
1144       --  Suppress calls to SS_Mark and SS_Release if VM_Target,
1145       --  since we never use the secondary stack on the VM.
1146
1147       if Uses_Sec_Stack (Current_Scope)
1148         and then not Sec_Stack_Needed_For_Return (Current_Scope)
1149         and then VM_Target = No_VM
1150       then
1151          Mark := Make_Defining_Identifier (Loc, New_Internal_Name ('M'));
1152          Append_To (New_Decls,
1153            Make_Object_Declaration (Loc,
1154              Defining_Identifier => Mark,
1155              Object_Definition   => New_Reference_To (RTE (RE_Mark_Id), Loc),
1156              Expression =>
1157                Make_Function_Call (Loc,
1158                  Name => New_Reference_To (RTE (RE_SS_Mark), Loc))));
1159
1160          Set_Uses_Sec_Stack (Current_Scope, False);
1161       end if;
1162
1163       --  If finalization list is present then expand:
1164       --   Local_Final_List : System.FI.Finalizable_Ptr;
1165
1166       if Present (Flist) then
1167          Append_To (New_Decls,
1168            Make_Object_Declaration (Loc,
1169              Defining_Identifier => Flist,
1170              Object_Definition   =>
1171                New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
1172       end if;
1173
1174       --  Clean-up procedure definition
1175
1176       Clean := Make_Defining_Identifier (Loc, Name_uClean);
1177       Set_Suppress_Elaboration_Warnings (Clean);
1178       Append_To (New_Decls,
1179         Make_Clean (N, Clean, Mark, Flist,
1180           Is_Task,
1181           Is_Master,
1182           Is_Protected,
1183           Is_Task_Allocation,
1184           Is_Asynchronous_Call,
1185           Previous_At_End_Proc));
1186
1187       --  The previous AT END procedure, if any, has been captured in Clean:
1188       --  reset it to Empty now because we check further on that we never
1189       --  overwrite an existing AT END call.
1190
1191       Set_At_End_Proc (Handled_Statement_Sequence (N), Empty);
1192
1193       --  If exception handlers are present, wrap the Sequence of statements in
1194       --  a block because it is not possible to get exception handlers and an
1195       --  AT END call in the same scope.
1196
1197       if Present (Exception_Handlers (Handled_Statement_Sequence (N))) then
1198
1199          --  Preserve end label to provide proper cross-reference information
1200
1201          End_Lab := End_Label (Handled_Statement_Sequence (N));
1202          Blok :=
1203            Make_Block_Statement (Loc,
1204              Handled_Statement_Sequence => Handled_Statement_Sequence (N));
1205          Set_Handled_Statement_Sequence (N,
1206            Make_Handled_Sequence_Of_Statements (Loc, New_List (Blok)));
1207          Set_End_Label (Handled_Statement_Sequence (N), End_Lab);
1208          Wrapped := True;
1209
1210          --  Comment needed here, see RH for 1.306 ???
1211
1212          if Nkind (N) = N_Subprogram_Body then
1213             Set_Has_Nested_Block_With_Handler (Current_Scope);
1214          end if;
1215
1216       --  Otherwise we do not wrap
1217
1218       else
1219          Wrapped := False;
1220          Blok    := Empty;
1221       end if;
1222
1223       --  Don't move the _chain Activation_Chain declaration in task
1224       --  allocation blocks. Task allocation blocks use this object
1225       --  in their cleanup handlers, and gigi complains if it is declared
1226       --  in the sequence of statements of the scope that declares the
1227       --  handler.
1228
1229       if Is_Task_Allocation then
1230          Chain := Activation_Chain_Entity (N);
1231
1232          Decl := First (Declarations (N));
1233          while Nkind (Decl) /= N_Object_Declaration
1234            or else Defining_Identifier (Decl) /= Chain
1235          loop
1236             Next (Decl);
1237             pragma Assert (Present (Decl));
1238          end loop;
1239
1240          Remove (Decl);
1241          Prepend_To (New_Decls, Decl);
1242       end if;
1243
1244       --  Now we move the declarations into the Sequence of statements
1245       --  in order to get them protected by the AT END call. It may seem
1246       --  weird to put declarations in the sequence of statement but in
1247       --  fact nothing forbids that at the tree level. We also set the
1248       --  First_Real_Statement field so that we remember where the real
1249       --  statements (i.e. original statements) begin. Note that if we
1250       --  wrapped the statements, the first real statement is inside the
1251       --  inner block. If the First_Real_Statement is already set (as is
1252       --  the case for subprogram bodies that are expansions of task bodies)
1253       --  then do not reset it, because its declarative part would migrate
1254       --  to the statement part.
1255
1256       if not Wrapped then
1257          if No (First_Real_Statement (Handled_Statement_Sequence (N))) then
1258             Set_First_Real_Statement (Handled_Statement_Sequence (N),
1259               First (Statements (Handled_Statement_Sequence (N))));
1260          end if;
1261
1262       else
1263          Set_First_Real_Statement (Handled_Statement_Sequence (N), Blok);
1264       end if;
1265
1266       Append_List_To (Declarations (N),
1267         Statements (Handled_Statement_Sequence (N)));
1268       Set_Statements (Handled_Statement_Sequence (N), Declarations (N));
1269
1270       --  We need to reset the Sloc of the handled statement sequence to
1271       --  properly reflect the new initial "statement" in the sequence.
1272
1273       Set_Sloc
1274         (Handled_Statement_Sequence (N), Sloc (First (Declarations (N))));
1275
1276       --  The declarations of the _Clean procedure and finalization chain
1277       --  replace the old declarations that have been moved inward.
1278
1279       Set_Declarations (N, New_Decls);
1280       Analyze_Declarations (New_Decls);
1281
1282       --  The At_End call is attached to the sequence of statements
1283
1284       declare
1285          HSS : Node_Id;
1286
1287       begin
1288          --  If the construct is a protected subprogram, then the call to
1289          --  the corresponding unprotected subprogram appears in a block which
1290          --  is the last statement in the body, and it is this block that must
1291          --  be covered by the At_End handler.
1292
1293          if Is_Protected then
1294             HSS := Handled_Statement_Sequence
1295               (Last (Statements (Handled_Statement_Sequence (N))));
1296          else
1297             HSS := Handled_Statement_Sequence (N);
1298          end if;
1299
1300          --  Never overwrite an existing AT END call
1301
1302          pragma Assert (No (At_End_Proc (HSS)));
1303
1304          Set_At_End_Proc (HSS, New_Occurrence_Of (Clean, Loc));
1305          Expand_At_End_Handler (HSS, Empty);
1306       end;
1307
1308       --  Restore saved polling mode
1309
1310       Polling_Required := Old_Poll;
1311    end Expand_Cleanup_Actions;
1312
1313    -------------------------------
1314    -- Expand_Ctrl_Function_Call --
1315    -------------------------------
1316
1317    procedure Expand_Ctrl_Function_Call (N : Node_Id) is
1318       Loc     : constant Source_Ptr := Sloc (N);
1319       Rtype   : constant Entity_Id  := Etype (N);
1320       Utype   : constant Entity_Id  := Underlying_Type (Rtype);
1321       Ref     : Node_Id;
1322       Action  : Node_Id;
1323       Action2 : Node_Id := Empty;
1324
1325       Attach_Level : Uint    := Uint_1;
1326       Len_Ref      : Node_Id := Empty;
1327
1328       function Last_Array_Component
1329         (Ref : Node_Id;
1330          Typ : Entity_Id) return Node_Id;
1331       --  Creates a reference to the last component of the array object
1332       --  designated by Ref whose type is Typ.
1333
1334       --------------------------
1335       -- Last_Array_Component --
1336       --------------------------
1337
1338       function Last_Array_Component
1339         (Ref : Node_Id;
1340          Typ : Entity_Id) return Node_Id
1341       is
1342          Index_List : constant List_Id := New_List;
1343
1344       begin
1345          for N in 1 .. Number_Dimensions (Typ) loop
1346             Append_To (Index_List,
1347               Make_Attribute_Reference (Loc,
1348                 Prefix         => Duplicate_Subexpr_No_Checks (Ref),
1349                 Attribute_Name => Name_Last,
1350                 Expressions    => New_List (
1351                   Make_Integer_Literal (Loc, N))));
1352          end loop;
1353
1354          return
1355            Make_Indexed_Component (Loc,
1356              Prefix      => Duplicate_Subexpr (Ref),
1357              Expressions => Index_List);
1358       end Last_Array_Component;
1359
1360    --  Start of processing for Expand_Ctrl_Function_Call
1361
1362    begin
1363       --  Optimization, if the returned value (which is on the sec-stack) is
1364       --  returned again, no need to copy/readjust/finalize, we can just pass
1365       --  the value thru (see Expand_N_Simple_Return_Statement), and thus no
1366       --  attachment is needed
1367
1368       if Nkind (Parent (N)) = N_Simple_Return_Statement then
1369          return;
1370       end if;
1371
1372       --  Resolution is now finished, make sure we don't start analysis again
1373       --  because of the duplication
1374
1375       Set_Analyzed (N);
1376       Ref := Duplicate_Subexpr_No_Checks (N);
1377
1378       --  Now we can generate the Attach Call, note that this value is
1379       --  always in the (secondary) stack and thus is attached to a singly
1380       --  linked final list:
1381
1382       --    Resx := F (X)'reference;
1383       --    Attach_To_Final_List (_Lx, Resx.all, 1);
1384
1385       --  or when there are controlled components
1386
1387       --    Attach_To_Final_List (_Lx, Resx._controller, 1);
1388
1389       --  or when it is both is_controlled and has_controlled_components
1390
1391       --    Attach_To_Final_List (_Lx, Resx._controller, 1);
1392       --    Attach_To_Final_List (_Lx, Resx, 1);
1393
1394       --  or if it is an array with is_controlled (and has_controlled)
1395
1396       --    Attach_To_Final_List (_Lx, Resx (Resx'last), 3);
1397       --    An attach level of 3 means that a whole array is to be
1398       --    attached to the finalization list (including the controlled
1399       --    components)
1400
1401       --  or if it is an array with has_controlled components but not
1402       --  is_controlled
1403
1404       --    Attach_To_Final_List (_Lx, Resx (Resx'last)._controller, 3);
1405
1406       --  If the context is an aggregate, the call will be expanded into an
1407       --  assignment, and the attachment will be done when the aggregate
1408       --  expansion is complete. See body of Exp_Aggr for the treatment of
1409       --  other controlled components.
1410
1411       if Nkind (Parent (N)) = N_Aggregate then
1412          return;
1413       end if;
1414
1415       --  Case where type has controlled components
1416
1417       if Has_Controlled_Component (Rtype) then
1418          declare
1419             T1 : Entity_Id := Rtype;
1420             T2 : Entity_Id := Utype;
1421
1422          begin
1423             if Is_Array_Type (T2) then
1424                Len_Ref :=
1425                  Make_Attribute_Reference (Loc,
1426                  Prefix =>
1427                    Duplicate_Subexpr_Move_Checks
1428                      (Unchecked_Convert_To (T2, Ref)),
1429                  Attribute_Name => Name_Length);
1430             end if;
1431
1432             while Is_Array_Type (T2) loop
1433                if T1 /= T2 then
1434                   Ref := Unchecked_Convert_To (T2, Ref);
1435                end if;
1436
1437                Ref := Last_Array_Component (Ref, T2);
1438                Attach_Level := Uint_3;
1439                T1 := Component_Type (T2);
1440                T2 := Underlying_Type (T1);
1441             end loop;
1442
1443             --  If the type has controlled components, go to the controller
1444             --  except in the case of arrays of controlled objects since in
1445             --  this case objects and their components are already chained
1446             --  and the head of the chain is the last array element.
1447
1448             if Is_Array_Type (Rtype) and then Is_Controlled (T2) then
1449                null;
1450
1451             elsif Has_Controlled_Component (T2) then
1452                if T1 /= T2 then
1453                   Ref := Unchecked_Convert_To (T2, Ref);
1454                end if;
1455
1456                Ref :=
1457                  Make_Selected_Component (Loc,
1458                    Prefix        => Ref,
1459                    Selector_Name => Make_Identifier (Loc, Name_uController));
1460             end if;
1461          end;
1462
1463          --  Here we know that 'Ref' has a controller so we may as well
1464          --  attach it directly
1465
1466          Action :=
1467            Make_Attach_Call (
1468              Obj_Ref      => Ref,
1469              Flist_Ref    => Find_Final_List (Current_Scope),
1470              With_Attach  => Make_Integer_Literal (Loc, Attach_Level));
1471
1472          --  If it is also Is_Controlled we need to attach the global object
1473
1474          if Is_Controlled (Rtype) then
1475             Action2 :=
1476               Make_Attach_Call (
1477                 Obj_Ref      => Duplicate_Subexpr_No_Checks (N),
1478                 Flist_Ref    => Find_Final_List (Current_Scope),
1479                 With_Attach  => Make_Integer_Literal (Loc, Attach_Level));
1480          end if;
1481
1482       --  Here, we have a controlled type that does not seem to have
1483       --  controlled components but it could be a class wide type whose
1484       --  further derivations have controlled components. So we don't know
1485       --  if the object itself needs to be attached or if it has a record
1486       --  controller. We need to call a runtime function (Deep_Tag_Attach)
1487       --  which knows what to do thanks to the RC_Offset in the dispatch table.
1488
1489       else
1490          Action :=
1491            Make_Procedure_Call_Statement (Loc,
1492              Name => New_Reference_To (RTE (RE_Deep_Tag_Attach), Loc),
1493              Parameter_Associations => New_List (
1494                Find_Final_List (Current_Scope),
1495
1496                Make_Attribute_Reference (Loc,
1497                    Prefix => Ref,
1498                    Attribute_Name => Name_Address),
1499
1500                Make_Integer_Literal (Loc, Attach_Level)));
1501       end if;
1502
1503       if Present (Len_Ref) then
1504          Action :=
1505            Make_Implicit_If_Statement (N,
1506              Condition => Make_Op_Gt (Loc,
1507                Left_Opnd  => Len_Ref,
1508                Right_Opnd => Make_Integer_Literal (Loc, 0)),
1509              Then_Statements => New_List (Action));
1510       end if;
1511
1512       Insert_Action (N, Action);
1513       if Present (Action2) then
1514          Insert_Action (N, Action2);
1515       end if;
1516    end Expand_Ctrl_Function_Call;
1517
1518    ---------------------------
1519    -- Expand_N_Package_Body --
1520    ---------------------------
1521
1522    --  Add call to Activate_Tasks if body is an activator (actual processing
1523    --  is in chapter 9).
1524
1525    --  Generate subprogram descriptor for elaboration routine
1526
1527    --  Encode entity names in package body
1528
1529    procedure Expand_N_Package_Body (N : Node_Id) is
1530       Ent : constant Entity_Id := Corresponding_Spec (N);
1531
1532    begin
1533       --  This is done only for non-generic packages
1534
1535       if Ekind (Ent) = E_Package then
1536          Push_Scope (Corresponding_Spec (N));
1537
1538          --  Build dispatch tables of library level tagged types
1539
1540          if Is_Library_Level_Entity (Ent) then
1541             Build_Static_Dispatch_Tables (N);
1542          end if;
1543
1544          Build_Task_Activation_Call (N);
1545          Pop_Scope;
1546       end if;
1547
1548       Set_Elaboration_Flag (N, Corresponding_Spec (N));
1549       Set_In_Package_Body (Ent, False);
1550
1551       --  Set to encode entity names in package body before gigi is called
1552
1553       Qualify_Entity_Names (N);
1554    end Expand_N_Package_Body;
1555
1556    ----------------------------------
1557    -- Expand_N_Package_Declaration --
1558    ----------------------------------
1559
1560    --  Add call to Activate_Tasks if there are tasks declared and the package
1561    --  has no body. Note that in Ada83, this may result in premature activation
1562    --  of some tasks, given that we cannot tell whether a body will eventually
1563    --  appear.
1564
1565    procedure Expand_N_Package_Declaration (N : Node_Id) is
1566       Spec    : constant Node_Id   := Specification (N);
1567       Id      : constant Entity_Id := Defining_Entity (N);
1568       Decls   : List_Id;
1569       No_Body : Boolean := False;
1570       --  True in the case of a package declaration that is a compilation unit
1571       --  and for which no associated body will be compiled in
1572       --  this compilation.
1573
1574    begin
1575       --  Case of a package declaration other than a compilation unit
1576
1577       if Nkind (Parent (N)) /= N_Compilation_Unit then
1578          null;
1579
1580       --  Case of a compilation unit that does not require a body
1581
1582       elsif not Body_Required (Parent (N))
1583         and then not Unit_Requires_Body (Id)
1584       then
1585          No_Body := True;
1586
1587       --  Special case of generating calling stubs for a remote call interface
1588       --  package: even though the package declaration requires one, the
1589       --  body won't be processed in this compilation (so any stubs for RACWs
1590       --  declared in the package must be generated here, along with the
1591       --  spec).
1592
1593       elsif Parent (N) = Cunit (Main_Unit)
1594         and then Is_Remote_Call_Interface (Id)
1595         and then Distribution_Stub_Mode = Generate_Caller_Stub_Body
1596       then
1597          No_Body := True;
1598       end if;
1599
1600       --  For a package declaration that implies no associated body, generate
1601       --  task activation call and RACW supporting bodies now (since we won't
1602       --  have a specific separate compilation unit for that).
1603
1604       if No_Body then
1605          Push_Scope (Id);
1606
1607          if Has_RACW (Id) then
1608
1609             --  Generate RACW subprogram bodies
1610
1611             Decls := Private_Declarations (Spec);
1612
1613             if No (Decls) then
1614                Decls := Visible_Declarations (Spec);
1615             end if;
1616
1617             if No (Decls) then
1618                Decls := New_List;
1619                Set_Visible_Declarations (Spec, Decls);
1620             end if;
1621
1622             Append_RACW_Bodies (Decls, Id);
1623             Analyze_List (Decls);
1624          end if;
1625
1626          if Present (Activation_Chain_Entity (N)) then
1627
1628             --  Generate task activation call as last step of elaboration
1629
1630             Build_Task_Activation_Call (N);
1631          end if;
1632
1633          Pop_Scope;
1634       end if;
1635
1636       --  Build dispatch tables of library level tagged types
1637
1638       if Is_Compilation_Unit (Id)
1639         or else (Is_Generic_Instance (Id)
1640                    and then Is_Library_Level_Entity (Id))
1641       then
1642          Build_Static_Dispatch_Tables (N);
1643       end if;
1644
1645       --  Note: it is not necessary to worry about generating a subprogram
1646       --  descriptor, since the only way to get exception handlers into a
1647       --  package spec is to include instantiations, and that would cause
1648       --  generation of subprogram descriptors to be delayed in any case.
1649
1650       --  Set to encode entity names in package spec before gigi is called
1651
1652       Qualify_Entity_Names (N);
1653    end Expand_N_Package_Declaration;
1654
1655    ---------------------
1656    -- Find_Final_List --
1657    ---------------------
1658
1659    function Find_Final_List
1660      (E   : Entity_Id;
1661       Ref : Node_Id := Empty) return Node_Id
1662    is
1663       Loc : constant Source_Ptr := Sloc (Ref);
1664       S   : Entity_Id;
1665       Id  : Entity_Id;
1666       R   : Node_Id;
1667
1668    begin
1669       --  If the restriction No_Finalization applies, then there's not any
1670       --  finalization list available to return, so return Empty.
1671
1672       if Restriction_Active (No_Finalization) then
1673          return Empty;
1674
1675       --  Case of an internal component. The Final list is the record
1676       --  controller of the enclosing record.
1677
1678       elsif Present (Ref) then
1679          R := Ref;
1680          loop
1681             case Nkind (R) is
1682                when N_Unchecked_Type_Conversion | N_Type_Conversion =>
1683                   R := Expression (R);
1684
1685                when N_Indexed_Component | N_Explicit_Dereference =>
1686                   R := Prefix (R);
1687
1688                when  N_Selected_Component =>
1689                   R := Prefix (R);
1690                   exit;
1691
1692                when  N_Identifier =>
1693                   exit;
1694
1695                when others =>
1696                   raise Program_Error;
1697             end case;
1698          end loop;
1699
1700          return
1701            Make_Selected_Component (Loc,
1702              Prefix =>
1703                Make_Selected_Component (Loc,
1704                  Prefix        => R,
1705                  Selector_Name => Make_Identifier (Loc, Name_uController)),
1706              Selector_Name => Make_Identifier (Loc, Name_F));
1707
1708       --  Case of a dynamically allocated object whose access type has an
1709       --  Associated_Final_Chain. The final list is the corresponding list
1710       --  controller (the next entity in the scope of the access type with
1711       --  the right type). If the type comes from a With_Type clause, no
1712       --  controller was created, we use the global chain instead. (The code
1713       --  related to with_type clauses should presumably be removed at some
1714       --  point since that feature is obsolete???)
1715
1716       --  An anonymous access type either has a list created for it when the
1717       --  allocator is a for an access parameter or an access discriminant,
1718       --  or else it uses the list of the enclosing dynamic scope, when the
1719       --  context is a declaration or an assignment.
1720
1721       elsif Is_Access_Type (E)
1722         and then (Present (Associated_Final_Chain (E))
1723                    or else From_With_Type (E))
1724       then
1725          if From_With_Type (E) then
1726             return New_Reference_To (RTE (RE_Global_Final_List), Sloc (E));
1727
1728          --  Use the access type's associated finalization chain
1729
1730          else
1731             return
1732               Make_Selected_Component (Loc,
1733                 Prefix        =>
1734                   New_Reference_To
1735                     (Associated_Final_Chain (Base_Type (E)), Loc),
1736                 Selector_Name => Make_Identifier (Loc, Name_F));
1737          end if;
1738
1739       else
1740          if Is_Dynamic_Scope (E) then
1741             S := E;
1742          else
1743             S := Enclosing_Dynamic_Scope (E);
1744          end if;
1745
1746          --  When the finalization chain entity is 'Error', it means that
1747          --  there should not be any chain at that level and that the
1748          --  enclosing one should be used
1749
1750          --  This is a nasty kludge, see ??? note in exp_ch11
1751
1752          while Finalization_Chain_Entity (S) = Error loop
1753             S := Enclosing_Dynamic_Scope (S);
1754          end loop;
1755
1756          if S = Standard_Standard then
1757             return New_Reference_To (RTE (RE_Global_Final_List), Sloc (E));
1758          else
1759             if No (Finalization_Chain_Entity (S)) then
1760                Id :=
1761                  Make_Defining_Identifier (Sloc (S),
1762                    Chars => New_Internal_Name ('F'));
1763                Set_Finalization_Chain_Entity (S, Id);
1764
1765                --  Set momentarily some semantics attributes to allow normal
1766                --  analysis of expansions containing references to this chain.
1767                --  Will be fully decorated during the expansion of the scope
1768                --  itself.
1769
1770                Set_Ekind (Id, E_Variable);
1771                Set_Etype (Id, RTE (RE_Finalizable_Ptr));
1772             end if;
1773
1774             return New_Reference_To (Finalization_Chain_Entity (S), Sloc (E));
1775          end if;
1776       end if;
1777    end Find_Final_List;
1778
1779    -----------------------------
1780    -- Find_Node_To_Be_Wrapped --
1781    -----------------------------
1782
1783    function Find_Node_To_Be_Wrapped (N : Node_Id) return Node_Id is
1784       P          : Node_Id;
1785       The_Parent : Node_Id;
1786
1787    begin
1788       The_Parent := N;
1789       loop
1790          P := The_Parent;
1791          pragma Assert (P /= Empty);
1792          The_Parent := Parent (P);
1793
1794          case Nkind (The_Parent) is
1795
1796             --  Simple statement can be wrapped
1797
1798             when N_Pragma =>
1799                return The_Parent;
1800
1801             --  Usually assignments are good candidate for wrapping
1802             --  except when they have been generated as part of a
1803             --  controlled aggregate where the wrapping should take
1804             --  place more globally.
1805
1806             when N_Assignment_Statement =>
1807                if No_Ctrl_Actions (The_Parent) then
1808                   null;
1809                else
1810                   return The_Parent;
1811                end if;
1812
1813             --  An entry call statement is a special case if it occurs in
1814             --  the context of a Timed_Entry_Call. In this case we wrap
1815             --  the entire timed entry call.
1816
1817             when N_Entry_Call_Statement     |
1818                  N_Procedure_Call_Statement =>
1819                if Nkind (Parent (The_Parent)) = N_Entry_Call_Alternative
1820                  and then Nkind_In (Parent (Parent (The_Parent)),
1821                                     N_Timed_Entry_Call,
1822                                     N_Conditional_Entry_Call)
1823                then
1824                   return Parent (Parent (The_Parent));
1825                else
1826                   return The_Parent;
1827                end if;
1828
1829             --  Object declarations are also a boundary for the transient scope
1830             --  even if they are not really wrapped
1831             --  (see Wrap_Transient_Declaration)
1832
1833             when N_Object_Declaration          |
1834                  N_Object_Renaming_Declaration |
1835                  N_Subtype_Declaration         =>
1836                return The_Parent;
1837
1838             --  The expression itself is to be wrapped if its parent is a
1839             --  compound statement or any other statement where the expression
1840             --  is known to be scalar
1841
1842             when N_Accept_Alternative               |
1843                  N_Attribute_Definition_Clause      |
1844                  N_Case_Statement                   |
1845                  N_Code_Statement                   |
1846                  N_Delay_Alternative                |
1847                  N_Delay_Until_Statement            |
1848                  N_Delay_Relative_Statement         |
1849                  N_Discriminant_Association         |
1850                  N_Elsif_Part                       |
1851                  N_Entry_Body_Formal_Part           |
1852                  N_Exit_Statement                   |
1853                  N_If_Statement                     |
1854                  N_Iteration_Scheme                 |
1855                  N_Terminate_Alternative            =>
1856                return P;
1857
1858             when N_Attribute_Reference =>
1859
1860                if Is_Procedure_Attribute_Name
1861                     (Attribute_Name (The_Parent))
1862                then
1863                   return The_Parent;
1864                end if;
1865
1866             --  A raise statement can be wrapped. This will arise when the
1867             --  expression in a raise_with_expression uses the secondary
1868             --  stack, for example.
1869
1870             when N_Raise_Statement =>
1871                return The_Parent;
1872
1873             --  If the expression is within the iteration scheme of a loop,
1874             --  we must create a declaration for it, followed by an assignment
1875             --  in order to have a usable statement to wrap.
1876
1877             when N_Loop_Parameter_Specification =>
1878                return Parent (The_Parent);
1879
1880             --  The following nodes contains "dummy calls" which don't
1881             --  need to be wrapped.
1882
1883             when N_Parameter_Specification     |
1884                  N_Discriminant_Specification  |
1885                  N_Component_Declaration       =>
1886                return Empty;
1887
1888             --  The return statement is not to be wrapped when the function
1889             --  itself needs wrapping at the outer-level
1890
1891             when N_Simple_Return_Statement =>
1892                declare
1893                   Applies_To : constant Entity_Id :=
1894                                  Return_Applies_To
1895                                    (Return_Statement_Entity (The_Parent));
1896                   Return_Type : constant Entity_Id := Etype (Applies_To);
1897                begin
1898                   if Requires_Transient_Scope (Return_Type) then
1899                      return Empty;
1900                   else
1901                      return The_Parent;
1902                   end if;
1903                end;
1904
1905             --  If we leave a scope without having been able to find a node to
1906             --  wrap, something is going wrong but this can happen in error
1907             --  situation that are not detected yet (such as a dynamic string
1908             --  in a pragma export)
1909
1910             when N_Subprogram_Body     |
1911                  N_Package_Declaration |
1912                  N_Package_Body        |
1913                  N_Block_Statement     =>
1914                return Empty;
1915
1916             --  otherwise continue the search
1917
1918             when others =>
1919                null;
1920          end case;
1921       end loop;
1922    end Find_Node_To_Be_Wrapped;
1923
1924    ----------------------
1925    -- Global_Flist_Ref --
1926    ----------------------
1927
1928    function Global_Flist_Ref  (Flist_Ref : Node_Id) return Boolean is
1929       Flist : Entity_Id;
1930
1931    begin
1932       --  Look for the Global_Final_List
1933
1934       if Is_Entity_Name (Flist_Ref) then
1935          Flist := Entity (Flist_Ref);
1936
1937       --  Look for the final list associated with an access to controlled
1938
1939       elsif  Nkind (Flist_Ref) = N_Selected_Component
1940         and then Is_Entity_Name (Prefix (Flist_Ref))
1941       then
1942          Flist :=  Entity (Prefix (Flist_Ref));
1943       else
1944          return False;
1945       end if;
1946
1947       return Present (Flist)
1948         and then Present (Scope (Flist))
1949         and then Enclosing_Dynamic_Scope (Flist) = Standard_Standard;
1950    end Global_Flist_Ref;
1951
1952    ----------------------------------
1953    -- Has_New_Controlled_Component --
1954    ----------------------------------
1955
1956    function Has_New_Controlled_Component (E : Entity_Id) return Boolean is
1957       Comp : Entity_Id;
1958
1959    begin
1960       if not Is_Tagged_Type (E) then
1961          return Has_Controlled_Component (E);
1962       elsif not Is_Derived_Type (E) then
1963          return Has_Controlled_Component (E);
1964       end if;
1965
1966       Comp := First_Component (E);
1967       while Present (Comp) loop
1968
1969          if Chars (Comp) = Name_uParent then
1970             null;
1971
1972          elsif Scope (Original_Record_Component (Comp)) = E
1973            and then Needs_Finalization (Etype (Comp))
1974          then
1975             return True;
1976          end if;
1977
1978          Next_Component (Comp);
1979       end loop;
1980
1981       return False;
1982    end Has_New_Controlled_Component;
1983
1984    --------------------------
1985    -- In_Finalization_Root --
1986    --------------------------
1987
1988    --  It would seem simpler to test Scope (RTE (RE_Root_Controlled)) but
1989    --  the purpose of this function is to avoid a circular call to Rtsfind
1990    --  which would been caused by such a test.
1991
1992    function In_Finalization_Root (E : Entity_Id) return Boolean is
1993       S : constant Entity_Id := Scope (E);
1994
1995    begin
1996       return Chars (Scope (S))     = Name_System
1997         and then Chars (S)         = Name_Finalization_Root
1998         and then Scope (Scope (S)) = Standard_Standard;
1999    end  In_Finalization_Root;
2000
2001    ------------------------------------
2002    -- Insert_Actions_In_Scope_Around --
2003    ------------------------------------
2004
2005    procedure Insert_Actions_In_Scope_Around (N : Node_Id) is
2006       SE     : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
2007       Target : Node_Id;
2008
2009    begin
2010       --  If the node to be wrapped is the triggering statement of an
2011       --  asynchronous select, it is not part of a statement list. The
2012       --  actions must be inserted before the Select itself, which is
2013       --  part of some list of statements. Note that the triggering
2014       --  alternative includes the triggering statement and an optional
2015       --  statement list. If the node to be wrapped is part of that list,
2016       --  the normal insertion applies.
2017
2018       if Nkind (Parent (Node_To_Be_Wrapped)) = N_Triggering_Alternative
2019         and then not Is_List_Member (Node_To_Be_Wrapped)
2020       then
2021          Target := Parent (Parent (Node_To_Be_Wrapped));
2022       else
2023          Target := N;
2024       end if;
2025
2026       if Present (SE.Actions_To_Be_Wrapped_Before) then
2027          Insert_List_Before (Target, SE.Actions_To_Be_Wrapped_Before);
2028          SE.Actions_To_Be_Wrapped_Before := No_List;
2029       end if;
2030
2031       if Present (SE.Actions_To_Be_Wrapped_After) then
2032          Insert_List_After (Target, SE.Actions_To_Be_Wrapped_After);
2033          SE.Actions_To_Be_Wrapped_After := No_List;
2034       end if;
2035    end Insert_Actions_In_Scope_Around;
2036
2037    -----------------------
2038    -- Make_Adjust_Call --
2039    -----------------------
2040
2041    function Make_Adjust_Call
2042      (Ref         : Node_Id;
2043       Typ         : Entity_Id;
2044       Flist_Ref   : Node_Id;
2045       With_Attach : Node_Id;
2046       Allocator   : Boolean := False) return List_Id
2047    is
2048       Loc    : constant Source_Ptr := Sloc (Ref);
2049       Res    : constant List_Id    := New_List;
2050       Utyp   : Entity_Id;
2051       Proc   : Entity_Id;
2052       Cref   : Node_Id := Ref;
2053       Cref2  : Node_Id;
2054       Attach : Node_Id := With_Attach;
2055
2056    begin
2057       if Is_Class_Wide_Type (Typ) then
2058          Utyp := Underlying_Type (Base_Type (Root_Type (Typ)));
2059       else
2060          Utyp := Underlying_Type (Base_Type (Typ));
2061       end if;
2062
2063       Set_Assignment_OK (Cref);
2064
2065       --  Deal with non-tagged derivation of private views
2066
2067       if Is_Untagged_Derivation (Typ) then
2068          Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
2069          Cref := Unchecked_Convert_To (Utyp, Cref);
2070          Set_Assignment_OK (Cref);
2071          --  To prevent problems with UC see 1.156 RH ???
2072       end if;
2073
2074       --  If the underlying_type is a subtype, we are dealing with
2075       --  the completion of a private type. We need to access
2076       --  the base type and generate a conversion to it.
2077
2078       if Utyp /= Base_Type (Utyp) then
2079          pragma Assert (Is_Private_Type (Typ));
2080          Utyp := Base_Type (Utyp);
2081          Cref := Unchecked_Convert_To (Utyp, Cref);
2082       end if;
2083
2084       --  If the object is unanalyzed, set its expected type for use
2085       --  in Convert_View in case an additional conversion is needed.
2086
2087       if No (Etype (Cref))
2088         and then Nkind (Cref) /= N_Unchecked_Type_Conversion
2089       then
2090          Set_Etype (Cref, Typ);
2091       end if;
2092
2093       --  We do not need to attach to one of the Global Final Lists
2094       --  the objects whose type is Finalize_Storage_Only
2095
2096       if Finalize_Storage_Only (Typ)
2097         and then (Global_Flist_Ref (Flist_Ref)
2098           or else Entity (Constant_Value (RTE (RE_Garbage_Collected)))
2099                   = Standard_True)
2100       then
2101          Attach := Make_Integer_Literal (Loc, 0);
2102       end if;
2103
2104       --  Special case for allocators: need initialization of the chain
2105       --  pointers. For the 0 case, reset them to null.
2106
2107       if Allocator then
2108          pragma Assert (Nkind (Attach) = N_Integer_Literal);
2109
2110          if Intval (Attach) = 0 then
2111             Set_Intval (Attach, Uint_4);
2112          end if;
2113       end if;
2114
2115       --  Generate:
2116       --    Deep_Adjust (Flist_Ref, Ref, Attach);
2117
2118       if Has_Controlled_Component (Utyp)
2119         or else Is_Class_Wide_Type (Typ)
2120       then
2121          if Is_Tagged_Type (Utyp) then
2122             Proc := Find_Prim_Op (Utyp, TSS_Deep_Adjust);
2123
2124          else
2125             Proc := TSS (Utyp, TSS_Deep_Adjust);
2126          end if;
2127
2128          Cref := Convert_View (Proc, Cref, 2);
2129
2130          Append_To (Res,
2131            Make_Procedure_Call_Statement (Loc,
2132              Name => New_Reference_To (Proc, Loc),
2133              Parameter_Associations =>
2134                New_List (Flist_Ref, Cref, Attach)));
2135
2136       --  Generate:
2137       --    if With_Attach then
2138       --       Attach_To_Final_List (Ref, Flist_Ref);
2139       --    end if;
2140       --    Adjust (Ref);
2141
2142       else -- Is_Controlled (Utyp)
2143
2144          Proc  := Find_Prim_Op (Utyp, Name_Of (Adjust_Case));
2145          Cref  := Convert_View (Proc, Cref);
2146          Cref2 := New_Copy_Tree (Cref);
2147
2148          Append_To (Res,
2149            Make_Procedure_Call_Statement (Loc,
2150            Name => New_Reference_To (Proc, Loc),
2151            Parameter_Associations => New_List (Cref2)));
2152
2153          Append_To (Res, Make_Attach_Call (Cref, Flist_Ref, Attach));
2154       end if;
2155
2156       return Res;
2157    end Make_Adjust_Call;
2158
2159    ----------------------
2160    -- Make_Attach_Call --
2161    ----------------------
2162
2163    --  Generate:
2164    --    System.FI.Attach_To_Final_List (Flist, Ref, Nb_Link)
2165
2166    function Make_Attach_Call
2167      (Obj_Ref     : Node_Id;
2168       Flist_Ref   : Node_Id;
2169       With_Attach : Node_Id) return Node_Id
2170    is
2171       Loc : constant Source_Ptr := Sloc (Obj_Ref);
2172
2173    begin
2174       --  Optimization: If the number of links is statically '0', don't
2175       --  call the attach_proc.
2176
2177       if Nkind (With_Attach) = N_Integer_Literal
2178         and then Intval (With_Attach) = Uint_0
2179       then
2180          return Make_Null_Statement (Loc);
2181       end if;
2182
2183       return
2184         Make_Procedure_Call_Statement (Loc,
2185           Name => New_Reference_To (RTE (RE_Attach_To_Final_List), Loc),
2186           Parameter_Associations => New_List (
2187             Flist_Ref,
2188             OK_Convert_To (RTE (RE_Finalizable), Obj_Ref),
2189             With_Attach));
2190    end Make_Attach_Call;
2191
2192    ----------------
2193    -- Make_Clean --
2194    ----------------
2195
2196    function Make_Clean
2197      (N                          : Node_Id;
2198       Clean                      : Entity_Id;
2199       Mark                       : Entity_Id;
2200       Flist                      : Entity_Id;
2201       Is_Task                    : Boolean;
2202       Is_Master                  : Boolean;
2203       Is_Protected_Subprogram    : Boolean;
2204       Is_Task_Allocation_Block   : Boolean;
2205       Is_Asynchronous_Call_Block : Boolean;
2206       Chained_Cleanup_Action     : Node_Id) return Node_Id
2207    is
2208       Loc  : constant Source_Ptr := Sloc (Clean);
2209       Stmt : constant List_Id    := New_List;
2210
2211       Sbody        : Node_Id;
2212       Spec         : Node_Id;
2213       Name         : Node_Id;
2214       Param        : Node_Id;
2215       Param_Type   : Entity_Id;
2216       Pid          : Entity_Id := Empty;
2217       Cancel_Param : Entity_Id;
2218
2219    begin
2220       if Is_Task then
2221          if Restricted_Profile then
2222             Append_To
2223               (Stmt, Build_Runtime_Call (Loc, RE_Complete_Restricted_Task));
2224          else
2225             Append_To (Stmt, Build_Runtime_Call (Loc, RE_Complete_Task));
2226          end if;
2227
2228       elsif Is_Master then
2229          if Restriction_Active (No_Task_Hierarchy) = False then
2230             Append_To (Stmt, Build_Runtime_Call (Loc, RE_Complete_Master));
2231          end if;
2232
2233       elsif Is_Protected_Subprogram then
2234
2235          --  Add statements to the cleanup handler of the (ordinary)
2236          --  subprogram expanded to implement a protected subprogram,
2237          --  unlocking the protected object parameter and undeferring abort.
2238          --  If this is a protected procedure, and the object contains
2239          --  entries, this also calls the entry service routine.
2240
2241          --  NOTE: This cleanup handler references _object, a parameter
2242          --        to the procedure.
2243
2244          --  Find the _object parameter representing the protected object
2245
2246          Spec := Parent (Corresponding_Spec (N));
2247
2248          Param := First (Parameter_Specifications (Spec));
2249          loop
2250             Param_Type := Etype (Parameter_Type (Param));
2251
2252             if Ekind (Param_Type) = E_Record_Type then
2253                Pid := Corresponding_Concurrent_Type (Param_Type);
2254             end if;
2255
2256             exit when No (Param) or else Present (Pid);
2257             Next (Param);
2258          end loop;
2259
2260          pragma Assert (Present (Param));
2261
2262          --  If the associated protected object declares entries,
2263          --  a protected procedure has to service entry queues.
2264          --  In this case, add
2265
2266          --  Service_Entries (_object._object'Access);
2267
2268          --  _object is the record used to implement the protected object.
2269          --  It is a parameter to the protected subprogram.
2270
2271          if Nkind (Specification (N)) = N_Procedure_Specification
2272            and then Has_Entries (Pid)
2273          then
2274             case Corresponding_Runtime_Package (Pid) is
2275                when System_Tasking_Protected_Objects_Entries =>
2276                   Name := New_Reference_To (RTE (RE_Service_Entries), Loc);
2277
2278                when System_Tasking_Protected_Objects_Single_Entry =>
2279                   Name := New_Reference_To (RTE (RE_Service_Entry), Loc);
2280
2281                when others =>
2282                   raise Program_Error;
2283             end case;
2284
2285             Append_To (Stmt,
2286               Make_Procedure_Call_Statement (Loc,
2287                 Name => Name,
2288                 Parameter_Associations => New_List (
2289                   Make_Attribute_Reference (Loc,
2290                     Prefix =>
2291                       Make_Selected_Component (Loc,
2292                         Prefix => New_Reference_To (
2293                           Defining_Identifier (Param), Loc),
2294                         Selector_Name =>
2295                           Make_Identifier (Loc, Name_uObject)),
2296                     Attribute_Name => Name_Unchecked_Access))));
2297
2298          else
2299             --  Unlock (_object._object'Access);
2300
2301             --  object is the record used to implement the protected object.
2302             --  It is a parameter to the protected subprogram.
2303
2304             case Corresponding_Runtime_Package (Pid) is
2305                when System_Tasking_Protected_Objects_Entries =>
2306                   Name := New_Reference_To (RTE (RE_Unlock_Entries), Loc);
2307
2308                when System_Tasking_Protected_Objects_Single_Entry =>
2309                   Name := New_Reference_To (RTE (RE_Unlock_Entry), Loc);
2310
2311                when System_Tasking_Protected_Objects =>
2312                   Name := New_Reference_To (RTE (RE_Unlock), Loc);
2313
2314                when others =>
2315                   raise Program_Error;
2316             end case;
2317
2318             Append_To (Stmt,
2319               Make_Procedure_Call_Statement (Loc,
2320                 Name => Name,
2321                 Parameter_Associations => New_List (
2322                   Make_Attribute_Reference (Loc,
2323                     Prefix =>
2324                       Make_Selected_Component (Loc,
2325                         Prefix =>
2326                           New_Reference_To (Defining_Identifier (Param), Loc),
2327                         Selector_Name =>
2328                           Make_Identifier (Loc, Name_uObject)),
2329                     Attribute_Name => Name_Unchecked_Access))));
2330          end if;
2331
2332          if Abort_Allowed then
2333
2334             --  Abort_Undefer;
2335
2336             Append_To (Stmt,
2337               Make_Procedure_Call_Statement (Loc,
2338                 Name =>
2339                   New_Reference_To (
2340                     RTE (RE_Abort_Undefer), Loc),
2341                 Parameter_Associations => Empty_List));
2342          end if;
2343
2344       elsif Is_Task_Allocation_Block then
2345
2346          --  Add a call to Expunge_Unactivated_Tasks to the cleanup
2347          --  handler of a block created for the dynamic allocation of
2348          --  tasks:
2349
2350          --  Expunge_Unactivated_Tasks (_chain);
2351
2352          --  where _chain is the list of tasks created by the allocator
2353          --  but not yet activated. This list will be empty unless
2354          --  the block completes abnormally.
2355
2356          --  This only applies to dynamically allocated tasks;
2357          --  other unactivated tasks are completed by Complete_Task or
2358          --  Complete_Master.
2359
2360          --  NOTE: This cleanup handler references _chain, a local
2361          --        object.
2362
2363          Append_To (Stmt,
2364            Make_Procedure_Call_Statement (Loc,
2365              Name =>
2366                New_Reference_To (
2367                  RTE (RE_Expunge_Unactivated_Tasks), Loc),
2368              Parameter_Associations => New_List (
2369                New_Reference_To (Activation_Chain_Entity (N), Loc))));
2370
2371       elsif Is_Asynchronous_Call_Block then
2372
2373          --  Add a call to attempt to cancel the asynchronous entry call
2374          --  whenever the block containing the abortable part is exited.
2375
2376          --  NOTE: This cleanup handler references C, a local object
2377
2378          --  Get the argument to the Cancel procedure
2379          Cancel_Param := Entry_Cancel_Parameter (Entity (Identifier (N)));
2380
2381          --  If it is of type Communication_Block, this must be a
2382          --  protected entry call.
2383
2384          if Is_RTE (Etype (Cancel_Param), RE_Communication_Block) then
2385
2386             Append_To (Stmt,
2387
2388             --  if Enqueued (Cancel_Parameter) then
2389
2390               Make_Implicit_If_Statement (Clean,
2391                 Condition => Make_Function_Call (Loc,
2392                   Name => New_Reference_To (
2393                     RTE (RE_Enqueued), Loc),
2394                   Parameter_Associations => New_List (
2395                     New_Reference_To (Cancel_Param, Loc))),
2396                 Then_Statements => New_List (
2397
2398             --  Cancel_Protected_Entry_Call (Cancel_Param);
2399
2400                   Make_Procedure_Call_Statement (Loc,
2401                     Name => New_Reference_To (
2402                       RTE (RE_Cancel_Protected_Entry_Call), Loc),
2403                     Parameter_Associations => New_List (
2404                       New_Reference_To (Cancel_Param, Loc))))));
2405
2406          --  Asynchronous delay
2407
2408          elsif Is_RTE (Etype (Cancel_Param), RE_Delay_Block) then
2409             Append_To (Stmt,
2410               Make_Procedure_Call_Statement (Loc,
2411                 Name => New_Reference_To (RTE (RE_Cancel_Async_Delay), Loc),
2412                 Parameter_Associations => New_List (
2413                   Make_Attribute_Reference (Loc,
2414                     Prefix => New_Reference_To (Cancel_Param, Loc),
2415                     Attribute_Name => Name_Unchecked_Access))));
2416
2417          --  Task entry call
2418
2419          else
2420             --  Append call to Cancel_Task_Entry_Call (C);
2421
2422             Append_To (Stmt,
2423               Make_Procedure_Call_Statement (Loc,
2424                 Name => New_Reference_To (
2425                   RTE (RE_Cancel_Task_Entry_Call),
2426                   Loc),
2427                 Parameter_Associations => New_List (
2428                   New_Reference_To (Cancel_Param, Loc))));
2429
2430          end if;
2431       end if;
2432
2433       if Present (Flist) then
2434          Append_To (Stmt,
2435            Make_Procedure_Call_Statement (Loc,
2436              Name => New_Reference_To (RTE (RE_Finalize_List), Loc),
2437              Parameter_Associations => New_List (
2438                     New_Reference_To (Flist, Loc))));
2439       end if;
2440
2441       if Present (Mark) then
2442          Append_To (Stmt,
2443            Make_Procedure_Call_Statement (Loc,
2444              Name => New_Reference_To (RTE (RE_SS_Release), Loc),
2445              Parameter_Associations => New_List (
2446                     New_Reference_To (Mark, Loc))));
2447       end if;
2448
2449       if Present (Chained_Cleanup_Action) then
2450          Append_To (Stmt,
2451            Make_Procedure_Call_Statement (Loc,
2452              Name => Chained_Cleanup_Action));
2453       end if;
2454
2455       Sbody :=
2456         Make_Subprogram_Body (Loc,
2457           Specification =>
2458             Make_Procedure_Specification (Loc,
2459               Defining_Unit_Name => Clean),
2460
2461           Declarations  => New_List,
2462
2463           Handled_Statement_Sequence =>
2464             Make_Handled_Sequence_Of_Statements (Loc,
2465               Statements => Stmt));
2466
2467       if Present (Flist) or else Is_Task or else Is_Master then
2468          Wrap_Cleanup_Procedure (Sbody);
2469       end if;
2470
2471       --  We do not want debug information for _Clean routines,
2472       --  since it just confuses the debugging operation unless
2473       --  we are debugging generated code.
2474
2475       if not Debug_Generated_Code then
2476          Set_Debug_Info_Off (Clean, True);
2477       end if;
2478
2479       return Sbody;
2480    end Make_Clean;
2481
2482    --------------------------
2483    -- Make_Deep_Array_Body --
2484    --------------------------
2485
2486    --  Array components are initialized and adjusted in the normal order
2487    --  and finalized in the reverse order. Exceptions are handled and
2488    --  Program_Error is re-raise in the Adjust and Finalize case
2489    --  (RM 7.6.1(12)). Generate the following code :
2490    --
2491    --  procedure Deep_<P>   --  with <P> being Initialize or Adjust or Finalize
2492    --   (L : in out Finalizable_Ptr;
2493    --    V : in out Typ)
2494    --  is
2495    --  begin
2496    --     for J1 in             Typ'First (1) .. Typ'Last (1) loop
2497    --               ^ reverse ^  --  in the finalization case
2498    --        ...
2499    --           for J2 in Typ'First (n) .. Typ'Last (n) loop
2500    --                 Make_<P>_Call (Typ, V (J1, .. , Jn), L, V);
2501    --           end loop;
2502    --        ...
2503    --     end loop;
2504    --  exception                                --  not in the
2505    --     when others => raise Program_Error;   --     Initialize case
2506    --  end Deep_<P>;
2507
2508    function Make_Deep_Array_Body
2509      (Prim : Final_Primitives;
2510       Typ  : Entity_Id) return List_Id
2511    is
2512       Loc : constant Source_Ptr := Sloc (Typ);
2513
2514       Index_List : constant List_Id := New_List;
2515       --  Stores the list of references to the indexes (one per dimension)
2516
2517       function One_Component return List_Id;
2518       --  Create one statement to initialize/adjust/finalize one array
2519       --  component, designated by a full set of indices.
2520
2521       function One_Dimension (N : Int) return List_Id;
2522       --  Create loop to deal with one dimension of the array. The single
2523       --  statement in the body of the loop initializes the inner dimensions if
2524       --  any, or else a single component.
2525
2526       -------------------
2527       -- One_Component --
2528       -------------------
2529
2530       function One_Component return List_Id is
2531          Comp_Typ : constant Entity_Id := Component_Type (Typ);
2532          Comp_Ref : constant Node_Id :=
2533                       Make_Indexed_Component (Loc,
2534                         Prefix      => Make_Identifier (Loc, Name_V),
2535                         Expressions => Index_List);
2536
2537       begin
2538          --  Set the etype of the component Reference, which is used to
2539          --  determine whether a conversion to a parent type is needed.
2540
2541          Set_Etype (Comp_Ref, Comp_Typ);
2542
2543          case Prim is
2544             when Initialize_Case =>
2545                return Make_Init_Call (Comp_Ref, Comp_Typ,
2546                         Make_Identifier (Loc, Name_L),
2547                         Make_Identifier (Loc, Name_B));
2548
2549             when Adjust_Case =>
2550                return Make_Adjust_Call (Comp_Ref, Comp_Typ,
2551                         Make_Identifier (Loc, Name_L),
2552                         Make_Identifier (Loc, Name_B));
2553
2554             when Finalize_Case =>
2555                return Make_Final_Call (Comp_Ref, Comp_Typ,
2556                         Make_Identifier (Loc, Name_B));
2557          end case;
2558       end One_Component;
2559
2560       -------------------
2561       -- One_Dimension --
2562       -------------------
2563
2564       function One_Dimension (N : Int) return List_Id is
2565          Index : Entity_Id;
2566
2567       begin
2568          if N > Number_Dimensions (Typ) then
2569             return One_Component;
2570
2571          else
2572             Index :=
2573               Make_Defining_Identifier (Loc, New_External_Name ('J', N));
2574
2575             Append_To (Index_List, New_Reference_To (Index, Loc));
2576
2577             return New_List (
2578               Make_Implicit_Loop_Statement (Typ,
2579                 Identifier => Empty,
2580                 Iteration_Scheme =>
2581                   Make_Iteration_Scheme (Loc,
2582                     Loop_Parameter_Specification =>
2583                       Make_Loop_Parameter_Specification (Loc,
2584                         Defining_Identifier => Index,
2585                         Discrete_Subtype_Definition =>
2586                           Make_Attribute_Reference (Loc,
2587                             Prefix => Make_Identifier (Loc, Name_V),
2588                             Attribute_Name  => Name_Range,
2589                             Expressions => New_List (
2590                               Make_Integer_Literal (Loc, N))),
2591                         Reverse_Present => Prim = Finalize_Case)),
2592                 Statements => One_Dimension (N + 1)));
2593          end if;
2594       end One_Dimension;
2595
2596    --  Start of processing for Make_Deep_Array_Body
2597
2598    begin
2599       return One_Dimension (1);
2600    end Make_Deep_Array_Body;
2601
2602    --------------------
2603    -- Make_Deep_Proc --
2604    --------------------
2605
2606    --  Generate:
2607    --    procedure DEEP_<prim>
2608    --      (L : IN OUT Finalizable_Ptr;    -- not for Finalize
2609    --       V : IN OUT <typ>;
2610    --       B : IN Short_Short_Integer) is
2611    --    begin
2612    --       <stmts>;
2613    --    exception                   --  Finalize and Adjust Cases only
2614    --       raise Program_Error;     --  idem
2615    --    end DEEP_<prim>;
2616
2617    function Make_Deep_Proc
2618      (Prim  : Final_Primitives;
2619       Typ   : Entity_Id;
2620       Stmts : List_Id) return Entity_Id
2621    is
2622       Loc       : constant Source_Ptr := Sloc (Typ);
2623       Formals   : List_Id;
2624       Proc_Name : Entity_Id;
2625       Handler   : List_Id := No_List;
2626       Type_B    : Entity_Id;
2627
2628    begin
2629       if Prim = Finalize_Case then
2630          Formals := New_List;
2631          Type_B := Standard_Boolean;
2632
2633       else
2634          Formals := New_List (
2635            Make_Parameter_Specification (Loc,
2636              Defining_Identifier => Make_Defining_Identifier (Loc, Name_L),
2637              In_Present          => True,
2638              Out_Present         => True,
2639              Parameter_Type      =>
2640                New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
2641          Type_B := Standard_Short_Short_Integer;
2642       end if;
2643
2644       Append_To (Formals,
2645         Make_Parameter_Specification (Loc,
2646           Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
2647           In_Present          => True,
2648           Out_Present         => True,
2649           Parameter_Type      => New_Reference_To (Typ, Loc)));
2650
2651       Append_To (Formals,
2652         Make_Parameter_Specification (Loc,
2653           Defining_Identifier => Make_Defining_Identifier (Loc, Name_B),
2654           Parameter_Type      => New_Reference_To (Type_B, Loc)));
2655
2656       if Prim = Finalize_Case or else Prim = Adjust_Case then
2657          Handler := New_List (Make_Handler_For_Ctrl_Operation (Loc));
2658       end if;
2659
2660       Proc_Name :=
2661         Make_Defining_Identifier (Loc,
2662           Chars => Make_TSS_Name (Typ, Deep_Name_Of (Prim)));
2663
2664       Discard_Node (
2665         Make_Subprogram_Body (Loc,
2666           Specification =>
2667             Make_Procedure_Specification (Loc,
2668               Defining_Unit_Name       => Proc_Name,
2669               Parameter_Specifications => Formals),
2670
2671           Declarations =>  Empty_List,
2672           Handled_Statement_Sequence =>
2673             Make_Handled_Sequence_Of_Statements (Loc,
2674               Statements         => Stmts,
2675               Exception_Handlers => Handler)));
2676
2677       return Proc_Name;
2678    end Make_Deep_Proc;
2679
2680    ---------------------------
2681    -- Make_Deep_Record_Body --
2682    ---------------------------
2683
2684    --  The Deep procedures call the appropriate Controlling proc on the
2685    --  the controller component. In the init case, it also attach the
2686    --  controller to the current finalization list.
2687
2688    function Make_Deep_Record_Body
2689      (Prim : Final_Primitives;
2690       Typ  : Entity_Id) return List_Id
2691    is
2692       Loc            : constant Source_Ptr := Sloc (Typ);
2693       Controller_Typ : Entity_Id;
2694       Obj_Ref        : constant Node_Id := Make_Identifier (Loc, Name_V);
2695       Controller_Ref : constant Node_Id :=
2696                          Make_Selected_Component (Loc,
2697                            Prefix        => Obj_Ref,
2698                            Selector_Name =>
2699                              Make_Identifier (Loc, Name_uController));
2700       Res            : constant List_Id := New_List;
2701
2702    begin
2703       if Is_Inherently_Limited_Type (Typ) then
2704          Controller_Typ := RTE (RE_Limited_Record_Controller);
2705       else
2706          Controller_Typ := RTE (RE_Record_Controller);
2707       end if;
2708
2709       case Prim is
2710          when Initialize_Case =>
2711             Append_List_To (Res,
2712               Make_Init_Call (
2713                 Ref          => Controller_Ref,
2714                 Typ          => Controller_Typ,
2715                 Flist_Ref    => Make_Identifier (Loc, Name_L),
2716                 With_Attach  => Make_Identifier (Loc, Name_B)));
2717
2718             --  When the type is also a controlled type by itself,
2719             --  initialize it and attach it to the finalization chain.
2720
2721             if Is_Controlled (Typ) then
2722                Append_To (Res,
2723                  Make_Procedure_Call_Statement (Loc,
2724                    Name => New_Reference_To (
2725                      Find_Prim_Op (Typ, Name_Of (Prim)), Loc),
2726                    Parameter_Associations =>
2727                      New_List (New_Copy_Tree (Obj_Ref))));
2728
2729                Append_To (Res, Make_Attach_Call (
2730                  Obj_Ref      => New_Copy_Tree (Obj_Ref),
2731                  Flist_Ref    => Make_Identifier (Loc, Name_L),
2732                  With_Attach => Make_Identifier (Loc, Name_B)));
2733             end if;
2734
2735          when Adjust_Case =>
2736             Append_List_To (Res,
2737               Make_Adjust_Call (Controller_Ref, Controller_Typ,
2738                 Make_Identifier (Loc, Name_L),
2739                 Make_Identifier (Loc, Name_B)));
2740
2741             --  When the type is also a controlled type by itself,
2742             --  adjust it and attach it to the finalization chain.
2743
2744             if Is_Controlled (Typ) then
2745                Append_To (Res,
2746                  Make_Procedure_Call_Statement (Loc,
2747                    Name => New_Reference_To (
2748                      Find_Prim_Op (Typ, Name_Of (Prim)), Loc),
2749                    Parameter_Associations =>
2750                      New_List (New_Copy_Tree (Obj_Ref))));
2751
2752                Append_To (Res, Make_Attach_Call (
2753                  Obj_Ref      => New_Copy_Tree (Obj_Ref),
2754                  Flist_Ref    => Make_Identifier (Loc, Name_L),
2755                  With_Attach => Make_Identifier (Loc, Name_B)));
2756             end if;
2757
2758          when Finalize_Case =>
2759             if Is_Controlled (Typ) then
2760                Append_To (Res,
2761                  Make_Implicit_If_Statement (Obj_Ref,
2762                    Condition => Make_Identifier (Loc, Name_B),
2763                    Then_Statements => New_List (
2764                      Make_Procedure_Call_Statement (Loc,
2765                        Name => New_Reference_To (RTE (RE_Finalize_One), Loc),
2766                        Parameter_Associations => New_List (
2767                          OK_Convert_To (RTE (RE_Finalizable),
2768                            New_Copy_Tree (Obj_Ref))))),
2769
2770                    Else_Statements => New_List (
2771                      Make_Procedure_Call_Statement (Loc,
2772                        Name => New_Reference_To (
2773                          Find_Prim_Op (Typ, Name_Of (Prim)), Loc),
2774                        Parameter_Associations =>
2775                         New_List (New_Copy_Tree (Obj_Ref))))));
2776             end if;
2777
2778             Append_List_To (Res,
2779               Make_Final_Call (Controller_Ref, Controller_Typ,
2780                 Make_Identifier (Loc, Name_B)));
2781       end case;
2782       return Res;
2783    end Make_Deep_Record_Body;
2784
2785    ----------------------
2786    -- Make_Final_Call --
2787    ----------------------
2788
2789    function Make_Final_Call
2790      (Ref         : Node_Id;
2791       Typ         : Entity_Id;
2792       With_Detach : Node_Id) return List_Id
2793    is
2794       Loc   : constant Source_Ptr := Sloc (Ref);
2795       Res   : constant List_Id    := New_List;
2796       Cref  : Node_Id;
2797       Cref2 : Node_Id;
2798       Proc  : Entity_Id;
2799       Utyp  : Entity_Id;
2800
2801    begin
2802       if Is_Class_Wide_Type (Typ) then
2803          Utyp := Root_Type (Typ);
2804          Cref := Ref;
2805
2806       elsif Is_Concurrent_Type (Typ) then
2807          Utyp := Corresponding_Record_Type (Typ);
2808          Cref := Convert_Concurrent (Ref, Typ);
2809
2810       elsif Is_Private_Type (Typ)
2811         and then Present (Full_View (Typ))
2812         and then Is_Concurrent_Type (Full_View (Typ))
2813       then
2814          Utyp := Corresponding_Record_Type (Full_View (Typ));
2815          Cref := Convert_Concurrent (Ref, Full_View (Typ));
2816       else
2817          Utyp := Typ;
2818          Cref := Ref;
2819       end if;
2820
2821       Utyp := Underlying_Type (Base_Type (Utyp));
2822       Set_Assignment_OK (Cref);
2823
2824       --  Deal with non-tagged derivation of private views. If the parent is
2825       --  now known to be protected, the finalization routine is the one
2826       --  defined on the corresponding record of the ancestor (corresponding
2827       --  records do not automatically inherit operations, but maybe they
2828       --  should???)
2829
2830       if Is_Untagged_Derivation (Typ) then
2831          if Is_Protected_Type (Typ) then
2832             Utyp := Corresponding_Record_Type (Root_Type (Base_Type (Typ)));
2833          else
2834             Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
2835          end if;
2836
2837          Cref := Unchecked_Convert_To (Utyp, Cref);
2838
2839          --  We need to set Assignment_OK to prevent problems with unchecked
2840          --  conversions, where we do not want them to be converted back in the
2841          --  case of untagged record derivation (see code in Make_*_Call
2842          --  procedures for similar situations).
2843
2844          Set_Assignment_OK (Cref);
2845       end if;
2846
2847       --  If the underlying_type is a subtype, we are dealing with
2848       --  the completion of a private type. We need to access
2849       --  the base type and generate a conversion to it.
2850
2851       if Utyp /= Base_Type (Utyp) then
2852          pragma Assert (Is_Private_Type (Typ));
2853          Utyp := Base_Type (Utyp);
2854          Cref := Unchecked_Convert_To (Utyp, Cref);
2855       end if;
2856
2857       --  Generate:
2858       --    Deep_Finalize (Ref, With_Detach);
2859
2860       if Has_Controlled_Component (Utyp)
2861         or else Is_Class_Wide_Type (Typ)
2862       then
2863          if Is_Tagged_Type (Utyp) then
2864             Proc := Find_Prim_Op (Utyp, TSS_Deep_Finalize);
2865          else
2866             Proc := TSS (Utyp, TSS_Deep_Finalize);
2867          end if;
2868
2869          Cref := Convert_View (Proc, Cref);
2870
2871          Append_To (Res,
2872            Make_Procedure_Call_Statement (Loc,
2873              Name => New_Reference_To (Proc, Loc),
2874              Parameter_Associations =>
2875                New_List (Cref, With_Detach)));
2876
2877       --  Generate:
2878       --    if With_Detach then
2879       --       Finalize_One (Ref);
2880       --    else
2881       --       Finalize (Ref);
2882       --    end if;
2883
2884       else
2885          Proc := Find_Prim_Op (Utyp, Name_Of (Finalize_Case));
2886
2887          if Chars (With_Detach) = Chars (Standard_True) then
2888             Append_To (Res,
2889               Make_Procedure_Call_Statement (Loc,
2890                 Name => New_Reference_To (RTE (RE_Finalize_One), Loc),
2891                 Parameter_Associations => New_List (
2892                   OK_Convert_To (RTE (RE_Finalizable), Cref))));
2893
2894          elsif Chars (With_Detach) = Chars (Standard_False) then
2895             Append_To (Res,
2896               Make_Procedure_Call_Statement (Loc,
2897                 Name => New_Reference_To (Proc, Loc),
2898                 Parameter_Associations =>
2899                   New_List (Convert_View (Proc, Cref))));
2900
2901          else
2902             Cref2 := New_Copy_Tree (Cref);
2903             Append_To (Res,
2904               Make_Implicit_If_Statement (Ref,
2905                 Condition => With_Detach,
2906                 Then_Statements => New_List (
2907                   Make_Procedure_Call_Statement (Loc,
2908                     Name => New_Reference_To (RTE (RE_Finalize_One), Loc),
2909                     Parameter_Associations => New_List (
2910                       OK_Convert_To (RTE (RE_Finalizable), Cref)))),
2911
2912                 Else_Statements => New_List (
2913                   Make_Procedure_Call_Statement (Loc,
2914                     Name => New_Reference_To (Proc, Loc),
2915                     Parameter_Associations =>
2916                       New_List (Convert_View (Proc, Cref2))))));
2917          end if;
2918       end if;
2919
2920       return Res;
2921    end Make_Final_Call;
2922
2923    -------------------------------------
2924    -- Make_Handler_For_Ctrl_Operation --
2925    -------------------------------------
2926
2927    --  Generate:
2928
2929    --    when E : others =>
2930    --      Raise_From_Controlled_Operation (X => E);
2931
2932    --  or:
2933
2934    --    when others =>
2935    --      raise Program_Error [finalize raised exception];
2936
2937    --  depending on whether Raise_From_Controlled_Operation is available
2938
2939    function Make_Handler_For_Ctrl_Operation
2940      (Loc : Source_Ptr) return Node_Id
2941    is
2942       E_Occ : Entity_Id;
2943       --  Choice parameter (for the first case above)
2944
2945       Raise_Node : Node_Id;
2946       --  Procedure call or raise statement
2947
2948    begin
2949       if RTE_Available (RE_Raise_From_Controlled_Operation) then
2950
2951          --  Standard runtime: add choice parameter E, and pass it to
2952          --  Raise_From_Controlled_Operation so that the original exception
2953          --  name and message can be recorded in the exception message for
2954          --  Program_Error.
2955
2956          E_Occ := Make_Defining_Identifier (Loc, Name_E);
2957          Raise_Node := Make_Procedure_Call_Statement (Loc,
2958                          Name =>
2959                            New_Occurrence_Of (
2960                              RTE (RE_Raise_From_Controlled_Operation), Loc),
2961                          Parameter_Associations => New_List (
2962                            New_Occurrence_Of (E_Occ, Loc)));
2963
2964       else
2965          --  Restricted runtime: exception messages are not supported
2966
2967          E_Occ := Empty;
2968          Raise_Node := Make_Raise_Program_Error (Loc,
2969                          Reason => PE_Finalize_Raised_Exception);
2970       end if;
2971
2972       return Make_Implicit_Exception_Handler (Loc,
2973                Exception_Choices => New_List (Make_Others_Choice (Loc)),
2974                Choice_Parameter  => E_Occ,
2975                Statements        => New_List (Raise_Node));
2976    end Make_Handler_For_Ctrl_Operation;
2977
2978    --------------------
2979    -- Make_Init_Call --
2980    --------------------
2981
2982    function Make_Init_Call
2983      (Ref          : Node_Id;
2984       Typ          : Entity_Id;
2985       Flist_Ref    : Node_Id;
2986       With_Attach  : Node_Id) return List_Id
2987    is
2988       Loc     : constant Source_Ptr := Sloc (Ref);
2989       Is_Conc : Boolean;
2990       Res     : constant List_Id := New_List;
2991       Proc    : Entity_Id;
2992       Utyp    : Entity_Id;
2993       Cref    : Node_Id;
2994       Cref2   : Node_Id;
2995       Attach  : Node_Id := With_Attach;
2996
2997    begin
2998       if Is_Concurrent_Type (Typ) then
2999          Is_Conc := True;
3000          Utyp    := Corresponding_Record_Type (Typ);
3001          Cref    := Convert_Concurrent (Ref, Typ);
3002
3003       elsif Is_Private_Type (Typ)
3004         and then Present (Full_View (Typ))
3005         and then Is_Concurrent_Type (Underlying_Type (Typ))
3006       then
3007          Is_Conc := True;
3008          Utyp    := Corresponding_Record_Type (Underlying_Type (Typ));
3009          Cref    := Convert_Concurrent (Ref, Underlying_Type (Typ));
3010
3011       else
3012          Is_Conc := False;
3013          Utyp    := Typ;
3014          Cref    := Ref;
3015       end if;
3016
3017       Utyp := Underlying_Type (Base_Type (Utyp));
3018
3019       Set_Assignment_OK (Cref);
3020
3021       --  Deal with non-tagged derivation of private views
3022
3023       if Is_Untagged_Derivation (Typ)
3024         and then not Is_Conc
3025       then
3026          Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
3027          Cref := Unchecked_Convert_To (Utyp, Cref);
3028          Set_Assignment_OK (Cref);
3029          --  To prevent problems with UC see 1.156 RH ???
3030       end if;
3031
3032       --  If the underlying_type is a subtype, we are dealing with
3033       --  the completion of a private type. We need to access
3034       --  the base type and generate a conversion to it.
3035
3036       if Utyp /= Base_Type (Utyp) then
3037          pragma Assert (Is_Private_Type (Typ));
3038          Utyp := Base_Type (Utyp);
3039          Cref := Unchecked_Convert_To (Utyp, Cref);
3040       end if;
3041
3042       --  We do not need to attach to one of the Global Final Lists
3043       --  the objects whose type is Finalize_Storage_Only
3044
3045       if Finalize_Storage_Only (Typ)
3046         and then (Global_Flist_Ref (Flist_Ref)
3047           or else Entity (Constant_Value (RTE (RE_Garbage_Collected)))
3048                   = Standard_True)
3049       then
3050          Attach := Make_Integer_Literal (Loc, 0);
3051       end if;
3052
3053       --  Generate:
3054       --    Deep_Initialize (Ref, Flist_Ref);
3055
3056       if Has_Controlled_Component (Utyp) then
3057          Proc := TSS (Utyp, Deep_Name_Of (Initialize_Case));
3058
3059          Cref := Convert_View (Proc, Cref, 2);
3060
3061          Append_To (Res,
3062            Make_Procedure_Call_Statement (Loc,
3063              Name => New_Reference_To (Proc, Loc),
3064              Parameter_Associations => New_List (
3065                Node1 => Flist_Ref,
3066                Node2 => Cref,
3067                Node3 => Attach)));
3068
3069       --  Generate:
3070       --    Attach_To_Final_List (Ref, Flist_Ref);
3071       --    Initialize (Ref);
3072
3073       else -- Is_Controlled (Utyp)
3074          Proc  := Find_Prim_Op (Utyp, Name_Of (Initialize_Case));
3075          Check_Visibly_Controlled (Initialize_Case, Typ, Proc, Cref);
3076
3077          Cref  := Convert_View (Proc, Cref);
3078          Cref2 := New_Copy_Tree (Cref);
3079
3080          Append_To (Res,
3081            Make_Procedure_Call_Statement (Loc,
3082            Name => New_Reference_To (Proc, Loc),
3083            Parameter_Associations => New_List (Cref2)));
3084
3085          Append_To (Res,
3086            Make_Attach_Call (Cref, Flist_Ref, Attach));
3087       end if;
3088
3089       return Res;
3090    end Make_Init_Call;
3091
3092    --------------------------
3093    -- Make_Transient_Block --
3094    --------------------------
3095
3096    --  If finalization is involved, this function just wraps the instruction
3097    --  into a block whose name is the transient block entity, and then
3098    --  Expand_Cleanup_Actions (called on the expansion of the handled
3099    --  sequence of statements will do the necessary expansions for
3100    --  cleanups).
3101
3102    function Make_Transient_Block
3103      (Loc    : Source_Ptr;
3104       Action : Node_Id) return Node_Id
3105    is
3106       Flist  : constant Entity_Id := Finalization_Chain_Entity (Current_Scope);
3107       Decls  : constant List_Id   := New_List;
3108       Par    : constant Node_Id   := Parent (Action);
3109       Instrs : constant List_Id   := New_List (Action);
3110       Blk    : Node_Id;
3111
3112    begin
3113       --  Case where only secondary stack use is involved
3114
3115       if VM_Target = No_VM
3116         and then Uses_Sec_Stack (Current_Scope)
3117         and then No (Flist)
3118         and then Nkind (Action) /= N_Simple_Return_Statement
3119         and then Nkind (Par) /= N_Exception_Handler
3120       then
3121          declare
3122             S  : Entity_Id;
3123             K  : Entity_Kind;
3124
3125          begin
3126             S := Scope (Current_Scope);
3127             loop
3128                K := Ekind (S);
3129
3130                --  At the outer level, no need to release the sec stack
3131
3132                if S = Standard_Standard then
3133                   Set_Uses_Sec_Stack (Current_Scope, False);
3134                   exit;
3135
3136                --  In a function, only release the sec stack if the
3137                --  function does not return on the sec stack otherwise
3138                --  the result may be lost. The caller is responsible for
3139                --  releasing.
3140
3141                elsif K = E_Function then
3142                   Set_Uses_Sec_Stack (Current_Scope, False);
3143
3144                   if not Requires_Transient_Scope (Etype (S)) then
3145                      Set_Uses_Sec_Stack (S, True);
3146                      Check_Restriction (No_Secondary_Stack, Action);
3147                   end if;
3148
3149                   exit;
3150
3151                --  In a loop or entry we should install a block encompassing
3152                --  all the construct. For now just release right away.
3153
3154                elsif K = E_Loop or else K = E_Entry then
3155                   exit;
3156
3157                --  In a procedure or a block, we release on exit of the
3158                --  procedure or block. ??? memory leak can be created by
3159                --  recursive calls.
3160
3161                elsif K = E_Procedure
3162                  or else K = E_Block
3163                then
3164                   Set_Uses_Sec_Stack (S, True);
3165                   Check_Restriction (No_Secondary_Stack, Action);
3166                   Set_Uses_Sec_Stack (Current_Scope, False);
3167                   exit;
3168
3169                else
3170                   S := Scope (S);
3171                end if;
3172             end loop;
3173          end;
3174       end if;
3175
3176       --  Insert actions stuck in the transient scopes as well as all
3177       --  freezing nodes needed by those actions
3178
3179       Insert_Actions_In_Scope_Around (Action);
3180
3181       declare
3182          Last_Inserted : Node_Id := Prev (Action);
3183       begin
3184          if Present (Last_Inserted) then
3185             Freeze_All (First_Entity (Current_Scope), Last_Inserted);
3186          end if;
3187       end;
3188
3189       Blk :=
3190         Make_Block_Statement (Loc,
3191           Identifier => New_Reference_To (Current_Scope, Loc),
3192           Declarations => Decls,
3193           Handled_Statement_Sequence =>
3194             Make_Handled_Sequence_Of_Statements (Loc, Statements => Instrs),
3195           Has_Created_Identifier => True);
3196
3197       --  When the transient scope was established, we pushed the entry for
3198       --  the transient scope onto the scope stack, so that the scope was
3199       --  active for the installation of finalizable entities etc. Now we
3200       --  must remove this entry, since we have constructed a proper block.
3201
3202       Pop_Scope;
3203
3204       return Blk;
3205    end Make_Transient_Block;
3206
3207    ------------------------
3208    -- Needs_Finalization --
3209    ------------------------
3210
3211    function Needs_Finalization (T : Entity_Id) return Boolean is
3212
3213       function Has_Some_Controlled_Component (Rec : Entity_Id) return Boolean;
3214       --  If type is not frozen yet, check explicitly among its components,
3215       --  because the Has_Controlled_Component flag is not necessarily set.
3216
3217       -----------------------------------
3218       -- Has_Some_Controlled_Component --
3219       -----------------------------------
3220
3221       function Has_Some_Controlled_Component
3222         (Rec : Entity_Id) return Boolean
3223       is
3224          Comp : Entity_Id;
3225
3226       begin
3227          if Has_Controlled_Component (Rec) then
3228             return True;
3229
3230          elsif not Is_Frozen (Rec) then
3231             if Is_Record_Type (Rec) then
3232                Comp := First_Entity (Rec);
3233
3234                while Present (Comp) loop
3235                   if not Is_Type (Comp)
3236                     and then Needs_Finalization (Etype (Comp))
3237                   then
3238                      return True;
3239                   end if;
3240
3241                   Next_Entity (Comp);
3242                end loop;
3243
3244                return False;
3245
3246             elsif Is_Array_Type (Rec) then
3247                return Needs_Finalization (Component_Type (Rec));
3248
3249             else
3250                return Has_Controlled_Component (Rec);
3251             end if;
3252          else
3253             return False;
3254          end if;
3255       end Has_Some_Controlled_Component;
3256
3257    --  Start of processing for Needs_Finalization
3258
3259    begin
3260       --  Class-wide types must be treated as controlled because they may
3261       --  contain an extension that has controlled components
3262
3263       --  We can skip this if finalization is not available
3264
3265       return (Is_Class_Wide_Type (T)
3266                 and then not In_Finalization_Root (T)
3267                 and then not Restriction_Active (No_Finalization))
3268         or else Is_Controlled (T)
3269         or else Has_Some_Controlled_Component (T)
3270         or else (Is_Concurrent_Type (T)
3271                   and then Present (Corresponding_Record_Type (T))
3272                   and then Needs_Finalization (Corresponding_Record_Type (T)));
3273    end Needs_Finalization;
3274
3275    ------------------------
3276    -- Node_To_Be_Wrapped --
3277    ------------------------
3278
3279    function Node_To_Be_Wrapped return Node_Id is
3280    begin
3281       return Scope_Stack.Table (Scope_Stack.Last).Node_To_Be_Wrapped;
3282    end Node_To_Be_Wrapped;
3283
3284    ----------------------------
3285    -- Set_Node_To_Be_Wrapped --
3286    ----------------------------
3287
3288    procedure Set_Node_To_Be_Wrapped (N : Node_Id) is
3289    begin
3290       Scope_Stack.Table (Scope_Stack.Last).Node_To_Be_Wrapped := N;
3291    end Set_Node_To_Be_Wrapped;
3292
3293    ----------------------------------
3294    -- Store_After_Actions_In_Scope --
3295    ----------------------------------
3296
3297    procedure Store_After_Actions_In_Scope (L : List_Id) is
3298       SE : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
3299
3300    begin
3301       if Present (SE.Actions_To_Be_Wrapped_After) then
3302          Insert_List_Before_And_Analyze (
3303           First (SE.Actions_To_Be_Wrapped_After), L);
3304
3305       else
3306          SE.Actions_To_Be_Wrapped_After := L;
3307
3308          if Is_List_Member (SE.Node_To_Be_Wrapped) then
3309             Set_Parent (L, Parent (SE.Node_To_Be_Wrapped));
3310          else
3311             Set_Parent (L, SE.Node_To_Be_Wrapped);
3312          end if;
3313
3314          Analyze_List (L);
3315       end if;
3316    end Store_After_Actions_In_Scope;
3317
3318    -----------------------------------
3319    -- Store_Before_Actions_In_Scope --
3320    -----------------------------------
3321
3322    procedure Store_Before_Actions_In_Scope (L : List_Id) is
3323       SE : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
3324
3325    begin
3326       if Present (SE.Actions_To_Be_Wrapped_Before) then
3327          Insert_List_After_And_Analyze (
3328            Last (SE.Actions_To_Be_Wrapped_Before), L);
3329
3330       else
3331          SE.Actions_To_Be_Wrapped_Before := L;
3332
3333          if Is_List_Member (SE.Node_To_Be_Wrapped) then
3334             Set_Parent (L, Parent (SE.Node_To_Be_Wrapped));
3335          else
3336             Set_Parent (L, SE.Node_To_Be_Wrapped);
3337          end if;
3338
3339          Analyze_List (L);
3340       end if;
3341    end Store_Before_Actions_In_Scope;
3342
3343    --------------------------------
3344    -- Wrap_Transient_Declaration --
3345    --------------------------------
3346
3347    --  If a transient scope has been established during the processing of the
3348    --  Expression of an Object_Declaration, it is not possible to wrap the
3349    --  declaration into a transient block as usual case, otherwise the object
3350    --  would be itself declared in the wrong scope. Therefore, all entities (if
3351    --  any) defined in the transient block are moved to the proper enclosing
3352    --  scope, furthermore, if they are controlled variables they are finalized
3353    --  right after the declaration. The finalization list of the transient
3354    --  scope is defined as a renaming of the enclosing one so during their
3355    --  initialization they will be attached to the proper finalization
3356    --  list. For instance, the following declaration :
3357
3358    --        X : Typ := F (G (A), G (B));
3359
3360    --  (where G(A) and G(B) return controlled values, expanded as _v1 and _v2)
3361    --  is expanded into :
3362
3363    --    _local_final_list_1 : Finalizable_Ptr;
3364    --    X : Typ := [ complex Expression-Action ];
3365    --    Finalize_One(_v1);
3366    --    Finalize_One (_v2);
3367
3368    procedure Wrap_Transient_Declaration (N : Node_Id) is
3369       S           : Entity_Id;
3370       LC          : Entity_Id := Empty;
3371       Nodes       : List_Id;
3372       Loc         : constant Source_Ptr := Sloc (N);
3373       Enclosing_S : Entity_Id;
3374       Uses_SS     : Boolean;
3375       Next_N      : constant Node_Id := Next (N);
3376
3377    begin
3378       S := Current_Scope;
3379       Enclosing_S := Scope (S);
3380
3381       --  Insert Actions kept in the Scope stack
3382
3383       Insert_Actions_In_Scope_Around (N);
3384
3385       --  If the declaration is consuming some secondary stack, mark the
3386       --  Enclosing scope appropriately.
3387
3388       Uses_SS := Uses_Sec_Stack (S);
3389       Pop_Scope;
3390
3391       --  Create a List controller and rename the final list to be its
3392       --  internal final pointer:
3393       --       Lxxx : Simple_List_Controller;
3394       --       Fxxx : Finalizable_Ptr renames Lxxx.F;
3395
3396       if Present (Finalization_Chain_Entity (S)) then
3397          LC := Make_Defining_Identifier (Loc, New_Internal_Name ('L'));
3398
3399          Nodes := New_List (
3400            Make_Object_Declaration (Loc,
3401              Defining_Identifier => LC,
3402              Object_Definition   =>
3403                New_Reference_To (RTE (RE_Simple_List_Controller), Loc)),
3404
3405            Make_Object_Renaming_Declaration (Loc,
3406              Defining_Identifier => Finalization_Chain_Entity (S),
3407              Subtype_Mark => New_Reference_To (RTE (RE_Finalizable_Ptr), Loc),
3408              Name =>
3409                Make_Selected_Component (Loc,
3410                  Prefix        => New_Reference_To (LC, Loc),
3411                  Selector_Name => Make_Identifier (Loc, Name_F))));
3412
3413          --  Put the declaration at the beginning of the declaration part
3414          --  to make sure it will be before all other actions that have been
3415          --  inserted before N.
3416
3417          Insert_List_Before_And_Analyze (First (List_Containing (N)), Nodes);
3418
3419          --  Generate the Finalization calls by finalizing the list controller
3420          --  right away. It will be re-finalized on scope exit but it doesn't
3421          --  matter. It cannot be done when the call initializes a renaming
3422          --  object though because in this case, the object becomes a pointer
3423          --  to the temporary and thus increases its life span. Ditto if this
3424          --  is a renaming of a component of an expression (such as a function
3425          --  call).
3426
3427          --  Note that there is a problem if an actual in the call needs
3428          --  finalization, because in that case the call itself is the master,
3429          --  and the actual should be finalized on return from the call ???
3430
3431          if Nkind (N) = N_Object_Renaming_Declaration
3432            and then Needs_Finalization (Etype (Defining_Identifier (N)))
3433          then
3434             null;
3435
3436          elsif Nkind (N) = N_Object_Renaming_Declaration
3437            and then
3438              Nkind_In (Renamed_Object (Defining_Identifier (N)),
3439                        N_Selected_Component,
3440                        N_Indexed_Component)
3441            and then
3442              Needs_Finalization
3443                (Etype (Prefix (Renamed_Object (Defining_Identifier (N)))))
3444          then
3445             null;
3446
3447          else
3448             Nodes :=
3449               Make_Final_Call
3450                 (Ref         => New_Reference_To (LC, Loc),
3451                  Typ         => Etype (LC),
3452                  With_Detach => New_Reference_To (Standard_False, Loc));
3453
3454             if Present (Next_N) then
3455                Insert_List_Before_And_Analyze (Next_N, Nodes);
3456             else
3457                Append_List_To (List_Containing (N), Nodes);
3458             end if;
3459          end if;
3460       end if;
3461
3462       --  Put the local entities back in the enclosing scope, and set the
3463       --  Is_Public flag appropriately.
3464
3465       Transfer_Entities (S, Enclosing_S);
3466
3467       --  Mark the enclosing dynamic scope so that the sec stack will be
3468       --  released upon its exit unless this is a function that returns on
3469       --  the sec stack in which case this will be done by the caller.
3470
3471       if VM_Target = No_VM and then Uses_SS then
3472          S := Enclosing_Dynamic_Scope (S);
3473
3474          if Ekind (S) = E_Function
3475            and then Requires_Transient_Scope (Etype (S))
3476          then
3477             null;
3478          else
3479             Set_Uses_Sec_Stack (S);
3480             Check_Restriction (No_Secondary_Stack, N);
3481          end if;
3482       end if;
3483    end Wrap_Transient_Declaration;
3484
3485    -------------------------------
3486    -- Wrap_Transient_Expression --
3487    -------------------------------
3488
3489    --  Insert actions before <Expression>:
3490
3491    --  (lines marked with <CTRL> are expanded only in presence of Controlled
3492    --   objects needing finalization)
3493
3494    --     _E : Etyp;
3495    --     declare
3496    --        _M : constant Mark_Id := SS_Mark;
3497    --        Local_Final_List : System.FI.Finalizable_Ptr;    <CTRL>
3498
3499    --        procedure _Clean is
3500    --        begin
3501    --           Abort_Defer;
3502    --           System.FI.Finalize_List (Local_Final_List);   <CTRL>
3503    --           SS_Release (M);
3504    --           Abort_Undefer;
3505    --        end _Clean;
3506
3507    --     begin
3508    --        _E := <Expression>;
3509    --     at end
3510    --        _Clean;
3511    --     end;
3512
3513    --    then expression is replaced by _E
3514
3515    procedure Wrap_Transient_Expression (N : Node_Id) is
3516       Loc  : constant Source_Ptr := Sloc (N);
3517       E    : constant Entity_Id :=
3518                Make_Defining_Identifier (Loc, New_Internal_Name ('E'));
3519       Etyp : constant Entity_Id := Etype (N);
3520
3521    begin
3522       Insert_Actions (N, New_List (
3523         Make_Object_Declaration (Loc,
3524           Defining_Identifier => E,
3525           Object_Definition   => New_Reference_To (Etyp, Loc)),
3526
3527         Make_Transient_Block (Loc,
3528           Action =>
3529             Make_Assignment_Statement (Loc,
3530               Name       => New_Reference_To (E, Loc),
3531               Expression => Relocate_Node (N)))));
3532
3533       Rewrite (N, New_Reference_To (E, Loc));
3534       Analyze_And_Resolve (N, Etyp);
3535    end Wrap_Transient_Expression;
3536
3537    ------------------------------
3538    -- Wrap_Transient_Statement --
3539    ------------------------------
3540
3541    --  Transform <Instruction> into
3542
3543    --  (lines marked with <CTRL> are expanded only in presence of Controlled
3544    --   objects needing finalization)
3545
3546    --    declare
3547    --       _M : Mark_Id := SS_Mark;
3548    --       Local_Final_List : System.FI.Finalizable_Ptr ;    <CTRL>
3549
3550    --       procedure _Clean is
3551    --       begin
3552    --          Abort_Defer;
3553    --          System.FI.Finalize_List (Local_Final_List);    <CTRL>
3554    --          SS_Release (_M);
3555    --          Abort_Undefer;
3556    --       end _Clean;
3557
3558    --    begin
3559    --       <Instruction>;
3560    --    at end
3561    --       _Clean;
3562    --    end;
3563
3564    procedure Wrap_Transient_Statement (N : Node_Id) is
3565       Loc           : constant Source_Ptr := Sloc (N);
3566       New_Statement : constant Node_Id := Relocate_Node (N);
3567
3568    begin
3569       Rewrite (N, Make_Transient_Block (Loc, New_Statement));
3570
3571       --  With the scope stack back to normal, we can call analyze on the
3572       --  resulting block. At this point, the transient scope is being
3573       --  treated like a perfectly normal scope, so there is nothing
3574       --  special about it.
3575
3576       --  Note: Wrap_Transient_Statement is called with the node already
3577       --  analyzed (i.e. Analyzed (N) is True). This is important, since
3578       --  otherwise we would get a recursive processing of the node when
3579       --  we do this Analyze call.
3580
3581       Analyze (N);
3582    end Wrap_Transient_Statement;
3583
3584 end Exp_Ch7;