OSDN Git Service

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