OSDN Git Service

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