OSDN Git Service

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