OSDN Git Service

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