OSDN Git Service

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