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-2021, Free Software Foundation, Inc.         --
10--                                                                          --
11-- GNAT is free software;  you can  redistribute it  and/or modify it under --
12-- terms of the  GNU General Public License as published  by the Free Soft- --
13-- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14-- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15-- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16-- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17-- for  more details.  You should have  received  a copy of the GNU General --
18-- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19-- http://www.gnu.org/licenses for a complete copy of the license.          --
20--                                                                          --
21-- GNAT was originally developed  by the GNAT team at  New York University. --
22-- Extensive contributions were provided by Ada Core Technologies Inc.      --
23--                                                                          --
24------------------------------------------------------------------------------
25
26--  This package contains virtually all expansion mechanisms related to
27--    - controlled types
28--    - transient scopes
29
30with Atree;          use Atree;
31with Contracts;      use Contracts;
32with Debug;          use Debug;
33with Einfo;          use Einfo;
34with Einfo.Entities; use Einfo.Entities;
35with Einfo.Utils;    use Einfo.Utils;
36with Elists;         use Elists;
37with Errout;         use Errout;
38with Exp_Ch6;        use Exp_Ch6;
39with Exp_Ch9;        use Exp_Ch9;
40with Exp_Ch11;       use Exp_Ch11;
41with Exp_Dbug;       use Exp_Dbug;
42with Exp_Dist;       use Exp_Dist;
43with Exp_Disp;       use Exp_Disp;
44with Exp_Prag;       use Exp_Prag;
45with Exp_Tss;        use Exp_Tss;
46with Exp_Util;       use Exp_Util;
47with Freeze;         use Freeze;
48with GNAT_CUDA;      use GNAT_CUDA;
49with Lib;            use Lib;
50with Nlists;         use Nlists;
51with Nmake;          use Nmake;
52with Opt;            use Opt;
53with Output;         use Output;
54with Restrict;       use Restrict;
55with Rident;         use Rident;
56with Rtsfind;        use Rtsfind;
57with Sinfo;          use Sinfo;
58with Sinfo.Nodes;    use Sinfo.Nodes;
59with Sinfo.Utils;    use Sinfo.Utils;
60with Sem;            use Sem;
61with Sem_Aux;        use Sem_Aux;
62with Sem_Ch3;        use Sem_Ch3;
63with Sem_Ch7;        use Sem_Ch7;
64with Sem_Ch8;        use Sem_Ch8;
65with Sem_Res;        use Sem_Res;
66with Sem_Util;       use Sem_Util;
67with Snames;         use Snames;
68with Stand;          use Stand;
69with Tbuild;         use Tbuild;
70with Ttypes;         use Ttypes;
71with Uintp;          use Uintp;
72
73package body Exp_Ch7 is
74
75   --------------------------------
76   -- Transient Scope Management --
77   --------------------------------
78
79   --  A transient scope is created when temporary objects are created by the
80   --  compiler. These temporary objects are allocated on the secondary stack
81   --  and the transient scope is responsible for finalizing the object when
82   --  appropriate and reclaiming the memory at the right time. The temporary
83   --  objects are generally the objects allocated to store the result of a
84   --  function returning an unconstrained or a tagged value. Expressions
85   --  needing to be wrapped in a transient scope (functions calls returning
86   --  unconstrained or tagged values) may appear in 3 different contexts which
87   --  lead to 3 different kinds of transient scope expansion:
88
89   --   1. In a simple statement (procedure call, assignment, ...). In this
90   --      case the instruction is wrapped into a transient block. See
91   --      Wrap_Transient_Statement for details.
92
93   --   2. In an expression of a control structure (test in a IF statement,
94   --      expression in a CASE statement, ...). See Wrap_Transient_Expression
95   --      for details.
96
97   --   3. In a expression of an object_declaration. No wrapping is possible
98   --      here, so the finalization actions, if any, are done right after the
99   --      declaration and the secondary stack deallocation is done in the
100   --      proper enclosing scope. See Wrap_Transient_Declaration for details.
101
102   --  Note about functions returning tagged types: it has been decided to
103   --  always allocate their result in the secondary stack, even though is not
104   --  absolutely mandatory when the tagged type is constrained because the
105   --  caller knows the size of the returned object and thus could allocate the
106   --  result in the primary stack. An exception to this is when the function
107   --  builds its result in place, as is done for functions with inherently
108   --  limited result types for Ada 2005. In that case, certain callers may
109   --  pass the address of a constrained object as the target object for the
110   --  function result.
111
112   --  By allocating tagged results in the secondary stack a number of
113   --  implementation difficulties are avoided:
114
115   --    - If it is a dispatching function call, the computation of the size of
116   --      the result is possible but complex from the outside.
117
118   --    - If the returned type is controlled, the assignment of the returned
119   --      value to the anonymous object involves an Adjust, and we have no
120   --      easy way to access the anonymous object created by the back end.
121
122   --    - If the returned type is class-wide, this is an unconstrained type
123   --      anyway.
124
125   --  Furthermore, the small loss in efficiency which is the result of this
126   --  decision is not such a big deal because functions returning tagged types
127   --  are not as common in practice compared to functions returning access to
128   --  a tagged type.
129
130   --------------------------------------------------
131   -- Transient Blocks and Finalization Management --
132   --------------------------------------------------
133
134   procedure Insert_Actions_In_Scope_Around
135     (N         : Node_Id;
136      Clean     : Boolean;
137      Manage_SS : Boolean);
138   --  Insert the before-actions kept in the scope stack before N, and the
139   --  after-actions after N, which must be a member of a list. If flag Clean
140   --  is set, insert any cleanup actions. If flag Manage_SS is set, insert
141   --  calls to mark and release the secondary stack.
142
143   function Make_Transient_Block
144     (Loc    : Source_Ptr;
145      Action : Node_Id;
146      Par    : Node_Id) return Node_Id;
147   --  Action is a single statement or object declaration. Par is the proper
148   --  parent of the generated block. Create a transient block whose name is
149   --  the current scope and the only handled statement is Action. If Action
150   --  involves controlled objects or secondary stack usage, the corresponding
151   --  cleanup actions are performed at the end of the block.
152
153   procedure Store_Actions_In_Scope (AK : Scope_Action_Kind; L : List_Id);
154   --  Shared processing for Store_xxx_Actions_In_Scope
155
156   -----------------------------
157   -- Finalization Management --
158   -----------------------------
159
160   --  This part describe how Initialization/Adjustment/Finalization procedures
161   --  are generated and called. Two cases must be considered, types that are
162   --  Controlled (Is_Controlled flag set) and composite types that contain
163   --  controlled components (Has_Controlled_Component flag set). In the first
164   --  case the procedures to call are the user-defined primitive operations
165   --  Initialize/Adjust/Finalize. In the second case, GNAT generates
166   --  Deep_Initialize, Deep_Adjust and Deep_Finalize that are in charge
167   --  of calling the former procedures on the controlled components.
168
169   --  For records with Has_Controlled_Component set, a hidden "controller"
170   --  component is inserted. This controller component contains its own
171   --  finalization list on which all controlled components are attached
172   --  creating an indirection on the upper-level Finalization list. This
173   --  technique facilitates the management of objects whose number of
174   --  controlled components changes during execution. This controller
175   --  component is itself controlled and is attached to the upper-level
176   --  finalization chain. Its adjust primitive is in charge of calling adjust
177   --  on the components and adjusting the finalization pointer to match their
178   --  new location (see a-finali.adb).
179
180   --  It is not possible to use a similar technique for arrays that have
181   --  Has_Controlled_Component set. In this case, deep procedures are
182   --  generated that call initialize/adjust/finalize + attachment or
183   --  detachment on the finalization list for all component.
184
185   --  Initialize calls: they are generated for declarations or dynamic
186   --  allocations of Controlled objects with no initial value. They are always
187   --  followed by an attachment to the current Finalization Chain. For the
188   --  dynamic allocation case this the chain attached to the scope of the
189   --  access type definition otherwise, this is the chain of the current
190   --  scope.
191
192   --  Adjust Calls: They are generated on 2 occasions: (1) for declarations
193   --  or dynamic allocations of Controlled objects with an initial value.
194   --  (2) after an assignment. In the first case they are followed by an
195   --  attachment to the final chain, in the second case they are not.
196
197   --  Finalization Calls: They are generated on (1) scope exit, (2)
198   --  assignments, (3) unchecked deallocations. In case (3) they have to
199   --  be detached from the final chain, in case (2) they must not and in
200   --  case (1) this is not important since we are exiting the scope anyway.
201
202   --  Other details:
203
204   --    Type extensions will have a new record controller at each derivation
205   --    level containing controlled components. The record controller for
206   --    the parent/ancestor is attached to the finalization list of the
207   --    extension's record controller (i.e. the parent is like a component
208   --    of the extension).
209
210   --    For types that are both Is_Controlled and Has_Controlled_Components,
211   --    the record controller and the object itself are handled separately.
212   --    It could seem simpler to attach the object at the end of its record
213   --    controller but this would not tackle view conversions properly.
214
215   --    A classwide type can always potentially have controlled components
216   --    but the record controller of the corresponding actual type may not
217   --    be known at compile time so the dispatch table contains a special
218   --    field that allows computation of the offset of the record controller
219   --    dynamically. See s-finimp.Deep_Tag_Attach and a-tags.RC_Offset.
220
221   --  Here is a simple example of the expansion of a controlled block :
222
223   --    declare
224   --       X : Controlled;
225   --       Y : Controlled := Init;
226   --
227   --       type R is record
228   --          C : Controlled;
229   --       end record;
230   --       W : R;
231   --       Z : R := (C => X);
232
233   --    begin
234   --       X := Y;
235   --       W := Z;
236   --    end;
237   --
238   --  is expanded into
239   --
240   --    declare
241   --       _L : System.FI.Finalizable_Ptr;
242
243   --       procedure _Clean is
244   --       begin
245   --          Abort_Defer;
246   --          System.FI.Finalize_List (_L);
247   --          Abort_Undefer;
248   --       end _Clean;
249
250   --       X : Controlled;
251   --       begin
252   --          Abort_Defer;
253   --          Initialize (X);
254   --          Attach_To_Final_List (_L, Finalizable (X), 1);
255   --       at end: Abort_Undefer;
256   --       Y : Controlled := Init;
257   --       Adjust (Y);
258   --       Attach_To_Final_List (_L, Finalizable (Y), 1);
259   --
260   --       type R is record
261   --          C : Controlled;
262   --       end record;
263   --       W : R;
264   --       begin
265   --          Abort_Defer;
266   --          Deep_Initialize (W, _L, 1);
267   --       at end: Abort_Under;
268   --       Z : R := (C => X);
269   --       Deep_Adjust (Z, _L, 1);
270
271   --    begin
272   --       _Assign (X, Y);
273   --       Deep_Finalize (W, False);
274   --       <save W's final pointers>
275   --       W := Z;
276   --       <restore W's final pointers>
277   --       Deep_Adjust (W, _L, 0);
278   --    at end
279   --       _Clean;
280   --    end;
281
282   type Final_Primitives is
283     (Initialize_Case, Adjust_Case, Finalize_Case, Address_Case);
284   --  This enumeration type is defined in order to ease sharing code for
285   --  building finalization procedures for composite types.
286
287   Name_Of      : constant array (Final_Primitives) of Name_Id :=
288                    (Initialize_Case => Name_Initialize,
289                     Adjust_Case     => Name_Adjust,
290                     Finalize_Case   => Name_Finalize,
291                     Address_Case    => Name_Finalize_Address);
292   Deep_Name_Of : constant array (Final_Primitives) of TSS_Name_Type :=
293                    (Initialize_Case => TSS_Deep_Initialize,
294                     Adjust_Case     => TSS_Deep_Adjust,
295                     Finalize_Case   => TSS_Deep_Finalize,
296                     Address_Case    => TSS_Finalize_Address);
297
298   function Allows_Finalization_Master (Typ : Entity_Id) return Boolean;
299   --  Determine whether access type Typ may have a finalization master
300
301   procedure Build_Array_Deep_Procs (Typ : Entity_Id);
302   --  Build the deep Initialize/Adjust/Finalize for a record Typ with
303   --  Has_Controlled_Component set and store them using the TSS mechanism.
304
305   function Build_Cleanup_Statements
306     (N                  : Node_Id;
307      Additional_Cleanup : List_Id) return List_Id;
308   --  Create the cleanup calls for an asynchronous call block, task master,
309   --  protected subprogram body, task allocation block or task body, or
310   --  additional cleanup actions parked on a transient block. If the context
311   --  does not contain the above constructs, the routine returns an empty
312   --  list.
313
314   procedure Build_Finalizer
315     (N           : Node_Id;
316      Clean_Stmts : List_Id;
317      Mark_Id     : Entity_Id;
318      Top_Decls   : List_Id;
319      Defer_Abort : Boolean;
320      Fin_Id      : out Entity_Id);
321   --  N may denote an accept statement, block, entry body, package body,
322   --  package spec, protected body, subprogram body, or a task body. Create
323   --  a procedure which contains finalization calls for all controlled objects
324   --  declared in the declarative or statement region of N. The calls are
325   --  built in reverse order relative to the original declarations. In the
326   --  case of a task body, the routine delays the creation of the finalizer
327   --  until all statements have been moved to the task body procedure.
328   --  Clean_Stmts may contain additional context-dependent code used to abort
329   --  asynchronous calls or complete tasks (see Build_Cleanup_Statements).
330   --  Mark_Id is the secondary stack used in the current context or Empty if
331   --  missing. Top_Decls is the list on which the declaration of the finalizer
332   --  is attached in the non-package case. Defer_Abort indicates that the
333   --  statements passed in perform actions that require abort to be deferred,
334   --  such as for task termination. Fin_Id is the finalizer declaration
335   --  entity.
336
337   procedure Build_Finalizer_Helper
338     (N                 : Node_Id;
339      Clean_Stmts       : List_Id;
340      Mark_Id           : Entity_Id;
341      Top_Decls         : List_Id;
342      Defer_Abort       : Boolean;
343      Fin_Id            : out Entity_Id;
344      Finalize_Old_Only : Boolean);
345   --  An internal routine which does all of the heavy lifting on behalf of
346   --  Build_Finalizer.
347
348   procedure Build_Finalizer_Call (N : Node_Id; Fin_Id : Entity_Id);
349   --  N is a construct which contains a handled sequence of statements, Fin_Id
350   --  is the entity of a finalizer. Create an At_End handler which covers the
351   --  statements of N and calls Fin_Id. If the handled statement sequence has
352   --  an exception handler, the statements will be wrapped in a block to avoid
353   --  unwanted interaction with the new At_End handler.
354
355   procedure Build_Record_Deep_Procs (Typ : Entity_Id);
356   --  Build the deep Initialize/Adjust/Finalize for a record Typ with
357   --  Has_Component_Component set and store them using the TSS mechanism.
358
359   -------------------------------------------
360   -- Unnesting procedures for CCG and LLVM --
361   -------------------------------------------
362
363   --  Expansion generates subprograms for controlled types management that
364   --  may appear in declarative lists in package declarations and bodies.
365   --  These subprograms appear within generated blocks that contain local
366   --  declarations and a call to finalization procedures. To ensure that
367   --  such subprograms get activation records when needed, we transform the
368   --  block into a procedure body, followed by a call to it in the same
369   --  declarative list.
370
371   procedure Check_Unnesting_Elaboration_Code (N : Node_Id);
372   --  The statement part of a package body that is a compilation unit may
373   --  contain blocks that declare local subprograms. In Subprogram_Unnesting_
374   --  Mode such subprograms must be handled as nested inside the (implicit)
375   --  elaboration procedure that executes that statement part. To handle
376   --  properly uplevel references we construct that subprogram explicitly,
377   --  to contain blocks and inner subprograms, the statement part becomes
378   --  a call to this subprogram. This is only done if blocks are present
379   --  in the statement list of the body. (It would be nice to unify this
380   --  procedure with Check_Unnesting_In_Decls_Or_Stmts, if possible, since
381   --  they're doing very similar work, but are structured differently. ???)
382
383   procedure Check_Unnesting_In_Decls_Or_Stmts (Decls_Or_Stmts : List_Id);
384   --  Similarly, the declarations or statements in library-level packages may
385   --  have created blocks with nested subprograms. Such a block must be
386   --  transformed into a procedure followed by a call to it, so that unnesting
387   --  can handle uplevel references within these nested subprograms (typically
388   --  subprograms that handle finalization actions). This also applies to
389   --  nested packages, including instantiations, in which case it must
390   --  recursively process inner bodies.
391
392   procedure Check_Unnesting_In_Handlers (N : Node_Id);
393   --  Similarly, check for blocks with nested subprograms occurring within
394   --  a set of exception handlers associated with a package body N.
395
396   procedure Unnest_Block (Decl : Node_Id);
397   --  Blocks that contain nested subprograms with up-level references need to
398   --  create activation records for them. We do this by rewriting the block as
399   --  a procedure, followed by a call to it in the same declarative list, to
400   --  replicate the semantics of the original block.
401   --
402   --  A common source for such block is a transient block created for a
403   --  construct (declaration, assignment, etc.) that involves controlled
404   --  actions or secondary-stack management, in which case the nested
405   --  subprogram is a finalizer.
406
407   procedure Unnest_If_Statement (If_Stmt : Node_Id);
408   --  The separate statement lists associated with an if-statement (then part,
409   --  elsif parts, else part) may require unnesting if they directly contain
410   --  a subprogram body that references up-level objects. Each statement list
411   --  is traversed to locate such subprogram bodies, and if a part's statement
412   --  list contains a body, then the list is replaced with a new procedure
413   --  containing the part's statements followed by a call to the procedure.
414   --  Furthermore, any nested blocks, loops, or if statements will also be
415   --  traversed to determine the need for further unnesting transformations.
416
417   procedure Unnest_Statement_List (Stmts : in out List_Id);
418   --  A list of statements that directly contains a subprogram at its outer
419   --  level, that may reference objects declared in that same statement list,
420   --  is rewritten as a procedure containing the statement list Stmts (which
421   --  includes any such objects as well as the nested subprogram), followed by
422   --  a call to the new procedure, and Stmts becomes the list containing the
423   --  procedure and the call. This ensures that Unnest_Subprogram will later
424   --  properly handle up-level references from the nested subprogram to
425   --  objects declared earlier in statement list, by creating an activation
426   --  record and passing it to the nested subprogram. This procedure also
427   --  resets the Scope of objects declared in the statement list, as well as
428   --  the Scope of the nested subprogram, to refer to the new procedure.
429   --  Also, the new procedure is marked Has_Nested_Subprogram, so this should
430   --  only be called when known that the statement list contains a subprogram.
431
432   procedure Unnest_Loop (Loop_Stmt : Node_Id);
433   --  Top-level Loops that contain nested subprograms with up-level references
434   --  need to have activation records. We do this by rewriting the loop as a
435   --  procedure containing the loop, followed by a call to the procedure in
436   --  the same library-level declarative list, to replicate the semantics of
437   --  the original loop. Such loops can occur due to aggregate expansions and
438   --  other constructs.
439
440   procedure Check_Visibly_Controlled
441     (Prim : Final_Primitives;
442      Typ  : Entity_Id;
443      E    : in out Entity_Id;
444      Cref : in out Node_Id);
445   --  The controlled operation declared for a derived type may not be
446   --  overriding, if the controlled operations of the parent type are hidden,
447   --  for example when the parent is a private type whose full view is
448   --  controlled. For other primitive operations we modify the name of the
449   --  operation to indicate that it is not overriding, but this is not
450   --  possible for Initialize, etc. because they have to be retrievable by
451   --  name. Before generating the proper call to one of these operations we
452   --  check whether Typ is known to be controlled at the point of definition.
453   --  If it is not then we must retrieve the hidden operation of the parent
454   --  and use it instead. This is one case that might be solved more cleanly
455   --  once Overriding pragmas or declarations are in place.
456
457   function Contains_Subprogram (Blk : Entity_Id) return Boolean;
458   --  Check recursively whether a loop or block contains a subprogram that
459   --  may need an activation record.
460
461   function Convert_View
462     (Proc : Entity_Id;
463      Arg  : Node_Id;
464      Ind  : Pos := 1) return Node_Id;
465   --  Proc is one of the Initialize/Adjust/Finalize operations, and Arg is the
466   --  argument being passed to it. Ind indicates which formal of procedure
467   --  Proc we are trying to match. This function will, if necessary, generate
468   --  a conversion between the partial and full view of Arg to match the type
469   --  of the formal of Proc, or force a conversion to the class-wide type in
470   --  the case where the operation is abstract.
471
472   function Enclosing_Function (E : Entity_Id) return Entity_Id;
473   --  Given an arbitrary entity, traverse the scope chain looking for the
474   --  first enclosing function. Return Empty if no function was found.
475
476   function Make_Call
477     (Loc       : Source_Ptr;
478      Proc_Id   : Entity_Id;
479      Param     : Node_Id;
480      Skip_Self : Boolean := False) return Node_Id;
481   --  Subsidiary to Make_Adjust_Call and Make_Final_Call. Given the entity of
482   --  routine [Deep_]Adjust or [Deep_]Finalize and an object parameter, create
483   --  an adjust or finalization call. When flag Skip_Self is set, the related
484   --  action has an effect on the components only (if any).
485
486   function Make_Deep_Proc
487     (Prim  : Final_Primitives;
488      Typ   : Entity_Id;
489      Stmts : List_Id) return Entity_Id;
490   --  This function generates the tree for Deep_Initialize, Deep_Adjust or
491   --  Deep_Finalize procedures according to the first parameter. These
492   --  procedures operate on the type Typ. The Stmts parameter gives the
493   --  body of the procedure.
494
495   function Make_Deep_Array_Body
496     (Prim : Final_Primitives;
497      Typ  : Entity_Id) return List_Id;
498   --  This function generates the list of statements for implementing
499   --  Deep_Initialize, Deep_Adjust or Deep_Finalize procedures according to
500   --  the first parameter, these procedures operate on the array type Typ.
501
502   function Make_Deep_Record_Body
503     (Prim     : Final_Primitives;
504      Typ      : Entity_Id;
505      Is_Local : Boolean := False) return List_Id;
506   --  This function generates the list of statements for implementing
507   --  Deep_Initialize, Deep_Adjust or Deep_Finalize procedures according to
508   --  the first parameter, these procedures operate on the record type Typ.
509   --  Flag Is_Local is used in conjunction with Deep_Finalize to designate
510   --  whether the inner logic should be dictated by state counters.
511
512   function Make_Finalize_Address_Stmts (Typ : Entity_Id) return List_Id;
513   --  Subsidiary to Make_Finalize_Address_Body, Make_Deep_Array_Body and
514   --  Make_Deep_Record_Body. Generate the following statements:
515   --
516   --    declare
517   --       type Acc_Typ is access all Typ;
518   --       for Acc_Typ'Storage_Size use 0;
519   --    begin
520   --       [Deep_]Finalize (Acc_Typ (V).all);
521   --    end;
522
523   --------------------------------
524   -- Allows_Finalization_Master --
525   --------------------------------
526
527   function Allows_Finalization_Master (Typ : Entity_Id) return Boolean is
528      function In_Deallocation_Instance (E : Entity_Id) return Boolean;
529      --  Determine whether entity E is inside a wrapper package created for
530      --  an instance of Ada.Unchecked_Deallocation.
531
532      ------------------------------
533      -- In_Deallocation_Instance --
534      ------------------------------
535
536      function In_Deallocation_Instance (E : Entity_Id) return Boolean is
537         Pkg : constant Entity_Id := Scope (E);
538         Par : Node_Id := Empty;
539
540      begin
541         if Ekind (Pkg) = E_Package
542           and then Present (Related_Instance (Pkg))
543           and then Ekind (Related_Instance (Pkg)) = E_Procedure
544         then
545            Par := Generic_Parent (Parent (Related_Instance (Pkg)));
546
547            return
548              Present (Par)
549                and then Chars (Par) = Name_Unchecked_Deallocation
550                and then Chars (Scope (Par)) = Name_Ada
551                and then Scope (Scope (Par)) = Standard_Standard;
552         end if;
553
554         return False;
555      end In_Deallocation_Instance;
556
557      --  Local variables
558
559      Desig_Typ : constant Entity_Id := Designated_Type (Typ);
560      Ptr_Typ   : constant Entity_Id :=
561                    Root_Type_Of_Full_View (Base_Type (Typ));
562
563   --  Start of processing for Allows_Finalization_Master
564
565   begin
566      --  Certain run-time configurations and targets do not provide support
567      --  for controlled types and therefore do not need masters.
568
569      if Restriction_Active (No_Finalization) then
570         return False;
571
572      --  Do not consider C and C++ types since it is assumed that the non-Ada
573      --  side will handle their cleanup.
574
575      elsif Convention (Desig_Typ) = Convention_C
576        or else Convention (Desig_Typ) = Convention_CPP
577      then
578         return False;
579
580      --  Do not consider an access type that returns on the secondary stack
581
582      elsif Present (Associated_Storage_Pool (Ptr_Typ))
583        and then Is_RTE (Associated_Storage_Pool (Ptr_Typ), RE_SS_Pool)
584      then
585         return False;
586
587      --  Do not consider an access type that can never allocate an object
588
589      elsif No_Pool_Assigned (Ptr_Typ) then
590         return False;
591
592      --  Do not consider an access type coming from an Unchecked_Deallocation
593      --  instance. Even though the designated type may be controlled, the
594      --  access type will never participate in any allocations.
595
596      elsif In_Deallocation_Instance (Ptr_Typ) then
597         return False;
598
599      --  Do not consider a non-library access type when No_Nested_Finalization
600      --  is in effect since finalization masters are controlled objects and if
601      --  created will violate the restriction.
602
603      elsif Restriction_Active (No_Nested_Finalization)
604        and then not Is_Library_Level_Entity (Ptr_Typ)
605      then
606         return False;
607
608      --  Do not consider an access type subject to pragma No_Heap_Finalization
609      --  because objects allocated through such a type are not to be finalized
610      --  when the access type goes out of scope.
611
612      elsif No_Heap_Finalization (Ptr_Typ) then
613         return False;
614
615      --  Do not create finalization masters in GNATprove mode because this
616      --  causes unwanted extra expansion. A compilation in this mode must
617      --  keep the tree as close as possible to the original sources.
618
619      elsif GNATprove_Mode then
620         return False;
621
622      --  Otherwise the access type may use a finalization master
623
624      else
625         return True;
626      end if;
627   end Allows_Finalization_Master;
628
629   ----------------------------
630   -- Build_Anonymous_Master --
631   ----------------------------
632
633   procedure Build_Anonymous_Master (Ptr_Typ : Entity_Id) is
634      function Create_Anonymous_Master
635        (Desig_Typ : Entity_Id;
636         Unit_Id   : Entity_Id;
637         Unit_Decl : Node_Id) return Entity_Id;
638      --  Create a new anonymous master for access type Ptr_Typ with designated
639      --  type Desig_Typ. The declaration of the master and its initialization
640      --  are inserted in the declarative part of unit Unit_Decl. Unit_Id is
641      --  the entity of Unit_Decl.
642
643      function Current_Anonymous_Master
644        (Desig_Typ : Entity_Id;
645         Unit_Id   : Entity_Id) return Entity_Id;
646      --  Find an anonymous master declared within unit Unit_Id which services
647      --  designated type Desig_Typ. If there is no such master, return Empty.
648
649      -----------------------------
650      -- Create_Anonymous_Master --
651      -----------------------------
652
653      function Create_Anonymous_Master
654        (Desig_Typ : Entity_Id;
655         Unit_Id   : Entity_Id;
656         Unit_Decl : Node_Id) return Entity_Id
657      is
658         Loc : constant Source_Ptr := Sloc (Unit_Id);
659
660         All_FMs   : Elist_Id;
661         Decls     : List_Id;
662         FM_Decl   : Node_Id;
663         FM_Id     : Entity_Id;
664         FM_Init   : Node_Id;
665         Unit_Spec : Node_Id;
666
667      begin
668         --  Generate:
669         --    <FM_Id> : Finalization_Master;
670
671         FM_Id := Make_Temporary (Loc, 'A');
672
673         FM_Decl :=
674           Make_Object_Declaration (Loc,
675             Defining_Identifier => FM_Id,
676             Object_Definition   =>
677               New_Occurrence_Of (RTE (RE_Finalization_Master), Loc));
678
679         --  Generate:
680         --    Set_Base_Pool
681         --      (<FM_Id>, Global_Pool_Object'Unrestricted_Access);
682
683         FM_Init :=
684           Make_Procedure_Call_Statement (Loc,
685             Name                   =>
686               New_Occurrence_Of (RTE (RE_Set_Base_Pool), Loc),
687             Parameter_Associations => New_List (
688               New_Occurrence_Of (FM_Id, Loc),
689               Make_Attribute_Reference (Loc,
690                 Prefix         =>
691                   New_Occurrence_Of (RTE (RE_Global_Pool_Object), Loc),
692                 Attribute_Name => Name_Unrestricted_Access)));
693
694         --  Find the declarative list of the unit
695
696         if Nkind (Unit_Decl) = N_Package_Declaration then
697            Unit_Spec := Specification (Unit_Decl);
698            Decls     := Visible_Declarations (Unit_Spec);
699
700            if No (Decls) then
701               Decls := New_List;
702               Set_Visible_Declarations (Unit_Spec, Decls);
703            end if;
704
705         --  Package body or subprogram case
706
707         --  ??? A subprogram spec or body that acts as a compilation unit may
708         --  contain a formal parameter of an anonymous access-to-controlled
709         --  type initialized by an allocator.
710
711         --    procedure Comp_Unit_Proc (Param : access Ctrl := new Ctrl);
712
713         --  There is no suitable place to create the master as the subprogram
714         --  is not in a declarative list.
715
716         else
717            Decls := Declarations (Unit_Decl);
718
719            if No (Decls) then
720               Decls := New_List;
721               Set_Declarations (Unit_Decl, Decls);
722            end if;
723         end if;
724
725         Prepend_To (Decls, FM_Init);
726         Prepend_To (Decls, FM_Decl);
727
728         --  Use the scope of the unit when analyzing the declaration of the
729         --  master and its initialization actions.
730
731         Push_Scope (Unit_Id);
732         Analyze (FM_Decl);
733         Analyze (FM_Init);
734         Pop_Scope;
735
736         --  Mark the master as servicing this specific designated type
737
738         Set_Anonymous_Designated_Type (FM_Id, Desig_Typ);
739
740         --  Include the anonymous master in the list of existing masters which
741         --  appear in this unit. This effectively creates a mapping between a
742         --  master and a designated type which in turn allows for the reuse of
743         --  masters on a per-unit basis.
744
745         All_FMs := Anonymous_Masters (Unit_Id);
746
747         if No (All_FMs) then
748            All_FMs := New_Elmt_List;
749            Set_Anonymous_Masters (Unit_Id, All_FMs);
750         end if;
751
752         Prepend_Elmt (FM_Id, All_FMs);
753
754         return FM_Id;
755      end Create_Anonymous_Master;
756
757      ------------------------------
758      -- Current_Anonymous_Master --
759      ------------------------------
760
761      function Current_Anonymous_Master
762        (Desig_Typ : Entity_Id;
763         Unit_Id   : Entity_Id) return Entity_Id
764      is
765         All_FMs : constant Elist_Id := Anonymous_Masters (Unit_Id);
766         FM_Elmt : Elmt_Id;
767         FM_Id   : Entity_Id;
768
769      begin
770         --  Inspect the list of anonymous masters declared within the unit
771         --  looking for an existing master which services the same designated
772         --  type.
773
774         if Present (All_FMs) then
775            FM_Elmt := First_Elmt (All_FMs);
776            while Present (FM_Elmt) loop
777               FM_Id := Node (FM_Elmt);
778
779               --  The currect master services the same designated type. As a
780               --  result the master can be reused and associated with another
781               --  anonymous access-to-controlled type.
782
783               if Anonymous_Designated_Type (FM_Id) = Desig_Typ then
784                  return FM_Id;
785               end if;
786
787               Next_Elmt (FM_Elmt);
788            end loop;
789         end if;
790
791         return Empty;
792      end Current_Anonymous_Master;
793
794      --  Local variables
795
796      Desig_Typ : Entity_Id;
797      FM_Id     : Entity_Id;
798      Priv_View : Entity_Id;
799      Unit_Decl : Node_Id;
800      Unit_Id   : Entity_Id;
801
802   --  Start of processing for Build_Anonymous_Master
803
804   begin
805      --  Nothing to do if the circumstances do not allow for a finalization
806      --  master.
807
808      if not Allows_Finalization_Master (Ptr_Typ) then
809         return;
810      end if;
811
812      Unit_Decl := Unit (Cunit (Current_Sem_Unit));
813      Unit_Id   := Unique_Defining_Entity (Unit_Decl);
814
815      --  The compilation unit is a package instantiation. In this case the
816      --  anonymous master is associated with the package spec as both the
817      --  spec and body appear at the same level.
818
819      if Nkind (Unit_Decl) = N_Package_Body
820        and then Nkind (Original_Node (Unit_Decl)) = N_Package_Instantiation
821      then
822         Unit_Id   := Corresponding_Spec (Unit_Decl);
823         Unit_Decl := Unit_Declaration_Node (Unit_Id);
824      end if;
825
826      --  Use the initial declaration of the designated type when it denotes
827      --  the full view of an incomplete or private type. This ensures that
828      --  types with one and two views are treated the same.
829
830      Desig_Typ := Directly_Designated_Type (Ptr_Typ);
831      Priv_View := Incomplete_Or_Partial_View (Desig_Typ);
832
833      if Present (Priv_View) then
834         Desig_Typ := Priv_View;
835      end if;
836
837      --  Determine whether the current semantic unit already has an anonymous
838      --  master which services the designated type.
839
840      FM_Id := Current_Anonymous_Master (Desig_Typ, Unit_Id);
841
842      --  If this is not the case, create a new master
843
844      if No (FM_Id) then
845         FM_Id := Create_Anonymous_Master (Desig_Typ, Unit_Id, Unit_Decl);
846      end if;
847
848      Set_Finalization_Master (Ptr_Typ, FM_Id);
849   end Build_Anonymous_Master;
850
851   ----------------------------
852   -- Build_Array_Deep_Procs --
853   ----------------------------
854
855   procedure Build_Array_Deep_Procs (Typ : Entity_Id) is
856   begin
857      Set_TSS (Typ,
858        Make_Deep_Proc
859          (Prim  => Initialize_Case,
860           Typ   => Typ,
861           Stmts => Make_Deep_Array_Body (Initialize_Case, Typ)));
862
863      if not Is_Limited_View (Typ) then
864         Set_TSS (Typ,
865           Make_Deep_Proc
866             (Prim  => Adjust_Case,
867              Typ   => Typ,
868              Stmts => Make_Deep_Array_Body (Adjust_Case, Typ)));
869      end if;
870
871      --  Do not generate Deep_Finalize and Finalize_Address if finalization is
872      --  suppressed since these routine will not be used.
873
874      if not Restriction_Active (No_Finalization) then
875         Set_TSS (Typ,
876           Make_Deep_Proc
877             (Prim  => Finalize_Case,
878              Typ   => Typ,
879              Stmts => Make_Deep_Array_Body (Finalize_Case, Typ)));
880
881         --  Create TSS primitive Finalize_Address (unless CodePeer_Mode)
882
883         if not CodePeer_Mode then
884            Set_TSS (Typ,
885              Make_Deep_Proc
886                (Prim  => Address_Case,
887                 Typ   => Typ,
888                 Stmts => Make_Deep_Array_Body (Address_Case, Typ)));
889         end if;
890      end if;
891   end Build_Array_Deep_Procs;
892
893   ------------------------------
894   -- Build_Cleanup_Statements --
895   ------------------------------
896
897   function Build_Cleanup_Statements
898     (N                  : Node_Id;
899      Additional_Cleanup : List_Id) return List_Id
900   is
901      Is_Asynchronous_Call : constant Boolean :=
902                               Nkind (N) = N_Block_Statement
903                                 and then Is_Asynchronous_Call_Block (N);
904      Is_Master            : constant Boolean :=
905                               Nkind (N) /= N_Entry_Body
906                                 and then Is_Task_Master (N);
907      Is_Protected_Body    : constant Boolean :=
908                               Nkind (N) = N_Subprogram_Body
909                                 and then Is_Protected_Subprogram_Body (N);
910      Is_Task_Allocation   : constant Boolean :=
911                               Nkind (N) = N_Block_Statement
912                                 and then Is_Task_Allocation_Block (N);
913      Is_Task_Body         : constant Boolean :=
914                               Nkind (Original_Node (N)) = N_Task_Body;
915
916      Loc   : constant Source_Ptr := Sloc (N);
917      Stmts : constant List_Id    := New_List;
918
919   begin
920      if Is_Task_Body then
921         if Restricted_Profile then
922            Append_To (Stmts,
923              Build_Runtime_Call (Loc, RE_Complete_Restricted_Task));
924         else
925            Append_To (Stmts, Build_Runtime_Call (Loc, RE_Complete_Task));
926         end if;
927
928      elsif Is_Master then
929         if Restriction_Active (No_Task_Hierarchy) = False then
930            Append_To (Stmts, Build_Runtime_Call (Loc, RE_Complete_Master));
931         end if;
932
933      --  Add statements to unlock the protected object parameter and to
934      --  undefer abort. If the context is a protected procedure and the object
935      --  has entries, call the entry service routine.
936
937      --  NOTE: The generated code references _object, a parameter to the
938      --  procedure.
939
940      elsif Is_Protected_Body then
941         declare
942            Spec      : constant Node_Id := Parent (Corresponding_Spec (N));
943            Conc_Typ  : Entity_Id := Empty;
944            Param     : Node_Id;
945            Param_Typ : Entity_Id;
946
947         begin
948            --  Find the _object parameter representing the protected object
949
950            Param := First (Parameter_Specifications (Spec));
951            loop
952               Param_Typ := Etype (Parameter_Type (Param));
953
954               if Ekind (Param_Typ) = E_Record_Type then
955                  Conc_Typ := Corresponding_Concurrent_Type (Param_Typ);
956               end if;
957
958               exit when No (Param) or else Present (Conc_Typ);
959               Next (Param);
960            end loop;
961
962            pragma Assert (Present (Param));
963            pragma Assert (Present (Conc_Typ));
964
965            --  Historical note: In earlier versions of GNAT, there was code
966            --  at this point to generate stuff to service entry queues. It is
967            --  now abstracted in Build_Protected_Subprogram_Call_Cleanup.
968
969            Build_Protected_Subprogram_Call_Cleanup
970              (Specification (N), Conc_Typ, Loc, Stmts);
971         end;
972
973      --  Add a call to Expunge_Unactivated_Tasks for dynamically allocated
974      --  tasks. Other unactivated tasks are completed by Complete_Task or
975      --  Complete_Master.
976
977      --  NOTE: The generated code references _chain, a local object
978
979      elsif Is_Task_Allocation then
980
981         --  Generate:
982         --     Expunge_Unactivated_Tasks (_chain);
983
984         --  where _chain is the list of tasks created by the allocator but not
985         --  yet activated. This list will be empty unless the block completes
986         --  abnormally.
987
988         Append_To (Stmts,
989           Make_Procedure_Call_Statement (Loc,
990             Name =>
991               New_Occurrence_Of
992                 (RTE (RE_Expunge_Unactivated_Tasks), Loc),
993             Parameter_Associations => New_List (
994               New_Occurrence_Of (Activation_Chain_Entity (N), Loc))));
995
996      --  Attempt to cancel an asynchronous entry call whenever the block which
997      --  contains the abortable part is exited.
998
999      --  NOTE: The generated code references Cnn, a local object
1000
1001      elsif Is_Asynchronous_Call then
1002         declare
1003            Cancel_Param : constant Entity_Id :=
1004                             Entry_Cancel_Parameter (Entity (Identifier (N)));
1005
1006         begin
1007            --  If it is of type Communication_Block, this must be a protected
1008            --  entry call. Generate:
1009
1010            --    if Enqueued (Cancel_Param) then
1011            --       Cancel_Protected_Entry_Call (Cancel_Param);
1012            --    end if;
1013
1014            if Is_RTE (Etype (Cancel_Param), RE_Communication_Block) then
1015               Append_To (Stmts,
1016                 Make_If_Statement (Loc,
1017                   Condition =>
1018                     Make_Function_Call (Loc,
1019                       Name                   =>
1020                         New_Occurrence_Of (RTE (RE_Enqueued), Loc),
1021                       Parameter_Associations => New_List (
1022                         New_Occurrence_Of (Cancel_Param, Loc))),
1023
1024                   Then_Statements => New_List (
1025                     Make_Procedure_Call_Statement (Loc,
1026                       Name =>
1027                         New_Occurrence_Of
1028                           (RTE (RE_Cancel_Protected_Entry_Call), Loc),
1029                         Parameter_Associations => New_List (
1030                           New_Occurrence_Of (Cancel_Param, Loc))))));
1031
1032            --  Asynchronous delay, generate:
1033            --    Cancel_Async_Delay (Cancel_Param);
1034
1035            elsif Is_RTE (Etype (Cancel_Param), RE_Delay_Block) then
1036               Append_To (Stmts,
1037                 Make_Procedure_Call_Statement (Loc,
1038                   Name                   =>
1039                     New_Occurrence_Of (RTE (RE_Cancel_Async_Delay), Loc),
1040                   Parameter_Associations => New_List (
1041                     Make_Attribute_Reference (Loc,
1042                       Prefix         =>
1043                         New_Occurrence_Of (Cancel_Param, Loc),
1044                       Attribute_Name => Name_Unchecked_Access))));
1045
1046            --  Task entry call, generate:
1047            --    Cancel_Task_Entry_Call (Cancel_Param);
1048
1049            else
1050               Append_To (Stmts,
1051                 Make_Procedure_Call_Statement (Loc,
1052                   Name                   =>
1053                     New_Occurrence_Of (RTE (RE_Cancel_Task_Entry_Call), Loc),
1054                   Parameter_Associations => New_List (
1055                     New_Occurrence_Of (Cancel_Param, Loc))));
1056            end if;
1057         end;
1058      end if;
1059
1060      Append_List_To (Stmts, Additional_Cleanup);
1061      return Stmts;
1062   end Build_Cleanup_Statements;
1063
1064   -----------------------------
1065   -- Build_Controlling_Procs --
1066   -----------------------------
1067
1068   procedure Build_Controlling_Procs (Typ : Entity_Id) is
1069   begin
1070      if Is_Array_Type (Typ) then
1071         Build_Array_Deep_Procs (Typ);
1072      else pragma Assert (Is_Record_Type (Typ));
1073         Build_Record_Deep_Procs (Typ);
1074      end if;
1075   end Build_Controlling_Procs;
1076
1077   -----------------------------
1078   -- Build_Exception_Handler --
1079   -----------------------------
1080
1081   function Build_Exception_Handler
1082     (Data        : Finalization_Exception_Data;
1083      For_Library : Boolean := False) return Node_Id
1084   is
1085      Actuals      : List_Id;
1086      Proc_To_Call : Entity_Id;
1087      Except       : Node_Id;
1088      Stmts        : List_Id;
1089
1090   begin
1091      pragma Assert (Present (Data.Raised_Id));
1092
1093      if Exception_Extra_Info
1094        or else (For_Library and not Restricted_Profile)
1095      then
1096         if Exception_Extra_Info then
1097
1098            --  Generate:
1099
1100            --    Get_Current_Excep.all
1101
1102            Except :=
1103              Make_Function_Call (Data.Loc,
1104                Name =>
1105                  Make_Explicit_Dereference (Data.Loc,
1106                    Prefix =>
1107                      New_Occurrence_Of
1108                        (RTE (RE_Get_Current_Excep), Data.Loc)));
1109
1110         else
1111            --  Generate:
1112
1113            --    null
1114
1115            Except := Make_Null (Data.Loc);
1116         end if;
1117
1118         if For_Library and then not Restricted_Profile then
1119            Proc_To_Call := RTE (RE_Save_Library_Occurrence);
1120            Actuals := New_List (Except);
1121
1122         else
1123            Proc_To_Call := RTE (RE_Save_Occurrence);
1124
1125            --  The dereference occurs only when Exception_Extra_Info is true,
1126            --  and therefore Except is not null.
1127
1128            Actuals :=
1129              New_List (
1130                New_Occurrence_Of (Data.E_Id, Data.Loc),
1131                Make_Explicit_Dereference (Data.Loc, Except));
1132         end if;
1133
1134         --  Generate:
1135
1136         --    when others =>
1137         --       if not Raised_Id then
1138         --          Raised_Id := True;
1139
1140         --          Save_Occurrence (E_Id, Get_Current_Excep.all.all);
1141         --            or
1142         --          Save_Library_Occurrence (Get_Current_Excep.all);
1143         --       end if;
1144
1145         Stmts :=
1146           New_List (
1147             Make_If_Statement (Data.Loc,
1148               Condition       =>
1149                 Make_Op_Not (Data.Loc,
1150                   Right_Opnd => New_Occurrence_Of (Data.Raised_Id, Data.Loc)),
1151
1152               Then_Statements => New_List (
1153                 Make_Assignment_Statement (Data.Loc,
1154                   Name       => New_Occurrence_Of (Data.Raised_Id, Data.Loc),
1155                   Expression => New_Occurrence_Of (Standard_True, Data.Loc)),
1156
1157                 Make_Procedure_Call_Statement (Data.Loc,
1158                   Name                   =>
1159                     New_Occurrence_Of (Proc_To_Call, Data.Loc),
1160                   Parameter_Associations => Actuals))));
1161
1162      else
1163         --  Generate:
1164
1165         --    Raised_Id := True;
1166
1167         Stmts := New_List (
1168           Make_Assignment_Statement (Data.Loc,
1169             Name       => New_Occurrence_Of (Data.Raised_Id, Data.Loc),
1170             Expression => New_Occurrence_Of (Standard_True, Data.Loc)));
1171      end if;
1172
1173      --  Generate:
1174
1175      --    when others =>
1176
1177      return
1178        Make_Exception_Handler (Data.Loc,
1179          Exception_Choices => New_List (Make_Others_Choice (Data.Loc)),
1180          Statements        => Stmts);
1181   end Build_Exception_Handler;
1182
1183   -------------------------------
1184   -- Build_Finalization_Master --
1185   -------------------------------
1186
1187   procedure Build_Finalization_Master
1188     (Typ            : Entity_Id;
1189      For_Lib_Level  : Boolean   := False;
1190      For_Private    : Boolean   := False;
1191      Context_Scope  : Entity_Id := Empty;
1192      Insertion_Node : Node_Id   := Empty)
1193   is
1194      procedure Add_Pending_Access_Type
1195        (Typ     : Entity_Id;
1196         Ptr_Typ : Entity_Id);
1197      --  Add access type Ptr_Typ to the pending access type list for type Typ
1198
1199      -----------------------------
1200      -- Add_Pending_Access_Type --
1201      -----------------------------
1202
1203      procedure Add_Pending_Access_Type
1204        (Typ     : Entity_Id;
1205         Ptr_Typ : Entity_Id)
1206      is
1207         List : Elist_Id;
1208
1209      begin
1210         if Present (Pending_Access_Types (Typ)) then
1211            List := Pending_Access_Types (Typ);
1212         else
1213            List := New_Elmt_List;
1214            Set_Pending_Access_Types (Typ, List);
1215         end if;
1216
1217         Prepend_Elmt (Ptr_Typ, List);
1218      end Add_Pending_Access_Type;
1219
1220      --  Local variables
1221
1222      Desig_Typ : constant Entity_Id := Designated_Type (Typ);
1223
1224      Ptr_Typ : constant Entity_Id := Root_Type_Of_Full_View (Base_Type (Typ));
1225      --  A finalization master created for a named access type is associated
1226      --  with the full view (if applicable) as a consequence of freezing. The
1227      --  full view criteria does not apply to anonymous access types because
1228      --  those cannot have a private and a full view.
1229
1230   --  Start of processing for Build_Finalization_Master
1231
1232   begin
1233      --  Nothing to do if the circumstances do not allow for a finalization
1234      --  master.
1235
1236      if not Allows_Finalization_Master (Typ) then
1237         return;
1238
1239      --  Various machinery such as freezing may have already created a
1240      --  finalization master.
1241
1242      elsif Present (Finalization_Master (Ptr_Typ)) then
1243         return;
1244      end if;
1245
1246      declare
1247         Actions    : constant List_Id    := New_List;
1248         Loc        : constant Source_Ptr := Sloc (Ptr_Typ);
1249         Fin_Mas_Id : Entity_Id;
1250         Pool_Id    : Entity_Id;
1251
1252      begin
1253         --  Source access types use fixed master names since the master is
1254         --  inserted in the same source unit only once. The only exception to
1255         --  this are instances using the same access type as generic actual.
1256
1257         if Comes_From_Source (Ptr_Typ) and then not Inside_A_Generic then
1258            Fin_Mas_Id :=
1259              Make_Defining_Identifier (Loc,
1260                Chars => New_External_Name (Chars (Ptr_Typ), "FM"));
1261
1262         --  Internally generated access types use temporaries as their names
1263         --  due to possible collision with identical names coming from other
1264         --  packages.
1265
1266         else
1267            Fin_Mas_Id := Make_Temporary (Loc, 'F');
1268         end if;
1269
1270         Set_Finalization_Master (Ptr_Typ, Fin_Mas_Id);
1271
1272         --  Generate:
1273         --    <Ptr_Typ>FM : aliased Finalization_Master;
1274
1275         Append_To (Actions,
1276           Make_Object_Declaration (Loc,
1277             Defining_Identifier => Fin_Mas_Id,
1278             Aliased_Present     => True,
1279             Object_Definition   =>
1280               New_Occurrence_Of (RTE (RE_Finalization_Master), Loc)));
1281
1282         if Debug_Generated_Code then
1283            Set_Debug_Info_Needed (Fin_Mas_Id);
1284         end if;
1285
1286         --  Set the associated pool and primitive Finalize_Address of the new
1287         --  finalization master.
1288
1289         --  The access type has a user-defined storage pool, use it
1290
1291         if Present (Associated_Storage_Pool (Ptr_Typ)) then
1292            Pool_Id := Associated_Storage_Pool (Ptr_Typ);
1293
1294         --  Otherwise the default choice is the global storage pool
1295
1296         else
1297            Pool_Id := RTE (RE_Global_Pool_Object);
1298            Set_Associated_Storage_Pool (Ptr_Typ, Pool_Id);
1299         end if;
1300
1301         --  Generate:
1302         --    Set_Base_Pool (<Ptr_Typ>FM, Pool_Id'Unchecked_Access);
1303
1304         Append_To (Actions,
1305           Make_Procedure_Call_Statement (Loc,
1306             Name                   =>
1307               New_Occurrence_Of (RTE (RE_Set_Base_Pool), Loc),
1308             Parameter_Associations => New_List (
1309               New_Occurrence_Of (Fin_Mas_Id, Loc),
1310               Make_Attribute_Reference (Loc,
1311                 Prefix         => New_Occurrence_Of (Pool_Id, Loc),
1312                 Attribute_Name => Name_Unrestricted_Access))));
1313
1314         --  Finalize_Address is not generated in CodePeer mode because the
1315         --  body contains address arithmetic. Skip this step.
1316
1317         if CodePeer_Mode then
1318            null;
1319
1320         --  Associate the Finalize_Address primitive of the designated type
1321         --  with the finalization master of the access type. The designated
1322         --  type must be forzen as Finalize_Address is generated when the
1323         --  freeze node is expanded.
1324
1325         elsif Is_Frozen (Desig_Typ)
1326           and then Present (Finalize_Address (Desig_Typ))
1327
1328           --  The finalization master of an anonymous access type may need
1329           --  to be inserted in a specific place in the tree. For instance:
1330
1331           --    type Comp_Typ;
1332
1333           --    <finalization master of "access Comp_Typ">
1334
1335           --    type Rec_Typ is record
1336           --       Comp : access Comp_Typ;
1337           --    end record;
1338
1339           --    <freeze node for Comp_Typ>
1340           --    <freeze node for Rec_Typ>
1341
1342           --  Due to this oddity, the anonymous access type is stored for
1343           --  later processing (see below).
1344
1345           and then Ekind (Ptr_Typ) /= E_Anonymous_Access_Type
1346         then
1347            --  Generate:
1348            --    Set_Finalize_Address
1349            --      (<Ptr_Typ>FM, <Desig_Typ>FD'Unrestricted_Access);
1350
1351            Append_To (Actions,
1352              Make_Set_Finalize_Address_Call
1353                (Loc     => Loc,
1354                 Ptr_Typ => Ptr_Typ));
1355
1356         --  Otherwise the designated type is either anonymous access or a
1357         --  Taft-amendment type and has not been frozen. Store the access
1358         --  type for later processing (see Freeze_Type).
1359
1360         else
1361            Add_Pending_Access_Type (Desig_Typ, Ptr_Typ);
1362         end if;
1363
1364         --  A finalization master created for an access designating a type
1365         --  with private components is inserted before a context-dependent
1366         --  node.
1367
1368         if For_Private then
1369
1370            --  At this point both the scope of the context and the insertion
1371            --  mode must be known.
1372
1373            pragma Assert (Present (Context_Scope));
1374            pragma Assert (Present (Insertion_Node));
1375
1376            Push_Scope (Context_Scope);
1377
1378            --  Treat use clauses as declarations and insert directly in front
1379            --  of them.
1380
1381            if Nkind (Insertion_Node) in
1382                 N_Use_Package_Clause | N_Use_Type_Clause
1383            then
1384               Insert_List_Before_And_Analyze (Insertion_Node, Actions);
1385            else
1386               Insert_Actions (Insertion_Node, Actions);
1387            end if;
1388
1389            Pop_Scope;
1390
1391         --  The finalization master belongs to an access result type related
1392         --  to a build-in-place function call used to initialize a library
1393         --  level object. The master must be inserted in front of the access
1394         --  result type declaration denoted by Insertion_Node.
1395
1396         elsif For_Lib_Level then
1397            pragma Assert (Present (Insertion_Node));
1398            Insert_Actions (Insertion_Node, Actions);
1399
1400         --  Otherwise the finalization master and its initialization become a
1401         --  part of the freeze node.
1402
1403         else
1404            Append_Freeze_Actions (Ptr_Typ, Actions);
1405         end if;
1406
1407         Analyze_List (Actions);
1408
1409         --  When the type the finalization master is being generated for was
1410         --  created to store a 'Old object, then mark it as such so its
1411         --  finalization can be delayed until after postconditions have been
1412         --  checked.
1413
1414         if Stores_Attribute_Old_Prefix (Ptr_Typ) then
1415            Set_Stores_Attribute_Old_Prefix (Fin_Mas_Id);
1416         end if;
1417      end;
1418   end Build_Finalization_Master;
1419
1420   ----------------------------
1421   -- Build_Finalizer_Helper --
1422   ----------------------------
1423
1424   procedure Build_Finalizer_Helper
1425     (N                 : Node_Id;
1426      Clean_Stmts       : List_Id;
1427      Mark_Id           : Entity_Id;
1428      Top_Decls         : List_Id;
1429      Defer_Abort       : Boolean;
1430      Fin_Id            : out Entity_Id;
1431      Finalize_Old_Only : Boolean)
1432   is
1433      Acts_As_Clean    : constant Boolean :=
1434                           Present (Mark_Id)
1435                             or else
1436                               (Present (Clean_Stmts)
1437                                 and then Is_Non_Empty_List (Clean_Stmts));
1438
1439      For_Package_Body : constant Boolean := Nkind (N) = N_Package_Body;
1440      For_Package_Spec : constant Boolean := Nkind (N) = N_Package_Declaration;
1441      For_Package      : constant Boolean :=
1442                           For_Package_Body or else For_Package_Spec;
1443      Loc              : constant Source_Ptr := Sloc (N);
1444
1445      --  NOTE: Local variable declarations are conservative and do not create
1446      --  structures right from the start. Entities and lists are created once
1447      --  it has been established that N has at least one controlled object.
1448
1449      Components_Built : Boolean := False;
1450      --  A flag used to avoid double initialization of entities and lists. If
1451      --  the flag is set then the following variables have been initialized:
1452      --    Counter_Id
1453      --    Finalizer_Decls
1454      --    Finalizer_Stmts
1455      --    Jump_Alts
1456
1457      Counter_Id  : Entity_Id := Empty;
1458      Counter_Val : Nat       := 0;
1459      --  Name and value of the state counter
1460
1461      Decls : List_Id := No_List;
1462      --  Declarative region of N (if available). If N is a package declaration
1463      --  Decls denotes the visible declarations.
1464
1465      Finalizer_Data : Finalization_Exception_Data;
1466      --  Data for the exception
1467
1468      Finalizer_Decls : List_Id := No_List;
1469      --  Local variable declarations. This list holds the label declarations
1470      --  of all jump block alternatives as well as the declaration of the
1471      --  local exception occurrence and the raised flag:
1472      --     E : Exception_Occurrence;
1473      --     Raised : Boolean := False;
1474      --     L<counter value> : label;
1475
1476      Finalizer_Insert_Nod : Node_Id := Empty;
1477      --  Insertion point for the finalizer body. Depending on the context
1478      --  (Nkind of N) and the individual grouping of controlled objects, this
1479      --  node may denote a package declaration or body, package instantiation,
1480      --  block statement or a counter update statement.
1481
1482      Finalizer_Stmts : List_Id := No_List;
1483      --  The statement list of the finalizer body. It contains the following:
1484      --
1485      --    Abort_Defer;               --  Added if abort is allowed
1486      --    <call to Prev_At_End>      --  Added if exists
1487      --    <cleanup statements>       --  Added if Acts_As_Clean
1488      --    <jump block>               --  Added if Has_Ctrl_Objs
1489      --    <finalization statements>  --  Added if Has_Ctrl_Objs
1490      --    <stack release>            --  Added if Mark_Id exists
1491      --    Abort_Undefer;             --  Added if abort is allowed
1492
1493      Has_Ctrl_Objs : Boolean := False;
1494      --  A general flag which denotes whether N has at least one controlled
1495      --  object.
1496
1497      Has_Tagged_Types : Boolean := False;
1498      --  A general flag which indicates whether N has at least one library-
1499      --  level tagged type declaration.
1500
1501      HSS : Node_Id := Empty;
1502      --  The sequence of statements of N (if available)
1503
1504      Jump_Alts : List_Id := No_List;
1505      --  Jump block alternatives. Depending on the value of the state counter,
1506      --  the control flow jumps to a sequence of finalization statements. This
1507      --  list contains the following:
1508      --
1509      --     when <counter value> =>
1510      --        goto L<counter value>;
1511
1512      Jump_Block_Insert_Nod : Node_Id := Empty;
1513      --  Specific point in the finalizer statements where the jump block is
1514      --  inserted.
1515
1516      Last_Top_Level_Ctrl_Construct : Node_Id := Empty;
1517      --  The last controlled construct encountered when processing the top
1518      --  level lists of N. This can be a nested package, an instantiation or
1519      --  an object declaration.
1520
1521      Prev_At_End : Entity_Id := Empty;
1522      --  The previous at end procedure of the handled statements block of N
1523
1524      Priv_Decls : List_Id := No_List;
1525      --  The private declarations of N if N is a package declaration
1526
1527      Spec_Id    : Entity_Id := Empty;
1528      Spec_Decls : List_Id   := Top_Decls;
1529      Stmts      : List_Id   := No_List;
1530
1531      Tagged_Type_Stmts : List_Id := No_List;
1532      --  Contains calls to Ada.Tags.Unregister_Tag for all library-level
1533      --  tagged types found in N.
1534
1535      -----------------------
1536      -- Local subprograms --
1537      -----------------------
1538
1539      procedure Build_Components;
1540      --  Create all entites and initialize all lists used in the creation of
1541      --  the finalizer.
1542
1543      procedure Create_Finalizer;
1544      --  Create the spec and body of the finalizer and insert them in the
1545      --  proper place in the tree depending on the context.
1546
1547      function New_Finalizer_Name
1548        (Spec_Id : Node_Id; For_Spec : Boolean) return Name_Id;
1549      --  Create a fully qualified name of a package spec or body finalizer.
1550      --  The generated name is of the form: xx__yy__finalize_[spec|body].
1551
1552      procedure Process_Declarations
1553        (Decls      : List_Id;
1554         Preprocess : Boolean := False;
1555         Top_Level  : Boolean := False);
1556      --  Inspect a list of declarations or statements which may contain
1557      --  objects that need finalization. When flag Preprocess is set, the
1558      --  routine will simply count the total number of controlled objects in
1559      --  Decls and set Counter_Val accordingly. Top_Level is only relevant
1560      --  when Preprocess is set and if True, the processing is performed for
1561      --  objects in nested package declarations or instances.
1562
1563      procedure Process_Object_Declaration
1564        (Decl         : Node_Id;
1565         Has_No_Init  : Boolean := False;
1566         Is_Protected : Boolean := False);
1567      --  Generate all the machinery associated with the finalization of a
1568      --  single object. Flag Has_No_Init is used to denote certain contexts
1569      --  where Decl does not have initialization call(s). Flag Is_Protected
1570      --  is set when Decl denotes a simple protected object.
1571
1572      procedure Process_Tagged_Type_Declaration (Decl : Node_Id);
1573      --  Generate all the code necessary to unregister the external tag of a
1574      --  tagged type.
1575
1576      ----------------------
1577      -- Build_Components --
1578      ----------------------
1579
1580      procedure Build_Components is
1581         Counter_Decl     : Node_Id;
1582         Counter_Typ      : Entity_Id;
1583         Counter_Typ_Decl : Node_Id;
1584
1585      begin
1586         pragma Assert (Present (Decls));
1587
1588         --  This routine might be invoked several times when dealing with
1589         --  constructs that have two lists (either two declarative regions
1590         --  or declarations and statements). Avoid double initialization.
1591
1592         if Components_Built then
1593            return;
1594         end if;
1595
1596         Components_Built := True;
1597
1598         if Has_Ctrl_Objs then
1599
1600            --  Create entities for the counter, its type, the local exception
1601            --  and the raised flag.
1602
1603            Counter_Id  := Make_Temporary (Loc, 'C');
1604            Counter_Typ := Make_Temporary (Loc, 'T');
1605
1606            Finalizer_Decls := New_List;
1607
1608            Build_Object_Declarations
1609              (Finalizer_Data, Finalizer_Decls, Loc, For_Package);
1610
1611            --  Since the total number of controlled objects is always known,
1612            --  build a subtype of Natural with precise bounds. This allows
1613            --  the backend to optimize the case statement. Generate:
1614            --
1615            --    subtype Tnn is Natural range 0 .. Counter_Val;
1616
1617            Counter_Typ_Decl :=
1618              Make_Subtype_Declaration (Loc,
1619                Defining_Identifier => Counter_Typ,
1620                Subtype_Indication  =>
1621                  Make_Subtype_Indication (Loc,
1622                    Subtype_Mark => New_Occurrence_Of (Standard_Natural, Loc),
1623                    Constraint   =>
1624                      Make_Range_Constraint (Loc,
1625                        Range_Expression =>
1626                          Make_Range (Loc,
1627                            Low_Bound  =>
1628                              Make_Integer_Literal (Loc, Uint_0),
1629                            High_Bound =>
1630                              Make_Integer_Literal (Loc, Counter_Val)))));
1631
1632            --  Generate the declaration of the counter itself:
1633            --
1634            --    Counter : Integer := 0;
1635
1636            Counter_Decl :=
1637              Make_Object_Declaration (Loc,
1638                Defining_Identifier => Counter_Id,
1639                Object_Definition   => New_Occurrence_Of (Counter_Typ, Loc),
1640                Expression          => Make_Integer_Literal (Loc, 0));
1641
1642            --  Set the type of the counter explicitly to prevent errors when
1643            --  examining object declarations later on.
1644
1645            Set_Etype (Counter_Id, Counter_Typ);
1646
1647            if Debug_Generated_Code then
1648               Set_Debug_Info_Needed (Counter_Id);
1649            end if;
1650
1651            --  The counter and its type are inserted before the source
1652            --  declarations of N.
1653
1654            Prepend_To (Decls, Counter_Decl);
1655            Prepend_To (Decls, Counter_Typ_Decl);
1656
1657            --  The counter and its associated type must be manually analyzed
1658            --  since N has already been analyzed. Use the scope of the spec
1659            --  when inserting in a package.
1660
1661            if For_Package then
1662               Push_Scope (Spec_Id);
1663               Analyze (Counter_Typ_Decl);
1664               Analyze (Counter_Decl);
1665               Pop_Scope;
1666
1667            else
1668               Analyze (Counter_Typ_Decl);
1669               Analyze (Counter_Decl);
1670            end if;
1671
1672            Jump_Alts := New_List;
1673         end if;
1674
1675         --  If the context requires additional cleanup, the finalization
1676         --  machinery is added after the cleanup code.
1677
1678         if Acts_As_Clean then
1679            Finalizer_Stmts       := Clean_Stmts;
1680            Jump_Block_Insert_Nod := Last (Finalizer_Stmts);
1681         else
1682            Finalizer_Stmts := New_List;
1683         end if;
1684
1685         if Has_Tagged_Types then
1686            Tagged_Type_Stmts := New_List;
1687         end if;
1688      end Build_Components;
1689
1690      ----------------------
1691      -- Create_Finalizer --
1692      ----------------------
1693
1694      procedure Create_Finalizer is
1695         Body_Id    : Entity_Id;
1696         Fin_Body   : Node_Id;
1697         Fin_Spec   : Node_Id;
1698         Jump_Block : Node_Id;
1699         Label      : Node_Id;
1700         Label_Id   : Entity_Id;
1701
1702      begin
1703         --  Step 1: Creation of the finalizer name
1704
1705         --  Packages must use a distinct name for their finalizers since the
1706         --  binder will have to generate calls to them by name. The name is
1707         --  of the following form:
1708
1709         --    xx__yy__finalize_[spec|body]
1710
1711         if For_Package then
1712            Fin_Id := Make_Defining_Identifier
1713                        (Loc, New_Finalizer_Name (Spec_Id, For_Package_Spec));
1714            Set_Has_Qualified_Name       (Fin_Id);
1715            Set_Has_Fully_Qualified_Name (Fin_Id);
1716
1717         --  The default name is _finalizer
1718
1719         else
1720            --  Generation of a finalization procedure exclusively for 'Old
1721            --  interally generated constants requires different name since
1722            --  there will need to be multiple finalization routines in the
1723            --  same scope. See Build_Finalizer for details.
1724
1725            if Finalize_Old_Only then
1726               Fin_Id :=
1727                 Make_Defining_Identifier (Loc,
1728                   Chars => New_External_Name (Name_uFinalizer_Old));
1729            else
1730               Fin_Id :=
1731                 Make_Defining_Identifier (Loc,
1732                   Chars => New_External_Name (Name_uFinalizer));
1733            end if;
1734
1735            --  The visibility semantics of AT_END handlers force a strange
1736            --  separation of spec and body for stack-related finalizers:
1737
1738            --     declare : Enclosing_Scope
1739            --        procedure _finalizer;
1740            --     begin
1741            --        <controlled objects>
1742            --        procedure _finalizer is
1743            --           ...
1744            --     at end
1745            --        _finalizer;
1746            --     end;
1747
1748            --  Both spec and body are within the same construct and scope, but
1749            --  the body is part of the handled sequence of statements. This
1750            --  placement confuses the elaboration mechanism on targets where
1751            --  AT_END handlers are expanded into "when all others" handlers:
1752
1753            --     exception
1754            --        when all others =>
1755            --           _finalizer;  --  appears to require elab checks
1756            --     at end
1757            --        _finalizer;
1758            --     end;
1759
1760            --  Since the compiler guarantees that the body of a _finalizer is
1761            --  always inserted in the same construct where the AT_END handler
1762            --  resides, there is no need for elaboration checks.
1763
1764            Set_Kill_Elaboration_Checks (Fin_Id);
1765
1766            --  Inlining the finalizer produces a substantial speedup at -O2.
1767            --  It is inlined by default at -O3. Either way, it is called
1768            --  exactly twice (once on the normal path, and once for
1769            --  exceptions/abort), so this won't bloat the code too much.
1770
1771            Set_Is_Inlined (Fin_Id);
1772         end if;
1773
1774         if Debug_Generated_Code then
1775            Set_Debug_Info_Needed (Fin_Id);
1776         end if;
1777
1778         --  Step 2: Creation of the finalizer specification
1779
1780         --  Generate:
1781         --    procedure Fin_Id;
1782
1783         Fin_Spec :=
1784           Make_Subprogram_Declaration (Loc,
1785             Specification =>
1786               Make_Procedure_Specification (Loc,
1787                 Defining_Unit_Name => Fin_Id));
1788
1789         if For_Package then
1790            Set_Is_Exported (Fin_Id);
1791            Set_Interface_Name (Fin_Id,
1792              Make_String_Literal (Loc,
1793                Strval => Get_Name_String (Chars (Fin_Id))));
1794         end if;
1795
1796         --  Step 3: Creation of the finalizer body
1797
1798        --  Has_Ctrl_Objs might be set because of a generic package body having
1799        --  controlled objects. In this case, Jump_Alts may be empty and no
1800        --  case nor goto statements are needed.
1801
1802         if Has_Ctrl_Objs
1803           and then not Is_Empty_List (Jump_Alts)
1804         then
1805            --  Add L0, the default destination to the jump block
1806
1807            Label_Id := Make_Identifier (Loc, New_External_Name ('L', 0));
1808            Set_Entity (Label_Id,
1809              Make_Defining_Identifier (Loc, Chars (Label_Id)));
1810            Label := Make_Label (Loc, Label_Id);
1811
1812            --  Generate:
1813            --    L0 : label;
1814
1815            Prepend_To (Finalizer_Decls,
1816              Make_Implicit_Label_Declaration (Loc,
1817                Defining_Identifier => Entity (Label_Id),
1818                Label_Construct     => Label));
1819
1820            --  Generate:
1821            --    when others =>
1822            --       goto L0;
1823
1824            Append_To (Jump_Alts,
1825              Make_Case_Statement_Alternative (Loc,
1826                Discrete_Choices => New_List (Make_Others_Choice (Loc)),
1827                Statements       => New_List (
1828                  Make_Goto_Statement (Loc,
1829                    Name => New_Occurrence_Of (Entity (Label_Id), Loc)))));
1830
1831            --  Generate:
1832            --    <<L0>>
1833
1834            Append_To (Finalizer_Stmts, Label);
1835
1836            --  Create the jump block which controls the finalization flow
1837            --  depending on the value of the state counter.
1838
1839            Jump_Block :=
1840              Make_Case_Statement (Loc,
1841                Expression   => Make_Identifier (Loc, Chars (Counter_Id)),
1842                Alternatives => Jump_Alts);
1843
1844            if Acts_As_Clean and then Present (Jump_Block_Insert_Nod) then
1845               Insert_After (Jump_Block_Insert_Nod, Jump_Block);
1846            else
1847               Prepend_To (Finalizer_Stmts, Jump_Block);
1848            end if;
1849         end if;
1850
1851         --  Add the library-level tagged type unregistration machinery before
1852         --  the jump block circuitry. This ensures that external tags will be
1853         --  removed even if a finalization exception occurs at some point.
1854
1855         if Has_Tagged_Types then
1856            Prepend_List_To (Finalizer_Stmts, Tagged_Type_Stmts);
1857         end if;
1858
1859         --  Add a call to the previous At_End handler if it exists. The call
1860         --  must always precede the jump block.
1861
1862         if Present (Prev_At_End) then
1863            Prepend_To (Finalizer_Stmts,
1864              Make_Procedure_Call_Statement (Loc, Prev_At_End));
1865
1866            --  Clear the At_End handler since we have already generated the
1867            --  proper replacement call for it.
1868
1869            Set_At_End_Proc (HSS, Empty);
1870         end if;
1871
1872         --  Release the secondary stack
1873
1874         if Present (Mark_Id) then
1875            declare
1876               Release : Node_Id := Build_SS_Release_Call (Loc, Mark_Id);
1877
1878            begin
1879               --  If the context is a build-in-place function, the secondary
1880               --  stack must be released, unless the build-in-place function
1881               --  itself is returning on the secondary stack. Generate:
1882               --
1883               --    if BIP_Alloc_Form /= Secondary_Stack then
1884               --       SS_Release (Mark_Id);
1885               --    end if;
1886               --
1887               --  Note that if the function returns on the secondary stack,
1888               --  then the responsibility of reclaiming the space is always
1889               --  left to the caller (recursively if needed).
1890
1891               if Nkind (N) = N_Subprogram_Body then
1892                  declare
1893                     Spec_Id : constant Entity_Id :=
1894                                 Unique_Defining_Entity (N);
1895                     BIP_SS  : constant Boolean :=
1896                                 Is_Build_In_Place_Function (Spec_Id)
1897                                   and then Needs_BIP_Alloc_Form (Spec_Id);
1898                  begin
1899                     if BIP_SS then
1900                        Release :=
1901                          Make_If_Statement (Loc,
1902                            Condition       =>
1903                              Make_Op_Ne (Loc,
1904                                Left_Opnd  =>
1905                                  New_Occurrence_Of
1906                                    (Build_In_Place_Formal
1907                                      (Spec_Id, BIP_Alloc_Form), Loc),
1908                                Right_Opnd =>
1909                                  Make_Integer_Literal (Loc,
1910                                    UI_From_Int
1911                                      (BIP_Allocation_Form'Pos
1912                                        (Secondary_Stack)))),
1913
1914                            Then_Statements => New_List (Release));
1915                     end if;
1916                  end;
1917               end if;
1918
1919               Append_To (Finalizer_Stmts, Release);
1920            end;
1921         end if;
1922
1923         --  Protect the statements with abort defer/undefer. This is only when
1924         --  aborts are allowed and the cleanup statements require deferral or
1925         --  there are controlled objects to be finalized. Note that the abort
1926         --  defer/undefer pair does not require an extra block because each
1927         --  finalization exception is caught in its corresponding finalization
1928         --  block. As a result, the call to Abort_Defer always takes place.
1929
1930         if Abort_Allowed and then (Defer_Abort or Has_Ctrl_Objs) then
1931            Prepend_To (Finalizer_Stmts,
1932              Build_Runtime_Call (Loc, RE_Abort_Defer));
1933
1934            Append_To (Finalizer_Stmts,
1935              Build_Runtime_Call (Loc, RE_Abort_Undefer));
1936         end if;
1937
1938         --  The local exception does not need to be reraised for library-level
1939         --  finalizers. Note that this action must be carried out after object
1940         --  cleanup, secondary stack release, and abort undeferral. Generate:
1941
1942         --    if Raised and then not Abort then
1943         --       Raise_From_Controlled_Operation (E);
1944         --    end if;
1945
1946         if Has_Ctrl_Objs and Exceptions_OK and not For_Package then
1947            Append_To (Finalizer_Stmts,
1948              Build_Raise_Statement (Finalizer_Data));
1949         end if;
1950
1951         --  Generate:
1952         --    procedure Fin_Id is
1953         --       Abort  : constant Boolean := Triggered_By_Abort;
1954         --         <or>
1955         --       Abort  : constant Boolean := False;  --  no abort
1956
1957         --       E      : Exception_Occurrence;  --  All added if flag
1958         --       Raised : Boolean := False;      --  Has_Ctrl_Objs is set
1959         --       L0     : label;
1960         --       ...
1961         --       Lnn    : label;
1962
1963         --    begin
1964         --       Abort_Defer;               --  Added if abort is allowed
1965         --       <call to Prev_At_End>      --  Added if exists
1966         --       <cleanup statements>       --  Added if Acts_As_Clean
1967         --       <jump block>               --  Added if Has_Ctrl_Objs
1968         --       <finalization statements>  --  Added if Has_Ctrl_Objs
1969         --       <stack release>            --  Added if Mark_Id exists
1970         --       Abort_Undefer;             --  Added if abort is allowed
1971         --       <exception propagation>    --  Added if Has_Ctrl_Objs
1972         --    end Fin_Id;
1973
1974         --  Create the body of the finalizer
1975
1976         Body_Id := Make_Defining_Identifier (Loc, Chars (Fin_Id));
1977
1978         if Debug_Generated_Code then
1979            Set_Debug_Info_Needed (Body_Id);
1980         end if;
1981
1982         if For_Package then
1983            Set_Has_Qualified_Name       (Body_Id);
1984            Set_Has_Fully_Qualified_Name (Body_Id);
1985         end if;
1986
1987         Fin_Body :=
1988           Make_Subprogram_Body (Loc,
1989             Specification              =>
1990               Make_Procedure_Specification (Loc,
1991                 Defining_Unit_Name => Body_Id),
1992             Declarations               => Finalizer_Decls,
1993             Handled_Statement_Sequence =>
1994               Make_Handled_Sequence_Of_Statements (Loc,
1995                 Statements => Finalizer_Stmts));
1996
1997         --  Step 4: Spec and body insertion, analysis
1998
1999         if For_Package then
2000
2001            --  If the package spec has private declarations, the finalizer
2002            --  body must be added to the end of the list in order to have
2003            --  visibility of all private controlled objects.
2004
2005            if For_Package_Spec then
2006               if Present (Priv_Decls) then
2007                  Append_To (Priv_Decls, Fin_Spec);
2008                  Append_To (Priv_Decls, Fin_Body);
2009               else
2010                  Append_To (Decls, Fin_Spec);
2011                  Append_To (Decls, Fin_Body);
2012               end if;
2013
2014            --  For package bodies, both the finalizer spec and body are
2015            --  inserted at the end of the package declarations.
2016
2017            else
2018               Append_To (Decls, Fin_Spec);
2019               Append_To (Decls, Fin_Body);
2020            end if;
2021
2022            --  Push the name of the package
2023
2024            Push_Scope (Spec_Id);
2025            Analyze (Fin_Spec);
2026            Analyze (Fin_Body);
2027            Pop_Scope;
2028
2029         --  Non-package case
2030
2031         else
2032            --  Create the spec for the finalizer. The At_End handler must be
2033            --  able to call the body which resides in a nested structure.
2034
2035            --  Generate:
2036            --    declare
2037            --       procedure Fin_Id;                  --  Spec
2038            --    begin
2039            --       <objects and possibly statements>
2040            --       procedure Fin_Id is ...            --  Body
2041            --       <statements>
2042            --    at end
2043            --       Fin_Id;                            --  At_End handler
2044            --    end;
2045
2046            pragma Assert (Present (Spec_Decls));
2047
2048            --  It maybe possible that we are finalizing 'Old objects which
2049            --  exist in the spec declarations. When this is the case the
2050            --  Finalizer_Insert_Node will come before the end of the
2051            --  Spec_Decls. So, to mitigate this, we insert the finalizer spec
2052            --  earlier at the Finalizer_Insert_Nod instead of appending to the
2053            --  end of Spec_Decls to prevent its body appearing before its
2054            --  corresponding spec.
2055
2056            if Present (Finalizer_Insert_Nod)
2057              and then List_Containing (Finalizer_Insert_Nod) = Spec_Decls
2058            then
2059               Insert_After_And_Analyze (Finalizer_Insert_Nod, Fin_Spec);
2060               Finalizer_Insert_Nod := Fin_Spec;
2061
2062            --  Otherwise, Finalizer_Insert_Nod is not in Spec_Decls
2063
2064            else
2065               Append_To (Spec_Decls, Fin_Spec);
2066               Analyze (Fin_Spec);
2067            end if;
2068
2069            --  When the finalizer acts solely as a cleanup routine, the body
2070            --  is inserted right after the spec.
2071
2072            if Acts_As_Clean and not Has_Ctrl_Objs then
2073               Insert_After (Fin_Spec, Fin_Body);
2074
2075            --  In all other cases the body is inserted after either:
2076            --
2077            --    1) The counter update statement of the last controlled object
2078            --    2) The last top level nested controlled package
2079            --    3) The last top level controlled instantiation
2080
2081            else
2082               --  Manually freeze the spec. This is somewhat of a hack because
2083               --  a subprogram is frozen when its body is seen and the freeze
2084               --  node appears right before the body. However, in this case,
2085               --  the spec must be frozen earlier since the At_End handler
2086               --  must be able to call it.
2087               --
2088               --    declare
2089               --       procedure Fin_Id;               --  Spec
2090               --       [Fin_Id]                        --  Freeze node
2091               --    begin
2092               --       ...
2093               --    at end
2094               --       Fin_Id;                         --  At_End handler
2095               --    end;
2096
2097               Ensure_Freeze_Node (Fin_Id);
2098               Insert_After (Fin_Spec, Freeze_Node (Fin_Id));
2099               Set_Is_Frozen (Fin_Id);
2100
2101               --  In the case where the last construct to contain a controlled
2102               --  object is either a nested package, an instantiation or a
2103               --  freeze node, the body must be inserted directly after the
2104               --  construct.
2105
2106               if Nkind (Last_Top_Level_Ctrl_Construct) in
2107                    N_Freeze_Entity | N_Package_Declaration | N_Package_Body
2108               then
2109                  Finalizer_Insert_Nod := Last_Top_Level_Ctrl_Construct;
2110               end if;
2111
2112               Insert_After (Finalizer_Insert_Nod, Fin_Body);
2113            end if;
2114
2115            Analyze (Fin_Body, Suppress => All_Checks);
2116         end if;
2117
2118         --  Never consider that the finalizer procedure is enabled Ghost, even
2119         --  when the corresponding unit is Ghost, as this would lead to an
2120         --  an external name with a ___ghost_ prefix that the binder cannot
2121         --  generate, as it has no knowledge of the Ghost status of units.
2122
2123         Set_Is_Checked_Ghost_Entity (Fin_Id, False);
2124      end Create_Finalizer;
2125
2126      ------------------------
2127      -- New_Finalizer_Name --
2128      ------------------------
2129
2130      function New_Finalizer_Name
2131        (Spec_Id : Node_Id; For_Spec : Boolean) return Name_Id
2132      is
2133         procedure New_Finalizer_Name (Id : Entity_Id);
2134         --  Place "__<name-of-Id>" in the name buffer. If the identifier
2135         --  has a non-standard scope, process the scope first.
2136
2137         ------------------------
2138         -- New_Finalizer_Name --
2139         ------------------------
2140
2141         procedure New_Finalizer_Name (Id : Entity_Id) is
2142         begin
2143            if Scope (Id) = Standard_Standard then
2144               Get_Name_String (Chars (Id));
2145
2146            else
2147               New_Finalizer_Name (Scope (Id));
2148               Add_Str_To_Name_Buffer ("__");
2149               Get_Name_String_And_Append (Chars (Id));
2150            end if;
2151         end New_Finalizer_Name;
2152
2153      --  Start of processing for New_Finalizer_Name
2154
2155      begin
2156         --  Create the fully qualified name of the enclosing scope
2157
2158         New_Finalizer_Name (Spec_Id);
2159
2160         --  Generate:
2161         --    __finalize_[spec|body]
2162
2163         Add_Str_To_Name_Buffer ("__finalize_");
2164
2165         if For_Spec then
2166            Add_Str_To_Name_Buffer ("spec");
2167         else
2168            Add_Str_To_Name_Buffer ("body");
2169         end if;
2170
2171         return Name_Find;
2172      end New_Finalizer_Name;
2173
2174      --------------------------
2175      -- Process_Declarations --
2176      --------------------------
2177
2178      procedure Process_Declarations
2179        (Decls      : List_Id;
2180         Preprocess : Boolean := False;
2181         Top_Level  : Boolean := False)
2182      is
2183         Decl    : Node_Id;
2184         Expr    : Node_Id;
2185         Obj_Id  : Entity_Id;
2186         Obj_Typ : Entity_Id;
2187         Pack_Id : Entity_Id;
2188         Spec    : Node_Id;
2189         Typ     : Entity_Id;
2190
2191         Old_Counter_Val : Nat;
2192         --  This variable is used to determine whether a nested package or
2193         --  instance contains at least one controlled object.
2194
2195         procedure Processing_Actions
2196           (Has_No_Init  : Boolean := False;
2197            Is_Protected : Boolean := False);
2198         --  Depending on the mode of operation of Process_Declarations, either
2199         --  increment the controlled object counter, set the controlled object
2200         --  flag and store the last top level construct or process the current
2201         --  declaration. Flag Has_No_Init is used to propagate scenarios where
2202         --  the current declaration may not have initialization proc(s). Flag
2203         --  Is_Protected should be set when the current declaration denotes a
2204         --  simple protected object.
2205
2206         ------------------------
2207         -- Processing_Actions --
2208         ------------------------
2209
2210         procedure Processing_Actions
2211           (Has_No_Init  : Boolean := False;
2212            Is_Protected : Boolean := False)
2213         is
2214         begin
2215            --  Library-level tagged type
2216
2217            if Nkind (Decl) = N_Full_Type_Declaration then
2218               if Preprocess then
2219                  Has_Tagged_Types := True;
2220
2221                  if Top_Level and then No (Last_Top_Level_Ctrl_Construct) then
2222                     Last_Top_Level_Ctrl_Construct := Decl;
2223                  end if;
2224
2225               else
2226                  Process_Tagged_Type_Declaration (Decl);
2227               end if;
2228
2229            --  Controlled object declaration
2230
2231            else
2232               if Preprocess then
2233                  Counter_Val   := Counter_Val + 1;
2234                  Has_Ctrl_Objs := True;
2235
2236                  if Top_Level and then No (Last_Top_Level_Ctrl_Construct) then
2237                     Last_Top_Level_Ctrl_Construct := Decl;
2238                  end if;
2239
2240               else
2241                  Process_Object_Declaration (Decl, Has_No_Init, Is_Protected);
2242               end if;
2243            end if;
2244         end Processing_Actions;
2245
2246      --  Start of processing for Process_Declarations
2247
2248      begin
2249         if No (Decls) or else Is_Empty_List (Decls) then
2250            return;
2251         end if;
2252
2253         --  Process all declarations in reverse order
2254
2255         Decl := Last_Non_Pragma (Decls);
2256         while Present (Decl) loop
2257            --  Depending on the value of flag Finalize_Old_Only we determine
2258            --  which objects get finalized as part of the current finalizer
2259            --  being built.
2260
2261            --  When True, only temporaries capturing the value of attribute
2262            --  'Old are finalized and all other cases are ignored.
2263
2264            --  When False, temporary objects used to capture the value of 'Old
2265            --  are ignored and all others are considered.
2266
2267            if Finalize_Old_Only
2268                 xor (Nkind (Decl) = N_Object_Declaration
2269                       and then Stores_Attribute_Old_Prefix
2270                                  (Defining_Identifier (Decl)))
2271            then
2272               null;
2273
2274            --  Library-level tagged types
2275
2276            elsif Nkind (Decl) = N_Full_Type_Declaration then
2277               Typ := Defining_Identifier (Decl);
2278
2279               --  Ignored Ghost types do not need any cleanup actions because
2280               --  they will not appear in the final tree.
2281
2282               if Is_Ignored_Ghost_Entity (Typ) then
2283                  null;
2284
2285               elsif Is_Tagged_Type (Typ)
2286                 and then Is_Library_Level_Entity (Typ)
2287                 and then Convention (Typ) = Convention_Ada
2288                 and then Present (Access_Disp_Table (Typ))
2289                 and then RTE_Available (RE_Register_Tag)
2290                 and then not Is_Abstract_Type (Typ)
2291                 and then not No_Run_Time_Mode
2292               then
2293                  Processing_Actions;
2294               end if;
2295
2296            --  Regular object declarations
2297
2298            elsif Nkind (Decl) = N_Object_Declaration then
2299               Obj_Id  := Defining_Identifier (Decl);
2300               Obj_Typ := Base_Type (Etype (Obj_Id));
2301               Expr    := Expression (Decl);
2302
2303               --  Bypass any form of processing for objects which have their
2304               --  finalization disabled. This applies only to objects at the
2305               --  library level.
2306
2307               if For_Package and then Finalize_Storage_Only (Obj_Typ) then
2308                  null;
2309
2310               --  Finalization of transient objects are treated separately in
2311               --  order to handle sensitive cases. These include:
2312
2313               --    * Aggregate expansion
2314               --    * If, case, and expression with actions expansion
2315               --    * Transient scopes
2316
2317               --  If one of those contexts has marked the transient object as
2318               --  ignored, do not generate finalization actions for it.
2319
2320               elsif Is_Finalized_Transient (Obj_Id)
2321                 or else Is_Ignored_Transient (Obj_Id)
2322               then
2323                  null;
2324
2325               --  Ignored Ghost objects do not need any cleanup actions
2326               --  because they will not appear in the final tree.
2327
2328               elsif Is_Ignored_Ghost_Entity (Obj_Id) then
2329                  null;
2330
2331               --  The object is of the form:
2332               --    Obj : [constant] Typ [:= Expr];
2333
2334               --  Do not process tag-to-class-wide conversions because they do
2335               --  not yield an object. Do not process the incomplete view of a
2336               --  deferred constant. Note that an object initialized by means
2337               --  of a build-in-place function call may appear as a deferred
2338               --  constant after expansion activities. These kinds of objects
2339               --  must be finalized.
2340
2341               elsif not Is_Imported (Obj_Id)
2342                 and then Needs_Finalization (Obj_Typ)
2343                 and then not Is_Tag_To_Class_Wide_Conversion (Obj_Id)
2344                 and then not (Ekind (Obj_Id) = E_Constant
2345                                and then not Has_Completion (Obj_Id)
2346                                and then No (BIP_Initialization_Call (Obj_Id)))
2347               then
2348                  Processing_Actions;
2349
2350               --  The object is of the form:
2351               --    Obj : Access_Typ := Non_BIP_Function_Call'reference;
2352
2353               --    Obj : Access_Typ :=
2354               --            BIP_Function_Call (BIPalloc => 2, ...)'reference;
2355
2356               elsif Is_Access_Type (Obj_Typ)
2357                 and then Needs_Finalization
2358                            (Available_View (Designated_Type (Obj_Typ)))
2359                 and then Present (Expr)
2360                 and then
2361                   (Is_Secondary_Stack_BIP_Func_Call (Expr)
2362                     or else
2363                       (Is_Non_BIP_Func_Call (Expr)
2364                         and then not Is_Related_To_Func_Return (Obj_Id)))
2365               then
2366                  Processing_Actions (Has_No_Init => True);
2367
2368               --  Processing for "hook" objects generated for transient
2369               --  objects declared inside an Expression_With_Actions.
2370
2371               elsif Is_Access_Type (Obj_Typ)
2372                 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
2373                 and then Nkind (Status_Flag_Or_Transient_Decl (Obj_Id)) =
2374                                                       N_Object_Declaration
2375               then
2376                  Processing_Actions (Has_No_Init => True);
2377
2378               --  Process intermediate results of an if expression with one
2379               --  of the alternatives using a controlled function call.
2380
2381               elsif Is_Access_Type (Obj_Typ)
2382                 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
2383                 and then Nkind (Status_Flag_Or_Transient_Decl (Obj_Id)) =
2384                                                       N_Defining_Identifier
2385                 and then Present (Expr)
2386                 and then Nkind (Expr) = N_Null
2387               then
2388                  Processing_Actions (Has_No_Init => True);
2389
2390               --  Simple protected objects which use type System.Tasking.
2391               --  Protected_Objects.Protection to manage their locks should
2392               --  be treated as controlled since they require manual cleanup.
2393               --  The only exception is illustrated in the following example:
2394
2395               --     package Pkg is
2396               --        type Ctrl is new Controlled ...
2397               --        procedure Finalize (Obj : in out Ctrl);
2398               --        Lib_Obj : Ctrl;
2399               --     end Pkg;
2400
2401               --     package body Pkg is
2402               --        protected Prot is
2403               --           procedure Do_Something (Obj : in out Ctrl);
2404               --        end Prot;
2405
2406               --        protected body Prot is
2407               --           procedure Do_Something (Obj : in out Ctrl) is ...
2408               --        end Prot;
2409
2410               --        procedure Finalize (Obj : in out Ctrl) is
2411               --        begin
2412               --           Prot.Do_Something (Obj);
2413               --        end Finalize;
2414               --     end Pkg;
2415
2416               --  Since for the most part entities in package bodies depend on
2417               --  those in package specs, Prot's lock should be cleaned up
2418               --  first. The subsequent cleanup of the spec finalizes Lib_Obj.
2419               --  This act however attempts to invoke Do_Something and fails
2420               --  because the lock has disappeared.
2421
2422               elsif Ekind (Obj_Id) = E_Variable
2423                 and then not In_Library_Level_Package_Body (Obj_Id)
2424                 and then (Is_Simple_Protected_Type (Obj_Typ)
2425                            or else Has_Simple_Protected_Object (Obj_Typ))
2426               then
2427                  Processing_Actions (Is_Protected => True);
2428               end if;
2429
2430            --  Specific cases of object renamings
2431
2432            elsif Nkind (Decl) = N_Object_Renaming_Declaration then
2433               Obj_Id  := Defining_Identifier (Decl);
2434               Obj_Typ := Base_Type (Etype (Obj_Id));
2435
2436               --  Bypass any form of processing for objects which have their
2437               --  finalization disabled. This applies only to objects at the
2438               --  library level.
2439
2440               if For_Package and then Finalize_Storage_Only (Obj_Typ) then
2441                  null;
2442
2443               --  Ignored Ghost object renamings do not need any cleanup
2444               --  actions because they will not appear in the final tree.
2445
2446               elsif Is_Ignored_Ghost_Entity (Obj_Id) then
2447                  null;
2448
2449               --  Return object of a build-in-place function. This case is
2450               --  recognized and marked by the expansion of an extended return
2451               --  statement (see Expand_N_Extended_Return_Statement).
2452
2453               elsif Needs_Finalization (Obj_Typ)
2454                 and then Is_Return_Object (Obj_Id)
2455                 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
2456               then
2457                  Processing_Actions (Has_No_Init => True);
2458
2459               --  Detect a case where a source object has been initialized by
2460               --  a controlled function call or another object which was later
2461               --  rewritten as a class-wide conversion of Ada.Tags.Displace.
2462
2463               --     Obj1 : CW_Type := Src_Obj;
2464               --     Obj2 : CW_Type := Function_Call (...);
2465
2466               --     Obj1 : CW_Type renames (... Ada.Tags.Displace (Src_Obj));
2467               --     Tmp  : ... := Function_Call (...)'reference;
2468               --     Obj2 : CW_Type renames (... Ada.Tags.Displace (Tmp));
2469
2470               elsif Is_Displacement_Of_Object_Or_Function_Result (Obj_Id) then
2471                  Processing_Actions (Has_No_Init => True);
2472               end if;
2473
2474            --  Inspect the freeze node of an access-to-controlled type and
2475            --  look for a delayed finalization master. This case arises when
2476            --  the freeze actions are inserted at a later time than the
2477            --  expansion of the context. Since Build_Finalizer is never called
2478            --  on a single construct twice, the master will be ultimately
2479            --  left out and never finalized. This is also needed for freeze
2480            --  actions of designated types themselves, since in some cases the
2481            --  finalization master is associated with a designated type's
2482            --  freeze node rather than that of the access type (see handling
2483            --  for freeze actions in Build_Finalization_Master).
2484
2485            elsif Nkind (Decl) = N_Freeze_Entity
2486              and then Present (Actions (Decl))
2487            then
2488               Typ := Entity (Decl);
2489
2490               --  Freeze nodes for ignored Ghost types do not need cleanup
2491               --  actions because they will never appear in the final tree.
2492
2493               if Is_Ignored_Ghost_Entity (Typ) then
2494                  null;
2495
2496               elsif (Is_Access_Object_Type (Typ)
2497                        and then Needs_Finalization
2498                                   (Available_View (Designated_Type (Typ))))
2499                      or else (Is_Type (Typ) and then Needs_Finalization (Typ))
2500               then
2501                  Old_Counter_Val := Counter_Val;
2502
2503                  --  Freeze nodes are considered to be identical to packages
2504                  --  and blocks in terms of nesting. The difference is that
2505                  --  a finalization master created inside the freeze node is
2506                  --  at the same nesting level as the node itself.
2507
2508                  Process_Declarations (Actions (Decl), Preprocess);
2509
2510                  --  The freeze node contains a finalization master
2511
2512                  if Preprocess
2513                    and then Top_Level
2514                    and then No (Last_Top_Level_Ctrl_Construct)
2515                    and then Counter_Val > Old_Counter_Val
2516                  then
2517                     Last_Top_Level_Ctrl_Construct := Decl;
2518                  end if;
2519               end if;
2520
2521            --  Nested package declarations, avoid generics
2522
2523            elsif Nkind (Decl) = N_Package_Declaration then
2524               Pack_Id := Defining_Entity (Decl);
2525               Spec    := Specification   (Decl);
2526
2527               --  Do not inspect an ignored Ghost package because all code
2528               --  found within will not appear in the final tree.
2529
2530               if Is_Ignored_Ghost_Entity (Pack_Id) then
2531                  null;
2532
2533               elsif Ekind (Pack_Id) /= E_Generic_Package then
2534                  Old_Counter_Val := Counter_Val;
2535                  Process_Declarations
2536                    (Private_Declarations (Spec), Preprocess);
2537                  Process_Declarations
2538                    (Visible_Declarations (Spec), Preprocess);
2539
2540                  --  Either the visible or the private declarations contain a
2541                  --  controlled object. The nested package declaration is the
2542                  --  last such construct.
2543
2544                  if Preprocess
2545                    and then Top_Level
2546                    and then No (Last_Top_Level_Ctrl_Construct)
2547                    and then Counter_Val > Old_Counter_Val
2548                  then
2549                     Last_Top_Level_Ctrl_Construct := Decl;
2550                  end if;
2551               end if;
2552
2553               --  Call the xxx__finalize_body procedure of a library level
2554               --  package instantiation if the body contains finalization
2555               --  statements.
2556
2557               if Present (Generic_Parent (Spec))
2558                 and then Is_Library_Level_Entity (Pack_Id)
2559                 and then Present (Body_Entity (Generic_Parent (Spec)))
2560               then
2561                  if Preprocess then
2562                     declare
2563                        P : Node_Id;
2564                     begin
2565                        P := Parent (Body_Entity (Generic_Parent (Spec)));
2566                        while Present (P)
2567                          and then Nkind (P) /= N_Package_Body
2568                        loop
2569                           P := Parent (P);
2570                        end loop;
2571
2572                        if Present (P) then
2573                           Old_Counter_Val := Counter_Val;
2574                           Process_Declarations (Declarations (P), Preprocess);
2575
2576                           --  Note that we are processing the generic body
2577                           --  template and not the actually instantiation
2578                           --  (which is generated too late for us to process
2579                           --  it), so there is no need to update in particular
2580                           --  to update Last_Top_Level_Ctrl_Construct here.
2581
2582                           if Counter_Val > Old_Counter_Val then
2583                              Counter_Val := Old_Counter_Val;
2584                              Set_Has_Controlled_Component (Pack_Id);
2585                           end if;
2586                        end if;
2587                     end;
2588
2589                  elsif Has_Controlled_Component (Pack_Id) then
2590
2591                     --  We import the xxx__finalize_body routine since the
2592                     --  generic body will be instantiated later.
2593
2594                     declare
2595                        Id : constant Node_Id :=
2596                          Make_Defining_Identifier (Loc,
2597                            New_Finalizer_Name (Defining_Unit_Name (Spec),
2598                              For_Spec => False));
2599
2600                     begin
2601                        Set_Has_Qualified_Name       (Id);
2602                        Set_Has_Fully_Qualified_Name (Id);
2603                        Set_Is_Imported              (Id);
2604                        Set_Has_Completion           (Id);
2605                        Set_Interface_Name (Id,
2606                          Make_String_Literal (Loc,
2607                            Strval => Get_Name_String (Chars (Id))));
2608
2609                        Append_New_To (Finalizer_Stmts,
2610                          Make_Subprogram_Declaration (Loc,
2611                            Make_Procedure_Specification (Loc,
2612                              Defining_Unit_Name => Id)));
2613                        Append_To (Finalizer_Stmts,
2614                          Make_Procedure_Call_Statement (Loc,
2615                            Name => New_Occurrence_Of (Id, Loc)));
2616                     end;
2617                  end if;
2618               end if;
2619
2620            --  Nested package bodies, avoid generics
2621
2622            elsif Nkind (Decl) = N_Package_Body then
2623
2624               --  Do not inspect an ignored Ghost package body because all
2625               --  code found within will not appear in the final tree.
2626
2627               if Is_Ignored_Ghost_Entity (Defining_Entity (Decl)) then
2628                  null;
2629
2630               elsif Ekind (Corresponding_Spec (Decl)) /= E_Generic_Package
2631               then
2632                  Old_Counter_Val := Counter_Val;
2633                  Process_Declarations (Declarations (Decl), Preprocess);
2634
2635                  --  The nested package body is the last construct to contain
2636                  --  a controlled object.
2637
2638                  if Preprocess
2639                    and then Top_Level
2640                    and then No (Last_Top_Level_Ctrl_Construct)
2641                    and then Counter_Val > Old_Counter_Val
2642                  then
2643                     Last_Top_Level_Ctrl_Construct := Decl;
2644                  end if;
2645               end if;
2646
2647            --  Handle a rare case caused by a controlled transient object
2648            --  created as part of a record init proc. The variable is wrapped
2649            --  in a block, but the block is not associated with a transient
2650            --  scope.
2651
2652            elsif Nkind (Decl) = N_Block_Statement
2653              and then Inside_Init_Proc
2654            then
2655               Old_Counter_Val := Counter_Val;
2656
2657               if Present (Handled_Statement_Sequence (Decl)) then
2658                  Process_Declarations
2659                    (Statements (Handled_Statement_Sequence (Decl)),
2660                     Preprocess);
2661               end if;
2662
2663               Process_Declarations (Declarations (Decl), Preprocess);
2664
2665               --  Either the declaration or statement list of the block has a
2666               --  controlled object.
2667
2668               if Preprocess
2669                 and then Top_Level
2670                 and then No (Last_Top_Level_Ctrl_Construct)
2671                 and then Counter_Val > Old_Counter_Val
2672               then
2673                  Last_Top_Level_Ctrl_Construct := Decl;
2674               end if;
2675
2676            --  Handle the case where the original context has been wrapped in
2677            --  a block to avoid interference between exception handlers and
2678            --  At_End handlers. Treat the block as transparent and process its
2679            --  contents.
2680
2681            elsif Nkind (Decl) = N_Block_Statement
2682              and then Is_Finalization_Wrapper (Decl)
2683            then
2684               if Present (Handled_Statement_Sequence (Decl)) then
2685                  Process_Declarations
2686                    (Statements (Handled_Statement_Sequence (Decl)),
2687                     Preprocess);
2688               end if;
2689
2690               Process_Declarations (Declarations (Decl), Preprocess);
2691            end if;
2692
2693            Prev_Non_Pragma (Decl);
2694         end loop;
2695      end Process_Declarations;
2696
2697      --------------------------------
2698      -- Process_Object_Declaration --
2699      --------------------------------
2700
2701      procedure Process_Object_Declaration
2702        (Decl         : Node_Id;
2703         Has_No_Init  : Boolean := False;
2704         Is_Protected : Boolean := False)
2705      is
2706         Loc    : constant Source_Ptr := Sloc (Decl);
2707         Obj_Id : constant Entity_Id := Defining_Identifier (Decl);
2708
2709         Init_Typ : Entity_Id;
2710         --  The initialization type of the related object declaration. Note
2711         --  that this is not necessarily the same type as Obj_Typ because of
2712         --  possible type derivations.
2713
2714         Obj_Typ : Entity_Id;
2715         --  The type of the related object declaration
2716
2717         function Build_BIP_Cleanup_Stmts (Func_Id : Entity_Id) return Node_Id;
2718         --  Func_Id denotes a build-in-place function. Generate the following
2719         --  cleanup code:
2720         --
2721         --    if BIPallocfrom > Secondary_Stack'Pos
2722         --      and then BIPfinalizationmaster /= null
2723         --    then
2724         --       declare
2725         --          type Ptr_Typ is access Obj_Typ;
2726         --          for Ptr_Typ'Storage_Pool
2727         --            use Base_Pool (BIPfinalizationmaster);
2728         --       begin
2729         --          Free (Ptr_Typ (Temp));
2730         --       end;
2731         --    end if;
2732         --
2733         --  Obj_Typ is the type of the current object, Temp is the original
2734         --  allocation which Obj_Id renames.
2735
2736         procedure Find_Last_Init
2737           (Last_Init   : out Node_Id;
2738            Body_Insert : out Node_Id);
2739         --  Find the last initialization call related to object declaration
2740         --  Decl. Last_Init denotes the last initialization call which follows
2741         --  Decl. Body_Insert denotes a node where the finalizer body could be
2742         --  potentially inserted after (if blocks are involved).
2743
2744         -----------------------------
2745         -- Build_BIP_Cleanup_Stmts --
2746         -----------------------------
2747
2748         function Build_BIP_Cleanup_Stmts
2749           (Func_Id : Entity_Id) return Node_Id
2750         is
2751            Decls      : constant List_Id := New_List;
2752            Fin_Mas_Id : constant Entity_Id :=
2753                           Build_In_Place_Formal
2754                             (Func_Id, BIP_Finalization_Master);
2755            Func_Typ   : constant Entity_Id := Etype (Func_Id);
2756            Temp_Id    : constant Entity_Id :=
2757                           Entity (Prefix (Name (Parent (Obj_Id))));
2758
2759            Cond      : Node_Id;
2760            Free_Blk  : Node_Id;
2761            Free_Stmt : Node_Id;
2762            Pool_Id   : Entity_Id;
2763            Ptr_Typ   : Entity_Id;
2764
2765         begin
2766            --  Generate:
2767            --    Pool_Id renames Base_Pool (BIPfinalizationmaster.all).all;
2768
2769            Pool_Id := Make_Temporary (Loc, 'P');
2770
2771            Append_To (Decls,
2772              Make_Object_Renaming_Declaration (Loc,
2773                Defining_Identifier => Pool_Id,
2774                Subtype_Mark        =>
2775                  New_Occurrence_Of (RTE (RE_Root_Storage_Pool), Loc),
2776                Name                =>
2777                  Make_Explicit_Dereference (Loc,
2778                    Prefix =>
2779                      Make_Function_Call (Loc,
2780                        Name                   =>
2781                          New_Occurrence_Of (RTE (RE_Base_Pool), Loc),
2782                        Parameter_Associations => New_List (
2783                          Make_Explicit_Dereference (Loc,
2784                            Prefix =>
2785                              New_Occurrence_Of (Fin_Mas_Id, Loc)))))));
2786
2787            --  Create an access type which uses the storage pool of the
2788            --  caller's finalization master.
2789
2790            --  Generate:
2791            --    type Ptr_Typ is access Func_Typ;
2792
2793            Ptr_Typ := Make_Temporary (Loc, 'P');
2794
2795            Append_To (Decls,
2796              Make_Full_Type_Declaration (Loc,
2797                Defining_Identifier => Ptr_Typ,
2798                Type_Definition     =>
2799                  Make_Access_To_Object_Definition (Loc,
2800                    Subtype_Indication => New_Occurrence_Of (Func_Typ, Loc))));
2801
2802            --  Perform minor decoration in order to set the master and the
2803            --  storage pool attributes.
2804
2805            Mutate_Ekind (Ptr_Typ, E_Access_Type);
2806            Set_Finalization_Master     (Ptr_Typ, Fin_Mas_Id);
2807            Set_Associated_Storage_Pool (Ptr_Typ, Pool_Id);
2808
2809            if Debug_Generated_Code then
2810               Set_Debug_Info_Needed (Pool_Id);
2811            end if;
2812
2813            --  Create an explicit free statement. Note that the free uses the
2814            --  caller's pool expressed as a renaming.
2815
2816            Free_Stmt :=
2817              Make_Free_Statement (Loc,
2818                Expression =>
2819                  Unchecked_Convert_To (Ptr_Typ,
2820                    New_Occurrence_Of (Temp_Id, Loc)));
2821
2822            Set_Storage_Pool (Free_Stmt, Pool_Id);
2823
2824            --  Create a block to house the dummy type and the instantiation as
2825            --  well as to perform the cleanup the temporary.
2826
2827            --  Generate:
2828            --    declare
2829            --       <Decls>
2830            --    begin
2831            --       Free (Ptr_Typ (Temp_Id));
2832            --    end;
2833
2834            Free_Blk :=
2835              Make_Block_Statement (Loc,
2836                Declarations               => Decls,
2837                Handled_Statement_Sequence =>
2838                  Make_Handled_Sequence_Of_Statements (Loc,
2839                    Statements => New_List (Free_Stmt)));
2840
2841            --  Generate:
2842            --    if BIPfinalizationmaster /= null then
2843
2844            Cond :=
2845              Make_Op_Ne (Loc,
2846                Left_Opnd  => New_Occurrence_Of (Fin_Mas_Id, Loc),
2847                Right_Opnd => Make_Null (Loc));
2848
2849            --  For constrained or tagged results escalate the condition to
2850            --  include the allocation format. Generate:
2851
2852            --    if BIPallocform > Secondary_Stack'Pos
2853            --      and then BIPfinalizationmaster /= null
2854            --    then
2855
2856            if not Is_Constrained (Func_Typ)
2857              or else Is_Tagged_Type (Func_Typ)
2858            then
2859               declare
2860                  Alloc : constant Entity_Id :=
2861                            Build_In_Place_Formal (Func_Id, BIP_Alloc_Form);
2862               begin
2863                  Cond :=
2864                    Make_And_Then (Loc,
2865                      Left_Opnd  =>
2866                        Make_Op_Gt (Loc,
2867                          Left_Opnd  => New_Occurrence_Of (Alloc, Loc),
2868                          Right_Opnd =>
2869                            Make_Integer_Literal (Loc,
2870                              UI_From_Int
2871                                (BIP_Allocation_Form'Pos (Secondary_Stack)))),
2872
2873                      Right_Opnd => Cond);
2874               end;
2875            end if;
2876
2877            --  Generate:
2878            --    if <Cond> then
2879            --       <Free_Blk>
2880            --    end if;
2881
2882            return
2883              Make_If_Statement (Loc,
2884                Condition       => Cond,
2885                Then_Statements => New_List (Free_Blk));
2886         end Build_BIP_Cleanup_Stmts;
2887
2888         --------------------
2889         -- Find_Last_Init --
2890         --------------------
2891
2892         procedure Find_Last_Init
2893           (Last_Init   : out Node_Id;
2894            Body_Insert : out Node_Id)
2895         is
2896            function Find_Last_Init_In_Block (Blk : Node_Id) return Node_Id;
2897            --  Find the last initialization call within the statements of
2898            --  block Blk.
2899
2900            function Is_Init_Call (N : Node_Id) return Boolean;
2901            --  Determine whether node N denotes one of the initialization
2902            --  procedures of types Init_Typ or Obj_Typ.
2903
2904            function Next_Suitable_Statement (Stmt : Node_Id) return Node_Id;
2905            --  Obtain the next statement which follows list member Stmt while
2906            --  ignoring artifacts related to access-before-elaboration checks.
2907
2908            -----------------------------
2909            -- Find_Last_Init_In_Block --
2910            -----------------------------
2911
2912            function Find_Last_Init_In_Block (Blk : Node_Id) return Node_Id is
2913               HSS  : constant Node_Id := Handled_Statement_Sequence (Blk);
2914               Stmt : Node_Id;
2915
2916            begin
2917               --  Examine the individual statements of the block in reverse to
2918               --  locate the last initialization call.
2919
2920               if Present (HSS) and then Present (Statements (HSS)) then
2921                  Stmt := Last (Statements (HSS));
2922                  while Present (Stmt) loop
2923
2924                     --  Peek inside nested blocks in case aborts are allowed
2925
2926                     if Nkind (Stmt) = N_Block_Statement then
2927                        return Find_Last_Init_In_Block (Stmt);
2928
2929                     elsif Is_Init_Call (Stmt) then
2930                        return Stmt;
2931                     end if;
2932
2933                     Prev (Stmt);
2934                  end loop;
2935               end if;
2936
2937               return Empty;
2938            end Find_Last_Init_In_Block;
2939
2940            ------------------
2941            -- Is_Init_Call --
2942            ------------------
2943
2944            function Is_Init_Call (N : Node_Id) return Boolean is
2945               function Is_Init_Proc_Of
2946                 (Subp_Id : Entity_Id;
2947                  Typ     : Entity_Id) return Boolean;
2948               --  Determine whether subprogram Subp_Id is a valid init proc of
2949               --  type Typ.
2950
2951               ---------------------
2952               -- Is_Init_Proc_Of --
2953               ---------------------
2954
2955               function Is_Init_Proc_Of
2956                 (Subp_Id : Entity_Id;
2957                  Typ     : Entity_Id) return Boolean
2958               is
2959                  Deep_Init : Entity_Id := Empty;
2960                  Prim_Init : Entity_Id := Empty;
2961                  Type_Init : Entity_Id := Empty;
2962
2963               begin
2964                  --  Obtain all possible initialization routines of the
2965                  --  related type and try to match the subprogram entity
2966                  --  against one of them.
2967
2968                  --  Deep_Initialize
2969
2970                  Deep_Init := TSS (Typ, TSS_Deep_Initialize);
2971
2972                  --  Primitive Initialize
2973
2974                  if Is_Controlled (Typ) then
2975                     Prim_Init := Find_Optional_Prim_Op (Typ, Name_Initialize);
2976
2977                     if Present (Prim_Init) then
2978                        Prim_Init := Ultimate_Alias (Prim_Init);
2979                     end if;
2980                  end if;
2981
2982                  --  Type initialization routine
2983
2984                  if Has_Non_Null_Base_Init_Proc (Typ) then
2985                     Type_Init := Base_Init_Proc (Typ);
2986                  end if;
2987
2988                  return
2989                    (Present (Deep_Init) and then Subp_Id = Deep_Init)
2990                      or else
2991                    (Present (Prim_Init) and then Subp_Id = Prim_Init)
2992                      or else
2993                    (Present (Type_Init) and then Subp_Id = Type_Init);
2994               end Is_Init_Proc_Of;
2995
2996               --  Local variables
2997
2998               Call_Id : Entity_Id;
2999
3000            --  Start of processing for Is_Init_Call
3001
3002            begin
3003               if Nkind (N) = N_Procedure_Call_Statement
3004                 and then Nkind (Name (N)) = N_Identifier
3005               then
3006                  Call_Id := Entity (Name (N));
3007
3008                  --  Consider both the type of the object declaration and its
3009                  --  related initialization type.
3010
3011                  return
3012                    Is_Init_Proc_Of (Call_Id, Init_Typ)
3013                      or else
3014                    Is_Init_Proc_Of (Call_Id, Obj_Typ);
3015               end if;
3016
3017               return False;
3018            end Is_Init_Call;
3019
3020            -----------------------------
3021            -- Next_Suitable_Statement --
3022            -----------------------------
3023
3024            function Next_Suitable_Statement (Stmt : Node_Id) return Node_Id is
3025               Result : Node_Id;
3026
3027            begin
3028               --  Skip call markers and Program_Error raises installed by the
3029               --  ABE mechanism.
3030
3031               Result := Next (Stmt);
3032               while Present (Result) loop
3033                  exit when Nkind (Result) not in
3034                              N_Call_Marker | N_Raise_Program_Error;
3035
3036                  Next (Result);
3037               end loop;
3038
3039               return Result;
3040            end Next_Suitable_Statement;
3041
3042            --  Local variables
3043
3044            Call   : Node_Id;
3045            Stmt   : Node_Id;
3046            Stmt_2 : Node_Id;
3047
3048            Deep_Init_Found : Boolean := False;
3049            --  A flag set when a call to [Deep_]Initialize has been found
3050
3051         --  Start of processing for Find_Last_Init
3052
3053         begin
3054            Last_Init   := Decl;
3055            Body_Insert := Empty;
3056
3057            --  Object renamings and objects associated with controlled
3058            --  function results do not require initialization.
3059
3060            if Has_No_Init then
3061               return;
3062            end if;
3063
3064            Stmt := Next_Suitable_Statement (Decl);
3065
3066            --  For an object with suppressed initialization, we check whether
3067            --  there is in fact no initialization expression. If there is not,
3068            --  then this is an object declaration that has been turned into a
3069            --  different object declaration that calls the build-in-place
3070            --  function in a 'Reference attribute, as in "F(...)'Reference".
3071            --  We search for that later object declaration, so that the
3072            --  Inc_Decl will be inserted after the call. Otherwise, if the
3073            --  call raises an exception, we will finalize the (uninitialized)
3074            --  object, which is wrong.
3075
3076            if No_Initialization (Decl) then
3077               if No (Expression (Last_Init)) then
3078                  loop
3079                     Next (Last_Init);
3080                     exit when No (Last_Init);
3081                     exit when Nkind (Last_Init) = N_Object_Declaration
3082                       and then Nkind (Expression (Last_Init)) = N_Reference
3083                       and then Nkind (Prefix (Expression (Last_Init))) =
3084                                  N_Function_Call
3085                       and then Is_Expanded_Build_In_Place_Call
3086                                  (Prefix (Expression (Last_Init)));
3087                  end loop;
3088               end if;
3089
3090               return;
3091
3092            --  In all other cases the initialization calls follow the related
3093            --  object. The general structure of object initialization built by
3094            --  routine Default_Initialize_Object is as follows:
3095
3096            --   [begin                                --  aborts allowed
3097            --       Abort_Defer;]
3098            --       Type_Init_Proc (Obj);
3099            --      [begin]                            --  exceptions allowed
3100            --          Deep_Initialize (Obj);
3101            --      [exception                         --  exceptions allowed
3102            --          when others =>
3103            --             Deep_Finalize (Obj, Self => False);
3104            --             raise;
3105            --       end;]
3106            --   [at end                               --  aborts allowed
3107            --       Abort_Undefer;
3108            --    end;]
3109
3110            --  When aborts are allowed, the initialization calls are housed
3111            --  within a block.
3112
3113            elsif Nkind (Stmt) = N_Block_Statement then
3114               Last_Init   := Find_Last_Init_In_Block (Stmt);
3115               Body_Insert := Stmt;
3116
3117            --  Otherwise the initialization calls follow the related object
3118
3119            else
3120               pragma Assert (Present (Stmt));
3121
3122               Stmt_2 := Next_Suitable_Statement (Stmt);
3123
3124               --  Check for an optional call to Deep_Initialize which may
3125               --  appear within a block depending on whether the object has
3126               --  controlled components.
3127
3128               if Present (Stmt_2) then
3129                  if Nkind (Stmt_2) = N_Block_Statement then
3130                     Call := Find_Last_Init_In_Block (Stmt_2);
3131
3132                     if Present (Call) then
3133                        Deep_Init_Found := True;
3134                        Last_Init       := Call;
3135                        Body_Insert     := Stmt_2;
3136                     end if;
3137
3138                  elsif Is_Init_Call (Stmt_2) then
3139                     Deep_Init_Found := True;
3140                     Last_Init       := Stmt_2;
3141                     Body_Insert     := Last_Init;
3142                  end if;
3143               end if;
3144
3145               --  If the object lacks a call to Deep_Initialize, then it must
3146               --  have a call to its related type init proc.
3147
3148               if not Deep_Init_Found and then Is_Init_Call (Stmt) then
3149                  Last_Init   := Stmt;
3150                  Body_Insert := Last_Init;
3151               end if;
3152            end if;
3153         end Find_Last_Init;
3154
3155         --  Local variables
3156
3157         Body_Ins  : Node_Id;
3158         Count_Ins : Node_Id;
3159         Fin_Call  : Node_Id;
3160         Fin_Stmts : List_Id := No_List;
3161         Inc_Decl  : Node_Id;
3162         Label     : Node_Id;
3163         Label_Id  : Entity_Id;
3164         Obj_Ref   : Node_Id;
3165
3166      --  Start of processing for Process_Object_Declaration
3167
3168      begin
3169         --  Handle the object type and the reference to the object
3170
3171         Obj_Ref := New_Occurrence_Of (Obj_Id, Loc);
3172         Obj_Typ := Base_Type (Etype (Obj_Id));
3173
3174         loop
3175            if Is_Access_Type (Obj_Typ) then
3176               Obj_Typ := Directly_Designated_Type (Obj_Typ);
3177               Obj_Ref := Make_Explicit_Dereference (Loc, Obj_Ref);
3178
3179            elsif Is_Concurrent_Type (Obj_Typ)
3180              and then Present (Corresponding_Record_Type (Obj_Typ))
3181            then
3182               Obj_Typ := Corresponding_Record_Type (Obj_Typ);
3183               Obj_Ref := Unchecked_Convert_To (Obj_Typ, Obj_Ref);
3184
3185            elsif Is_Private_Type (Obj_Typ)
3186              and then Present (Full_View (Obj_Typ))
3187            then
3188               Obj_Typ := Full_View (Obj_Typ);
3189               Obj_Ref := Unchecked_Convert_To (Obj_Typ, Obj_Ref);
3190
3191            elsif Obj_Typ /= Base_Type (Obj_Typ) then
3192               Obj_Typ := Base_Type (Obj_Typ);
3193               Obj_Ref := Unchecked_Convert_To (Obj_Typ, Obj_Ref);
3194
3195            else
3196               exit;
3197            end if;
3198         end loop;
3199
3200         Set_Etype (Obj_Ref, Obj_Typ);
3201
3202         --  Handle the initialization type of the object declaration
3203
3204         Init_Typ := Obj_Typ;
3205         loop
3206            if Is_Private_Type (Init_Typ)
3207              and then Present (Full_View (Init_Typ))
3208            then
3209               Init_Typ := Full_View (Init_Typ);
3210
3211            elsif Is_Untagged_Derivation (Init_Typ) then
3212               Init_Typ := Root_Type (Init_Typ);
3213
3214            else
3215               exit;
3216            end if;
3217         end loop;
3218
3219         --  Set a new value for the state counter and insert the statement
3220         --  after the object declaration. Generate:
3221
3222         --    Counter := <value>;
3223
3224         Inc_Decl :=
3225           Make_Assignment_Statement (Loc,
3226             Name       => New_Occurrence_Of (Counter_Id, Loc),
3227             Expression => Make_Integer_Literal (Loc, Counter_Val));
3228
3229         --  Insert the counter after all initialization has been done. The
3230         --  place of insertion depends on the context.
3231
3232         if Ekind (Obj_Id) in E_Constant | E_Variable then
3233
3234            --  The object is initialized by a build-in-place function call.
3235            --  The counter insertion point is after the function call.
3236
3237            if Present (BIP_Initialization_Call (Obj_Id)) then
3238               Count_Ins := BIP_Initialization_Call (Obj_Id);
3239               Body_Ins  := Empty;
3240
3241            --  The object is initialized by an aggregate. Insert the counter
3242            --  after the last aggregate assignment.
3243
3244            elsif Present (Last_Aggregate_Assignment (Obj_Id)) then
3245               Count_Ins := Last_Aggregate_Assignment (Obj_Id);
3246               Body_Ins  := Empty;
3247
3248            --  In all other cases the counter is inserted after the last call
3249            --  to either [Deep_]Initialize or the type-specific init proc.
3250
3251            else
3252               Find_Last_Init (Count_Ins, Body_Ins);
3253            end if;
3254
3255         --  In all other cases the counter is inserted after the last call to
3256         --  either [Deep_]Initialize or the type-specific init proc.
3257
3258         else
3259            Find_Last_Init (Count_Ins, Body_Ins);
3260         end if;
3261
3262         --  If the Initialize function is null or trivial, the call will have
3263         --  been replaced with a null statement, in which case place counter
3264         --  declaration after object declaration itself.
3265
3266         if No (Count_Ins) then
3267            Count_Ins := Decl;
3268         end if;
3269
3270         Insert_After (Count_Ins, Inc_Decl);
3271         Analyze (Inc_Decl);
3272
3273         --  If the current declaration is the last in the list, the finalizer
3274         --  body needs to be inserted after the set counter statement for the
3275         --  current object declaration. This is complicated by the fact that
3276         --  the set counter statement may appear in abort deferred block. In
3277         --  that case, the proper insertion place is after the block.
3278
3279         if No (Finalizer_Insert_Nod) then
3280
3281            --  Insertion after an abort deferred block
3282
3283            if Present (Body_Ins) then
3284               Finalizer_Insert_Nod := Body_Ins;
3285            else
3286               Finalizer_Insert_Nod := Inc_Decl;
3287            end if;
3288         end if;
3289
3290         --  Create the associated label with this object, generate:
3291
3292         --    L<counter> : label;
3293
3294         Label_Id :=
3295           Make_Identifier (Loc, New_External_Name ('L', Counter_Val));
3296         Set_Entity
3297           (Label_Id, Make_Defining_Identifier (Loc, Chars (Label_Id)));
3298         Label := Make_Label (Loc, Label_Id);
3299
3300         Prepend_To (Finalizer_Decls,
3301           Make_Implicit_Label_Declaration (Loc,
3302             Defining_Identifier => Entity (Label_Id),
3303             Label_Construct     => Label));
3304
3305         --  Create the associated jump with this object, generate:
3306
3307         --    when <counter> =>
3308         --       goto L<counter>;
3309
3310         Prepend_To (Jump_Alts,
3311           Make_Case_Statement_Alternative (Loc,
3312             Discrete_Choices => New_List (
3313               Make_Integer_Literal (Loc, Counter_Val)),
3314             Statements       => New_List (
3315               Make_Goto_Statement (Loc,
3316                 Name => New_Occurrence_Of (Entity (Label_Id), Loc)))));
3317
3318         --  Insert the jump destination, generate:
3319
3320         --     <<L<counter>>>
3321
3322         Append_To (Finalizer_Stmts, Label);
3323
3324         --  Disable warnings on Obj_Id. This works around an issue where GCC
3325         --  is not able to detect that Obj_Id is protected by a counter and
3326         --  emits spurious warnings.
3327
3328         if not Comes_From_Source (Obj_Id) then
3329            Set_Warnings_Off (Obj_Id);
3330         end if;
3331
3332         --  Processing for simple protected objects. Such objects require
3333         --  manual finalization of their lock managers.
3334
3335         if Is_Protected then
3336            if Is_Simple_Protected_Type (Obj_Typ) then
3337               Fin_Call := Cleanup_Protected_Object (Decl, Obj_Ref);
3338
3339               if Present (Fin_Call) then
3340                  Fin_Stmts := New_List (Fin_Call);
3341               end if;
3342
3343            elsif Has_Simple_Protected_Object (Obj_Typ) then
3344               if Is_Record_Type (Obj_Typ) then
3345                  Fin_Stmts := Cleanup_Record (Decl, Obj_Ref, Obj_Typ);
3346               elsif Is_Array_Type (Obj_Typ) then
3347                  Fin_Stmts := Cleanup_Array (Decl, Obj_Ref, Obj_Typ);
3348               end if;
3349            end if;
3350
3351            --  Generate:
3352            --    begin
3353            --       System.Tasking.Protected_Objects.Finalize_Protection
3354            --         (Obj._object);
3355
3356            --    exception
3357            --       when others =>
3358            --          null;
3359            --    end;
3360
3361            if Present (Fin_Stmts) and then Exceptions_OK then
3362               Fin_Stmts := New_List (
3363                 Make_Block_Statement (Loc,
3364                   Handled_Statement_Sequence =>
3365                     Make_Handled_Sequence_Of_Statements (Loc,
3366                       Statements         => Fin_Stmts,
3367
3368                       Exception_Handlers => New_List (
3369                         Make_Exception_Handler (Loc,
3370                           Exception_Choices => New_List (
3371                             Make_Others_Choice (Loc)),
3372
3373                           Statements     => New_List (
3374                             Make_Null_Statement (Loc)))))));
3375            end if;
3376
3377         --  Processing for regular controlled objects
3378
3379         else
3380            --  Generate:
3381            --    begin
3382            --       [Deep_]Finalize (Obj);
3383
3384            --    exception
3385            --       when Id : others =>
3386            --          if not Raised then
3387            --             Raised := True;
3388            --             Save_Occurrence (E, Id);
3389            --          end if;
3390            --    end;
3391
3392            Fin_Call :=
3393              Make_Final_Call (
3394                Obj_Ref => Obj_Ref,
3395                Typ     => Obj_Typ);
3396
3397            --  Guard against a missing [Deep_]Finalize when the object type
3398            --  was not properly frozen.
3399
3400            if No (Fin_Call) then
3401               Fin_Call := Make_Null_Statement (Loc);
3402            end if;
3403
3404            --  For CodePeer, the exception handlers normally generated here
3405            --  generate complex flowgraphs which result in capacity problems.
3406            --  Omitting these handlers for CodePeer is justified as follows:
3407
3408            --    If a handler is dead, then omitting it is surely ok
3409
3410            --    If a handler is live, then CodePeer should flag the
3411            --      potentially-exception-raising construct that causes it
3412            --      to be live. That is what we are interested in, not what
3413            --      happens after the exception is raised.
3414
3415            if Exceptions_OK and not CodePeer_Mode then
3416               Fin_Stmts := New_List (
3417                 Make_Block_Statement (Loc,
3418                   Handled_Statement_Sequence =>
3419                     Make_Handled_Sequence_Of_Statements (Loc,
3420                       Statements => New_List (Fin_Call),
3421
3422                    Exception_Handlers => New_List (
3423                      Build_Exception_Handler
3424                        (Finalizer_Data, For_Package)))));
3425
3426            --  When exception handlers are prohibited, the finalization call
3427            --  appears unprotected. Any exception raised during finalization
3428            --  will bypass the circuitry which ensures the cleanup of all
3429            --  remaining objects.
3430
3431            else
3432               Fin_Stmts := New_List (Fin_Call);
3433            end if;
3434
3435            --  If we are dealing with a return object of a build-in-place
3436            --  function, generate the following cleanup statements:
3437
3438            --    if BIPallocfrom > Secondary_Stack'Pos
3439            --      and then BIPfinalizationmaster /= null
3440            --    then
3441            --       declare
3442            --          type Ptr_Typ is access Obj_Typ;
3443            --          for Ptr_Typ'Storage_Pool use
3444            --                Base_Pool (BIPfinalizationmaster.all).all;
3445            --       begin
3446            --          Free (Ptr_Typ (Temp));
3447            --       end;
3448            --    end if;
3449
3450            --  The generated code effectively detaches the temporary from the
3451            --  caller finalization master and deallocates the object.
3452
3453            if Is_Return_Object (Obj_Id) then
3454               declare
3455                  Func_Id : constant Entity_Id := Enclosing_Function (Obj_Id);
3456               begin
3457                  if Is_Build_In_Place_Function (Func_Id)
3458                    and then Needs_BIP_Finalization_Master (Func_Id)
3459                  then
3460                     Append_To (Fin_Stmts, Build_BIP_Cleanup_Stmts (Func_Id));
3461                  end if;
3462               end;
3463            end if;
3464
3465            if Ekind (Obj_Id) in E_Constant | E_Variable
3466              and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
3467            then
3468               --  Temporaries created for the purpose of "exporting" a
3469               --  transient object out of an Expression_With_Actions (EWA)
3470               --  need guards. The following illustrates the usage of such
3471               --  temporaries.
3472
3473               --    Access_Typ : access [all] Obj_Typ;
3474               --    Temp       : Access_Typ := null;
3475               --    <Counter>  := ...;
3476
3477               --    do
3478               --       Ctrl_Trans : [access [all]] Obj_Typ := ...;
3479               --       Temp := Access_Typ (Ctrl_Trans);  --  when a pointer
3480               --         <or>
3481               --       Temp := Ctrl_Trans'Unchecked_Access;
3482               --    in ... end;
3483
3484               --  The finalization machinery does not process EWA nodes as
3485               --  this may lead to premature finalization of expressions. Note
3486               --  that Temp is marked as being properly initialized regardless
3487               --  of whether the initialization of Ctrl_Trans succeeded. Since
3488               --  a failed initialization may leave Temp with a value of null,
3489               --  add a guard to handle this case:
3490
3491               --    if Obj /= null then
3492               --       <object finalization statements>
3493               --    end if;
3494
3495               if Nkind (Status_Flag_Or_Transient_Decl (Obj_Id)) =
3496                                                      N_Object_Declaration
3497               then
3498                  Fin_Stmts := New_List (
3499                    Make_If_Statement (Loc,
3500                      Condition       =>
3501                        Make_Op_Ne (Loc,
3502                          Left_Opnd  => New_Occurrence_Of (Obj_Id, Loc),
3503                          Right_Opnd => Make_Null (Loc)),
3504                      Then_Statements => Fin_Stmts));
3505
3506               --  Return objects use a flag to aid in processing their
3507               --  potential finalization when the enclosing function fails
3508               --  to return properly. Generate:
3509
3510               --    if not Flag then
3511               --       <object finalization statements>
3512               --    end if;
3513
3514               else
3515                  Fin_Stmts := New_List (
3516                    Make_If_Statement (Loc,
3517                      Condition     =>
3518                        Make_Op_Not (Loc,
3519                          Right_Opnd =>
3520                            New_Occurrence_Of
3521                              (Status_Flag_Or_Transient_Decl (Obj_Id), Loc)),
3522
3523                    Then_Statements => Fin_Stmts));
3524               end if;
3525            end if;
3526         end if;
3527
3528         Append_List_To (Finalizer_Stmts, Fin_Stmts);
3529
3530         --  Since the declarations are examined in reverse, the state counter
3531         --  must be decremented in order to keep with the true position of
3532         --  objects.
3533
3534         Counter_Val := Counter_Val - 1;
3535      end Process_Object_Declaration;
3536
3537      -------------------------------------
3538      -- Process_Tagged_Type_Declaration --
3539      -------------------------------------
3540
3541      procedure Process_Tagged_Type_Declaration (Decl : Node_Id) is
3542         Typ    : constant Entity_Id := Defining_Identifier (Decl);
3543         DT_Ptr : constant Entity_Id :=
3544                    Node (First_Elmt (Access_Disp_Table (Typ)));
3545      begin
3546         --  Generate:
3547         --    Ada.Tags.Unregister_Tag (<Typ>P);
3548
3549         Append_To (Tagged_Type_Stmts,
3550           Make_Procedure_Call_Statement (Loc,
3551             Name                   =>
3552               New_Occurrence_Of (RTE (RE_Unregister_Tag), Loc),
3553             Parameter_Associations => New_List (
3554               New_Occurrence_Of (DT_Ptr, Loc))));
3555      end Process_Tagged_Type_Declaration;
3556
3557   --  Start of processing for Build_Finalizer_Helper
3558
3559   begin
3560      Fin_Id := Empty;
3561
3562      --  Do not perform this expansion in SPARK mode because it is not
3563      --  necessary.
3564
3565      if GNATprove_Mode then
3566         return;
3567      end if;
3568
3569      --  Step 1: Extract all lists which may contain controlled objects or
3570      --  library-level tagged types.
3571
3572      if For_Package_Spec then
3573         Decls      := Visible_Declarations (Specification (N));
3574         Priv_Decls := Private_Declarations (Specification (N));
3575
3576         --  Retrieve the package spec id
3577
3578         Spec_Id := Defining_Unit_Name (Specification (N));
3579
3580         if Nkind (Spec_Id) = N_Defining_Program_Unit_Name then
3581            Spec_Id := Defining_Identifier (Spec_Id);
3582         end if;
3583
3584      --  Accept statement, block, entry body, package body, protected body,
3585      --  subprogram body or task body.
3586
3587      else
3588         Decls := Declarations (N);
3589         HSS   := Handled_Statement_Sequence (N);
3590
3591         if Present (HSS) then
3592            if Present (Statements (HSS)) then
3593               Stmts := Statements (HSS);
3594            end if;
3595
3596            if Present (At_End_Proc (HSS)) then
3597               Prev_At_End := At_End_Proc (HSS);
3598            end if;
3599         end if;
3600
3601         --  Retrieve the package spec id for package bodies
3602
3603         if For_Package_Body then
3604            Spec_Id := Corresponding_Spec (N);
3605         end if;
3606      end if;
3607
3608      --  Do not process nested packages since those are handled by the
3609      --  enclosing scope's finalizer. Do not process non-expanded package
3610      --  instantiations since those will be re-analyzed and re-expanded.
3611
3612      if For_Package
3613        and then
3614          (not Is_Library_Level_Entity (Spec_Id)
3615
3616            --  Nested packages are library level entities, but do not need to
3617            --  be processed separately.
3618
3619            or else Scope_Depth (Spec_Id) /= Uint_1
3620            or else (Is_Generic_Instance (Spec_Id)
3621                      and then Package_Instantiation (Spec_Id) /= N))
3622
3623         --  Still need to process package body instantiations which may
3624         --  contain objects requiring finalization.
3625
3626        and then not
3627          (For_Package_Body
3628            and then Is_Library_Level_Entity (Spec_Id)
3629            and then Is_Generic_Instance (Spec_Id))
3630      then
3631         return;
3632      end if;
3633
3634      --  Step 2: Object [pre]processing
3635
3636      if For_Package then
3637
3638         --  Preprocess the visible declarations now in order to obtain the
3639         --  correct number of controlled object by the time the private
3640         --  declarations are processed.
3641
3642         Process_Declarations (Decls, Preprocess => True, Top_Level => True);
3643
3644         --  From all the possible contexts, only package specifications may
3645         --  have private declarations.
3646
3647         if For_Package_Spec then
3648            Process_Declarations
3649              (Priv_Decls, Preprocess => True, Top_Level => True);
3650         end if;
3651
3652         --  The current context may lack controlled objects, but require some
3653         --  other form of completion (task termination for instance). In such
3654         --  cases, the finalizer must be created and carry the additional
3655         --  statements.
3656
3657         if Acts_As_Clean or Has_Ctrl_Objs or Has_Tagged_Types then
3658            Build_Components;
3659         end if;
3660
3661         --  The preprocessing has determined that the context has controlled
3662         --  objects or library-level tagged types.
3663
3664         if Has_Ctrl_Objs or Has_Tagged_Types then
3665
3666            --  Private declarations are processed first in order to preserve
3667            --  possible dependencies between public and private objects.
3668
3669            if For_Package_Spec then
3670               Process_Declarations (Priv_Decls);
3671            end if;
3672
3673            Process_Declarations (Decls);
3674         end if;
3675
3676      --  Non-package case
3677
3678      else
3679         --  Preprocess both declarations and statements
3680
3681         Process_Declarations (Decls, Preprocess => True, Top_Level => True);
3682         Process_Declarations (Stmts, Preprocess => True, Top_Level => True);
3683
3684         --  At this point it is known that N has controlled objects. Ensure
3685         --  that N has a declarative list since the finalizer spec will be
3686         --  attached to it.
3687
3688         if Has_Ctrl_Objs and then No (Decls) then
3689            Set_Declarations (N, New_List);
3690            Decls      := Declarations (N);
3691            Spec_Decls := Decls;
3692         end if;
3693
3694         --  The current context may lack controlled objects, but require some
3695         --  other form of completion (task termination for instance). In such
3696         --  cases, the finalizer must be created and carry the additional
3697         --  statements.
3698
3699         if Acts_As_Clean or Has_Ctrl_Objs or Has_Tagged_Types then
3700            Build_Components;
3701         end if;
3702
3703         if Has_Ctrl_Objs or Has_Tagged_Types then
3704            Process_Declarations (Stmts);
3705            Process_Declarations (Decls);
3706         end if;
3707      end if;
3708
3709      --  Step 3: Finalizer creation
3710
3711      if Acts_As_Clean or Has_Ctrl_Objs or Has_Tagged_Types then
3712         Create_Finalizer;
3713      end if;
3714   end Build_Finalizer_Helper;
3715
3716   --------------------------
3717   -- Build_Finalizer_Call --
3718   --------------------------
3719
3720   procedure Build_Finalizer_Call (N : Node_Id; Fin_Id : Entity_Id) is
3721      Is_Prot_Body : constant Boolean :=
3722                       Nkind (N) = N_Subprogram_Body
3723                         and then Is_Protected_Subprogram_Body (N);
3724      --  Determine whether N denotes the protected version of a subprogram
3725      --  which belongs to a protected type.
3726
3727      Loc : constant Source_Ptr := Sloc (N);
3728      HSS : Node_Id;
3729
3730   begin
3731      --  Do not perform this expansion in SPARK mode because we do not create
3732      --  finalizers in the first place.
3733
3734      if GNATprove_Mode then
3735         return;
3736      end if;
3737
3738      --  The At_End handler should have been assimilated by the finalizer
3739
3740      HSS := Handled_Statement_Sequence (N);
3741      pragma Assert (No (At_End_Proc (HSS)));
3742
3743      --  If the construct to be cleaned up is a protected subprogram body, the
3744      --  finalizer call needs to be associated with the block which wraps the
3745      --  unprotected version of the subprogram. The following illustrates this
3746      --  scenario:
3747
3748      --     procedure Prot_SubpP is
3749      --        procedure finalizer is
3750      --        begin
3751      --           Service_Entries (Prot_Obj);
3752      --           Abort_Undefer;
3753      --        end finalizer;
3754
3755      --     begin
3756      --        . . .
3757      --        begin
3758      --           Prot_SubpN (Prot_Obj);
3759      --        at end
3760      --           finalizer;
3761      --        end;
3762      --     end Prot_SubpP;
3763
3764      if Is_Prot_Body then
3765         HSS := Handled_Statement_Sequence (Last (Statements (HSS)));
3766
3767      --  An At_End handler and regular exception handlers cannot coexist in
3768      --  the same statement sequence. Wrap the original statements in a block.
3769
3770      elsif Present (Exception_Handlers (HSS)) then
3771         declare
3772            End_Lab : constant Node_Id := End_Label (HSS);
3773            Block   : Node_Id;
3774
3775         begin
3776            Block :=
3777              Make_Block_Statement (Loc, Handled_Statement_Sequence => HSS);
3778
3779            Set_Handled_Statement_Sequence (N,
3780              Make_Handled_Sequence_Of_Statements (Loc, New_List (Block)));
3781
3782            HSS := Handled_Statement_Sequence (N);
3783            Set_End_Label (HSS, End_Lab);
3784         end;
3785      end if;
3786
3787      Set_At_End_Proc (HSS, New_Occurrence_Of (Fin_Id, Loc));
3788
3789      --  Attach reference to finalizer to tree, for LLVM use
3790
3791      Set_Parent (At_End_Proc (HSS), HSS);
3792
3793      Analyze (At_End_Proc (HSS));
3794      Expand_At_End_Handler (HSS, Empty);
3795   end Build_Finalizer_Call;
3796
3797   ---------------------
3798   -- Build_Finalizer --
3799   ---------------------
3800
3801   procedure Build_Finalizer
3802     (N           : Node_Id;
3803      Clean_Stmts : List_Id;
3804      Mark_Id     : Entity_Id;
3805      Top_Decls   : List_Id;
3806      Defer_Abort : Boolean;
3807      Fin_Id      : out Entity_Id)
3808   is
3809      Def_Ent : constant Entity_Id  := Unique_Defining_Entity (N);
3810      Loc     : constant Source_Ptr := Sloc (N);
3811
3812      --  Declarations used for the creation of _finalization_controller
3813
3814      Fin_Old_Id           : Entity_Id := Empty;
3815      Fin_Controller_Id    : Entity_Id := Empty;
3816      Fin_Controller_Decls : List_Id;
3817      Fin_Controller_Stmts : List_Id;
3818      Fin_Controller_Body  : Node_Id   := Empty;
3819      Fin_Controller_Spec  : Node_Id   := Empty;
3820      Postconditions_Call  : Node_Id   := Empty;
3821
3822      --  Defining identifiers for local objects used to store exception info
3823
3824      Raised_Post_Exception_Id         : Entity_Id := Empty;
3825      Raised_Finalization_Exception_Id : Entity_Id := Empty;
3826      Saved_Exception_Id               : Entity_Id := Empty;
3827
3828   --  Start of processing for Build_Finalizer
3829
3830   begin
3831      --  Create the general finalization routine
3832
3833      Build_Finalizer_Helper
3834        (N                 => N,
3835         Clean_Stmts       => Clean_Stmts,
3836         Mark_Id           => Mark_Id,
3837         Top_Decls         => Top_Decls,
3838         Defer_Abort       => Defer_Abort,
3839         Fin_Id            => Fin_Id,
3840         Finalize_Old_Only => False);
3841
3842      --  When postconditions are present, expansion gets much more complicated
3843      --  due to both the fact that they must be called after finalization and
3844      --  that finalization of 'Old objects must occur after the postconditions
3845      --  get checked.
3846
3847      --  Additionally, exceptions between general finalization and 'Old
3848      --  finalization must be propagated correctly and exceptions which happen
3849      --  during _postconditions need to be saved and reraised after
3850      --  finalization of 'Old objects.
3851
3852      --  Generate:
3853      --
3854      --    Postcond_Enabled := False;
3855      --
3856      --    procedure _finalization_controller is
3857      --
3858      --       --  Exception capturing and tracking
3859      --
3860      --       Saved_Exception               : Exception_Occurrence;
3861      --       Raised_Post_Exception         : Boolean := False;
3862      --       Raised_Finalization_Exception : Boolean := False;
3863      --
3864      --    --  Start of processing for _finalization_controller
3865      --
3866      --    begin
3867      --       --  Perform general finalization
3868      --
3869      --       begin
3870      --          _finalizer;
3871      --       exception
3872      --          when others =>
3873      --             --  Save the exception
3874      --
3875      --             Raised_Finalization_Exception := True;
3876      --             Save_Occurrence
3877      --               (Saved_Exception, Get_Current_Excep.all);
3878      --       end;
3879      --
3880      --       --  Perform postcondition checks after general finalization, but
3881      --       --  before finalization of 'Old related objects.
3882      --
3883      --       if not Raised_Finalization_Exception
3884      --         and then Return_Success_For_Postcond
3885      --       then
3886      --          begin
3887      --             --  Re-enable postconditions and check them
3888      --
3889      --             Postcond_Enabled := True;
3890      --             _postconditions [(Result_Obj_For_Postcond[.all])];
3891      --          exception
3892      --             when others =>
3893      --                --  Save the exception
3894      --
3895      --                Raised_Post_Exception := True;
3896      --                Save_Occurrence
3897      --                  (Saved_Exception, Get_Current_Excep.all);
3898      --          end;
3899      --       end if;
3900      --
3901      --       --  Finally finalize 'Old related objects
3902      --
3903      --       begin
3904      --          _finalizer_old;
3905      --       exception
3906      --          when others =>
3907      --             --  Reraise the previous finalization error if there is
3908      --             --  one.
3909      --
3910      --             if Raised_Finalization_Exception then
3911      --                Reraise_Occurrence (Saved_Exception);
3912      --             end if;
3913      --
3914      --             --  Otherwise, reraise the current one
3915      --
3916      --             raise;
3917      --       end;
3918      --
3919      --       --  Reraise any saved exception
3920      --
3921      --       if Raised_Finalization_Exception
3922      --            or else Raised_Post_Exception
3923      --       then
3924      --          Reraise_Occurrence (Saved_Exception);
3925      --       end if;
3926      --    end _finalization_controller;
3927
3928      if Nkind (N) = N_Subprogram_Body
3929        and then Present (Postconditions_Proc (Def_Ent))
3930      then
3931         Fin_Controller_Stmts := New_List;
3932         Fin_Controller_Decls := New_List;
3933
3934         --  Build the 'Old finalizer
3935
3936         Build_Finalizer_Helper
3937           (N                 => N,
3938            Clean_Stmts       => Empty_List,
3939            Mark_Id           => Mark_Id,
3940            Top_Decls         => Top_Decls,
3941            Defer_Abort       => Defer_Abort,
3942            Fin_Id            => Fin_Old_Id,
3943            Finalize_Old_Only => True);
3944
3945         --  Create local declarations for _finalization_controller needed for
3946         --  saving exceptions.
3947         --
3948         --  Generate:
3949         --
3950         --    Saved_Exception               : Exception_Occurrence;
3951         --    Raised_Post_Exception         : Boolean := False;
3952         --    Raised_Finalization_Exception : Boolean := False;
3953
3954         Saved_Exception_Id               := Make_Temporary (Loc, 'S');
3955         Raised_Post_Exception_Id         := Make_Temporary (Loc, 'P');
3956         Raised_Finalization_Exception_Id := Make_Temporary (Loc, 'F');
3957
3958         Append_List_To (Fin_Controller_Decls, New_List (
3959           Make_Object_Declaration (Loc,
3960             Defining_Identifier => Saved_Exception_Id,
3961             Object_Definition   =>
3962               New_Occurrence_Of (RTE (RE_Exception_Occurrence), Loc)),
3963           Make_Object_Declaration (Loc,
3964             Defining_Identifier => Raised_Post_Exception_Id,
3965             Object_Definition   => New_Occurrence_Of (Standard_Boolean, Loc),
3966             Expression          => New_Occurrence_Of (Standard_False, Loc)),
3967           Make_Object_Declaration (Loc,
3968             Defining_Identifier => Raised_Finalization_Exception_Id,
3969             Object_Definition   => New_Occurrence_Of (Standard_Boolean, Loc),
3970             Expression          => New_Occurrence_Of (Standard_False, Loc))));
3971
3972         --  Call _finalizer and save any exceptions which occur
3973
3974         --  Generate:
3975         --
3976         --    begin
3977         --       _finalizer;
3978         --    exception
3979         --       when others =>
3980         --          Raised_Finalization_Exception := True;
3981         --          Save_Occurrence
3982         --            (Saved_Exception, Get_Current_Excep.all);
3983         --    end;
3984
3985         if Present (Fin_Id) then
3986            Append_To (Fin_Controller_Stmts,
3987              Make_Block_Statement (Loc,
3988                Handled_Statement_Sequence =>
3989                  Make_Handled_Sequence_Of_Statements (Loc,
3990                    Statements         => New_List (
3991                      Make_Procedure_Call_Statement (Loc,
3992                        Name => New_Occurrence_Of (Fin_Id, Loc))),
3993                    Exception_Handlers => New_List (
3994                      Make_Exception_Handler (Loc,
3995                        Exception_Choices => New_List (
3996                          Make_Others_Choice (Loc)),
3997                        Statements        => New_List (
3998                          Make_Assignment_Statement (Loc,
3999                            Name       =>
4000                              New_Occurrence_Of
4001                                (Raised_Finalization_Exception_Id, Loc),
4002                            Expression =>
4003                              New_Occurrence_Of (Standard_True, Loc)),
4004                          Make_Procedure_Call_Statement (Loc,
4005                             Name                   =>
4006                               New_Occurrence_Of
4007                                 (RTE (RE_Save_Occurrence), Loc),
4008                             Parameter_Associations => New_List (
4009                               New_Occurrence_Of
4010                                 (Saved_Exception_Id, Loc),
4011                               Make_Explicit_Dereference (Loc,
4012                                 Prefix =>
4013                                   Make_Function_Call (Loc,
4014                                     Name =>
4015                                       Make_Explicit_Dereference (Loc,
4016                                         Prefix =>
4017                                           New_Occurrence_Of
4018                                             (RTE (RE_Get_Current_Excep),
4019                                              Loc))))))))))));
4020         end if;
4021
4022         --  Create the call to postconditions based on the kind of the current
4023         --  subprogram, and the type of the Result_Obj_For_Postcond.
4024
4025         --  Generate:
4026         --
4027         --    _postconditions (Result_Obj_For_Postcond[.all]);
4028         --
4029         --   or
4030         --
4031         --    _postconditions;
4032
4033         if Ekind (Def_Ent) = E_Procedure then
4034            Postconditions_Call :=
4035              Make_Procedure_Call_Statement (Loc,
4036                Name =>
4037                  New_Occurrence_Of
4038                    (Postconditions_Proc (Def_Ent), Loc));
4039         else
4040            Postconditions_Call :=
4041              Make_Procedure_Call_Statement (Loc,
4042                Name                   =>
4043                  New_Occurrence_Of
4044                    (Postconditions_Proc (Def_Ent), Loc),
4045                Parameter_Associations => New_List (
4046                  (if Is_Elementary_Type (Etype (Def_Ent)) then
4047                      New_Occurrence_Of
4048                        (Get_Result_Object_For_Postcond
4049                          (Def_Ent), Loc)
4050                   else
4051                      Make_Explicit_Dereference (Loc,
4052                        New_Occurrence_Of
4053                          (Get_Result_Object_For_Postcond
4054                            (Def_Ent), Loc)))));
4055         end if;
4056
4057         --  Call _postconditions when no general finalization exceptions have
4058         --  occured taking care to enable the postconditions and save any
4059         --  exception occurrences.
4060
4061         --  Generate:
4062         --
4063         --    if not Raised_Finalization_Exception
4064         --      and then Return_Success_For_Postcond
4065         --    then
4066         --       begin
4067         --          Postcond_Enabled := True;
4068         --          _postconditions [(Result_Obj_For_Postcond[.all])];
4069         --       exception
4070         --          when others =>
4071         --             Raised_Post_Exception := True;
4072         --             Save_Occurrence
4073         --               (Saved_Exception, Get_Current_Excep.all);
4074         --       end;
4075         --    end if;
4076
4077         Append_To (Fin_Controller_Stmts,
4078           Make_If_Statement (Loc,
4079             Condition       =>
4080               Make_And_Then (Loc,
4081                 Left_Opnd  =>
4082                   Make_Op_Not (Loc,
4083                     Right_Opnd =>
4084                       New_Occurrence_Of
4085                         (Raised_Finalization_Exception_Id, Loc)),
4086                 Right_Opnd =>
4087                   New_Occurrence_Of
4088                     (Get_Return_Success_For_Postcond (Def_Ent), Loc)),
4089             Then_Statements => New_List (
4090               Make_Block_Statement (Loc,
4091                 Handled_Statement_Sequence =>
4092                   Make_Handled_Sequence_Of_Statements (Loc,
4093                     Statements         => New_List (
4094                       Make_Assignment_Statement (Loc,
4095                         Name       =>
4096                           New_Occurrence_Of
4097                             (Get_Postcond_Enabled (Def_Ent), Loc),
4098                         Expression =>
4099                            New_Occurrence_Of
4100                              (Standard_True, Loc)),
4101                       Postconditions_Call),
4102                     Exception_Handlers => New_List (
4103                       Make_Exception_Handler (Loc,
4104                         Exception_Choices => New_List (
4105                           Make_Others_Choice (Loc)),
4106                         Statements        => New_List (
4107                           Make_Assignment_Statement (Loc,
4108                             Name       =>
4109                               New_Occurrence_Of
4110                                 (Raised_Post_Exception_Id, Loc),
4111                             Expression =>
4112                               New_Occurrence_Of (Standard_True, Loc)),
4113                           Make_Procedure_Call_Statement (Loc,
4114                              Name                   =>
4115                                New_Occurrence_Of
4116                                  (RTE (RE_Save_Occurrence), Loc),
4117                              Parameter_Associations => New_List (
4118                                New_Occurrence_Of
4119                                  (Saved_Exception_Id, Loc),
4120                                Make_Explicit_Dereference (Loc,
4121                                  Prefix =>
4122                                    Make_Function_Call (Loc,
4123                                      Name =>
4124                                        Make_Explicit_Dereference (Loc,
4125                                          Prefix =>
4126                                            New_Occurrence_Of
4127                                              (RTE (RE_Get_Current_Excep),
4128                                               Loc))))))))))))));
4129
4130         --  Call _finalizer_old and reraise any exception that occurred during
4131         --  initial finalization within the exception handler. Otherwise,
4132         --  propagate the current exception.
4133
4134         --  Generate:
4135         --
4136         --    begin
4137         --       _finalizer_old;
4138         --    exception
4139         --       when others =>
4140         --          if Raised_Finalization_Exception then
4141         --             Reraise_Occurrence (Saved_Exception);
4142         --          end if;
4143         --          raise;
4144         --    end;
4145
4146         if Present (Fin_Old_Id) then
4147            Append_To (Fin_Controller_Stmts,
4148              Make_Block_Statement (Loc,
4149                Handled_Statement_Sequence =>
4150                  Make_Handled_Sequence_Of_Statements (Loc,
4151                    Statements         => New_List (
4152                      Make_Procedure_Call_Statement (Loc,
4153                        Name => New_Occurrence_Of (Fin_Old_Id, Loc))),
4154                    Exception_Handlers => New_List (
4155                      Make_Exception_Handler (Loc,
4156                        Exception_Choices => New_List (
4157                          Make_Others_Choice (Loc)),
4158                        Statements        => New_List (
4159                          Make_If_Statement (Loc,
4160                            Condition       =>
4161                              New_Occurrence_Of
4162                                (Raised_Finalization_Exception_Id, Loc),
4163                            Then_Statements => New_List (
4164                              Make_Procedure_Call_Statement (Loc,
4165                                Name                   =>
4166                                  New_Occurrence_Of
4167                                    (RTE (RE_Reraise_Occurrence), Loc),
4168                                Parameter_Associations => New_List (
4169                                  New_Occurrence_Of
4170                                    (Saved_Exception_Id, Loc))))),
4171                          Make_Raise_Statement (Loc)))))));
4172         end if;
4173
4174         --  Once finalization is complete reraise any pending exceptions
4175
4176         --  Generate:
4177         --
4178         --    if Raised_Post_Exception
4179         --      or else Raised_Finalization_Exception
4180         --    then
4181         --       Reraise_Occurrence (Saved_Exception);
4182         --    end if;
4183
4184         Append_To (Fin_Controller_Stmts,
4185           Make_If_Statement (Loc,
4186             Condition       =>
4187               Make_Or_Else (Loc,
4188                 Left_Opnd  =>
4189                   New_Occurrence_Of
4190                     (Raised_Post_Exception_Id, Loc),
4191                 Right_Opnd =>
4192                   New_Occurrence_Of
4193                     (Raised_Finalization_Exception_Id, Loc)),
4194             Then_Statements => New_List (
4195               Make_Procedure_Call_Statement (Loc,
4196                 Name            =>
4197                   New_Occurrence_Of (RTE (RE_Reraise_Occurrence), Loc),
4198                 Parameter_Associations => New_List (
4199                   New_Occurrence_Of
4200                     (Saved_Exception_Id, Loc))))));
4201
4202         --  Make the finalization controller subprogram body and declaration.
4203
4204         --  Generate:
4205         --    procedure _finalization_controller;
4206         --
4207         --    procedure _finalization_controller is
4208         --    begin
4209         --       [Fin_Controller_Stmts];
4210         --    end;
4211
4212         Fin_Controller_Id :=
4213           Make_Defining_Identifier (Loc,
4214             Chars => New_External_Name (Name_uFinalization_Controller));
4215
4216         Fin_Controller_Spec :=
4217           Make_Subprogram_Declaration (Loc,
4218             Specification =>
4219               Make_Procedure_Specification (Loc,
4220                 Defining_Unit_Name => Fin_Controller_Id));
4221
4222         Fin_Controller_Body :=
4223           Make_Subprogram_Body (Loc,
4224             Specification              =>
4225               Make_Procedure_Specification (Loc,
4226                 Defining_Unit_Name =>
4227                   Make_Defining_Identifier (Loc, Chars (Fin_Controller_Id))),
4228             Declarations               => Fin_Controller_Decls,
4229             Handled_Statement_Sequence =>
4230               Make_Handled_Sequence_Of_Statements (Loc,
4231                 Statements => Fin_Controller_Stmts));
4232
4233         --  Disable _postconditions calls which get generated before return
4234         --  statements to delay their evaluation until after finalization.
4235
4236         --  This is done by way of the local Postcond_Enabled object which is
4237         --  initially assigned to True - we then create an assignment within
4238         --  the subprogram's declaration to make it False and assign it back
4239         --  to True before _postconditions is called within
4240         --  _finalization_controller.
4241
4242         --  Generate:
4243         --
4244         --    Postcond_Enable := False;
4245
4246         Append_To (Top_Decls,
4247           Make_Assignment_Statement (Loc,
4248             Name       =>
4249               New_Occurrence_Of
4250                 (Get_Postcond_Enabled (Def_Ent), Loc),
4251             Expression =>
4252               New_Occurrence_Of
4253                 (Standard_False, Loc)));
4254
4255         --  Add the subprogram to the list of declarations an analyze it
4256
4257         Append_To (Top_Decls, Fin_Controller_Spec);
4258         Analyze (Fin_Controller_Spec);
4259         Insert_After (Fin_Controller_Spec, Fin_Controller_Body);
4260         Analyze (Fin_Controller_Body, Suppress => All_Checks);
4261
4262         --  Return the finalization controller as the result Fin_Id
4263
4264         Fin_Id := Fin_Controller_Id;
4265      end if;
4266   end Build_Finalizer;
4267
4268   ---------------------
4269   -- Build_Late_Proc --
4270   ---------------------
4271
4272   procedure Build_Late_Proc (Typ : Entity_Id; Nam : Name_Id) is
4273   begin
4274      for Final_Prim in Name_Of'Range loop
4275         if Name_Of (Final_Prim) = Nam then
4276            Set_TSS (Typ,
4277              Make_Deep_Proc
4278                (Prim  => Final_Prim,
4279                 Typ   => Typ,
4280                 Stmts => Make_Deep_Record_Body (Final_Prim, Typ)));
4281         end if;
4282      end loop;
4283   end Build_Late_Proc;
4284
4285   -------------------------------
4286   -- Build_Object_Declarations --
4287   -------------------------------
4288
4289   procedure Build_Object_Declarations
4290     (Data        : out Finalization_Exception_Data;
4291      Decls       : List_Id;
4292      Loc         : Source_Ptr;
4293      For_Package : Boolean := False)
4294   is
4295      Decl : Node_Id;
4296
4297      Dummy : Entity_Id;
4298      --  This variable captures an unused dummy internal entity, see the
4299      --  comment associated with its use.
4300
4301   begin
4302      pragma Assert (Decls /= No_List);
4303
4304      --  Always set the proper location as it may be needed even when
4305      --  exception propagation is forbidden.
4306
4307      Data.Loc := Loc;
4308
4309      if Restriction_Active (No_Exception_Propagation) then
4310         Data.Abort_Id  := Empty;
4311         Data.E_Id      := Empty;
4312         Data.Raised_Id := Empty;
4313         return;
4314      end if;
4315
4316      Data.Raised_Id := Make_Temporary (Loc, 'R');
4317
4318      --  In certain scenarios, finalization can be triggered by an abort. If
4319      --  the finalization itself fails and raises an exception, the resulting
4320      --  Program_Error must be supressed and replaced by an abort signal. In
4321      --  order to detect this scenario, save the state of entry into the
4322      --  finalization code.
4323
4324      --  This is not needed for library-level finalizers as they are called by
4325      --  the environment task and cannot be aborted.
4326
4327      if not For_Package then
4328         if Abort_Allowed then
4329            Data.Abort_Id := Make_Temporary (Loc, 'A');
4330
4331            --  Generate:
4332            --    Abort_Id : constant Boolean := <A_Expr>;
4333
4334            Append_To (Decls,
4335              Make_Object_Declaration (Loc,
4336                Defining_Identifier => Data.Abort_Id,
4337                Constant_Present    => True,
4338                Object_Definition   =>
4339                  New_Occurrence_Of (Standard_Boolean, Loc),
4340                Expression          =>
4341                  New_Occurrence_Of (RTE (RE_Triggered_By_Abort), Loc)));
4342
4343         --  Abort is not required
4344
4345         else
4346            --  Generate a dummy entity to ensure that the internal symbols are
4347            --  in sync when a unit is compiled with and without aborts.
4348
4349            Dummy := Make_Temporary (Loc, 'A');
4350            Data.Abort_Id := Empty;
4351         end if;
4352
4353      --  Library-level finalizers
4354
4355      else
4356         Data.Abort_Id := Empty;
4357      end if;
4358
4359      if Exception_Extra_Info then
4360         Data.E_Id := Make_Temporary (Loc, 'E');
4361
4362         --  Generate:
4363         --    E_Id : Exception_Occurrence;
4364
4365         Decl :=
4366           Make_Object_Declaration (Loc,
4367             Defining_Identifier => Data.E_Id,
4368             Object_Definition   =>
4369               New_Occurrence_Of (RTE (RE_Exception_Occurrence), Loc));
4370         Set_No_Initialization (Decl);
4371
4372         Append_To (Decls, Decl);
4373
4374      else
4375         Data.E_Id := Empty;
4376      end if;
4377
4378      --  Generate:
4379      --    Raised_Id : Boolean := False;
4380
4381      Append_To (Decls,
4382        Make_Object_Declaration (Loc,
4383          Defining_Identifier => Data.Raised_Id,
4384          Object_Definition   => New_Occurrence_Of (Standard_Boolean, Loc),
4385          Expression          => New_Occurrence_Of (Standard_False, Loc)));
4386
4387      if Debug_Generated_Code then
4388         Set_Debug_Info_Needed (Data.Raised_Id);
4389      end if;
4390   end Build_Object_Declarations;
4391
4392   ---------------------------
4393   -- Build_Raise_Statement --
4394   ---------------------------
4395
4396   function Build_Raise_Statement
4397     (Data : Finalization_Exception_Data) return Node_Id
4398   is
4399      Stmt : Node_Id;
4400      Expr : Node_Id;
4401
4402   begin
4403      --  Standard run-time use the specialized routine
4404      --  Raise_From_Controlled_Operation.
4405
4406      if Exception_Extra_Info
4407        and then RTE_Available (RE_Raise_From_Controlled_Operation)
4408      then
4409         Stmt :=
4410           Make_Procedure_Call_Statement (Data.Loc,
4411              Name                   =>
4412                New_Occurrence_Of
4413                  (RTE (RE_Raise_From_Controlled_Operation), Data.Loc),
4414              Parameter_Associations =>
4415                New_List (New_Occurrence_Of (Data.E_Id, Data.Loc)));
4416
4417      --  Restricted run-time: exception messages are not supported and hence
4418      --  Raise_From_Controlled_Operation is not supported. Raise Program_Error
4419      --  instead.
4420
4421      else
4422         Stmt :=
4423           Make_Raise_Program_Error (Data.Loc,
4424             Reason => PE_Finalize_Raised_Exception);
4425      end if;
4426
4427      --  Generate:
4428
4429      --    Raised_Id and then not Abort_Id
4430      --      <or>
4431      --    Raised_Id
4432
4433      Expr := New_Occurrence_Of (Data.Raised_Id, Data.Loc);
4434
4435      if Present (Data.Abort_Id) then
4436         Expr := Make_And_Then (Data.Loc,
4437           Left_Opnd  => Expr,
4438           Right_Opnd =>
4439             Make_Op_Not (Data.Loc,
4440               Right_Opnd => New_Occurrence_Of (Data.Abort_Id, Data.Loc)));
4441      end if;
4442
4443      --  Generate:
4444
4445      --    if Raised_Id and then not Abort_Id then
4446      --       Raise_From_Controlled_Operation (E_Id);
4447      --         <or>
4448      --       raise Program_Error;  --  restricted runtime
4449      --    end if;
4450
4451      return
4452        Make_If_Statement (Data.Loc,
4453          Condition       => Expr,
4454          Then_Statements => New_List (Stmt));
4455   end Build_Raise_Statement;
4456
4457   -----------------------------
4458   -- Build_Record_Deep_Procs --
4459   -----------------------------
4460
4461   procedure Build_Record_Deep_Procs (Typ : Entity_Id) is
4462   begin
4463      Set_TSS (Typ,
4464        Make_Deep_Proc
4465          (Prim  => Initialize_Case,
4466           Typ   => Typ,
4467           Stmts => Make_Deep_Record_Body (Initialize_Case, Typ)));
4468
4469      if not Is_Limited_View (Typ) then
4470         Set_TSS (Typ,
4471           Make_Deep_Proc
4472             (Prim  => Adjust_Case,
4473              Typ   => Typ,
4474              Stmts => Make_Deep_Record_Body (Adjust_Case, Typ)));
4475      end if;
4476
4477      --  Do not generate Deep_Finalize and Finalize_Address if finalization is
4478      --  suppressed since these routine will not be used.
4479
4480      if not Restriction_Active (No_Finalization) then
4481         Set_TSS (Typ,
4482           Make_Deep_Proc
4483             (Prim  => Finalize_Case,
4484              Typ   => Typ,
4485              Stmts => Make_Deep_Record_Body (Finalize_Case, Typ)));
4486
4487         --  Create TSS primitive Finalize_Address (unless CodePeer_Mode)
4488
4489         if not CodePeer_Mode then
4490            Set_TSS (Typ,
4491              Make_Deep_Proc
4492                (Prim  => Address_Case,
4493                 Typ   => Typ,
4494                 Stmts => Make_Deep_Record_Body (Address_Case, Typ)));
4495         end if;
4496      end if;
4497   end Build_Record_Deep_Procs;
4498
4499   -------------------
4500   -- Cleanup_Array --
4501   -------------------
4502
4503   function Cleanup_Array
4504     (N    : Node_Id;
4505      Obj  : Node_Id;
4506      Typ  : Entity_Id) return List_Id
4507   is
4508      Loc        : constant Source_Ptr := Sloc (N);
4509      Index_List : constant List_Id := New_List;
4510
4511      function Free_Component return List_Id;
4512      --  Generate the code to finalize the task or protected  subcomponents
4513      --  of a single component of the array.
4514
4515      function Free_One_Dimension (Dim : Int) return List_Id;
4516      --  Generate a loop over one dimension of the array
4517
4518      --------------------
4519      -- Free_Component --
4520      --------------------
4521
4522      function Free_Component return List_Id is
4523         Stmts : List_Id := New_List;
4524         Tsk   : Node_Id;
4525         C_Typ : constant Entity_Id := Component_Type (Typ);
4526
4527      begin
4528         --  Component type is known to contain tasks or protected objects
4529
4530         Tsk :=
4531           Make_Indexed_Component (Loc,
4532             Prefix        => Duplicate_Subexpr_No_Checks (Obj),
4533             Expressions   => Index_List);
4534
4535         Set_Etype (Tsk, C_Typ);
4536
4537         if Is_Task_Type (C_Typ) then
4538            Append_To (Stmts, Cleanup_Task (N, Tsk));
4539
4540         elsif Is_Simple_Protected_Type (C_Typ) then
4541            Append_To (Stmts, Cleanup_Protected_Object (N, Tsk));
4542
4543         elsif Is_Record_Type (C_Typ) then
4544            Stmts := Cleanup_Record (N, Tsk, C_Typ);
4545
4546         elsif Is_Array_Type (C_Typ) then
4547            Stmts := Cleanup_Array (N, Tsk, C_Typ);
4548         end if;
4549
4550         return Stmts;
4551      end Free_Component;
4552
4553      ------------------------
4554      -- Free_One_Dimension --
4555      ------------------------
4556
4557      function Free_One_Dimension (Dim : Int) return List_Id is
4558         Index : Entity_Id;
4559
4560      begin
4561         if Dim > Number_Dimensions (Typ) then
4562            return Free_Component;
4563
4564         --  Here we generate the required loop
4565
4566         else
4567            Index := Make_Temporary (Loc, 'J');
4568            Append (New_Occurrence_Of (Index, Loc), Index_List);
4569
4570            return New_List (
4571              Make_Implicit_Loop_Statement (N,
4572                Identifier       => Empty,
4573                Iteration_Scheme =>
4574                  Make_Iteration_Scheme (Loc,
4575                    Loop_Parameter_Specification =>
4576                      Make_Loop_Parameter_Specification (Loc,
4577                        Defining_Identifier         => Index,
4578                        Discrete_Subtype_Definition =>
4579                          Make_Attribute_Reference (Loc,
4580                            Prefix          => Duplicate_Subexpr (Obj),
4581                            Attribute_Name  => Name_Range,
4582                            Expressions     => New_List (
4583                              Make_Integer_Literal (Loc, Dim))))),
4584                Statements       => Free_One_Dimension (Dim + 1)));
4585         end if;
4586      end Free_One_Dimension;
4587
4588   --  Start of processing for Cleanup_Array
4589
4590   begin
4591      return Free_One_Dimension (1);
4592   end Cleanup_Array;
4593
4594   --------------------
4595   -- Cleanup_Record --
4596   --------------------
4597
4598   function Cleanup_Record
4599     (N    : Node_Id;
4600      Obj  : Node_Id;
4601      Typ  : Entity_Id) return List_Id
4602   is
4603      Loc   : constant Source_Ptr := Sloc (N);
4604      Stmts : constant List_Id    := New_List;
4605      U_Typ : constant Entity_Id  := Underlying_Type (Typ);
4606
4607      Comp : Entity_Id;
4608      Tsk  : Node_Id;
4609
4610   begin
4611      if Has_Discriminants (U_Typ)
4612        and then Nkind (Parent (U_Typ)) = N_Full_Type_Declaration
4613        and then Nkind (Type_Definition (Parent (U_Typ))) = N_Record_Definition
4614        and then
4615          Present
4616            (Variant_Part (Component_List (Type_Definition (Parent (U_Typ)))))
4617      then
4618         --  For now, do not attempt to free a component that may appear in a
4619         --  variant, and instead issue a warning. Doing this "properly" would
4620         --  require building a case statement and would be quite a mess. Note
4621         --  that the RM only requires that free "work" for the case of a task
4622         --  access value, so already we go way beyond this in that we deal
4623         --  with the array case and non-discriminated record cases.
4624
4625         Error_Msg_N
4626           ("task/protected object in variant record will not be freed??", N);
4627         return New_List (Make_Null_Statement (Loc));
4628      end if;
4629
4630      Comp := First_Component (U_Typ);
4631      while Present (Comp) loop
4632         if Chars (Comp) /= Name_uParent
4633           and then (Has_Task (Etype (Comp))
4634             or else Has_Simple_Protected_Object (Etype (Comp)))
4635         then
4636            Tsk :=
4637              Make_Selected_Component (Loc,
4638                Prefix        => Duplicate_Subexpr_No_Checks (Obj),
4639                Selector_Name => New_Occurrence_Of (Comp, Loc));
4640            Set_Etype (Tsk, Etype (Comp));
4641
4642            if Is_Task_Type (Etype (Comp)) then
4643               Append_To (Stmts, Cleanup_Task (N, Tsk));
4644
4645            elsif Is_Simple_Protected_Type (Etype (Comp)) then
4646               Append_To (Stmts, Cleanup_Protected_Object (N, Tsk));
4647
4648            elsif Is_Record_Type (Etype (Comp)) then
4649
4650               --  Recurse, by generating the prefix of the argument to the
4651               --  eventual cleanup call.
4652
4653               Append_List_To (Stmts, Cleanup_Record (N, Tsk, Etype (Comp)));
4654
4655            elsif Is_Array_Type (Etype (Comp)) then
4656               Append_List_To (Stmts, Cleanup_Array (N, Tsk, Etype (Comp)));
4657            end if;
4658         end if;
4659
4660         Next_Component (Comp);
4661      end loop;
4662
4663      return Stmts;
4664   end Cleanup_Record;
4665
4666   ------------------------------
4667   -- Cleanup_Protected_Object --
4668   ------------------------------
4669
4670   function Cleanup_Protected_Object
4671     (N   : Node_Id;
4672      Ref : Node_Id) return Node_Id
4673   is
4674      Loc : constant Source_Ptr := Sloc (N);
4675
4676   begin
4677      --  For restricted run-time libraries (Ravenscar), tasks are
4678      --  non-terminating, and protected objects can only appear at library
4679      --  level, so we do not want finalization of protected objects.
4680
4681      if Restricted_Profile then
4682         return Empty;
4683
4684      else
4685         return
4686           Make_Procedure_Call_Statement (Loc,
4687             Name                   =>
4688               New_Occurrence_Of (RTE (RE_Finalize_Protection), Loc),
4689             Parameter_Associations => New_List (Concurrent_Ref (Ref)));
4690      end if;
4691   end Cleanup_Protected_Object;
4692
4693   ------------------
4694   -- Cleanup_Task --
4695   ------------------
4696
4697   function Cleanup_Task
4698     (N   : Node_Id;
4699      Ref : Node_Id) return Node_Id
4700   is
4701      Loc  : constant Source_Ptr := Sloc (N);
4702
4703   begin
4704      --  For restricted run-time libraries (Ravenscar), tasks are
4705      --  non-terminating and they can only appear at library level,
4706      --  so we do not want finalization of task objects.
4707
4708      if Restricted_Profile then
4709         return Empty;
4710
4711      else
4712         return
4713           Make_Procedure_Call_Statement (Loc,
4714             Name                   =>
4715               New_Occurrence_Of (RTE (RE_Free_Task), Loc),
4716             Parameter_Associations => New_List (Concurrent_Ref (Ref)));
4717      end if;
4718   end Cleanup_Task;
4719
4720   --------------------------------------
4721   -- Check_Unnesting_Elaboration_Code --
4722   --------------------------------------
4723
4724   procedure Check_Unnesting_Elaboration_Code (N : Node_Id) is
4725      Loc             : constant Source_Ptr := Sloc (N);
4726      Block_Elab_Proc : Entity_Id           := Empty;
4727
4728      procedure Set_Block_Elab_Proc;
4729      --  Create a defining identifier for a procedure that will replace
4730      --  a block with nested subprograms (unless it has already been created,
4731      --  in which case this is a no-op).
4732
4733      procedure Set_Block_Elab_Proc is
4734      begin
4735         if No (Block_Elab_Proc) then
4736            Block_Elab_Proc :=
4737              Make_Defining_Identifier (Loc, Chars => New_Internal_Name ('I'));
4738         end if;
4739      end Set_Block_Elab_Proc;
4740
4741      procedure Reset_Scopes_To_Block_Elab_Proc (L : List_Id);
4742      --  Find entities in the elaboration code of a library package body that
4743      --  contain or represent a subprogram body. A body can appear within a
4744      --  block or a loop or can appear by itself if generated for an object
4745      --  declaration that involves controlled actions. The first such entity
4746      --  forces creation of a new procedure entity (via Set_Block_Elab_Proc)
4747      --  that will be used to reset the scopes of all entities that become
4748      --  local to the new elaboration procedure. This is needed for subsequent
4749      --  unnesting actions, which depend on proper setting of the Scope links
4750      --  to determine the nesting level of each subprogram.
4751
4752      -----------------------
4753      --  Find_Local_Scope --
4754      -----------------------
4755
4756      procedure Reset_Scopes_To_Block_Elab_Proc (L : List_Id) is
4757         Id   : Entity_Id;
4758         Stat : Node_Id;
4759         Node : Node_Id;
4760
4761      begin
4762         Stat := First (L);
4763         while Present (Stat) loop
4764            case Nkind (Stat) is
4765               when N_Block_Statement =>
4766                  if Present (Identifier (Stat)) then
4767                     Id := Entity (Identifier (Stat));
4768
4769                     --  The Scope of this block needs to be reset to the new
4770                     --  procedure if the block contains nested subprograms.
4771
4772                     if Present (Id) and then Contains_Subprogram (Id) then
4773                        Set_Block_Elab_Proc;
4774                        Set_Scope (Id, Block_Elab_Proc);
4775                     end if;
4776                  end if;
4777
4778               when N_Loop_Statement =>
4779                  Id := Entity (Identifier (Stat));
4780
4781                  if Present (Id) and then Contains_Subprogram (Id) then
4782                     if Scope (Id) = Current_Scope then
4783                        Set_Block_Elab_Proc;
4784                        Set_Scope (Id, Block_Elab_Proc);
4785                     end if;
4786                  end if;
4787
4788                  --  We traverse the loop's statements as well, which may
4789                  --  include other block (etc.) statements that need to have
4790                  --  their Scope set to Block_Elab_Proc. (Is this really the
4791                  --  case, or do such nested blocks refer to the loop scope
4792                  --  rather than the loop's enclosing scope???.)
4793
4794                  Reset_Scopes_To_Block_Elab_Proc (Statements (Stat));
4795
4796               when N_If_Statement =>
4797                  Reset_Scopes_To_Block_Elab_Proc (Then_Statements (Stat));
4798                  Reset_Scopes_To_Block_Elab_Proc (Else_Statements (Stat));
4799
4800                  Node := First (Elsif_Parts (Stat));
4801                  while Present (Node) loop
4802                     Reset_Scopes_To_Block_Elab_Proc (Then_Statements (Node));
4803                     Next (Node);
4804                  end loop;
4805
4806               when N_Case_Statement =>
4807                  Node := First (Alternatives (Stat));
4808                  while Present (Node) loop
4809                     Reset_Scopes_To_Block_Elab_Proc (Statements (Node));
4810                     Next (Node);
4811                  end loop;
4812
4813               --  Reset the Scope of a subprogram occurring at the top level
4814
4815               when N_Subprogram_Body =>
4816                  Id := Defining_Entity (Stat);
4817
4818                  Set_Block_Elab_Proc;
4819                  Set_Scope (Id, Block_Elab_Proc);
4820
4821               when others =>
4822                  null;
4823            end case;
4824
4825            Next (Stat);
4826         end loop;
4827      end Reset_Scopes_To_Block_Elab_Proc;
4828
4829      --  Local variables
4830
4831      H_Seq     : constant Node_Id := Handled_Statement_Sequence (N);
4832      Elab_Body : Node_Id;
4833      Elab_Call : Node_Id;
4834
4835   --  Start of processing for Check_Unnesting_Elaboration_Code
4836
4837   begin
4838      if Present (H_Seq) then
4839         Reset_Scopes_To_Block_Elab_Proc (Statements (H_Seq));
4840
4841         --  There may be subprograms declared in the exception handlers
4842         --  of the current body.
4843
4844         if Present (Exception_Handlers (H_Seq)) then
4845            declare
4846               Handler : Node_Id := First (Exception_Handlers (H_Seq));
4847            begin
4848               while Present (Handler) loop
4849                  Reset_Scopes_To_Block_Elab_Proc (Statements (Handler));
4850
4851                  Next (Handler);
4852               end loop;
4853            end;
4854         end if;
4855
4856         if Present (Block_Elab_Proc) then
4857            Elab_Body :=
4858              Make_Subprogram_Body (Loc,
4859                Specification              =>
4860                  Make_Procedure_Specification (Loc,
4861                    Defining_Unit_Name => Block_Elab_Proc),
4862                Declarations               => New_List,
4863                Handled_Statement_Sequence =>
4864                  Relocate_Node (Handled_Statement_Sequence (N)));
4865
4866            Elab_Call :=
4867              Make_Procedure_Call_Statement (Loc,
4868                Name => New_Occurrence_Of (Block_Elab_Proc, Loc));
4869
4870            Append_To (Declarations (N), Elab_Body);
4871            Analyze (Elab_Body);
4872            Set_Has_Nested_Subprogram (Block_Elab_Proc);
4873
4874            Set_Handled_Statement_Sequence (N,
4875              Make_Handled_Sequence_Of_Statements (Loc,
4876                Statements => New_List (Elab_Call)));
4877
4878            Analyze (Elab_Call);
4879
4880            --  Could we reset the scopes of entities associated with the new
4881            --  procedure here via a loop over entities rather than doing it in
4882            --  the recursive Reset_Scopes_To_Elab_Proc procedure???
4883         end if;
4884      end if;
4885   end Check_Unnesting_Elaboration_Code;
4886
4887   ---------------------------------------
4888   -- Check_Unnesting_In_Decls_Or_Stmts --
4889   ---------------------------------------
4890
4891   procedure Check_Unnesting_In_Decls_Or_Stmts (Decls_Or_Stmts : List_Id) is
4892      Decl_Or_Stmt : Node_Id;
4893
4894   begin
4895      if Unnest_Subprogram_Mode
4896        and then Present (Decls_Or_Stmts)
4897      then
4898         Decl_Or_Stmt := First (Decls_Or_Stmts);
4899         while Present (Decl_Or_Stmt) loop
4900            if Nkind (Decl_Or_Stmt) = N_Block_Statement
4901              and then Contains_Subprogram (Entity (Identifier (Decl_Or_Stmt)))
4902            then
4903               Unnest_Block (Decl_Or_Stmt);
4904
4905            --  If-statements may contain subprogram bodies at the outer level
4906            --  of their statement lists, and the subprograms may make up-level
4907            --  references (such as to objects declared in the same statement
4908            --  list). Unlike block and loop cases, however, we don't have an
4909            --  entity on which to test the Contains_Subprogram flag, so
4910            --  Unnest_If_Statement must traverse the statement lists to
4911            --  determine whether there are nested subprograms present.
4912
4913            elsif Nkind (Decl_Or_Stmt) = N_If_Statement then
4914               Unnest_If_Statement (Decl_Or_Stmt);
4915
4916            elsif Nkind (Decl_Or_Stmt) = N_Loop_Statement then
4917               declare
4918                  Id : constant Entity_Id :=
4919                         Entity (Identifier (Decl_Or_Stmt));
4920
4921               begin
4922                  --  When a top-level loop within declarations of a library
4923                  --  package spec or body contains nested subprograms, we wrap
4924                  --  it in a procedure to handle possible up-level references
4925                  --  to entities associated with the loop (such as loop
4926                  --  parameters).
4927
4928                  if Present (Id) and then Contains_Subprogram (Id) then
4929                     Unnest_Loop (Decl_Or_Stmt);
4930                  end if;
4931               end;
4932
4933            elsif Nkind (Decl_Or_Stmt) = N_Package_Declaration
4934              and then not Modify_Tree_For_C
4935            then
4936               Check_Unnesting_In_Decls_Or_Stmts
4937                 (Visible_Declarations (Specification (Decl_Or_Stmt)));
4938               Check_Unnesting_In_Decls_Or_Stmts
4939                 (Private_Declarations (Specification (Decl_Or_Stmt)));
4940
4941            elsif Nkind (Decl_Or_Stmt) = N_Package_Body
4942              and then not Modify_Tree_For_C
4943            then
4944               Check_Unnesting_In_Decls_Or_Stmts (Declarations (Decl_Or_Stmt));
4945               if Present (Statements
4946                    (Handled_Statement_Sequence (Decl_Or_Stmt)))
4947               then
4948                  Check_Unnesting_In_Decls_Or_Stmts (Statements
4949                    (Handled_Statement_Sequence (Decl_Or_Stmt)));
4950                  Check_Unnesting_In_Handlers (Decl_Or_Stmt);
4951               end if;
4952            end if;
4953
4954            Next (Decl_Or_Stmt);
4955         end loop;
4956      end if;
4957   end Check_Unnesting_In_Decls_Or_Stmts;
4958
4959   ---------------------------------
4960   -- Check_Unnesting_In_Handlers --
4961   ---------------------------------
4962
4963   procedure Check_Unnesting_In_Handlers (N : Node_Id) is
4964      Stmt_Seq : constant Node_Id := Handled_Statement_Sequence (N);
4965
4966   begin
4967      if Present (Stmt_Seq)
4968        and then Present (Exception_Handlers (Stmt_Seq))
4969      then
4970         declare
4971            Handler : Node_Id := First (Exception_Handlers (Stmt_Seq));
4972         begin
4973            while Present (Handler) loop
4974               if Present (Statements (Handler)) then
4975                  Check_Unnesting_In_Decls_Or_Stmts (Statements (Handler));
4976               end if;
4977
4978               Next (Handler);
4979            end loop;
4980         end;
4981      end if;
4982   end Check_Unnesting_In_Handlers;
4983
4984   ------------------------------
4985   -- Check_Visibly_Controlled --
4986   ------------------------------
4987
4988   procedure Check_Visibly_Controlled
4989     (Prim : Final_Primitives;
4990      Typ  : Entity_Id;
4991      E    : in out Entity_Id;
4992      Cref : in out Node_Id)
4993   is
4994      Parent_Type : Entity_Id;
4995      Op          : Entity_Id;
4996
4997   begin
4998      if Is_Derived_Type (Typ)
4999        and then Comes_From_Source (E)
5000        and then not Present (Overridden_Operation (E))
5001      then
5002         --  We know that the explicit operation on the type does not override
5003         --  the inherited operation of the parent, and that the derivation
5004         --  is from a private type that is not visibly controlled.
5005
5006         Parent_Type := Etype (Typ);
5007         Op := Find_Optional_Prim_Op (Parent_Type, Name_Of (Prim));
5008
5009         if Present (Op) then
5010            E := Op;
5011
5012            --  Wrap the object to be initialized into the proper
5013            --  unchecked conversion, to be compatible with the operation
5014            --  to be called.
5015
5016            if Nkind (Cref) = N_Unchecked_Type_Conversion then
5017               Cref := Unchecked_Convert_To (Parent_Type, Expression (Cref));
5018            else
5019               Cref := Unchecked_Convert_To (Parent_Type, Cref);
5020            end if;
5021         end if;
5022      end if;
5023   end Check_Visibly_Controlled;
5024
5025   --------------------------
5026   --  Contains_Subprogram --
5027   --------------------------
5028
5029   function Contains_Subprogram (Blk : Entity_Id) return Boolean is
5030      E : Entity_Id;
5031
5032   begin
5033      E := First_Entity (Blk);
5034
5035      while Present (E) loop
5036         if Is_Subprogram (E) then
5037            return True;
5038
5039         elsif Ekind (E) in E_Block | E_Loop
5040           and then Contains_Subprogram (E)
5041         then
5042            return True;
5043         end if;
5044
5045         Next_Entity (E);
5046      end loop;
5047
5048      return False;
5049   end Contains_Subprogram;
5050
5051   ------------------
5052   -- Convert_View --
5053   ------------------
5054
5055   function Convert_View
5056     (Proc : Entity_Id;
5057      Arg  : Node_Id;
5058      Ind  : Pos := 1) return Node_Id
5059   is
5060      Fent : Entity_Id := First_Entity (Proc);
5061      Ftyp : Entity_Id;
5062      Atyp : Entity_Id;
5063
5064   begin
5065      for J in 2 .. Ind loop
5066         Next_Entity (Fent);
5067      end loop;
5068
5069      Ftyp := Etype (Fent);
5070
5071      if Nkind (Arg) in N_Type_Conversion | N_Unchecked_Type_Conversion then
5072         Atyp := Entity (Subtype_Mark (Arg));
5073      else
5074         Atyp := Etype (Arg);
5075      end if;
5076
5077      if Is_Abstract_Subprogram (Proc) and then Is_Tagged_Type (Ftyp) then
5078         return Unchecked_Convert_To (Class_Wide_Type (Ftyp), Arg);
5079
5080      elsif Ftyp /= Atyp
5081        and then Present (Atyp)
5082        and then (Is_Private_Type (Ftyp) or else Is_Private_Type (Atyp))
5083        and then Base_Type (Underlying_Type (Atyp)) =
5084                 Base_Type (Underlying_Type (Ftyp))
5085      then
5086         return Unchecked_Convert_To (Ftyp, Arg);
5087
5088      --  If the argument is already a conversion, as generated by
5089      --  Make_Init_Call, set the target type to the type of the formal
5090      --  directly, to avoid spurious typing problems.
5091
5092      elsif Nkind (Arg) in N_Unchecked_Type_Conversion | N_Type_Conversion
5093        and then not Is_Class_Wide_Type (Atyp)
5094      then
5095         Set_Subtype_Mark (Arg, New_Occurrence_Of (Ftyp, Sloc (Arg)));
5096         Set_Etype (Arg, Ftyp);
5097         return Arg;
5098
5099      --  Otherwise, introduce a conversion when the designated object
5100      --  has a type derived from the formal of the controlled routine.
5101
5102      elsif Is_Private_Type (Ftyp)
5103        and then Present (Atyp)
5104        and then Is_Derived_Type (Underlying_Type (Base_Type (Atyp)))
5105      then
5106         return Unchecked_Convert_To (Ftyp, Arg);
5107
5108      else
5109         return Arg;
5110      end if;
5111   end Convert_View;
5112
5113   ------------------------
5114   -- Enclosing_Function --
5115   ------------------------
5116
5117   function Enclosing_Function (E : Entity_Id) return Entity_Id is
5118      Func_Id : Entity_Id;
5119
5120   begin
5121      Func_Id := E;
5122      while Present (Func_Id) and then Func_Id /= Standard_Standard loop
5123         if Ekind (Func_Id) = E_Function then
5124            return Func_Id;
5125         end if;
5126
5127         Func_Id := Scope (Func_Id);
5128      end loop;
5129
5130      return Empty;
5131   end Enclosing_Function;
5132
5133   -------------------------------
5134   -- Establish_Transient_Scope --
5135   -------------------------------
5136
5137   --  This procedure is called each time a transient block has to be inserted
5138   --  that is to say for each call to a function with unconstrained or tagged
5139   --  result. It creates a new scope on the scope stack in order to enclose
5140   --  all transient variables generated.
5141
5142   procedure Establish_Transient_Scope
5143     (N                : Node_Id;
5144      Manage_Sec_Stack : Boolean)
5145   is
5146      function Is_Package_Or_Subprogram (Id : Entity_Id) return Boolean;
5147      --  Determine whether arbitrary Id denotes a package or subprogram [body]
5148
5149      function Find_Enclosing_Transient_Scope return Entity_Id;
5150      --  Examine the scope stack looking for the nearest enclosing transient
5151      --  scope within the innermost enclosing package or subprogram. Return
5152      --  Empty if no such scope exists.
5153
5154      function Find_Transient_Context (N : Node_Id) return Node_Id;
5155      --  Locate a suitable context for arbitrary node N which may need to be
5156      --  serviced by a transient scope. Return Empty if no suitable context
5157      --  is available.
5158
5159      procedure Delegate_Sec_Stack_Management;
5160      --  Move the management of the secondary stack to the nearest enclosing
5161      --  suitable scope.
5162
5163      procedure Create_Transient_Scope (Context : Node_Id);
5164      --  Place a new scope on the scope stack in order to service construct
5165      --  Context. Context is the node found by Find_Transient_Context. The
5166      --  new scope may also manage the secondary stack.
5167
5168      ----------------------------
5169      -- Create_Transient_Scope --
5170      ----------------------------
5171
5172      procedure Create_Transient_Scope (Context : Node_Id) is
5173         Loc : constant Source_Ptr := Sloc (N);
5174
5175         Iter_Loop  : Entity_Id;
5176         Trans_Scop : constant Entity_Id :=
5177           New_Internal_Entity (E_Block, Current_Scope, Loc, 'B');
5178
5179      begin
5180         Set_Etype (Trans_Scop, Standard_Void_Type);
5181
5182         --  Push a new scope, and set its Node_To_Be_Wrapped and Is_Transient
5183         --  fields.
5184
5185         Push_Scope (Trans_Scop);
5186         Scope_Stack.Table (Scope_Stack.Last).Node_To_Be_Wrapped := Context;
5187         Set_Scope_Is_Transient;
5188
5189         --  The transient scope must also manage the secondary stack
5190
5191         if Manage_Sec_Stack then
5192            Set_Uses_Sec_Stack (Trans_Scop);
5193            Check_Restriction (No_Secondary_Stack, N);
5194
5195            --  The expansion of iterator loops generates references to objects
5196            --  in order to extract elements from a container:
5197
5198            --    Ref : Reference_Type_Ptr := Reference (Container, Cursor);
5199            --    Obj : <object type> renames Ref.all.Element.all;
5200
5201            --  These references are controlled and returned on the secondary
5202            --  stack. A new reference is created at each iteration of the loop
5203            --  and as a result it must be finalized and the space occupied by
5204            --  it on the secondary stack reclaimed at the end of the current
5205            --  iteration.
5206
5207            --  When the context that requires a transient scope is a call to
5208            --  routine Reference, the node to be wrapped is the source object:
5209
5210            --    for Obj of Container loop
5211
5212            --  Routine Wrap_Transient_Declaration however does not generate
5213            --  a physical block as wrapping a declaration will kill it too
5214            --  early. To handle this peculiar case, mark the related iterator
5215            --  loop as requiring the secondary stack. This signals the
5216            --  finalization machinery to manage the secondary stack (see
5217            --  routine Process_Statements_For_Controlled_Objects).
5218
5219            Iter_Loop := Find_Enclosing_Iterator_Loop (Trans_Scop);
5220
5221            if Present (Iter_Loop) then
5222               Set_Uses_Sec_Stack (Iter_Loop);
5223            end if;
5224         end if;
5225
5226         if Debug_Flag_W then
5227            Write_Str ("    <Transient>");
5228            Write_Eol;
5229         end if;
5230      end Create_Transient_Scope;
5231
5232      -----------------------------------
5233      -- Delegate_Sec_Stack_Management --
5234      -----------------------------------
5235
5236      procedure Delegate_Sec_Stack_Management is
5237      begin
5238         for Index in reverse Scope_Stack.First .. Scope_Stack.Last loop
5239            declare
5240               Scope : Scope_Stack_Entry renames Scope_Stack.Table (Index);
5241            begin
5242               --  Prevent the search from going too far or within the scope
5243               --  space of another unit.
5244
5245               if Scope.Entity = Standard_Standard then
5246                  return;
5247
5248               --  No transient scope should be encountered during the
5249               --  traversal because Establish_Transient_Scope should have
5250               --  already handled this case.
5251
5252               elsif Scope.Is_Transient then
5253                  raise Program_Error;
5254
5255               --  The construct that requires secondary stack management is
5256               --  always enclosed by a package or subprogram scope.
5257
5258               elsif Is_Package_Or_Subprogram (Scope.Entity) then
5259                  Set_Uses_Sec_Stack (Scope.Entity);
5260                  Check_Restriction (No_Secondary_Stack, N);
5261
5262                  return;
5263               end if;
5264            end;
5265         end loop;
5266
5267         --  At this point no suitable scope was found. This should never occur
5268         --  because a construct is always enclosed by a compilation unit which
5269         --  has a scope.
5270
5271         pragma Assert (False);
5272      end Delegate_Sec_Stack_Management;
5273
5274      ------------------------------------
5275      -- Find_Enclosing_Transient_Scope --
5276      ------------------------------------
5277
5278      function Find_Enclosing_Transient_Scope return Entity_Id is
5279      begin
5280         for Index in reverse Scope_Stack.First .. Scope_Stack.Last loop
5281            declare
5282               Scope : Scope_Stack_Entry renames Scope_Stack.Table (Index);
5283            begin
5284               --  Prevent the search from going too far or within the scope
5285               --  space of another unit.
5286
5287               if Scope.Entity = Standard_Standard
5288                 or else Is_Package_Or_Subprogram (Scope.Entity)
5289               then
5290                  exit;
5291
5292               elsif Scope.Is_Transient then
5293                  return Scope.Entity;
5294               end if;
5295            end;
5296         end loop;
5297
5298         return Empty;
5299      end Find_Enclosing_Transient_Scope;
5300
5301      ----------------------------
5302      -- Find_Transient_Context --
5303      ----------------------------
5304
5305      function Find_Transient_Context (N : Node_Id) return Node_Id is
5306         Curr : Node_Id := N;
5307         Prev : Node_Id := Empty;
5308
5309      begin
5310         while Present (Curr) loop
5311            case Nkind (Curr) is
5312
5313               --  Declarations
5314
5315               --  Declarations act as a boundary for a transient scope even if
5316               --  they are not wrapped, see Wrap_Transient_Declaration.
5317
5318               when N_Object_Declaration
5319                  | N_Object_Renaming_Declaration
5320                  | N_Subtype_Declaration
5321               =>
5322                  return Curr;
5323
5324               --  Statements
5325
5326               --  Statements and statement-like constructs act as a boundary
5327               --  for a transient scope.
5328
5329               when N_Accept_Alternative
5330                  | N_Attribute_Definition_Clause
5331                  | N_Case_Statement
5332                  | N_Case_Statement_Alternative
5333                  | N_Code_Statement
5334                  | N_Delay_Alternative
5335                  | N_Delay_Until_Statement
5336                  | N_Delay_Relative_Statement
5337                  | N_Discriminant_Association
5338                  | N_Elsif_Part
5339                  | N_Entry_Body_Formal_Part
5340                  | N_Exit_Statement
5341                  | N_If_Statement
5342                  | N_Iteration_Scheme
5343                  | N_Terminate_Alternative
5344               =>
5345                  pragma Assert (Present (Prev));
5346                  return Prev;
5347
5348               when N_Assignment_Statement =>
5349                  return Curr;
5350
5351               when N_Entry_Call_Statement
5352                  | N_Procedure_Call_Statement
5353               =>
5354                  --  When an entry or procedure call acts as the alternative
5355                  --  of a conditional or timed entry call, the proper context
5356                  --  is that of the alternative.
5357
5358                  if Nkind (Parent (Curr)) = N_Entry_Call_Alternative
5359                    and then Nkind (Parent (Parent (Curr))) in
5360                               N_Conditional_Entry_Call | N_Timed_Entry_Call
5361                  then
5362                     return Parent (Parent (Curr));
5363
5364                  --  General case for entry or procedure calls
5365
5366                  else
5367                     return Curr;
5368                  end if;
5369
5370               when N_Pragma =>
5371
5372                  --  Pragma Check is not a valid transient context in
5373                  --  GNATprove mode because the pragma must remain unchanged.
5374
5375                  if GNATprove_Mode
5376                    and then Get_Pragma_Id (Curr) = Pragma_Check
5377                  then
5378                     return Empty;
5379
5380                  --  General case for pragmas
5381
5382                  else
5383                     return Curr;
5384                  end if;
5385
5386               when N_Raise_Statement =>
5387                  return Curr;
5388
5389               when N_Simple_Return_Statement =>
5390
5391                  --  A return statement is not a valid transient context when
5392                  --  the function itself requires transient scope management
5393                  --  because the result will be reclaimed too early.
5394
5395                  if Requires_Transient_Scope (Etype
5396                       (Return_Applies_To (Return_Statement_Entity (Curr))))
5397                  then
5398                     return Empty;
5399
5400                  --  General case for return statements
5401
5402                  else
5403                     return Curr;
5404                  end if;
5405
5406               --  Special
5407
5408               when N_Attribute_Reference =>
5409                  if Is_Procedure_Attribute_Name (Attribute_Name (Curr)) then
5410                     return Curr;
5411                  end if;
5412
5413               --  An Ada 2012 iterator specification is not a valid context
5414               --  because Analyze_Iterator_Specification already employs
5415               --  special processing for it.
5416
5417               when N_Iterator_Specification =>
5418                  return Empty;
5419
5420               when N_Loop_Parameter_Specification =>
5421
5422                  --  An iteration scheme is not a valid context because
5423                  --  routine Analyze_Iteration_Scheme already employs
5424                  --  special processing.
5425
5426                  if Nkind (Parent (Curr)) = N_Iteration_Scheme then
5427                     return Empty;
5428                  else
5429                     return Parent (Curr);
5430                  end if;
5431
5432               --  Termination
5433
5434               --  The following nodes represent "dummy contexts" which do not
5435               --  need to be wrapped.
5436
5437               when N_Component_Declaration
5438                  | N_Discriminant_Specification
5439                  | N_Parameter_Specification
5440               =>
5441                  return Empty;
5442
5443               --  If the traversal leaves a scope without having been able to
5444               --  find a construct to wrap, something is going wrong, but this
5445               --  can happen in error situations that are not detected yet
5446               --  (such as a dynamic string in a pragma Export).
5447
5448               when N_Block_Statement
5449                  | N_Entry_Body
5450                  | N_Package_Body
5451                  | N_Package_Declaration
5452                  | N_Protected_Body
5453                  | N_Subprogram_Body
5454                  | N_Task_Body
5455               =>
5456                  return Empty;
5457
5458               --  Default
5459
5460               when others =>
5461                  null;
5462            end case;
5463
5464            Prev := Curr;
5465            Curr := Parent (Curr);
5466         end loop;
5467
5468         return Empty;
5469      end Find_Transient_Context;
5470
5471      ------------------------------
5472      -- Is_Package_Or_Subprogram --
5473      ------------------------------
5474
5475      function Is_Package_Or_Subprogram (Id : Entity_Id) return Boolean is
5476      begin
5477         return Ekind (Id) in E_Entry
5478                            | E_Entry_Family
5479                            | E_Function
5480                            | E_Package
5481                            | E_Procedure
5482                            | E_Subprogram_Body;
5483      end Is_Package_Or_Subprogram;
5484
5485      --  Local variables
5486
5487      Trans_Id : constant Entity_Id := Find_Enclosing_Transient_Scope;
5488      Context  : Node_Id;
5489
5490   --  Start of processing for Establish_Transient_Scope
5491
5492   begin
5493      --  Do not create a new transient scope if there is already an enclosing
5494      --  transient scope within the innermost enclosing package or subprogram.
5495
5496      if Present (Trans_Id) then
5497
5498         --  If the transient scope was requested for purposes of managing the
5499         --  secondary stack, then the existing scope must perform this task.
5500
5501         if Manage_Sec_Stack then
5502            Set_Uses_Sec_Stack (Trans_Id);
5503         end if;
5504
5505         return;
5506      end if;
5507
5508      --  Find the construct that must be serviced by a new transient scope, if
5509      --  it exists.
5510
5511      Context := Find_Transient_Context (N);
5512
5513      if Present (Context) then
5514         if Nkind (Context) = N_Assignment_Statement then
5515
5516            --  An assignment statement with suppressed controlled semantics
5517            --  does not need a transient scope because finalization is not
5518            --  desirable at this point. Note that No_Ctrl_Actions is also
5519            --  set for non-controlled assignments to suppress dispatching
5520            --  _assign.
5521
5522            if No_Ctrl_Actions (Context)
5523              and then Needs_Finalization (Etype (Name (Context)))
5524            then
5525               --  When a controlled component is initialized by a function
5526               --  call, the result on the secondary stack is always assigned
5527               --  to the component. Signal the nearest suitable scope that it
5528               --  is safe to manage the secondary stack.
5529
5530               if Manage_Sec_Stack and then Within_Init_Proc then
5531                  Delegate_Sec_Stack_Management;
5532               end if;
5533
5534            --  Otherwise the assignment is a normal transient context and thus
5535            --  requires a transient scope.
5536
5537            else
5538               Create_Transient_Scope (Context);
5539            end if;
5540
5541         --  General case
5542
5543         else
5544            Create_Transient_Scope (Context);
5545         end if;
5546      end if;
5547   end Establish_Transient_Scope;
5548
5549   ----------------------------
5550   -- Expand_Cleanup_Actions --
5551   ----------------------------
5552
5553   procedure Expand_Cleanup_Actions (N : Node_Id) is
5554      pragma Assert
5555        (Nkind (N) in N_Block_Statement
5556                    | N_Entry_Body
5557                    | N_Extended_Return_Statement
5558                    | N_Subprogram_Body
5559                    | N_Task_Body);
5560
5561      Scop : constant Entity_Id := Current_Scope;
5562
5563      Is_Asynchronous_Call   : constant Boolean :=
5564                                 Nkind (N) = N_Block_Statement
5565                                   and then Is_Asynchronous_Call_Block (N);
5566      Is_Master              : constant Boolean :=
5567                                 Nkind (N) /= N_Extended_Return_Statement
5568                                   and then Nkind (N) /= N_Entry_Body
5569                                   and then Is_Task_Master (N);
5570      Is_Protected_Subp_Body : constant Boolean :=
5571                                 Nkind (N) = N_Subprogram_Body
5572                                   and then Is_Protected_Subprogram_Body (N);
5573      Is_Task_Allocation     : constant Boolean :=
5574                                 Nkind (N) = N_Block_Statement
5575                                   and then Is_Task_Allocation_Block (N);
5576      Is_Task_Body           : constant Boolean :=
5577                                 Nkind (Original_Node (N)) = N_Task_Body;
5578
5579      --  We mark the secondary stack if it is used in this construct, and
5580      --  we're not returning a function result on the secondary stack, except
5581      --  that a build-in-place function that might or might not return on the
5582      --  secondary stack always needs a mark. A run-time test is required in
5583      --  the case where the build-in-place function has a BIP_Alloc extra
5584      --  parameter (see Create_Finalizer).
5585
5586      Needs_Sec_Stack_Mark   : constant Boolean :=
5587                                   (Uses_Sec_Stack (Scop)
5588                                     and then
5589                                       not Sec_Stack_Needed_For_Return (Scop))
5590                                 or else
5591                                   (Is_Build_In_Place_Function (Scop)
5592                                     and then Needs_BIP_Alloc_Form (Scop));
5593
5594      Needs_Custom_Cleanup   : constant Boolean :=
5595                                 Nkind (N) = N_Block_Statement
5596                                   and then Present (Cleanup_Actions (N));
5597
5598      Has_Postcondition      : constant Boolean :=
5599                                 Nkind (N) = N_Subprogram_Body
5600                                   and then Present
5601                                              (Postconditions_Proc
5602                                                (Unique_Defining_Entity (N)));
5603
5604      Actions_Required       : constant Boolean :=
5605                                 Requires_Cleanup_Actions (N, True)
5606                                   or else Is_Asynchronous_Call
5607                                   or else Is_Master
5608                                   or else Is_Protected_Subp_Body
5609                                   or else Is_Task_Allocation
5610                                   or else Is_Task_Body
5611                                   or else Needs_Sec_Stack_Mark
5612                                   or else Needs_Custom_Cleanup;
5613
5614      HSS : Node_Id := Handled_Statement_Sequence (N);
5615      Loc : Source_Ptr;
5616      Cln : List_Id;
5617
5618      procedure Wrap_HSS_In_Block;
5619      --  Move HSS inside a new block along with the original exception
5620      --  handlers. Make the newly generated block the sole statement of HSS.
5621
5622      -----------------------
5623      -- Wrap_HSS_In_Block --
5624      -----------------------
5625
5626      procedure Wrap_HSS_In_Block is
5627         Block    : Node_Id;
5628         Block_Id : Entity_Id;
5629         End_Lab  : Node_Id;
5630
5631      begin
5632         --  Preserve end label to provide proper cross-reference information
5633
5634         End_Lab := End_Label (HSS);
5635         Block :=
5636           Make_Block_Statement (Loc, Handled_Statement_Sequence => HSS);
5637
5638         Block_Id := New_Internal_Entity (E_Block, Current_Scope, Loc, 'B');
5639         Set_Identifier (Block, New_Occurrence_Of (Block_Id, Loc));
5640         Set_Etype (Block_Id, Standard_Void_Type);
5641         Set_Block_Node (Block_Id, Identifier (Block));
5642
5643         --  Signal the finalization machinery that this particular block
5644         --  contains the original context.
5645
5646         Set_Is_Finalization_Wrapper (Block);
5647
5648         Set_Handled_Statement_Sequence (N,
5649           Make_Handled_Sequence_Of_Statements (Loc, New_List (Block)));
5650         HSS := Handled_Statement_Sequence (N);
5651
5652         Set_First_Real_Statement (HSS, Block);
5653         Set_End_Label (HSS, End_Lab);
5654
5655         --  Comment needed here, see RH for 1.306 ???
5656
5657         if Nkind (N) = N_Subprogram_Body then
5658            Set_Has_Nested_Block_With_Handler (Scop);
5659         end if;
5660      end Wrap_HSS_In_Block;
5661
5662   --  Start of processing for Expand_Cleanup_Actions
5663
5664   begin
5665      --  The current construct does not need any form of servicing
5666
5667      if not Actions_Required then
5668         return;
5669
5670      --  If the current node is a rewritten task body and the descriptors have
5671      --  not been delayed (due to some nested instantiations), do not generate
5672      --  redundant cleanup actions.
5673
5674      elsif Is_Task_Body
5675        and then Nkind (N) = N_Subprogram_Body
5676        and then not Delay_Subprogram_Descriptors (Corresponding_Spec (N))
5677      then
5678         return;
5679      end if;
5680
5681      --  If an extended return statement contains something like
5682      --
5683      --     X := F (...);
5684      --
5685      --  where F is a build-in-place function call returning a controlled
5686      --  type, then a temporary object will be implicitly declared as part
5687      --  of the statement list, and this will need cleanup. In such cases,
5688      --  we transform:
5689      --
5690      --    return Result : T := ... do
5691      --       <statements> -- possibly with handlers
5692      --    end return;
5693      --
5694      --  into:
5695      --
5696      --    return Result : T := ... do
5697      --       declare -- no declarations
5698      --       begin
5699      --          <statements> -- possibly with handlers
5700      --       end; -- no handlers
5701      --    end return;
5702      --
5703      --  So Expand_Cleanup_Actions will end up being called recursively on the
5704      --  block statement.
5705
5706      if Nkind (N) = N_Extended_Return_Statement then
5707         declare
5708            Block : constant Node_Id :=
5709                      Make_Block_Statement (Sloc (N),
5710                        Declarations               => Empty_List,
5711                        Handled_Statement_Sequence =>
5712                          Handled_Statement_Sequence (N));
5713         begin
5714            Set_Handled_Statement_Sequence (N,
5715              Make_Handled_Sequence_Of_Statements (Sloc (N),
5716                Statements => New_List (Block)));
5717
5718            Analyze (Block);
5719         end;
5720
5721         --  Analysis of the block did all the work
5722
5723         return;
5724      end if;
5725
5726      if Needs_Custom_Cleanup then
5727         Cln := Cleanup_Actions (N);
5728      else
5729         Cln := No_List;
5730      end if;
5731
5732      declare
5733         Decls     : List_Id := Declarations (N);
5734         Fin_Id    : Entity_Id;
5735         Mark      : Entity_Id := Empty;
5736         New_Decls : List_Id;
5737
5738      begin
5739         --  If we are generating expanded code for debugging purposes, use the
5740         --  Sloc of the point of insertion for the cleanup code. The Sloc will
5741         --  be updated subsequently to reference the proper line in .dg files.
5742         --  If we are not debugging generated code, use No_Location instead,
5743         --  so that no debug information is generated for the cleanup code.
5744         --  This makes the behavior of the NEXT command in GDB monotonic, and
5745         --  makes the placement of breakpoints more accurate.
5746
5747         if Debug_Generated_Code then
5748            Loc := Sloc (Scop);
5749         else
5750            Loc := No_Location;
5751         end if;
5752
5753         --  A task activation call has already been built for a task
5754         --  allocation block.
5755
5756         if not Is_Task_Allocation then
5757            Build_Task_Activation_Call (N);
5758         end if;
5759
5760         if Is_Master then
5761            Establish_Task_Master (N);
5762         end if;
5763
5764         New_Decls := New_List;
5765
5766         --  If secondary stack is in use, generate:
5767         --
5768         --    Mnn : constant Mark_Id := SS_Mark;
5769
5770         if Needs_Sec_Stack_Mark then
5771            Mark := Make_Temporary (Loc, 'M');
5772
5773            Append_To (New_Decls, Build_SS_Mark_Call (Loc, Mark));
5774            Set_Uses_Sec_Stack (Scop, False);
5775         end if;
5776
5777         --  If exception handlers are present, wrap the sequence of statements
5778         --  in a block since it is not possible to have exception handlers and
5779         --  an At_End handler in the same construct.
5780
5781         if Present (Exception_Handlers (HSS)) then
5782            Wrap_HSS_In_Block;
5783
5784         --  Ensure that the First_Real_Statement field is set
5785
5786         elsif No (First_Real_Statement (HSS)) then
5787            Set_First_Real_Statement (HSS, First (Statements (HSS)));
5788         end if;
5789
5790         --  Do not move the Activation_Chain declaration in the context of
5791         --  task allocation blocks. Task allocation blocks use _chain in their
5792         --  cleanup handlers and gigi complains if it is declared in the
5793         --  sequence of statements of the scope that declares the handler.
5794
5795         if Is_Task_Allocation then
5796            declare
5797               Chain : constant Entity_Id := Activation_Chain_Entity (N);
5798               Decl  : Node_Id;
5799
5800            begin
5801               Decl := First (Decls);
5802               while Nkind (Decl) /= N_Object_Declaration
5803                 or else Defining_Identifier (Decl) /= Chain
5804               loop
5805                  Next (Decl);
5806
5807                  --  A task allocation block should always include a _chain
5808                  --  declaration.
5809
5810                  pragma Assert (Present (Decl));
5811               end loop;
5812
5813               Remove (Decl);
5814               Prepend_To (New_Decls, Decl);
5815            end;
5816         end if;
5817
5818         --  Move the _postconditions subprogram declaration and its associated
5819         --  objects into the declarations section so that it is callable
5820         --  within _postconditions.
5821
5822         if Has_Postcondition then
5823            declare
5824               Decl      : Node_Id;
5825               Prev_Decl : Node_Id;
5826
5827            begin
5828               Decl :=
5829                 Prev (Subprogram_Body
5830                        (Postconditions_Proc (Current_Subprogram)));
5831               while Present (Decl) loop
5832                  Prev_Decl := Prev (Decl);
5833
5834                  Remove (Decl);
5835                  Prepend_To (New_Decls, Decl);
5836
5837                  exit when Nkind (Decl) = N_Subprogram_Declaration
5838                              and then Chars (Corresponding_Body (Decl))
5839                                         = Name_uPostconditions;
5840
5841                  Decl := Prev_Decl;
5842               end loop;
5843            end;
5844         end if;
5845
5846         --  Ensure the presence of a declaration list in order to successfully
5847         --  append all original statements to it.
5848
5849         if No (Decls) then
5850            Set_Declarations (N, New_List);
5851            Decls := Declarations (N);
5852         end if;
5853
5854         --  Move the declarations into the sequence of statements in order to
5855         --  have them protected by the At_End handler. It may seem weird to
5856         --  put declarations in the sequence of statement but in fact nothing
5857         --  forbids that at the tree level.
5858
5859         Append_List_To (Decls, Statements (HSS));
5860         Set_Statements (HSS, Decls);
5861
5862         --  Reset the Sloc of the handled statement sequence to properly
5863         --  reflect the new initial "statement" in the sequence.
5864
5865         Set_Sloc (HSS, Sloc (First (Decls)));
5866
5867         --  The declarations of finalizer spec and auxiliary variables replace
5868         --  the old declarations that have been moved inward.
5869
5870         Set_Declarations (N, New_Decls);
5871         Analyze_Declarations (New_Decls);
5872
5873         --  Generate finalization calls for all controlled objects appearing
5874         --  in the statements of N. Add context specific cleanup for various
5875         --  constructs.
5876
5877         Build_Finalizer
5878           (N           => N,
5879            Clean_Stmts => Build_Cleanup_Statements (N, Cln),
5880            Mark_Id     => Mark,
5881            Top_Decls   => New_Decls,
5882            Defer_Abort => Nkind (Original_Node (N)) = N_Task_Body
5883                             or else Is_Master,
5884            Fin_Id      => Fin_Id);
5885
5886         if Present (Fin_Id) then
5887            Build_Finalizer_Call (N, Fin_Id);
5888         end if;
5889      end;
5890   end Expand_Cleanup_Actions;
5891
5892   ---------------------------
5893   -- Expand_N_Package_Body --
5894   ---------------------------
5895
5896   --  Add call to Activate_Tasks if body is an activator (actual processing
5897   --  is in chapter 9).
5898
5899   --  Generate subprogram descriptor for elaboration routine
5900
5901   --  Encode entity names in package body
5902
5903   procedure Expand_N_Package_Body (N : Node_Id) is
5904      Spec_Id : constant Entity_Id := Corresponding_Spec (N);
5905      Fin_Id  : Entity_Id;
5906
5907   begin
5908      --  This is done only for non-generic packages
5909
5910      if Ekind (Spec_Id) = E_Package then
5911         Push_Scope (Spec_Id);
5912
5913         --  Build dispatch tables of library level tagged types
5914
5915         if Tagged_Type_Expansion
5916           and then Is_Library_Level_Entity (Spec_Id)
5917         then
5918            Build_Static_Dispatch_Tables (N);
5919         end if;
5920
5921         Expand_CUDA_Package (N);
5922
5923         Build_Task_Activation_Call (N);
5924
5925         --  Verify the run-time semantics of pragma Initial_Condition at the
5926         --  end of the body statements.
5927
5928         Expand_Pragma_Initial_Condition (Spec_Id, N);
5929
5930         --  If this is a library-level package and unnesting is enabled,
5931         --  check for the presence of blocks with nested subprograms occurring
5932         --  in elaboration code, and generate procedures to encapsulate the
5933         --  blocks in case the nested subprograms make up-level references.
5934
5935         if Unnest_Subprogram_Mode
5936           and then
5937             Is_Library_Level_Entity (Current_Scope)
5938         then
5939            Check_Unnesting_Elaboration_Code (N);
5940            Check_Unnesting_In_Decls_Or_Stmts (Declarations (N));
5941            Check_Unnesting_In_Handlers (N);
5942         end if;
5943
5944         Pop_Scope;
5945      end if;
5946
5947      Set_Elaboration_Flag (N, Spec_Id);
5948      Set_In_Package_Body (Spec_Id, False);
5949
5950      --  Set to encode entity names in package body before gigi is called
5951
5952      Qualify_Entity_Names (N);
5953
5954      if Ekind (Spec_Id) /= E_Generic_Package then
5955         Build_Finalizer
5956           (N           => N,
5957            Clean_Stmts => No_List,
5958            Mark_Id     => Empty,
5959            Top_Decls   => No_List,
5960            Defer_Abort => False,
5961            Fin_Id      => Fin_Id);
5962
5963         if Present (Fin_Id) then
5964            declare
5965               Body_Ent : Node_Id := Defining_Unit_Name (N);
5966
5967            begin
5968               if Nkind (Body_Ent) = N_Defining_Program_Unit_Name then
5969                  Body_Ent := Defining_Identifier (Body_Ent);
5970               end if;
5971
5972               Set_Finalizer (Body_Ent, Fin_Id);
5973            end;
5974         end if;
5975      end if;
5976   end Expand_N_Package_Body;
5977
5978   ----------------------------------
5979   -- Expand_N_Package_Declaration --
5980   ----------------------------------
5981
5982   --  Add call to Activate_Tasks if there are tasks declared and the package
5983   --  has no body. Note that in Ada 83 this may result in premature activation
5984   --  of some tasks, given that we cannot tell whether a body will eventually
5985   --  appear.
5986
5987   procedure Expand_N_Package_Declaration (N : Node_Id) is
5988      Id     : constant Entity_Id := Defining_Entity (N);
5989      Spec   : constant Node_Id   := Specification (N);
5990      Decls  : List_Id;
5991      Fin_Id : Entity_Id;
5992
5993      No_Body : Boolean := False;
5994      --  True in the case of a package declaration that is a compilation
5995      --  unit and for which no associated body will be compiled in this
5996      --  compilation.
5997
5998   begin
5999      --  Case of a package declaration other than a compilation unit
6000
6001      if Nkind (Parent (N)) /= N_Compilation_Unit then
6002         null;
6003
6004      --  Case of a compilation unit that does not require a body
6005
6006      elsif not Body_Required (Parent (N))
6007        and then not Unit_Requires_Body (Id)
6008      then
6009         No_Body := True;
6010
6011      --  Special case of generating calling stubs for a remote call interface
6012      --  package: even though the package declaration requires one, the body
6013      --  won't be processed in this compilation (so any stubs for RACWs
6014      --  declared in the package must be generated here, along with the spec).
6015
6016      elsif Parent (N) = Cunit (Main_Unit)
6017        and then Is_Remote_Call_Interface (Id)
6018        and then Distribution_Stub_Mode = Generate_Caller_Stub_Body
6019      then
6020         No_Body := True;
6021      end if;
6022
6023      --  For a nested instance, delay processing until freeze point
6024
6025      if Has_Delayed_Freeze (Id)
6026        and then Nkind (Parent (N)) /= N_Compilation_Unit
6027      then
6028         return;
6029      end if;
6030
6031      --  For a package declaration that implies no associated body, generate
6032      --  task activation call and RACW supporting bodies now (since we won't
6033      --  have a specific separate compilation unit for that).
6034
6035      if No_Body then
6036         Push_Scope (Id);
6037
6038         --  Generate RACW subprogram bodies
6039
6040         if Has_RACW (Id) then
6041            Decls := Private_Declarations (Spec);
6042
6043            if No (Decls) then
6044               Decls := Visible_Declarations (Spec);
6045            end if;
6046
6047            if No (Decls) then
6048               Decls := New_List;
6049               Set_Visible_Declarations (Spec, Decls);
6050            end if;
6051
6052            Append_RACW_Bodies (Decls, Id);
6053            Analyze_List (Decls);
6054         end if;
6055
6056         --  Generate task activation call as last step of elaboration
6057
6058         if Present (Activation_Chain_Entity (N)) then
6059            Build_Task_Activation_Call (N);
6060         end if;
6061
6062         --  Verify the run-time semantics of pragma Initial_Condition at the
6063         --  end of the private declarations when the package lacks a body.
6064
6065         Expand_Pragma_Initial_Condition (Id, N);
6066
6067         Pop_Scope;
6068      end if;
6069
6070      --  Build dispatch tables of library-level tagged types
6071
6072      if Tagged_Type_Expansion
6073        and then (Is_Compilation_Unit (Id)
6074                   or else (Is_Generic_Instance (Id)
6075                             and then Is_Library_Level_Entity (Id)))
6076      then
6077         Build_Static_Dispatch_Tables (N);
6078      end if;
6079
6080      --  Note: it is not necessary to worry about generating a subprogram
6081      --  descriptor, since the only way to get exception handlers into a
6082      --  package spec is to include instantiations, and that would cause
6083      --  generation of subprogram descriptors to be delayed in any case.
6084
6085      --  Set to encode entity names in package spec before gigi is called
6086
6087      Qualify_Entity_Names (N);
6088
6089      if Ekind (Id) /= E_Generic_Package then
6090         Build_Finalizer
6091           (N           => N,
6092            Clean_Stmts => No_List,
6093            Mark_Id     => Empty,
6094            Top_Decls   => No_List,
6095            Defer_Abort => False,
6096            Fin_Id      => Fin_Id);
6097
6098         Set_Finalizer (Id, Fin_Id);
6099      end if;
6100
6101      --  If this is a library-level package and unnesting is enabled,
6102      --  check for the presence of blocks with nested subprograms occurring
6103      --  in elaboration code, and generate procedures to encapsulate the
6104      --  blocks in case the nested subprograms make up-level references.
6105
6106      if Unnest_Subprogram_Mode
6107        and then Is_Library_Level_Entity (Current_Scope)
6108      then
6109         Check_Unnesting_In_Decls_Or_Stmts (Visible_Declarations (Spec));
6110         Check_Unnesting_In_Decls_Or_Stmts (Private_Declarations (Spec));
6111      end if;
6112   end Expand_N_Package_Declaration;
6113
6114   ---------------------------------
6115   -- Has_Simple_Protected_Object --
6116   ---------------------------------
6117
6118   function Has_Simple_Protected_Object (T : Entity_Id) return Boolean is
6119   begin
6120      if Has_Task (T) then
6121         return False;
6122
6123      elsif Is_Simple_Protected_Type (T) then
6124         return True;
6125
6126      elsif Is_Array_Type (T) then
6127         return Has_Simple_Protected_Object (Component_Type (T));
6128
6129      elsif Is_Record_Type (T) then
6130         declare
6131            Comp : Entity_Id;
6132
6133         begin
6134            Comp := First_Component (T);
6135            while Present (Comp) loop
6136               if Has_Simple_Protected_Object (Etype (Comp)) then
6137                  return True;
6138               end if;
6139
6140               Next_Component (Comp);
6141            end loop;
6142
6143            return False;
6144         end;
6145
6146      else
6147         return False;
6148      end if;
6149   end Has_Simple_Protected_Object;
6150
6151   ------------------------------------
6152   -- Insert_Actions_In_Scope_Around --
6153   ------------------------------------
6154
6155   procedure Insert_Actions_In_Scope_Around
6156     (N         : Node_Id;
6157      Clean     : Boolean;
6158      Manage_SS : Boolean)
6159   is
6160      Act_Before  : constant List_Id :=
6161        Scope_Stack.Table (Scope_Stack.Last).Actions_To_Be_Wrapped (Before);
6162      Act_After   : constant List_Id :=
6163        Scope_Stack.Table (Scope_Stack.Last).Actions_To_Be_Wrapped (After);
6164      Act_Cleanup : constant List_Id :=
6165        Scope_Stack.Table (Scope_Stack.Last).Actions_To_Be_Wrapped (Cleanup);
6166      --  Note: We used to use renamings of Scope_Stack.Table (Scope_Stack.
6167      --  Last), but this was incorrect as Process_Transients_In_Scope may
6168      --  introduce new scopes and cause a reallocation of Scope_Stack.Table.
6169
6170      procedure Process_Transients_In_Scope
6171        (First_Object : Node_Id;
6172         Last_Object  : Node_Id;
6173         Related_Node : Node_Id);
6174      --  Find all transient objects in the list First_Object .. Last_Object
6175      --  and generate finalization actions for them. Related_Node denotes the
6176      --  node which created all transient objects.
6177
6178      ---------------------------------
6179      -- Process_Transients_In_Scope --
6180      ---------------------------------
6181
6182      procedure Process_Transients_In_Scope
6183        (First_Object : Node_Id;
6184         Last_Object  : Node_Id;
6185         Related_Node : Node_Id)
6186      is
6187         Must_Hook : Boolean := False;
6188         --  Flag denoting whether the context requires transient object
6189         --  export to the outer finalizer.
6190
6191         function Is_Subprogram_Call (N : Node_Id) return Traverse_Result;
6192         --  Determine whether an arbitrary node denotes a subprogram call
6193
6194         procedure Detect_Subprogram_Call is
6195           new Traverse_Proc (Is_Subprogram_Call);
6196
6197         procedure Process_Transient_In_Scope
6198           (Obj_Decl  : Node_Id;
6199            Blk_Data  : Finalization_Exception_Data;
6200            Blk_Stmts : List_Id);
6201         --  Generate finalization actions for a single transient object
6202         --  denoted by object declaration Obj_Decl. Blk_Data is the
6203         --  exception data of the enclosing block. Blk_Stmts denotes the
6204         --  statements of the enclosing block.
6205
6206         ------------------------
6207         -- Is_Subprogram_Call --
6208         ------------------------
6209
6210         function Is_Subprogram_Call (N : Node_Id) return Traverse_Result is
6211         begin
6212            --  A regular procedure or function call
6213
6214            if Nkind (N) in N_Subprogram_Call then
6215               Must_Hook := True;
6216               return Abandon;
6217
6218            --  Special cases
6219
6220            --  Heavy expansion may relocate function calls outside the related
6221            --  node. Inspect the original node to detect the initial placement
6222            --  of the call.
6223
6224            elsif Is_Rewrite_Substitution (N) then
6225               Detect_Subprogram_Call (Original_Node (N));
6226
6227               if Must_Hook then
6228                  return Abandon;
6229               else
6230                  return OK;
6231               end if;
6232
6233            --  Generalized indexing always involves a function call
6234
6235            elsif Nkind (N) = N_Indexed_Component
6236              and then Present (Generalized_Indexing (N))
6237            then
6238               Must_Hook := True;
6239               return Abandon;
6240
6241            --  Keep searching
6242
6243            else
6244               return OK;
6245            end if;
6246         end Is_Subprogram_Call;
6247
6248         --------------------------------
6249         -- Process_Transient_In_Scope --
6250         --------------------------------
6251
6252         procedure Process_Transient_In_Scope
6253           (Obj_Decl  : Node_Id;
6254            Blk_Data  : Finalization_Exception_Data;
6255            Blk_Stmts : List_Id)
6256         is
6257            Loc         : constant Source_Ptr := Sloc (Obj_Decl);
6258            Obj_Id      : constant Entity_Id  := Defining_Entity (Obj_Decl);
6259            Fin_Call    : Node_Id;
6260            Fin_Stmts   : List_Id;
6261            Hook_Assign : Node_Id;
6262            Hook_Clear  : Node_Id;
6263            Hook_Decl   : Node_Id;
6264            Hook_Insert : Node_Id;
6265            Ptr_Decl    : Node_Id;
6266
6267         begin
6268            --  Mark the transient object as successfully processed to avoid
6269            --  double finalization.
6270
6271            Set_Is_Finalized_Transient (Obj_Id);
6272
6273            --  Construct all the pieces necessary to hook and finalize the
6274            --  transient object.
6275
6276            Build_Transient_Object_Statements
6277              (Obj_Decl    => Obj_Decl,
6278               Fin_Call    => Fin_Call,
6279               Hook_Assign => Hook_Assign,
6280               Hook_Clear  => Hook_Clear,
6281               Hook_Decl   => Hook_Decl,
6282               Ptr_Decl    => Ptr_Decl);
6283
6284            --  The context contains at least one subprogram call which may
6285            --  raise an exception. This scenario employs "hooking" to pass
6286            --  transient objects to the enclosing finalizer in case of an
6287            --  exception.
6288
6289            if Must_Hook then
6290
6291               --  Add the access type which provides a reference to the
6292               --  transient object. Generate:
6293
6294               --    type Ptr_Typ is access all Desig_Typ;
6295
6296               Insert_Action (Obj_Decl, Ptr_Decl);
6297
6298               --  Add the temporary which acts as a hook to the transient
6299               --  object. Generate:
6300
6301               --    Hook : Ptr_Typ := null;
6302
6303               Insert_Action (Obj_Decl, Hook_Decl);
6304
6305               --  When the transient object is initialized by an aggregate,
6306               --  the hook must capture the object after the last aggregate
6307               --  assignment takes place. Only then is the object considered
6308               --  fully initialized. Generate:
6309
6310               --    Hook := Ptr_Typ (Obj_Id);
6311               --      <or>
6312               --    Hook := Obj_Id'Unrestricted_Access;
6313
6314               --  Similarly if we have a build in place call: we must
6315               --  initialize Hook only after the call has happened, otherwise
6316               --  Obj_Id will not be initialized yet.
6317
6318               if Ekind (Obj_Id) in E_Constant | E_Variable then
6319                  if Present (Last_Aggregate_Assignment (Obj_Id)) then
6320                     Hook_Insert := Last_Aggregate_Assignment (Obj_Id);
6321                  elsif Present (BIP_Initialization_Call (Obj_Id)) then
6322                     Hook_Insert := BIP_Initialization_Call (Obj_Id);
6323                  else
6324                     Hook_Insert := Obj_Decl;
6325                  end if;
6326
6327               --  Otherwise the hook seizes the related object immediately
6328
6329               else
6330                  Hook_Insert := Obj_Decl;
6331               end if;
6332
6333               Insert_After_And_Analyze (Hook_Insert, Hook_Assign);
6334            end if;
6335
6336            --  When exception propagation is enabled wrap the hook clear
6337            --  statement and the finalization call into a block to catch
6338            --  potential exceptions raised during finalization. Generate:
6339
6340            --    begin
6341            --       [Hook := null;]
6342            --       [Deep_]Finalize (Obj_Ref);
6343
6344            --    exception
6345            --       when others =>
6346            --          if not Raised then
6347            --             Raised := True;
6348            --             Save_Occurrence
6349            --               (Enn, Get_Current_Excep.all.all);
6350            --          end if;
6351            --    end;
6352
6353            if Exceptions_OK then
6354               Fin_Stmts := New_List;
6355
6356               if Must_Hook then
6357                  Append_To (Fin_Stmts, Hook_Clear);
6358               end if;
6359
6360               Append_To (Fin_Stmts, Fin_Call);
6361
6362               Prepend_To (Blk_Stmts,
6363                 Make_Block_Statement (Loc,
6364                   Handled_Statement_Sequence =>
6365                     Make_Handled_Sequence_Of_Statements (Loc,
6366                       Statements         => Fin_Stmts,
6367                       Exception_Handlers => New_List (
6368                         Build_Exception_Handler (Blk_Data)))));
6369
6370            --  Otherwise generate:
6371
6372            --    [Hook := null;]
6373            --    [Deep_]Finalize (Obj_Ref);
6374
6375            --  Note that the statements are inserted in reverse order to
6376            --  achieve the desired final order outlined above.
6377
6378            else
6379               Prepend_To (Blk_Stmts, Fin_Call);
6380
6381               if Must_Hook then
6382                  Prepend_To (Blk_Stmts, Hook_Clear);
6383               end if;
6384            end if;
6385         end Process_Transient_In_Scope;
6386
6387         --  Local variables
6388
6389         Built     : Boolean := False;
6390         Blk_Data  : Finalization_Exception_Data;
6391         Blk_Decl  : Node_Id := Empty;
6392         Blk_Decls : List_Id := No_List;
6393         Blk_Ins   : Node_Id;
6394         Blk_Stmts : List_Id := No_List;
6395         Loc       : Source_Ptr := No_Location;
6396         Obj_Decl  : Node_Id;
6397
6398      --  Start of processing for Process_Transients_In_Scope
6399
6400      begin
6401         --  The expansion performed by this routine is as follows:
6402
6403         --    type Ptr_Typ_1 is access all Ctrl_Trans_Obj_1_Typ;
6404         --    Hook_1 : Ptr_Typ_1 := null;
6405         --    Ctrl_Trans_Obj_1 : ...;
6406         --    Hook_1 := Ctrl_Trans_Obj_1'Unrestricted_Access;
6407         --    . . .
6408         --    type Ptr_Typ_N is access all Ctrl_Trans_Obj_N_Typ;
6409         --    Hook_N : Ptr_Typ_N := null;
6410         --    Ctrl_Trans_Obj_N : ...;
6411         --    Hook_N := Ctrl_Trans_Obj_N'Unrestricted_Access;
6412
6413         --    declare
6414         --       Abrt   : constant Boolean := ...;
6415         --       Ex     : Exception_Occurrence;
6416         --       Raised : Boolean := False;
6417
6418         --    begin
6419         --       Abort_Defer;
6420
6421         --       begin
6422         --          Hook_N := null;
6423         --          [Deep_]Finalize (Ctrl_Trans_Obj_N);
6424
6425         --       exception
6426         --          when others =>
6427         --             if not Raised then
6428         --                Raised := True;
6429         --                Save_Occurrence (Ex, Get_Current_Excep.all.all);
6430         --       end;
6431         --       . . .
6432         --       begin
6433         --          Hook_1 := null;
6434         --          [Deep_]Finalize (Ctrl_Trans_Obj_1);
6435
6436         --       exception
6437         --          when others =>
6438         --             if not Raised then
6439         --                Raised := True;
6440         --                Save_Occurrence (Ex, Get_Current_Excep.all.all);
6441         --       end;
6442
6443         --       Abort_Undefer;
6444
6445         --       if Raised and not Abrt then
6446         --          Raise_From_Controlled_Operation (Ex);
6447         --       end if;
6448         --    end;
6449
6450         --  Recognize a scenario where the transient context is an object
6451         --  declaration initialized by a build-in-place function call:
6452
6453         --    Obj : ... := BIP_Function_Call (Ctrl_Func_Call);
6454
6455         --  The rough expansion of the above is:
6456
6457         --    Temp : ... := Ctrl_Func_Call;
6458         --    Obj  : ...;
6459         --    Res  : ... := BIP_Func_Call (..., Obj, ...);
6460
6461         --  The finalization of any transient object must happen after the
6462         --  build-in-place function call is executed.
6463
6464         if Nkind (N) = N_Object_Declaration
6465           and then Present (BIP_Initialization_Call (Defining_Identifier (N)))
6466         then
6467            Must_Hook := True;
6468            Blk_Ins   := BIP_Initialization_Call (Defining_Identifier (N));
6469
6470         --  Search the context for at least one subprogram call. If found, the
6471         --  machinery exports all transient objects to the enclosing finalizer
6472         --  due to the possibility of abnormal call termination.
6473
6474         else
6475            Detect_Subprogram_Call (N);
6476            Blk_Ins := Last_Object;
6477         end if;
6478
6479         if Clean then
6480            Insert_List_After_And_Analyze (Blk_Ins, Act_Cleanup);
6481         end if;
6482
6483         --  Examine all objects in the list First_Object .. Last_Object
6484
6485         Obj_Decl := First_Object;
6486         while Present (Obj_Decl) loop
6487            if Nkind (Obj_Decl) = N_Object_Declaration
6488              and then Analyzed (Obj_Decl)
6489              and then Is_Finalizable_Transient (Obj_Decl, N)
6490
6491              --  Do not process the node to be wrapped since it will be
6492              --  handled by the enclosing finalizer.
6493
6494              and then Obj_Decl /= Related_Node
6495            then
6496               Loc := Sloc (Obj_Decl);
6497
6498               --  Before generating the cleanup code for the first transient
6499               --  object, create a wrapper block which houses all hook clear
6500               --  statements and finalization calls. This wrapper is needed by
6501               --  the back end.
6502
6503               if not Built then
6504                  Built     := True;
6505                  Blk_Stmts := New_List;
6506
6507                  --  Generate:
6508                  --    Abrt   : constant Boolean := ...;
6509                  --    Ex     : Exception_Occurrence;
6510                  --    Raised : Boolean := False;
6511
6512                  if Exceptions_OK then
6513                     Blk_Decls := New_List;
6514                     Build_Object_Declarations (Blk_Data, Blk_Decls, Loc);
6515                  end if;
6516
6517                  Blk_Decl :=
6518                    Make_Block_Statement (Loc,
6519                      Declarations               => Blk_Decls,
6520                      Handled_Statement_Sequence =>
6521                        Make_Handled_Sequence_Of_Statements (Loc,
6522                          Statements => Blk_Stmts));
6523               end if;
6524
6525               --  Construct all necessary circuitry to hook and finalize a
6526               --  single transient object.
6527
6528               pragma Assert (Present (Blk_Stmts));
6529               Process_Transient_In_Scope
6530                 (Obj_Decl  => Obj_Decl,
6531                  Blk_Data  => Blk_Data,
6532                  Blk_Stmts => Blk_Stmts);
6533            end if;
6534
6535            --  Terminate the scan after the last object has been processed to
6536            --  avoid touching unrelated code.
6537
6538            if Obj_Decl = Last_Object then
6539               exit;
6540            end if;
6541
6542            Next (Obj_Decl);
6543         end loop;
6544
6545         --  Complete the decoration of the enclosing finalization block and
6546         --  insert it into the tree.
6547
6548         if Present (Blk_Decl) then
6549
6550            pragma Assert (Present (Blk_Stmts));
6551            pragma Assert (Loc /= No_Location);
6552
6553            --  Note that this Abort_Undefer does not require a extra block or
6554            --  an AT_END handler because each finalization exception is caught
6555            --  in its own corresponding finalization block. As a result, the
6556            --  call to Abort_Defer always takes place.
6557
6558            if Abort_Allowed then
6559               Prepend_To (Blk_Stmts,
6560                 Build_Runtime_Call (Loc, RE_Abort_Defer));
6561
6562               Append_To (Blk_Stmts,
6563                 Build_Runtime_Call (Loc, RE_Abort_Undefer));
6564            end if;
6565
6566            --  Generate:
6567            --    if Raised and then not Abrt then
6568            --       Raise_From_Controlled_Operation (Ex);
6569            --    end if;
6570
6571            if Exceptions_OK then
6572               Append_To (Blk_Stmts, Build_Raise_Statement (Blk_Data));
6573            end if;
6574
6575            Insert_After_And_Analyze (Blk_Ins, Blk_Decl);
6576         end if;
6577      end Process_Transients_In_Scope;
6578
6579      --  Local variables
6580
6581      Loc          : constant Source_Ptr := Sloc (N);
6582      Node_To_Wrap : constant Node_Id    := Node_To_Be_Wrapped;
6583      First_Obj    : Node_Id;
6584      Last_Obj     : Node_Id;
6585      Mark_Id      : Entity_Id;
6586      Target       : Node_Id;
6587
6588   --  Start of processing for Insert_Actions_In_Scope_Around
6589
6590   begin
6591      --  Nothing to do if the scope does not manage the secondary stack or
6592      --  does not contain meaningful actions for insertion.
6593
6594      if not Manage_SS
6595        and then No (Act_Before)
6596        and then No (Act_After)
6597        and then No (Act_Cleanup)
6598      then
6599         return;
6600      end if;
6601
6602      --  If the node to be wrapped is the trigger of an asynchronous select,
6603      --  it is not part of a statement list. The actions must be inserted
6604      --  before the select itself, which is part of some list of statements.
6605      --  Note that the triggering alternative includes the triggering
6606      --  statement and an optional statement list. If the node to be
6607      --  wrapped is part of that list, the normal insertion applies.
6608
6609      if Nkind (Parent (Node_To_Wrap)) = N_Triggering_Alternative
6610        and then not Is_List_Member (Node_To_Wrap)
6611      then
6612         Target := Parent (Parent (Node_To_Wrap));
6613      else
6614         Target := N;
6615      end if;
6616
6617      First_Obj := Target;
6618      Last_Obj  := Target;
6619
6620      --  Add all actions associated with a transient scope into the main tree.
6621      --  There are several scenarios here:
6622
6623      --       +--- Before ----+        +----- After ---+
6624      --    1) First_Obj ....... Target ........ Last_Obj
6625
6626      --    2) First_Obj ....... Target
6627
6628      --    3)                   Target ........ Last_Obj
6629
6630      --  Flag declarations are inserted before the first object
6631
6632      if Present (Act_Before) then
6633         First_Obj := First (Act_Before);
6634         Insert_List_Before (Target, Act_Before);
6635      end if;
6636
6637      --  Finalization calls are inserted after the last object
6638
6639      if Present (Act_After) then
6640         Last_Obj := Last (Act_After);
6641         Insert_List_After (Target, Act_After);
6642      end if;
6643
6644      --  Mark and release the secondary stack when the context warrants it
6645
6646      if Manage_SS then
6647         Mark_Id := Make_Temporary (Loc, 'M');
6648
6649         --  Generate:
6650         --    Mnn : constant Mark_Id := SS_Mark;
6651
6652         Insert_Before_And_Analyze
6653           (First_Obj, Build_SS_Mark_Call (Loc, Mark_Id));
6654
6655         --  Generate:
6656         --    SS_Release (Mnn);
6657
6658         Insert_After_And_Analyze
6659           (Last_Obj, Build_SS_Release_Call (Loc, Mark_Id));
6660      end if;
6661
6662      --  Check for transient objects associated with Target and generate the
6663      --  appropriate finalization actions for them.
6664
6665      Process_Transients_In_Scope
6666        (First_Object => First_Obj,
6667         Last_Object  => Last_Obj,
6668         Related_Node => Target);
6669
6670      --  Reset the action lists
6671
6672      Scope_Stack.Table
6673        (Scope_Stack.Last).Actions_To_Be_Wrapped (Before) := No_List;
6674      Scope_Stack.Table
6675        (Scope_Stack.Last).Actions_To_Be_Wrapped (After)  := No_List;
6676
6677      if Clean then
6678         Scope_Stack.Table
6679           (Scope_Stack.Last).Actions_To_Be_Wrapped (Cleanup) := No_List;
6680      end if;
6681   end Insert_Actions_In_Scope_Around;
6682
6683   ------------------------------
6684   -- Is_Simple_Protected_Type --
6685   ------------------------------
6686
6687   function Is_Simple_Protected_Type (T : Entity_Id) return Boolean is
6688   begin
6689      return
6690        Is_Protected_Type (T)
6691          and then not Uses_Lock_Free (T)
6692          and then not Has_Entries (T)
6693          and then Is_RTE (Find_Protection_Type (T), RE_Protection);
6694   end Is_Simple_Protected_Type;
6695
6696   -----------------------
6697   -- Make_Adjust_Call --
6698   -----------------------
6699
6700   function Make_Adjust_Call
6701     (Obj_Ref   : Node_Id;
6702      Typ       : Entity_Id;
6703      Skip_Self : Boolean := False) return Node_Id
6704   is
6705      Loc    : constant Source_Ptr := Sloc (Obj_Ref);
6706      Adj_Id : Entity_Id := Empty;
6707      Ref    : Node_Id;
6708      Utyp   : Entity_Id;
6709
6710   begin
6711      Ref := Obj_Ref;
6712
6713      --  Recover the proper type which contains Deep_Adjust
6714
6715      if Is_Class_Wide_Type (Typ) then
6716         Utyp := Root_Type (Typ);
6717      else
6718         Utyp := Typ;
6719      end if;
6720
6721      Utyp := Underlying_Type (Base_Type (Utyp));
6722      Set_Assignment_OK (Ref);
6723
6724      --  Deal with untagged derivation of private views
6725
6726      if Present (Utyp) and then Is_Untagged_Derivation (Typ) then
6727         Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
6728         Ref  := Unchecked_Convert_To (Utyp, Ref);
6729         Set_Assignment_OK (Ref);
6730      end if;
6731
6732      --  When dealing with the completion of a private type, use the base
6733      --  type instead.
6734
6735      if Present (Utyp) and then Utyp /= Base_Type (Utyp) then
6736         pragma Assert (Is_Private_Type (Typ));
6737
6738         Utyp := Base_Type (Utyp);
6739         Ref  := Unchecked_Convert_To (Utyp, Ref);
6740      end if;
6741
6742      --  The underlying type may not be present due to a missing full view. In
6743      --  this case freezing did not take place and there is no [Deep_]Adjust
6744      --  primitive to call.
6745
6746      if No (Utyp) then
6747         return Empty;
6748
6749      elsif Skip_Self then
6750         if Has_Controlled_Component (Utyp) then
6751            if Is_Tagged_Type (Utyp) then
6752               Adj_Id := Find_Optional_Prim_Op (Utyp, TSS_Deep_Adjust);
6753            else
6754               Adj_Id := TSS (Utyp, TSS_Deep_Adjust);
6755            end if;
6756         end if;
6757
6758      --  Class-wide types, interfaces and types with controlled components
6759
6760      elsif Is_Class_Wide_Type (Typ)
6761        or else Is_Interface (Typ)
6762        or else Has_Controlled_Component (Utyp)
6763      then
6764         if Is_Tagged_Type (Utyp) then
6765            Adj_Id := Find_Optional_Prim_Op (Utyp, TSS_Deep_Adjust);
6766         else
6767            Adj_Id := TSS (Utyp, TSS_Deep_Adjust);
6768         end if;
6769
6770      --  Derivations from [Limited_]Controlled
6771
6772      elsif Is_Controlled (Utyp) then
6773         if Has_Controlled_Component (Utyp) then
6774            Adj_Id := Find_Optional_Prim_Op (Utyp, TSS_Deep_Adjust);
6775         else
6776            Adj_Id := Find_Optional_Prim_Op (Utyp, Name_Of (Adjust_Case));
6777         end if;
6778
6779      --  Tagged types
6780
6781      elsif Is_Tagged_Type (Utyp) then
6782         Adj_Id := Find_Optional_Prim_Op (Utyp, TSS_Deep_Adjust);
6783
6784      else
6785         raise Program_Error;
6786      end if;
6787
6788      if Present (Adj_Id) then
6789
6790         --  If the object is unanalyzed, set its expected type for use in
6791         --  Convert_View in case an additional conversion is needed.
6792
6793         if No (Etype (Ref))
6794           and then Nkind (Ref) /= N_Unchecked_Type_Conversion
6795         then
6796            Set_Etype (Ref, Typ);
6797         end if;
6798
6799         --  The object reference may need another conversion depending on the
6800         --  type of the formal and that of the actual.
6801
6802         if not Is_Class_Wide_Type (Typ) then
6803            Ref := Convert_View (Adj_Id, Ref);
6804         end if;
6805
6806         return
6807           Make_Call (Loc,
6808             Proc_Id   => Adj_Id,
6809             Param     => Ref,
6810             Skip_Self => Skip_Self);
6811      else
6812         return Empty;
6813      end if;
6814   end Make_Adjust_Call;
6815
6816   ---------------
6817   -- Make_Call --
6818   ---------------
6819
6820   function Make_Call
6821     (Loc       : Source_Ptr;
6822      Proc_Id   : Entity_Id;
6823      Param     : Node_Id;
6824      Skip_Self : Boolean := False) return Node_Id
6825   is
6826      Params : constant List_Id := New_List (Param);
6827
6828   begin
6829      --  Do not apply the controlled action to the object itself by signaling
6830      --  the related routine to avoid self.
6831
6832      if Skip_Self then
6833         Append_To (Params, New_Occurrence_Of (Standard_False, Loc));
6834      end if;
6835
6836      return
6837        Make_Procedure_Call_Statement (Loc,
6838          Name                   => New_Occurrence_Of (Proc_Id, Loc),
6839          Parameter_Associations => Params);
6840   end Make_Call;
6841
6842   --------------------------
6843   -- Make_Deep_Array_Body --
6844   --------------------------
6845
6846   function Make_Deep_Array_Body
6847     (Prim : Final_Primitives;
6848      Typ  : Entity_Id) return List_Id
6849   is
6850      function Build_Adjust_Or_Finalize_Statements
6851        (Typ : Entity_Id) return List_Id;
6852      --  Create the statements necessary to adjust or finalize an array of
6853      --  controlled elements. Generate:
6854      --
6855      --    declare
6856      --       Abort  : constant Boolean := Triggered_By_Abort;
6857      --         <or>
6858      --       Abort  : constant Boolean := False;  --  no abort
6859      --
6860      --       E      : Exception_Occurrence;
6861      --       Raised : Boolean := False;
6862      --
6863      --    begin
6864      --       for J1 in [reverse] Typ'First (1) .. Typ'Last (1) loop
6865      --                 ^--  in the finalization case
6866      --          ...
6867      --          for Jn in [reverse] Typ'First (n) .. Typ'Last (n) loop
6868      --             begin
6869      --                [Deep_]Adjust / Finalize (V (J1, ..., Jn));
6870      --
6871      --             exception
6872      --                when others =>
6873      --                   if not Raised then
6874      --                      Raised := True;
6875      --                      Save_Occurrence (E, Get_Current_Excep.all.all);
6876      --                   end if;
6877      --             end;
6878      --          end loop;
6879      --          ...
6880      --       end loop;
6881      --
6882      --       if Raised and then not Abort then
6883      --          Raise_From_Controlled_Operation (E);
6884      --       end if;
6885      --    end;
6886
6887      function Build_Initialize_Statements (Typ : Entity_Id) return List_Id;
6888      --  Create the statements necessary to initialize an array of controlled
6889      --  elements. Include a mechanism to carry out partial finalization if an
6890      --  exception occurs. Generate:
6891      --
6892      --    declare
6893      --       Counter : Integer := 0;
6894      --
6895      --    begin
6896      --       for J1 in V'Range (1) loop
6897      --          ...
6898      --          for JN in V'Range (N) loop
6899      --             begin
6900      --                [Deep_]Initialize (V (J1, ..., JN));
6901      --
6902      --                Counter := Counter + 1;
6903      --
6904      --             exception
6905      --                when others =>
6906      --                   declare
6907      --                      Abort  : constant Boolean := Triggered_By_Abort;
6908      --                        <or>
6909      --                      Abort  : constant Boolean := False; --  no abort
6910      --                      E      : Exception_Occurrence;
6911      --                      Raised : Boolean := False;
6912
6913      --                   begin
6914      --                      Counter :=
6915      --                        V'Length (1) *
6916      --                        V'Length (2) *
6917      --                        ...
6918      --                        V'Length (N) - Counter;
6919
6920      --                      for F1 in reverse V'Range (1) loop
6921      --                         ...
6922      --                         for FN in reverse V'Range (N) loop
6923      --                            if Counter > 0 then
6924      --                               Counter := Counter - 1;
6925      --                            else
6926      --                               begin
6927      --                                  [Deep_]Finalize (V (F1, ..., FN));
6928
6929      --                               exception
6930      --                                  when others =>
6931      --                                     if not Raised then
6932      --                                        Raised := True;
6933      --                                        Save_Occurrence (E,
6934      --                                          Get_Current_Excep.all.all);
6935      --                                     end if;
6936      --                               end;
6937      --                            end if;
6938      --                         end loop;
6939      --                         ...
6940      --                      end loop;
6941      --                   end;
6942      --
6943      --                   if Raised and then not Abort then
6944      --                      Raise_From_Controlled_Operation (E);
6945      --                   end if;
6946      --
6947      --                   raise;
6948      --             end;
6949      --          end loop;
6950      --       end loop;
6951      --    end;
6952
6953      function New_References_To
6954        (L   : List_Id;
6955         Loc : Source_Ptr) return List_Id;
6956      --  Given a list of defining identifiers, return a list of references to
6957      --  the original identifiers, in the same order as they appear.
6958
6959      -----------------------------------------
6960      -- Build_Adjust_Or_Finalize_Statements --
6961      -----------------------------------------
6962
6963      function Build_Adjust_Or_Finalize_Statements
6964        (Typ : Entity_Id) return List_Id
6965      is
6966         Comp_Typ   : constant Entity_Id  := Component_Type (Typ);
6967         Index_List : constant List_Id    := New_List;
6968         Loc        : constant Source_Ptr := Sloc (Typ);
6969         Num_Dims   : constant Int        := Number_Dimensions (Typ);
6970
6971         procedure Build_Indexes;
6972         --  Generate the indexes used in the dimension loops
6973
6974         -------------------
6975         -- Build_Indexes --
6976         -------------------
6977
6978         procedure Build_Indexes is
6979         begin
6980            --  Generate the following identifiers:
6981            --    Jnn  -  for initialization
6982
6983            for Dim in 1 .. Num_Dims loop
6984               Append_To (Index_List,
6985                 Make_Defining_Identifier (Loc, New_External_Name ('J', Dim)));
6986            end loop;
6987         end Build_Indexes;
6988
6989         --  Local variables
6990
6991         Final_Decls : List_Id := No_List;
6992         Final_Data  : Finalization_Exception_Data;
6993         Block       : Node_Id;
6994         Call        : Node_Id;
6995         Comp_Ref    : Node_Id;
6996         Core_Loop   : Node_Id;
6997         Dim         : Int;
6998         J           : Entity_Id;
6999         Loop_Id     : Entity_Id;
7000         Stmts       : List_Id;
7001
7002      --  Start of processing for Build_Adjust_Or_Finalize_Statements
7003
7004      begin
7005         Final_Decls := New_List;
7006
7007         Build_Indexes;
7008         Build_Object_Declarations (Final_Data, Final_Decls, Loc);
7009
7010         Comp_Ref :=
7011           Make_Indexed_Component (Loc,
7012             Prefix      => Make_Identifier (Loc, Name_V),
7013             Expressions => New_References_To (Index_List, Loc));
7014         Set_Etype (Comp_Ref, Comp_Typ);
7015
7016         --  Generate:
7017         --    [Deep_]Adjust (V (J1, ..., JN))
7018
7019         if Prim = Adjust_Case then
7020            Call := Make_Adjust_Call (Obj_Ref => Comp_Ref, Typ => Comp_Typ);
7021
7022         --  Generate:
7023         --    [Deep_]Finalize (V (J1, ..., JN))
7024
7025         else pragma Assert (Prim = Finalize_Case);
7026            Call := Make_Final_Call (Obj_Ref => Comp_Ref, Typ => Comp_Typ);
7027         end if;
7028
7029         if Present (Call) then
7030
7031            --  Generate the block which houses the adjust or finalize call:
7032
7033            --    begin
7034            --       <adjust or finalize call>
7035
7036            --    exception
7037            --       when others =>
7038            --          if not Raised then
7039            --             Raised := True;
7040            --             Save_Occurrence (E, Get_Current_Excep.all.all);
7041            --          end if;
7042            --    end;
7043
7044            if Exceptions_OK then
7045               Core_Loop :=
7046                 Make_Block_Statement (Loc,
7047                   Handled_Statement_Sequence =>
7048                     Make_Handled_Sequence_Of_Statements (Loc,
7049                       Statements         => New_List (Call),
7050                       Exception_Handlers => New_List (
7051                         Build_Exception_Handler (Final_Data))));
7052            else
7053               Core_Loop := Call;
7054            end if;
7055
7056            --  Generate the dimension loops starting from the innermost one
7057
7058            --    for Jnn in [reverse] V'Range (Dim) loop
7059            --       <core loop>
7060            --    end loop;
7061
7062            J := Last (Index_List);
7063            Dim := Num_Dims;
7064            while Present (J) and then Dim > 0 loop
7065               Loop_Id := J;
7066               Prev (J);
7067               Remove (Loop_Id);
7068
7069               Core_Loop :=
7070                 Make_Loop_Statement (Loc,
7071                   Iteration_Scheme =>
7072                     Make_Iteration_Scheme (Loc,
7073                       Loop_Parameter_Specification =>
7074                         Make_Loop_Parameter_Specification (Loc,
7075                           Defining_Identifier         => Loop_Id,
7076                           Discrete_Subtype_Definition =>
7077                             Make_Attribute_Reference (Loc,
7078                               Prefix         => Make_Identifier (Loc, Name_V),
7079                               Attribute_Name => Name_Range,
7080                               Expressions    => New_List (
7081                                 Make_Integer_Literal (Loc, Dim))),
7082
7083                           Reverse_Present             =>
7084                             Prim = Finalize_Case)),
7085
7086                   Statements       => New_List (Core_Loop),
7087                   End_Label        => Empty);
7088
7089               Dim := Dim - 1;
7090            end loop;
7091
7092            --  Generate the block which contains the core loop, declarations
7093            --  of the abort flag, the exception occurrence, the raised flag
7094            --  and the conditional raise:
7095
7096            --    declare
7097            --       Abort  : constant Boolean := Triggered_By_Abort;
7098            --         <or>
7099            --       Abort  : constant Boolean := False;  --  no abort
7100
7101            --       E      : Exception_Occurrence;
7102            --       Raised : Boolean := False;
7103
7104            --    begin
7105            --       <core loop>
7106
7107            --       if Raised and then not Abort then
7108            --          Raise_From_Controlled_Operation (E);
7109            --       end if;
7110            --    end;
7111
7112            Stmts := New_List (Core_Loop);
7113
7114            if Exceptions_OK then
7115               Append_To (Stmts, Build_Raise_Statement (Final_Data));
7116            end if;
7117
7118            Block :=
7119              Make_Block_Statement (Loc,
7120                Declarations               => Final_Decls,
7121                Handled_Statement_Sequence =>
7122                  Make_Handled_Sequence_Of_Statements (Loc,
7123                    Statements => Stmts));
7124
7125         --  Otherwise previous errors or a missing full view may prevent the
7126         --  proper freezing of the component type. If this is the case, there
7127         --  is no [Deep_]Adjust or [Deep_]Finalize primitive to call.
7128
7129         else
7130            Block := Make_Null_Statement (Loc);
7131         end if;
7132
7133         return New_List (Block);
7134      end Build_Adjust_Or_Finalize_Statements;
7135
7136      ---------------------------------
7137      -- Build_Initialize_Statements --
7138      ---------------------------------
7139
7140      function Build_Initialize_Statements (Typ : Entity_Id) return List_Id is
7141         Comp_Typ   : constant Entity_Id  := Component_Type (Typ);
7142         Final_List : constant List_Id    := New_List;
7143         Index_List : constant List_Id    := New_List;
7144         Loc        : constant Source_Ptr := Sloc (Typ);
7145         Num_Dims   : constant Int        := Number_Dimensions (Typ);
7146
7147         function Build_Assignment (Counter_Id : Entity_Id) return Node_Id;
7148         --  Generate the following assignment:
7149         --    Counter := V'Length (1) *
7150         --               ...
7151         --               V'Length (N) - Counter;
7152         --
7153         --  Counter_Id denotes the entity of the counter.
7154
7155         function Build_Finalization_Call return Node_Id;
7156         --  Generate a deep finalization call for an array element
7157
7158         procedure Build_Indexes;
7159         --  Generate the initialization and finalization indexes used in the
7160         --  dimension loops.
7161
7162         function Build_Initialization_Call return Node_Id;
7163         --  Generate a deep initialization call for an array element
7164
7165         ----------------------
7166         -- Build_Assignment --
7167         ----------------------
7168
7169         function Build_Assignment (Counter_Id : Entity_Id) return Node_Id is
7170            Dim  : Int;
7171            Expr : Node_Id;
7172
7173         begin
7174            --  Start from the first dimension and generate:
7175            --    V'Length (1)
7176
7177            Dim := 1;
7178            Expr :=
7179              Make_Attribute_Reference (Loc,
7180                Prefix         => Make_Identifier (Loc, Name_V),
7181                Attribute_Name => Name_Length,
7182                Expressions    => New_List (Make_Integer_Literal (Loc, Dim)));
7183
7184            --  Process the rest of the dimensions, generate:
7185            --    Expr * V'Length (N)
7186
7187            Dim := Dim + 1;
7188            while Dim <= Num_Dims loop
7189               Expr :=
7190                 Make_Op_Multiply (Loc,
7191                   Left_Opnd  => Expr,
7192                   Right_Opnd =>
7193                     Make_Attribute_Reference (Loc,
7194                       Prefix         => Make_Identifier (Loc, Name_V),
7195                       Attribute_Name => Name_Length,
7196                       Expressions    => New_List (
7197                         Make_Integer_Literal (Loc, Dim))));
7198
7199               Dim := Dim + 1;
7200            end loop;
7201
7202            --  Generate:
7203            --    Counter := Expr - Counter;
7204
7205            return
7206              Make_Assignment_Statement (Loc,
7207                Name       => New_Occurrence_Of (Counter_Id, Loc),
7208                Expression =>
7209                  Make_Op_Subtract (Loc,
7210                    Left_Opnd  => Expr,
7211                    Right_Opnd => New_Occurrence_Of (Counter_Id, Loc)));
7212         end Build_Assignment;
7213
7214         -----------------------------
7215         -- Build_Finalization_Call --
7216         -----------------------------
7217
7218         function Build_Finalization_Call return Node_Id is
7219            Comp_Ref : constant Node_Id :=
7220                         Make_Indexed_Component (Loc,
7221                           Prefix      => Make_Identifier (Loc, Name_V),
7222                           Expressions => New_References_To (Final_List, Loc));
7223
7224         begin
7225            Set_Etype (Comp_Ref, Comp_Typ);
7226
7227            --  Generate:
7228            --    [Deep_]Finalize (V);
7229
7230            return Make_Final_Call (Obj_Ref => Comp_Ref, Typ => Comp_Typ);
7231         end Build_Finalization_Call;
7232
7233         -------------------
7234         -- Build_Indexes --
7235         -------------------
7236
7237         procedure Build_Indexes is
7238         begin
7239            --  Generate the following identifiers:
7240            --    Jnn  -  for initialization
7241            --    Fnn  -  for finalization
7242
7243            for Dim in 1 .. Num_Dims loop
7244               Append_To (Index_List,
7245                 Make_Defining_Identifier (Loc, New_External_Name ('J', Dim)));
7246
7247               Append_To (Final_List,
7248                 Make_Defining_Identifier (Loc, New_External_Name ('F', Dim)));
7249            end loop;
7250         end Build_Indexes;
7251
7252         -------------------------------
7253         -- Build_Initialization_Call --
7254         -------------------------------
7255
7256         function Build_Initialization_Call return Node_Id is
7257            Comp_Ref : constant Node_Id :=
7258                         Make_Indexed_Component (Loc,
7259                           Prefix      => Make_Identifier (Loc, Name_V),
7260                           Expressions => New_References_To (Index_List, Loc));
7261
7262         begin
7263            Set_Etype (Comp_Ref, Comp_Typ);
7264
7265            --  Generate:
7266            --    [Deep_]Initialize (V (J1, ..., JN));
7267
7268            return Make_Init_Call (Obj_Ref => Comp_Ref, Typ => Comp_Typ);
7269         end Build_Initialization_Call;
7270
7271         --  Local variables
7272
7273         Counter_Id  : Entity_Id;
7274         Dim         : Int;
7275         F           : Node_Id;
7276         Fin_Stmt    : Node_Id;
7277         Final_Block : Node_Id;
7278         Final_Data  : Finalization_Exception_Data;
7279         Final_Decls : List_Id := No_List;
7280         Final_Loop  : Node_Id;
7281         Init_Block  : Node_Id;
7282         Init_Call   : Node_Id;
7283         Init_Loop   : Node_Id;
7284         J           : Node_Id;
7285         Loop_Id     : Node_Id;
7286         Stmts       : List_Id;
7287
7288      --  Start of processing for Build_Initialize_Statements
7289
7290      begin
7291         Counter_Id  := Make_Temporary (Loc, 'C');
7292         Final_Decls := New_List;
7293
7294         Build_Indexes;
7295         Build_Object_Declarations (Final_Data, Final_Decls, Loc);
7296
7297         --  Generate the block which houses the finalization call, the index
7298         --  guard and the handler which triggers Program_Error later on.
7299
7300         --    if Counter > 0 then
7301         --       Counter := Counter - 1;
7302         --    else
7303         --       begin
7304         --          [Deep_]Finalize (V (F1, ..., FN));
7305         --       exception
7306         --          when others =>
7307         --             if not Raised then
7308         --                Raised := True;
7309         --                Save_Occurrence (E, Get_Current_Excep.all.all);
7310         --             end if;
7311         --       end;
7312         --    end if;
7313
7314         Fin_Stmt := Build_Finalization_Call;
7315
7316         if Present (Fin_Stmt) then
7317            if Exceptions_OK then
7318               Fin_Stmt :=
7319                 Make_Block_Statement (Loc,
7320                   Handled_Statement_Sequence =>
7321                     Make_Handled_Sequence_Of_Statements (Loc,
7322                       Statements         => New_List (Fin_Stmt),
7323                       Exception_Handlers => New_List (
7324                         Build_Exception_Handler (Final_Data))));
7325            end if;
7326
7327            --  This is the core of the loop, the dimension iterators are added
7328            --  one by one in reverse.
7329
7330            Final_Loop :=
7331              Make_If_Statement (Loc,
7332                Condition =>
7333                  Make_Op_Gt (Loc,
7334                    Left_Opnd  => New_Occurrence_Of (Counter_Id, Loc),
7335                    Right_Opnd => Make_Integer_Literal (Loc, 0)),
7336
7337                Then_Statements => New_List (
7338                  Make_Assignment_Statement (Loc,
7339                    Name       => New_Occurrence_Of (Counter_Id, Loc),
7340                    Expression =>
7341                      Make_Op_Subtract (Loc,
7342                        Left_Opnd  => New_Occurrence_Of (Counter_Id, Loc),
7343                        Right_Opnd => Make_Integer_Literal (Loc, 1)))),
7344
7345                Else_Statements => New_List (Fin_Stmt));
7346
7347            --  Generate all finalization loops starting from the innermost
7348            --  dimension.
7349
7350            --    for Fnn in reverse V'Range (Dim) loop
7351            --       <final loop>
7352            --    end loop;
7353
7354            F := Last (Final_List);
7355            Dim := Num_Dims;
7356            while Present (F) and then Dim > 0 loop
7357               Loop_Id := F;
7358               Prev (F);
7359               Remove (Loop_Id);
7360
7361               Final_Loop :=
7362                 Make_Loop_Statement (Loc,
7363                   Iteration_Scheme =>
7364                     Make_Iteration_Scheme (Loc,
7365                       Loop_Parameter_Specification =>
7366                         Make_Loop_Parameter_Specification (Loc,
7367                           Defining_Identifier         => Loop_Id,
7368                           Discrete_Subtype_Definition =>
7369                             Make_Attribute_Reference (Loc,
7370                               Prefix         => Make_Identifier (Loc, Name_V),
7371                               Attribute_Name => Name_Range,
7372                               Expressions    => New_List (
7373                                 Make_Integer_Literal (Loc, Dim))),
7374
7375                           Reverse_Present             => True)),
7376
7377                   Statements       => New_List (Final_Loop),
7378                   End_Label        => Empty);
7379
7380               Dim := Dim - 1;
7381            end loop;
7382
7383            --  Generate the block which contains the finalization loops, the
7384            --  declarations of the abort flag, the exception occurrence, the
7385            --  raised flag and the conditional raise.
7386
7387            --    declare
7388            --       Abort  : constant Boolean := Triggered_By_Abort;
7389            --         <or>
7390            --       Abort  : constant Boolean := False;  --  no abort
7391
7392            --       E      : Exception_Occurrence;
7393            --       Raised : Boolean := False;
7394
7395            --    begin
7396            --       Counter :=
7397            --         V'Length (1) *
7398            --         ...
7399            --         V'Length (N) - Counter;
7400
7401            --       <final loop>
7402
7403            --       if Raised and then not Abort then
7404            --          Raise_From_Controlled_Operation (E);
7405            --       end if;
7406
7407            --       raise;
7408            --    end;
7409
7410            Stmts := New_List (Build_Assignment (Counter_Id), Final_Loop);
7411
7412            if Exceptions_OK then
7413               Append_To (Stmts, Build_Raise_Statement (Final_Data));
7414               Append_To (Stmts, Make_Raise_Statement (Loc));
7415            end if;
7416
7417            Final_Block :=
7418              Make_Block_Statement (Loc,
7419                Declarations               => Final_Decls,
7420                Handled_Statement_Sequence =>
7421                  Make_Handled_Sequence_Of_Statements (Loc,
7422                    Statements => Stmts));
7423
7424         --  Otherwise previous errors or a missing full view may prevent the
7425         --  proper freezing of the component type. If this is the case, there
7426         --  is no [Deep_]Finalize primitive to call.
7427
7428         else
7429            Final_Block := Make_Null_Statement (Loc);
7430         end if;
7431
7432         --  Generate the block which contains the initialization call and
7433         --  the partial finalization code.
7434
7435         --    begin
7436         --       [Deep_]Initialize (V (J1, ..., JN));
7437
7438         --       Counter := Counter + 1;
7439
7440         --    exception
7441         --       when others =>
7442         --          <finalization code>
7443         --    end;
7444
7445         Init_Call := Build_Initialization_Call;
7446
7447         --  Only create finalization block if there is a nontrivial call
7448         --  to initialization or a Default_Initial_Condition check to be
7449         --  performed.
7450
7451         if (Present (Init_Call)
7452              and then Nkind (Init_Call) /= N_Null_Statement)
7453           or else
7454             (Has_DIC (Comp_Typ)
7455               and then not GNATprove_Mode
7456               and then Present (DIC_Procedure (Comp_Typ))
7457               and then not Has_Null_Body (DIC_Procedure (Comp_Typ)))
7458         then
7459            declare
7460               Init_Stmts : constant List_Id := New_List;
7461
7462            begin
7463               if Present (Init_Call) then
7464                  Append_To (Init_Stmts, Init_Call);
7465               end if;
7466
7467               if Has_DIC (Comp_Typ)
7468                 and then Present (DIC_Procedure (Comp_Typ))
7469               then
7470                  Append_To
7471                    (Init_Stmts,
7472                     Build_DIC_Call (Loc,
7473                         Make_Indexed_Component (Loc,
7474                           Prefix      => Make_Identifier (Loc, Name_V),
7475                           Expressions => New_References_To (Index_List, Loc)),
7476                         Comp_Typ));
7477               end if;
7478
7479               Init_Loop :=
7480                 Make_Block_Statement (Loc,
7481                   Handled_Statement_Sequence =>
7482                     Make_Handled_Sequence_Of_Statements (Loc,
7483                       Statements         => Init_Stmts,
7484                       Exception_Handlers => New_List (
7485                         Make_Exception_Handler (Loc,
7486                           Exception_Choices => New_List (
7487                             Make_Others_Choice (Loc)),
7488                           Statements        => New_List (Final_Block)))));
7489            end;
7490
7491            Append_To (Statements (Handled_Statement_Sequence (Init_Loop)),
7492              Make_Assignment_Statement (Loc,
7493                Name       => New_Occurrence_Of (Counter_Id, Loc),
7494                Expression =>
7495                  Make_Op_Add (Loc,
7496                    Left_Opnd  => New_Occurrence_Of (Counter_Id, Loc),
7497                    Right_Opnd => Make_Integer_Literal (Loc, 1))));
7498
7499            --  Generate all initialization loops starting from the innermost
7500            --  dimension.
7501
7502            --    for Jnn in V'Range (Dim) loop
7503            --       <init loop>
7504            --    end loop;
7505
7506            J := Last (Index_List);
7507            Dim := Num_Dims;
7508            while Present (J) and then Dim > 0 loop
7509               Loop_Id := J;
7510               Prev (J);
7511               Remove (Loop_Id);
7512
7513               Init_Loop :=
7514                 Make_Loop_Statement (Loc,
7515                   Iteration_Scheme =>
7516                     Make_Iteration_Scheme (Loc,
7517                       Loop_Parameter_Specification =>
7518                         Make_Loop_Parameter_Specification (Loc,
7519                           Defining_Identifier => Loop_Id,
7520                           Discrete_Subtype_Definition =>
7521                             Make_Attribute_Reference (Loc,
7522                               Prefix         => Make_Identifier (Loc, Name_V),
7523                               Attribute_Name => Name_Range,
7524                               Expressions    => New_List (
7525                                 Make_Integer_Literal (Loc, Dim))))),
7526
7527                   Statements => New_List (Init_Loop),
7528                   End_Label => Empty);
7529
7530               Dim := Dim - 1;
7531            end loop;
7532
7533            --  Generate the block which contains the counter variable and the
7534            --  initialization loops.
7535
7536            --    declare
7537            --       Counter : Integer := 0;
7538            --    begin
7539            --       <init loop>
7540            --    end;
7541
7542            Init_Block :=
7543              Make_Block_Statement (Loc,
7544               Declarations               => New_List (
7545                 Make_Object_Declaration (Loc,
7546                   Defining_Identifier => Counter_Id,
7547                   Object_Definition   =>
7548                     New_Occurrence_Of (Standard_Integer, Loc),
7549                   Expression          => Make_Integer_Literal (Loc, 0))),
7550
7551               Handled_Statement_Sequence =>
7552                 Make_Handled_Sequence_Of_Statements (Loc,
7553                   Statements => New_List (Init_Loop)));
7554
7555            if Debug_Generated_Code then
7556               Set_Debug_Info_Needed (Counter_Id);
7557            end if;
7558
7559         --  Otherwise previous errors or a missing full view may prevent the
7560         --  proper freezing of the component type. If this is the case, there
7561         --  is no [Deep_]Initialize primitive to call.
7562
7563         else
7564            Init_Block := Make_Null_Statement (Loc);
7565         end if;
7566
7567         return New_List (Init_Block);
7568      end Build_Initialize_Statements;
7569
7570      -----------------------
7571      -- New_References_To --
7572      -----------------------
7573
7574      function New_References_To
7575        (L   : List_Id;
7576         Loc : Source_Ptr) return List_Id
7577      is
7578         Refs : constant List_Id := New_List;
7579         Id   : Node_Id;
7580
7581      begin
7582         Id := First (L);
7583         while Present (Id) loop
7584            Append_To (Refs, New_Occurrence_Of (Id, Loc));
7585            Next (Id);
7586         end loop;
7587
7588         return Refs;
7589      end New_References_To;
7590
7591   --  Start of processing for Make_Deep_Array_Body
7592
7593   begin
7594      case Prim is
7595         when Address_Case =>
7596            return Make_Finalize_Address_Stmts (Typ);
7597
7598         when Adjust_Case
7599            | Finalize_Case
7600         =>
7601            return Build_Adjust_Or_Finalize_Statements (Typ);
7602
7603         when Initialize_Case =>
7604            return Build_Initialize_Statements (Typ);
7605      end case;
7606   end Make_Deep_Array_Body;
7607
7608   --------------------
7609   -- Make_Deep_Proc --
7610   --------------------
7611
7612   function Make_Deep_Proc
7613     (Prim  : Final_Primitives;
7614      Typ   : Entity_Id;
7615      Stmts : List_Id) return Entity_Id
7616   is
7617      Loc     : constant Source_Ptr := Sloc (Typ);
7618      Formals : List_Id;
7619      Proc_Id : Entity_Id;
7620
7621   begin
7622      --  Create the object formal, generate:
7623      --    V : System.Address
7624
7625      if Prim = Address_Case then
7626         Formals := New_List (
7627           Make_Parameter_Specification (Loc,
7628             Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
7629             Parameter_Type      =>
7630               New_Occurrence_Of (RTE (RE_Address), Loc)));
7631
7632      --  Default case
7633
7634      else
7635         --  V : in out Typ
7636
7637         Formals := New_List (
7638           Make_Parameter_Specification (Loc,
7639             Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
7640             In_Present          => True,
7641             Out_Present         => True,
7642             Parameter_Type      => New_Occurrence_Of (Typ, Loc)));
7643
7644         --  F : Boolean := True
7645
7646         if Prim = Adjust_Case
7647           or else Prim = Finalize_Case
7648         then
7649            Append_To (Formals,
7650              Make_Parameter_Specification (Loc,
7651                Defining_Identifier => Make_Defining_Identifier (Loc, Name_F),
7652                Parameter_Type      =>
7653                  New_Occurrence_Of (Standard_Boolean, Loc),
7654                Expression          =>
7655                  New_Occurrence_Of (Standard_True, Loc)));
7656         end if;
7657      end if;
7658
7659      Proc_Id :=
7660        Make_Defining_Identifier (Loc,
7661          Chars => Make_TSS_Name (Typ, Deep_Name_Of (Prim)));
7662
7663      --  Generate:
7664      --    procedure Deep_Initialize / Adjust / Finalize (V : in out <typ>) is
7665      --    begin
7666      --       <stmts>
7667      --    exception                --  Finalize and Adjust cases only
7668      --       raise Program_Error;
7669      --    end Deep_Initialize / Adjust / Finalize;
7670
7671      --       or
7672
7673      --    procedure Finalize_Address (V : System.Address) is
7674      --    begin
7675      --       <stmts>
7676      --    end Finalize_Address;
7677
7678      Discard_Node (
7679        Make_Subprogram_Body (Loc,
7680          Specification =>
7681            Make_Procedure_Specification (Loc,
7682              Defining_Unit_Name       => Proc_Id,
7683              Parameter_Specifications => Formals),
7684
7685          Declarations => Empty_List,
7686
7687          Handled_Statement_Sequence =>
7688            Make_Handled_Sequence_Of_Statements (Loc, Statements => Stmts)));
7689
7690      --  If there are no calls to component initialization, indicate that
7691      --  the procedure is trivial, so prevent calls to it.
7692
7693      if Is_Empty_List (Stmts)
7694        or else Nkind (First (Stmts)) = N_Null_Statement
7695      then
7696         Set_Is_Trivial_Subprogram (Proc_Id);
7697      end if;
7698
7699      return Proc_Id;
7700   end Make_Deep_Proc;
7701
7702   ---------------------------
7703   -- Make_Deep_Record_Body --
7704   ---------------------------
7705
7706   function Make_Deep_Record_Body
7707     (Prim     : Final_Primitives;
7708      Typ      : Entity_Id;
7709      Is_Local : Boolean := False) return List_Id
7710   is
7711      function Build_Adjust_Statements (Typ : Entity_Id) return List_Id;
7712      --  Build the statements necessary to adjust a record type. The type may
7713      --  have discriminants and contain variant parts. Generate:
7714      --
7715      --    begin
7716      --       begin
7717      --          [Deep_]Adjust (V.Comp_1);
7718      --       exception
7719      --          when Id : others =>
7720      --             if not Raised then
7721      --                Raised := True;
7722      --                Save_Occurrence (E, Get_Current_Excep.all.all);
7723      --             end if;
7724      --       end;
7725      --       .  .  .
7726      --       begin
7727      --          [Deep_]Adjust (V.Comp_N);
7728      --       exception
7729      --          when Id : others =>
7730      --             if not Raised then
7731      --                Raised := True;
7732      --                Save_Occurrence (E, Get_Current_Excep.all.all);
7733      --             end if;
7734      --       end;
7735      --
7736      --       begin
7737      --          Deep_Adjust (V._parent, False);  --  If applicable
7738      --       exception
7739      --          when Id : others =>
7740      --             if not Raised then
7741      --                Raised := True;
7742      --                Save_Occurrence (E, Get_Current_Excep.all.all);
7743      --             end if;
7744      --       end;
7745      --
7746      --       if F then
7747      --          begin
7748      --             Adjust (V);  --  If applicable
7749      --          exception
7750      --             when others =>
7751      --                if not Raised then
7752      --                   Raised := True;
7753      --                   Save_Occurrence (E, Get_Current_Excep.all.all);
7754      --                end if;
7755      --          end;
7756      --       end if;
7757      --
7758      --       if Raised and then not Abort then
7759      --          Raise_From_Controlled_Operation (E);
7760      --       end if;
7761      --    end;
7762
7763      function Build_Finalize_Statements (Typ : Entity_Id) return List_Id;
7764      --  Build the statements necessary to finalize a record type. The type
7765      --  may have discriminants and contain variant parts. Generate:
7766      --
7767      --    declare
7768      --       Abort  : constant Boolean := Triggered_By_Abort;
7769      --         <or>
7770      --       Abort  : constant Boolean := False;  --  no abort
7771      --       E      : Exception_Occurrence;
7772      --       Raised : Boolean := False;
7773      --
7774      --    begin
7775      --       if F then
7776      --          begin
7777      --             Finalize (V);  --  If applicable
7778      --          exception
7779      --             when others =>
7780      --                if not Raised then
7781      --                   Raised := True;
7782      --                   Save_Occurrence (E, Get_Current_Excep.all.all);
7783      --                end if;
7784      --          end;
7785      --       end if;
7786      --
7787      --       case Variant_1 is
7788      --          when Value_1 =>
7789      --             case State_Counter_N =>  --  If Is_Local is enabled
7790      --                when N =>                 .
7791      --                   goto LN;               .
7792      --                ...                       .
7793      --                when 1 =>                 .
7794      --                   goto L1;               .
7795      --                when others =>            .
7796      --                   goto L0;               .
7797      --             end case;                    .
7798      --
7799      --             <<LN>>                   --  If Is_Local is enabled
7800      --             begin
7801      --                [Deep_]Finalize (V.Comp_N);
7802      --             exception
7803      --                when others =>
7804      --                   if not Raised then
7805      --                      Raised := True;
7806      --                      Save_Occurrence (E, Get_Current_Excep.all.all);
7807      --                   end if;
7808      --             end;
7809      --             .  .  .
7810      --             <<L1>>
7811      --             begin
7812      --                [Deep_]Finalize (V.Comp_1);
7813      --             exception
7814      --                when others =>
7815      --                   if not Raised then
7816      --                      Raised := True;
7817      --                      Save_Occurrence (E, Get_Current_Excep.all.all);
7818      --                   end if;
7819      --             end;
7820      --             <<L0>>
7821      --       end case;
7822      --
7823      --       case State_Counter_1 =>  --  If Is_Local is enabled
7824      --          when M =>                 .
7825      --             goto LM;               .
7826      --       ...
7827      --
7828      --       begin
7829      --          Deep_Finalize (V._parent, False);  --  If applicable
7830      --       exception
7831      --          when Id : others =>
7832      --             if not Raised then
7833      --                Raised := True;
7834      --                Save_Occurrence (E, Get_Current_Excep.all.all);
7835      --             end if;
7836      --       end;
7837      --
7838      --       if Raised and then not Abort then
7839      --          Raise_From_Controlled_Operation (E);
7840      --       end if;
7841      --    end;
7842
7843      function Parent_Field_Type (Typ : Entity_Id) return Entity_Id;
7844      --  Given a derived tagged type Typ, traverse all components, find field
7845      --  _parent and return its type.
7846
7847      procedure Preprocess_Components
7848        (Comps     : Node_Id;
7849         Num_Comps : out Nat;
7850         Has_POC   : out Boolean);
7851      --  Examine all components in component list Comps, count all controlled
7852      --  components and determine whether at least one of them is per-object
7853      --  constrained. Component _parent is always skipped.
7854
7855      -----------------------------
7856      -- Build_Adjust_Statements --
7857      -----------------------------
7858
7859      function Build_Adjust_Statements (Typ : Entity_Id) return List_Id is
7860         Loc     : constant Source_Ptr := Sloc (Typ);
7861         Typ_Def : constant Node_Id    := Type_Definition (Parent (Typ));
7862
7863         Finalizer_Data : Finalization_Exception_Data;
7864
7865         function Process_Component_List_For_Adjust
7866           (Comps : Node_Id) return List_Id;
7867         --  Build all necessary adjust statements for a single component list
7868
7869         ---------------------------------------
7870         -- Process_Component_List_For_Adjust --
7871         ---------------------------------------
7872
7873         function Process_Component_List_For_Adjust
7874           (Comps : Node_Id) return List_Id
7875         is
7876            Stmts : constant List_Id := New_List;
7877
7878            procedure Process_Component_For_Adjust (Decl : Node_Id);
7879            --  Process the declaration of a single controlled component
7880
7881            ----------------------------------
7882            -- Process_Component_For_Adjust --
7883            ----------------------------------
7884
7885            procedure Process_Component_For_Adjust (Decl : Node_Id) is
7886               Id  : constant Entity_Id := Defining_Identifier (Decl);
7887               Typ : constant Entity_Id := Etype (Id);
7888
7889               Adj_Call : Node_Id;
7890
7891            begin
7892               --    begin
7893               --       [Deep_]Adjust (V.Id);
7894
7895               --    exception
7896               --       when others =>
7897               --          if not Raised then
7898               --             Raised := True;
7899               --             Save_Occurrence (E, Get_Current_Excep.all.all);
7900               --          end if;
7901               --    end;
7902
7903               Adj_Call :=
7904                 Make_Adjust_Call (
7905                   Obj_Ref =>
7906                     Make_Selected_Component (Loc,
7907                       Prefix        => Make_Identifier (Loc, Name_V),
7908                       Selector_Name => Make_Identifier (Loc, Chars (Id))),
7909                   Typ     => Typ);
7910
7911               --  Guard against a missing [Deep_]Adjust when the component
7912               --  type was not properly frozen.
7913
7914               if Present (Adj_Call) then
7915                  if Exceptions_OK then
7916                     Adj_Call :=
7917                       Make_Block_Statement (Loc,
7918                         Handled_Statement_Sequence =>
7919                           Make_Handled_Sequence_Of_Statements (Loc,
7920                             Statements         => New_List (Adj_Call),
7921                             Exception_Handlers => New_List (
7922                               Build_Exception_Handler (Finalizer_Data))));
7923                  end if;
7924
7925                  Append_To (Stmts, Adj_Call);
7926               end if;
7927            end Process_Component_For_Adjust;
7928
7929            --  Local variables
7930
7931            Decl      : Node_Id;
7932            Decl_Id   : Entity_Id;
7933            Decl_Typ  : Entity_Id;
7934            Has_POC   : Boolean;
7935            Num_Comps : Nat;
7936            Var_Case  : Node_Id;
7937
7938         --  Start of processing for Process_Component_List_For_Adjust
7939
7940         begin
7941            --  Perform an initial check, determine the number of controlled
7942            --  components in the current list and whether at least one of them
7943            --  is per-object constrained.
7944
7945            Preprocess_Components (Comps, Num_Comps, Has_POC);
7946
7947            --  The processing in this routine is done in the following order:
7948            --    1) Regular components
7949            --    2) Per-object constrained components
7950            --    3) Variant parts
7951
7952            if Num_Comps > 0 then
7953
7954               --  Process all regular components in order of declarations
7955
7956               Decl := First_Non_Pragma (Component_Items (Comps));
7957               while Present (Decl) loop
7958                  Decl_Id  := Defining_Identifier (Decl);
7959                  Decl_Typ := Etype (Decl_Id);
7960
7961                  --  Skip _parent as well as per-object constrained components
7962
7963                  if Chars (Decl_Id) /= Name_uParent
7964                    and then Needs_Finalization (Decl_Typ)
7965                  then
7966                     if Has_Access_Constraint (Decl_Id)
7967                       and then No (Expression (Decl))
7968                     then
7969                        null;
7970                     else
7971                        Process_Component_For_Adjust (Decl);
7972                     end if;
7973                  end if;
7974
7975                  Next_Non_Pragma (Decl);
7976               end loop;
7977
7978               --  Process all per-object constrained components in order of
7979               --  declarations.
7980
7981               if Has_POC then
7982                  Decl := First_Non_Pragma (Component_Items (Comps));
7983                  while Present (Decl) loop
7984                     Decl_Id  := Defining_Identifier (Decl);
7985                     Decl_Typ := Etype (Decl_Id);
7986
7987                     --  Skip _parent
7988
7989                     if Chars (Decl_Id) /= Name_uParent
7990                       and then Needs_Finalization (Decl_Typ)
7991                       and then Has_Access_Constraint (Decl_Id)
7992                       and then No (Expression (Decl))
7993                     then
7994                        Process_Component_For_Adjust (Decl);
7995                     end if;
7996
7997                     Next_Non_Pragma (Decl);
7998                  end loop;
7999               end if;
8000            end if;
8001
8002            --  Process all variants, if any
8003
8004            Var_Case := Empty;
8005            if Present (Variant_Part (Comps)) then
8006               declare
8007                  Var_Alts : constant List_Id := New_List;
8008                  Var      : Node_Id;
8009
8010               begin
8011                  Var := First_Non_Pragma (Variants (Variant_Part (Comps)));
8012                  while Present (Var) loop
8013
8014                     --  Generate:
8015                     --     when <discrete choices> =>
8016                     --        <adjust statements>
8017
8018                     Append_To (Var_Alts,
8019                       Make_Case_Statement_Alternative (Loc,
8020                         Discrete_Choices =>
8021                           New_Copy_List (Discrete_Choices (Var)),
8022                         Statements       =>
8023                           Process_Component_List_For_Adjust (
8024                             Component_List (Var))));
8025
8026                     Next_Non_Pragma (Var);
8027                  end loop;
8028
8029                  --  Generate:
8030                  --     case V.<discriminant> is
8031                  --        when <discrete choices 1> =>
8032                  --           <adjust statements 1>
8033                  --        ...
8034                  --        when <discrete choices N> =>
8035                  --           <adjust statements N>
8036                  --     end case;
8037
8038                  Var_Case :=
8039                    Make_Case_Statement (Loc,
8040                      Expression =>
8041                        Make_Selected_Component (Loc,
8042                          Prefix        => Make_Identifier (Loc, Name_V),
8043                          Selector_Name =>
8044                            Make_Identifier (Loc,
8045                              Chars => Chars (Name (Variant_Part (Comps))))),
8046                      Alternatives => Var_Alts);
8047               end;
8048            end if;
8049
8050            --  Add the variant case statement to the list of statements
8051
8052            if Present (Var_Case) then
8053               Append_To (Stmts, Var_Case);
8054            end if;
8055
8056            --  If the component list did not have any controlled components
8057            --  nor variants, return null.
8058
8059            if Is_Empty_List (Stmts) then
8060               Append_To (Stmts, Make_Null_Statement (Loc));
8061            end if;
8062
8063            return Stmts;
8064         end Process_Component_List_For_Adjust;
8065
8066         --  Local variables
8067
8068         Bod_Stmts       : List_Id := No_List;
8069         Finalizer_Decls : List_Id := No_List;
8070         Rec_Def         : Node_Id;
8071
8072      --  Start of processing for Build_Adjust_Statements
8073
8074      begin
8075         Finalizer_Decls := New_List;
8076         Build_Object_Declarations (Finalizer_Data, Finalizer_Decls, Loc);
8077
8078         if Nkind (Typ_Def) = N_Derived_Type_Definition then
8079            Rec_Def := Record_Extension_Part (Typ_Def);
8080         else
8081            Rec_Def := Typ_Def;
8082         end if;
8083
8084         --  Create an adjust sequence for all record components
8085
8086         if Present (Component_List (Rec_Def)) then
8087            Bod_Stmts :=
8088              Process_Component_List_For_Adjust (Component_List (Rec_Def));
8089         end if;
8090
8091         --  A derived record type must adjust all inherited components. This
8092         --  action poses the following problem:
8093
8094         --    procedure Deep_Adjust (Obj : in out Parent_Typ) is
8095         --    begin
8096         --       Adjust (Obj);
8097         --       ...
8098
8099         --    procedure Deep_Adjust (Obj : in out Derived_Typ) is
8100         --    begin
8101         --       Deep_Adjust (Obj._parent);
8102         --       ...
8103         --       Adjust (Obj);
8104         --       ...
8105
8106         --  Adjusting the derived type will invoke Adjust of the parent and
8107         --  then that of the derived type. This is undesirable because both
8108         --  routines may modify shared components. Only the Adjust of the
8109         --  derived type should be invoked.
8110
8111         --  To prevent this double adjustment of shared components,
8112         --  Deep_Adjust uses a flag to control the invocation of Adjust:
8113
8114         --    procedure Deep_Adjust
8115         --      (Obj  : in out Some_Type;
8116         --       Flag : Boolean := True)
8117         --    is
8118         --    begin
8119         --       if Flag then
8120         --          Adjust (Obj);
8121         --       end if;
8122         --       ...
8123
8124         --  When Deep_Adjust is invoked for field _parent, a value of False is
8125         --  provided for the flag:
8126
8127         --    Deep_Adjust (Obj._parent, False);
8128
8129         if Is_Tagged_Type (Typ) and then Is_Derived_Type (Typ) then
8130            declare
8131               Par_Typ  : constant Entity_Id := Parent_Field_Type (Typ);
8132               Adj_Stmt : Node_Id;
8133               Call     : Node_Id;
8134
8135            begin
8136               if Needs_Finalization (Par_Typ) then
8137                  Call :=
8138                    Make_Adjust_Call
8139                      (Obj_Ref   =>
8140                         Make_Selected_Component (Loc,
8141                           Prefix        => Make_Identifier (Loc, Name_V),
8142                           Selector_Name =>
8143                             Make_Identifier (Loc, Name_uParent)),
8144                       Typ       => Par_Typ,
8145                       Skip_Self => True);
8146
8147                  --  Generate:
8148                  --    begin
8149                  --       Deep_Adjust (V._parent, False);
8150
8151                  --    exception
8152                  --       when Id : others =>
8153                  --          if not Raised then
8154                  --             Raised := True;
8155                  --             Save_Occurrence (E,
8156                  --               Get_Current_Excep.all.all);
8157                  --          end if;
8158                  --    end;
8159
8160                  if Present (Call) then
8161                     Adj_Stmt := Call;
8162
8163                     if Exceptions_OK then
8164                        Adj_Stmt :=
8165                          Make_Block_Statement (Loc,
8166                            Handled_Statement_Sequence =>
8167                              Make_Handled_Sequence_Of_Statements (Loc,
8168                                Statements         => New_List (Adj_Stmt),
8169                                Exception_Handlers => New_List (
8170                                  Build_Exception_Handler (Finalizer_Data))));
8171                     end if;
8172
8173                     Prepend_To (Bod_Stmts, Adj_Stmt);
8174                  end if;
8175               end if;
8176            end;
8177         end if;
8178
8179         --  Adjust the object. This action must be performed last after all
8180         --  components have been adjusted.
8181
8182         if Is_Controlled (Typ) then
8183            declare
8184               Adj_Stmt : Node_Id;
8185               Proc     : Entity_Id;
8186
8187            begin
8188               Proc := Find_Optional_Prim_Op (Typ, Name_Adjust);
8189
8190               --  Generate:
8191               --    if F then
8192               --       begin
8193               --          Adjust (V);
8194
8195               --       exception
8196               --          when others =>
8197               --             if not Raised then
8198               --                Raised := True;
8199               --                Save_Occurrence (E,
8200               --                  Get_Current_Excep.all.all);
8201               --             end if;
8202               --       end;
8203               --    end if;
8204
8205               if Present (Proc) then
8206                  Adj_Stmt :=
8207                    Make_Procedure_Call_Statement (Loc,
8208                      Name                   => New_Occurrence_Of (Proc, Loc),
8209                      Parameter_Associations => New_List (
8210                        Make_Identifier (Loc, Name_V)));
8211
8212                  if Exceptions_OK then
8213                     Adj_Stmt :=
8214                       Make_Block_Statement (Loc,
8215                         Handled_Statement_Sequence =>
8216                           Make_Handled_Sequence_Of_Statements (Loc,
8217                             Statements         => New_List (Adj_Stmt),
8218                             Exception_Handlers => New_List (
8219                               Build_Exception_Handler
8220                                 (Finalizer_Data))));
8221                  end if;
8222
8223                  Append_To (Bod_Stmts,
8224                    Make_If_Statement (Loc,
8225                      Condition       => Make_Identifier (Loc, Name_F),
8226                      Then_Statements => New_List (Adj_Stmt)));
8227               end if;
8228            end;
8229         end if;
8230
8231         --  At this point either all adjustment statements have been generated
8232         --  or the type is not controlled.
8233
8234         if Is_Empty_List (Bod_Stmts) then
8235            Append_To (Bod_Stmts, Make_Null_Statement (Loc));
8236
8237            return Bod_Stmts;
8238
8239         --  Generate:
8240         --    declare
8241         --       Abort  : constant Boolean := Triggered_By_Abort;
8242         --         <or>
8243         --       Abort  : constant Boolean := False;  --  no abort
8244
8245         --       E      : Exception_Occurrence;
8246         --       Raised : Boolean := False;
8247
8248         --    begin
8249         --       <adjust statements>
8250
8251         --       if Raised and then not Abort then
8252         --          Raise_From_Controlled_Operation (E);
8253         --       end if;
8254         --    end;
8255
8256         else
8257            if Exceptions_OK then
8258               Append_To (Bod_Stmts, Build_Raise_Statement (Finalizer_Data));
8259            end if;
8260
8261            return
8262              New_List (
8263                Make_Block_Statement (Loc,
8264                  Declarations               =>
8265                    Finalizer_Decls,
8266                  Handled_Statement_Sequence =>
8267                    Make_Handled_Sequence_Of_Statements (Loc, Bod_Stmts)));
8268         end if;
8269      end Build_Adjust_Statements;
8270
8271      -------------------------------
8272      -- Build_Finalize_Statements --
8273      -------------------------------
8274
8275      function Build_Finalize_Statements (Typ : Entity_Id) return List_Id is
8276         Loc     : constant Source_Ptr := Sloc (Typ);
8277         Typ_Def : constant Node_Id    := Type_Definition (Parent (Typ));
8278
8279         Counter        : Nat := 0;
8280         Finalizer_Data : Finalization_Exception_Data;
8281
8282         function Process_Component_List_For_Finalize
8283           (Comps : Node_Id) return List_Id;
8284         --  Build all necessary finalization statements for a single component
8285         --  list. The statements may include a jump circuitry if flag Is_Local
8286         --  is enabled.
8287
8288         -----------------------------------------
8289         -- Process_Component_List_For_Finalize --
8290         -----------------------------------------
8291
8292         function Process_Component_List_For_Finalize
8293           (Comps : Node_Id) return List_Id
8294         is
8295            procedure Process_Component_For_Finalize
8296              (Decl      : Node_Id;
8297               Alts      : List_Id;
8298               Decls     : List_Id;
8299               Stmts     : List_Id;
8300               Num_Comps : in out Nat);
8301            --  Process the declaration of a single controlled component. If
8302            --  flag Is_Local is enabled, create the corresponding label and
8303            --  jump circuitry. Alts is the list of case alternatives, Decls
8304            --  is the top level declaration list where labels are declared
8305            --  and Stmts is the list of finalization actions. Num_Comps
8306            --  denotes the current number of components needing finalization.
8307
8308            ------------------------------------
8309            -- Process_Component_For_Finalize --
8310            ------------------------------------
8311
8312            procedure Process_Component_For_Finalize
8313              (Decl      : Node_Id;
8314               Alts      : List_Id;
8315               Decls     : List_Id;
8316               Stmts     : List_Id;
8317               Num_Comps : in out Nat)
8318            is
8319               Id       : constant Entity_Id := Defining_Identifier (Decl);
8320               Typ      : constant Entity_Id := Etype (Id);
8321               Fin_Call : Node_Id;
8322
8323            begin
8324               if Is_Local then
8325                  declare
8326                     Label    : Node_Id;
8327                     Label_Id : Entity_Id;
8328
8329                  begin
8330                     --  Generate:
8331                     --    LN : label;
8332
8333                     Label_Id :=
8334                       Make_Identifier (Loc,
8335                         Chars => New_External_Name ('L', Num_Comps));
8336                     Set_Entity (Label_Id,
8337                       Make_Defining_Identifier (Loc, Chars (Label_Id)));
8338                     Label := Make_Label (Loc, Label_Id);
8339
8340                     Append_To (Decls,
8341                       Make_Implicit_Label_Declaration (Loc,
8342                         Defining_Identifier => Entity (Label_Id),
8343                         Label_Construct     => Label));
8344
8345                     --  Generate:
8346                     --    when N =>
8347                     --      goto LN;
8348
8349                     Append_To (Alts,
8350                       Make_Case_Statement_Alternative (Loc,
8351                         Discrete_Choices => New_List (
8352                           Make_Integer_Literal (Loc, Num_Comps)),
8353
8354                         Statements => New_List (
8355                           Make_Goto_Statement (Loc,
8356                             Name =>
8357                               New_Occurrence_Of (Entity (Label_Id), Loc)))));
8358
8359                     --  Generate:
8360                     --    <<LN>>
8361
8362                     Append_To (Stmts, Label);
8363
8364                     --  Decrease the number of components to be processed.
8365                     --  This action yields a new Label_Id in future calls.
8366
8367                     Num_Comps := Num_Comps - 1;
8368                  end;
8369               end if;
8370
8371               --  Generate:
8372               --    [Deep_]Finalize (V.Id);  --  No_Exception_Propagation
8373
8374               --    begin                    --  Exception handlers allowed
8375               --       [Deep_]Finalize (V.Id);
8376               --    exception
8377               --       when others =>
8378               --          if not Raised then
8379               --             Raised := True;
8380               --             Save_Occurrence (E,
8381               --               Get_Current_Excep.all.all);
8382               --          end if;
8383               --    end;
8384
8385               Fin_Call :=
8386                 Make_Final_Call
8387                   (Obj_Ref =>
8388                      Make_Selected_Component (Loc,
8389                        Prefix        => Make_Identifier (Loc, Name_V),
8390                        Selector_Name => Make_Identifier (Loc, Chars (Id))),
8391                    Typ     => Typ);
8392
8393               --  Guard against a missing [Deep_]Finalize when the component
8394               --  type was not properly frozen.
8395
8396               if Present (Fin_Call) then
8397                  if Exceptions_OK then
8398                     Fin_Call :=
8399                       Make_Block_Statement (Loc,
8400                         Handled_Statement_Sequence =>
8401                           Make_Handled_Sequence_Of_Statements (Loc,
8402                             Statements         => New_List (Fin_Call),
8403                             Exception_Handlers => New_List (
8404                               Build_Exception_Handler (Finalizer_Data))));
8405                  end if;
8406
8407                  Append_To (Stmts, Fin_Call);
8408               end if;
8409            end Process_Component_For_Finalize;
8410
8411            --  Local variables
8412
8413            Alts       : List_Id;
8414            Counter_Id : Entity_Id := Empty;
8415            Decl       : Node_Id;
8416            Decl_Id    : Entity_Id;
8417            Decl_Typ   : Entity_Id;
8418            Decls      : List_Id;
8419            Has_POC    : Boolean;
8420            Jump_Block : Node_Id;
8421            Label      : Node_Id;
8422            Label_Id   : Entity_Id;
8423            Num_Comps  : Nat;
8424            Stmts      : List_Id;
8425            Var_Case   : Node_Id;
8426
8427         --  Start of processing for Process_Component_List_For_Finalize
8428
8429         begin
8430            --  Perform an initial check, look for controlled and per-object
8431            --  constrained components.
8432
8433            Preprocess_Components (Comps, Num_Comps, Has_POC);
8434
8435            --  Create a state counter to service the current component list.
8436            --  This step is performed before the variants are inspected in
8437            --  order to generate the same state counter names as those from
8438            --  Build_Initialize_Statements.
8439
8440            if Num_Comps > 0 and then Is_Local then
8441               Counter := Counter + 1;
8442
8443               Counter_Id :=
8444                 Make_Defining_Identifier (Loc,
8445                   Chars => New_External_Name ('C', Counter));
8446            end if;
8447
8448            --  Process the component in the following order:
8449            --    1) Variants
8450            --    2) Per-object constrained components
8451            --    3) Regular components
8452
8453            --  Start with the variant parts
8454
8455            Var_Case := Empty;
8456            if Present (Variant_Part (Comps)) then
8457               declare
8458                  Var_Alts : constant List_Id := New_List;
8459                  Var      : Node_Id;
8460
8461               begin
8462                  Var := First_Non_Pragma (Variants (Variant_Part (Comps)));
8463                  while Present (Var) loop
8464
8465                     --  Generate:
8466                     --     when <discrete choices> =>
8467                     --        <finalize statements>
8468
8469                     Append_To (Var_Alts,
8470                       Make_Case_Statement_Alternative (Loc,
8471                         Discrete_Choices =>
8472                           New_Copy_List (Discrete_Choices (Var)),
8473                         Statements =>
8474                           Process_Component_List_For_Finalize (
8475                             Component_List (Var))));
8476
8477                     Next_Non_Pragma (Var);
8478                  end loop;
8479
8480                  --  Generate:
8481                  --     case V.<discriminant> is
8482                  --        when <discrete choices 1> =>
8483                  --           <finalize statements 1>
8484                  --        ...
8485                  --        when <discrete choices N> =>
8486                  --           <finalize statements N>
8487                  --     end case;
8488
8489                  Var_Case :=
8490                    Make_Case_Statement (Loc,
8491                      Expression =>
8492                        Make_Selected_Component (Loc,
8493                          Prefix        => Make_Identifier (Loc, Name_V),
8494                          Selector_Name =>
8495                            Make_Identifier (Loc,
8496                              Chars => Chars (Name (Variant_Part (Comps))))),
8497                      Alternatives => Var_Alts);
8498               end;
8499            end if;
8500
8501            --  The current component list does not have a single controlled
8502            --  component, however it may contain variants. Return the case
8503            --  statement for the variants or nothing.
8504
8505            if Num_Comps = 0 then
8506               if Present (Var_Case) then
8507                  return New_List (Var_Case);
8508               else
8509                  return New_List (Make_Null_Statement (Loc));
8510               end if;
8511            end if;
8512
8513            --  Prepare all lists
8514
8515            Alts  := New_List;
8516            Decls := New_List;
8517            Stmts := New_List;
8518
8519            --  Process all per-object constrained components in reverse order
8520
8521            if Has_POC then
8522               Decl := Last_Non_Pragma (Component_Items (Comps));
8523               while Present (Decl) loop
8524                  Decl_Id  := Defining_Identifier (Decl);
8525                  Decl_Typ := Etype (Decl_Id);
8526
8527                  --  Skip _parent
8528
8529                  if Chars (Decl_Id) /= Name_uParent
8530                    and then Needs_Finalization (Decl_Typ)
8531                    and then Has_Access_Constraint (Decl_Id)
8532                    and then No (Expression (Decl))
8533                  then
8534                     Process_Component_For_Finalize
8535                       (Decl, Alts, Decls, Stmts, Num_Comps);
8536                  end if;
8537
8538                  Prev_Non_Pragma (Decl);
8539               end loop;
8540            end if;
8541
8542            --  Process the rest of the components in reverse order
8543
8544            Decl := Last_Non_Pragma (Component_Items (Comps));
8545            while Present (Decl) loop
8546               Decl_Id  := Defining_Identifier (Decl);
8547               Decl_Typ := Etype (Decl_Id);
8548
8549               --  Skip _parent
8550
8551               if Chars (Decl_Id) /= Name_uParent
8552                 and then Needs_Finalization (Decl_Typ)
8553               then
8554                  --  Skip per-object constrained components since they were
8555                  --  handled in the above step.
8556
8557                  if Has_Access_Constraint (Decl_Id)
8558                    and then No (Expression (Decl))
8559                  then
8560                     null;
8561                  else
8562                     Process_Component_For_Finalize
8563                       (Decl, Alts, Decls, Stmts, Num_Comps);
8564                  end if;
8565               end if;
8566
8567               Prev_Non_Pragma (Decl);
8568            end loop;
8569
8570            --  Generate:
8571            --    declare
8572            --       LN : label;        --  If Is_Local is enabled
8573            --       ...                    .
8574            --       L0 : label;            .
8575
8576            --    begin                     .
8577            --       case CounterX is       .
8578            --          when N =>           .
8579            --             goto LN;         .
8580            --          ...                 .
8581            --          when 1 =>           .
8582            --             goto L1;         .
8583            --          when others =>      .
8584            --             goto L0;         .
8585            --       end case;              .
8586
8587            --       <<LN>>             --  If Is_Local is enabled
8588            --          begin
8589            --             [Deep_]Finalize (V.CompY);
8590            --          exception
8591            --             when Id : others =>
8592            --                if not Raised then
8593            --                   Raised := True;
8594            --                   Save_Occurrence (E,
8595            --                     Get_Current_Excep.all.all);
8596            --                end if;
8597            --          end;
8598            --       ...
8599            --       <<L0>>  --  If Is_Local is enabled
8600            --    end;
8601
8602            if Is_Local then
8603
8604               --  Add the declaration of default jump location L0, its
8605               --  corresponding alternative and its place in the statements.
8606
8607               Label_Id := Make_Identifier (Loc, New_External_Name ('L', 0));
8608               Set_Entity (Label_Id,
8609                 Make_Defining_Identifier (Loc, Chars (Label_Id)));
8610               Label := Make_Label (Loc, Label_Id);
8611
8612               Append_To (Decls,          --  declaration
8613                 Make_Implicit_Label_Declaration (Loc,
8614                   Defining_Identifier => Entity (Label_Id),
8615                   Label_Construct     => Label));
8616
8617               Append_To (Alts,           --  alternative
8618                 Make_Case_Statement_Alternative (Loc,
8619                   Discrete_Choices => New_List (
8620                     Make_Others_Choice (Loc)),
8621
8622                   Statements => New_List (
8623                     Make_Goto_Statement (Loc,
8624                       Name => New_Occurrence_Of (Entity (Label_Id), Loc)))));
8625
8626               Append_To (Stmts, Label);  --  statement
8627
8628               --  Create the jump block
8629
8630               Prepend_To (Stmts,
8631                 Make_Case_Statement (Loc,
8632                   Expression   => Make_Identifier (Loc, Chars (Counter_Id)),
8633                   Alternatives => Alts));
8634            end if;
8635
8636            Jump_Block :=
8637              Make_Block_Statement (Loc,
8638                Declarations               => Decls,
8639                Handled_Statement_Sequence =>
8640                  Make_Handled_Sequence_Of_Statements (Loc, Stmts));
8641
8642            if Present (Var_Case) then
8643               return New_List (Var_Case, Jump_Block);
8644            else
8645               return New_List (Jump_Block);
8646            end if;
8647         end Process_Component_List_For_Finalize;
8648
8649         --  Local variables
8650
8651         Bod_Stmts       : List_Id := No_List;
8652         Finalizer_Decls : List_Id := No_List;
8653         Rec_Def         : Node_Id;
8654
8655      --  Start of processing for Build_Finalize_Statements
8656
8657      begin
8658         Finalizer_Decls := New_List;
8659         Build_Object_Declarations (Finalizer_Data, Finalizer_Decls, Loc);
8660
8661         if Nkind (Typ_Def) = N_Derived_Type_Definition then
8662            Rec_Def := Record_Extension_Part (Typ_Def);
8663         else
8664            Rec_Def := Typ_Def;
8665         end if;
8666
8667         --  Create a finalization sequence for all record components
8668
8669         if Present (Component_List (Rec_Def)) then
8670            Bod_Stmts :=
8671              Process_Component_List_For_Finalize (Component_List (Rec_Def));
8672         end if;
8673
8674         --  A derived record type must finalize all inherited components. This
8675         --  action poses the following problem:
8676
8677         --    procedure Deep_Finalize (Obj : in out Parent_Typ) is
8678         --    begin
8679         --       Finalize (Obj);
8680         --       ...
8681
8682         --    procedure Deep_Finalize (Obj : in out Derived_Typ) is
8683         --    begin
8684         --       Deep_Finalize (Obj._parent);
8685         --       ...
8686         --       Finalize (Obj);
8687         --       ...
8688
8689         --  Finalizing the derived type will invoke Finalize of the parent and
8690         --  then that of the derived type. This is undesirable because both
8691         --  routines may modify shared components. Only the Finalize of the
8692         --  derived type should be invoked.
8693
8694         --  To prevent this double adjustment of shared components,
8695         --  Deep_Finalize uses a flag to control the invocation of Finalize:
8696
8697         --    procedure Deep_Finalize
8698         --      (Obj  : in out Some_Type;
8699         --       Flag : Boolean := True)
8700         --    is
8701         --    begin
8702         --       if Flag then
8703         --          Finalize (Obj);
8704         --       end if;
8705         --       ...
8706
8707         --  When Deep_Finalize is invoked for field _parent, a value of False
8708         --  is provided for the flag:
8709
8710         --    Deep_Finalize (Obj._parent, False);
8711
8712         if Is_Tagged_Type (Typ) and then Is_Derived_Type (Typ) then
8713            declare
8714               Par_Typ  : constant Entity_Id := Parent_Field_Type (Typ);
8715               Call     : Node_Id;
8716               Fin_Stmt : Node_Id;
8717
8718            begin
8719               if Needs_Finalization (Par_Typ) then
8720                  Call :=
8721                    Make_Final_Call
8722                      (Obj_Ref   =>
8723                         Make_Selected_Component (Loc,
8724                           Prefix        => Make_Identifier (Loc, Name_V),
8725                           Selector_Name =>
8726                             Make_Identifier (Loc, Name_uParent)),
8727                       Typ       => Par_Typ,
8728                       Skip_Self => True);
8729
8730                  --  Generate:
8731                  --    begin
8732                  --       Deep_Finalize (V._parent, False);
8733
8734                  --    exception
8735                  --       when Id : others =>
8736                  --          if not Raised then
8737                  --             Raised := True;
8738                  --             Save_Occurrence (E,
8739                  --               Get_Current_Excep.all.all);
8740                  --          end if;
8741                  --    end;
8742
8743                  if Present (Call) then
8744                     Fin_Stmt := Call;
8745
8746                     if Exceptions_OK then
8747                        Fin_Stmt :=
8748                          Make_Block_Statement (Loc,
8749                            Handled_Statement_Sequence =>
8750                              Make_Handled_Sequence_Of_Statements (Loc,
8751                                Statements         => New_List (Fin_Stmt),
8752                                Exception_Handlers => New_List (
8753                                  Build_Exception_Handler
8754                                    (Finalizer_Data))));
8755                     end if;
8756
8757                     Append_To (Bod_Stmts, Fin_Stmt);
8758                  end if;
8759               end if;
8760            end;
8761         end if;
8762
8763         --  Finalize the object. This action must be performed first before
8764         --  all components have been finalized.
8765
8766         if Is_Controlled (Typ) and then not Is_Local then
8767            declare
8768               Fin_Stmt : Node_Id;
8769               Proc     : Entity_Id;
8770
8771            begin
8772               Proc := Find_Optional_Prim_Op (Typ, Name_Finalize);
8773
8774               --  Generate:
8775               --    if F then
8776               --       begin
8777               --          Finalize (V);
8778
8779               --       exception
8780               --          when others =>
8781               --             if not Raised then
8782               --                Raised := True;
8783               --                Save_Occurrence (E,
8784               --                  Get_Current_Excep.all.all);
8785               --             end if;
8786               --       end;
8787               --    end if;
8788
8789               if Present (Proc) then
8790                  Fin_Stmt :=
8791                    Make_Procedure_Call_Statement (Loc,
8792                      Name                   => New_Occurrence_Of (Proc, Loc),
8793                      Parameter_Associations => New_List (
8794                        Make_Identifier (Loc, Name_V)));
8795
8796                  if Exceptions_OK then
8797                     Fin_Stmt :=
8798                       Make_Block_Statement (Loc,
8799                         Handled_Statement_Sequence =>
8800                           Make_Handled_Sequence_Of_Statements (Loc,
8801                             Statements         => New_List (Fin_Stmt),
8802                             Exception_Handlers => New_List (
8803                               Build_Exception_Handler
8804                                 (Finalizer_Data))));
8805                  end if;
8806
8807                  Prepend_To (Bod_Stmts,
8808                    Make_If_Statement (Loc,
8809                      Condition       => Make_Identifier (Loc, Name_F),
8810                      Then_Statements => New_List (Fin_Stmt)));
8811               end if;
8812            end;
8813         end if;
8814
8815         --  At this point either all finalization statements have been
8816         --  generated or the type is not controlled.
8817
8818         if No (Bod_Stmts) then
8819            return New_List (Make_Null_Statement (Loc));
8820
8821         --  Generate:
8822         --    declare
8823         --       Abort  : constant Boolean := Triggered_By_Abort;
8824         --         <or>
8825         --       Abort  : constant Boolean := False;  --  no abort
8826
8827         --       E      : Exception_Occurrence;
8828         --       Raised : Boolean := False;
8829
8830         --    begin
8831         --       <finalize statements>
8832
8833         --       if Raised and then not Abort then
8834         --          Raise_From_Controlled_Operation (E);
8835         --       end if;
8836         --    end;
8837
8838         else
8839            if Exceptions_OK then
8840               Append_To (Bod_Stmts, Build_Raise_Statement (Finalizer_Data));
8841            end if;
8842
8843            return
8844              New_List (
8845                Make_Block_Statement (Loc,
8846                  Declarations               =>
8847                    Finalizer_Decls,
8848                  Handled_Statement_Sequence =>
8849                    Make_Handled_Sequence_Of_Statements (Loc, Bod_Stmts)));
8850         end if;
8851      end Build_Finalize_Statements;
8852
8853      -----------------------
8854      -- Parent_Field_Type --
8855      -----------------------
8856
8857      function Parent_Field_Type (Typ : Entity_Id) return Entity_Id is
8858         Field : Entity_Id;
8859
8860      begin
8861         Field := First_Entity (Typ);
8862         while Present (Field) loop
8863            if Chars (Field) = Name_uParent then
8864               return Etype (Field);
8865            end if;
8866
8867            Next_Entity (Field);
8868         end loop;
8869
8870         --  A derived tagged type should always have a parent field
8871
8872         raise Program_Error;
8873      end Parent_Field_Type;
8874
8875      ---------------------------
8876      -- Preprocess_Components --
8877      ---------------------------
8878
8879      procedure Preprocess_Components
8880        (Comps     : Node_Id;
8881         Num_Comps : out Nat;
8882         Has_POC   : out Boolean)
8883      is
8884         Decl : Node_Id;
8885         Id   : Entity_Id;
8886         Typ  : Entity_Id;
8887
8888      begin
8889         Num_Comps := 0;
8890         Has_POC   := False;
8891
8892         Decl := First_Non_Pragma (Component_Items (Comps));
8893         while Present (Decl) loop
8894            Id  := Defining_Identifier (Decl);
8895            Typ := Etype (Id);
8896
8897            --  Skip field _parent
8898
8899            if Chars (Id) /= Name_uParent
8900              and then Needs_Finalization (Typ)
8901            then
8902               Num_Comps := Num_Comps + 1;
8903
8904               if Has_Access_Constraint (Id)
8905                 and then No (Expression (Decl))
8906               then
8907                  Has_POC := True;
8908               end if;
8909            end if;
8910
8911            Next_Non_Pragma (Decl);
8912         end loop;
8913      end Preprocess_Components;
8914
8915   --  Start of processing for Make_Deep_Record_Body
8916
8917   begin
8918      case Prim is
8919         when Address_Case =>
8920            return Make_Finalize_Address_Stmts (Typ);
8921
8922         when Adjust_Case =>
8923            return Build_Adjust_Statements (Typ);
8924
8925         when Finalize_Case =>
8926            return Build_Finalize_Statements (Typ);
8927
8928         when Initialize_Case =>
8929            declare
8930               Loc : constant Source_Ptr := Sloc (Typ);
8931
8932            begin
8933               if Is_Controlled (Typ) then
8934                  return New_List (
8935                    Make_Procedure_Call_Statement (Loc,
8936                      Name                   =>
8937                        New_Occurrence_Of
8938                          (Find_Prim_Op (Typ, Name_Of (Prim)), Loc),
8939                      Parameter_Associations => New_List (
8940                        Make_Identifier (Loc, Name_V))));
8941               else
8942                  return Empty_List;
8943               end if;
8944            end;
8945      end case;
8946   end Make_Deep_Record_Body;
8947
8948   ----------------------
8949   -- Make_Final_Call --
8950   ----------------------
8951
8952   function Make_Final_Call
8953     (Obj_Ref   : Node_Id;
8954      Typ       : Entity_Id;
8955      Skip_Self : Boolean := False) return Node_Id
8956   is
8957      Loc      : constant Source_Ptr := Sloc (Obj_Ref);
8958      Atyp     : Entity_Id;
8959      Prot_Typ : Entity_Id := Empty;
8960      Fin_Id   : Entity_Id := Empty;
8961      Ref      : Node_Id;
8962      Utyp     : Entity_Id;
8963
8964   begin
8965      Ref := Obj_Ref;
8966
8967      --  Recover the proper type which contains [Deep_]Finalize
8968
8969      if Is_Class_Wide_Type (Typ) then
8970         Utyp := Root_Type (Typ);
8971         Atyp := Utyp;
8972
8973      elsif Is_Concurrent_Type (Typ) then
8974         Utyp := Corresponding_Record_Type (Typ);
8975         Atyp := Empty;
8976         Ref  := Convert_Concurrent (Ref, Typ);
8977
8978      elsif Is_Private_Type (Typ)
8979        and then Present (Underlying_Type (Typ))
8980        and then Is_Concurrent_Type (Underlying_Type (Typ))
8981      then
8982         Utyp := Corresponding_Record_Type (Underlying_Type (Typ));
8983         Atyp := Typ;
8984         Ref  := Convert_Concurrent (Ref, Underlying_Type (Typ));
8985
8986      else
8987         Utyp := Typ;
8988         Atyp := Typ;
8989      end if;
8990
8991      Utyp := Underlying_Type (Base_Type (Utyp));
8992      Set_Assignment_OK (Ref);
8993
8994      --  Deal with untagged derivation of private views. If the parent type
8995      --  is a protected type, Deep_Finalize is found on the corresponding
8996      --  record of the ancestor.
8997
8998      if Is_Untagged_Derivation (Typ) then
8999         if Is_Protected_Type (Typ) then
9000            Utyp := Corresponding_Record_Type (Root_Type (Base_Type (Typ)));
9001         else
9002            Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
9003
9004            if Is_Protected_Type (Utyp) then
9005               Utyp := Corresponding_Record_Type (Utyp);
9006            end if;
9007         end if;
9008
9009         Ref := Unchecked_Convert_To (Utyp, Ref);
9010         Set_Assignment_OK (Ref);
9011      end if;
9012
9013      --  Deal with derived private types which do not inherit primitives from
9014      --  their parents. In this case, [Deep_]Finalize can be found in the full
9015      --  view of the parent type.
9016
9017      if Present (Utyp)
9018        and then Is_Tagged_Type (Utyp)
9019        and then Is_Derived_Type (Utyp)
9020        and then Is_Empty_Elmt_List (Primitive_Operations (Utyp))
9021        and then Is_Private_Type (Etype (Utyp))
9022        and then Present (Full_View (Etype (Utyp)))
9023      then
9024         Utyp := Full_View (Etype (Utyp));
9025         Ref  := Unchecked_Convert_To (Utyp, Ref);
9026         Set_Assignment_OK (Ref);
9027      end if;
9028
9029      --  When dealing with the completion of a private type, use the base type
9030      --  instead.
9031
9032      if Present (Utyp) and then Utyp /= Base_Type (Utyp) then
9033         pragma Assert (Present (Atyp) and then Is_Private_Type (Atyp));
9034
9035         Utyp := Base_Type (Utyp);
9036         Ref  := Unchecked_Convert_To (Utyp, Ref);
9037         Set_Assignment_OK (Ref);
9038      end if;
9039
9040      --  Detect if Typ is a protected type or an expanded protected type and
9041      --  store the relevant type within Prot_Typ for later processing.
9042
9043      if Is_Protected_Type (Typ) then
9044         Prot_Typ := Typ;
9045
9046      elsif Ekind (Typ) = E_Record_Type
9047        and then Present (Corresponding_Concurrent_Type (Typ))
9048        and then Is_Protected_Type (Corresponding_Concurrent_Type (Typ))
9049      then
9050         Prot_Typ := Corresponding_Concurrent_Type (Typ);
9051      end if;
9052
9053      --  The underlying type may not be present due to a missing full view. In
9054      --  this case freezing did not take place and there is no [Deep_]Finalize
9055      --  primitive to call.
9056
9057      if No (Utyp) then
9058         return Empty;
9059
9060      elsif Skip_Self then
9061         if Has_Controlled_Component (Utyp) then
9062            if Is_Tagged_Type (Utyp) then
9063               Fin_Id := Find_Optional_Prim_Op (Utyp, TSS_Deep_Finalize);
9064            else
9065               Fin_Id := TSS (Utyp, TSS_Deep_Finalize);
9066            end if;
9067         end if;
9068
9069      --  Class-wide types, interfaces and types with controlled components
9070
9071      elsif Is_Class_Wide_Type (Typ)
9072        or else Is_Interface (Typ)
9073        or else Has_Controlled_Component (Utyp)
9074      then
9075         if Is_Tagged_Type (Utyp) then
9076            Fin_Id := Find_Optional_Prim_Op (Utyp, TSS_Deep_Finalize);
9077         else
9078            Fin_Id := TSS (Utyp, TSS_Deep_Finalize);
9079         end if;
9080
9081      --  Derivations from [Limited_]Controlled
9082
9083      elsif Is_Controlled (Utyp) then
9084         if Has_Controlled_Component (Utyp) then
9085            Fin_Id := Find_Optional_Prim_Op (Utyp, TSS_Deep_Finalize);
9086         else
9087            Fin_Id := Find_Optional_Prim_Op (Utyp, Name_Of (Finalize_Case));
9088         end if;
9089
9090      --  Tagged types
9091
9092      elsif Is_Tagged_Type (Utyp) then
9093         Fin_Id := Find_Optional_Prim_Op (Utyp, TSS_Deep_Finalize);
9094
9095      --  Protected types: these also require finalization even though they
9096      --  are not marked controlled explicitly.
9097
9098      elsif Present (Prot_Typ) then
9099         --  Protected objects do not need to be finalized on restricted
9100         --  runtimes.
9101
9102         if Restricted_Profile then
9103            return Empty;
9104
9105         --  ??? Only handle the simple case for now. Will not support a record
9106         --  or array containing protected objects.
9107
9108         elsif Is_Simple_Protected_Type (Prot_Typ) then
9109            Fin_Id := RTE (RE_Finalize_Protection);
9110         else
9111            raise Program_Error;
9112         end if;
9113      else
9114         raise Program_Error;
9115      end if;
9116
9117      if Present (Fin_Id) then
9118
9119         --  When finalizing a class-wide object, do not convert to the root
9120         --  type in order to produce a dispatching call.
9121
9122         if Is_Class_Wide_Type (Typ) then
9123            null;
9124
9125         --  Ensure that a finalization routine is at least decorated in order
9126         --  to inspect the object parameter.
9127
9128         elsif Analyzed (Fin_Id)
9129           or else Ekind (Fin_Id) = E_Procedure
9130         then
9131            --  In certain cases, such as the creation of Stream_Read, the
9132            --  visible entity of the type is its full view. Since Stream_Read
9133            --  will have to create an object of type Typ, the local object
9134            --  will be finalzed by the scope finalizer generated later on. The
9135            --  object parameter of Deep_Finalize will always use the private
9136            --  view of the type. To avoid such a clash between a private and a
9137            --  full view, perform an unchecked conversion of the object
9138            --  reference to the private view.
9139
9140            declare
9141               Formal_Typ : constant Entity_Id :=
9142                              Etype (First_Formal (Fin_Id));
9143            begin
9144               if Is_Private_Type (Formal_Typ)
9145                 and then Present (Full_View (Formal_Typ))
9146                 and then Full_View (Formal_Typ) = Utyp
9147               then
9148                  Ref := Unchecked_Convert_To (Formal_Typ, Ref);
9149               end if;
9150            end;
9151
9152            --  If the object is unanalyzed, set its expected type for use in
9153            --  Convert_View in case an additional conversion is needed.
9154
9155            if No (Etype (Ref))
9156              and then Nkind (Ref) /= N_Unchecked_Type_Conversion
9157            then
9158               Set_Etype (Ref, Typ);
9159            end if;
9160
9161            Ref := Convert_View (Fin_Id, Ref);
9162         end if;
9163
9164         return
9165           Make_Call (Loc,
9166             Proc_Id   => Fin_Id,
9167             Param     => Ref,
9168             Skip_Self => Skip_Self);
9169      else
9170         return Empty;
9171      end if;
9172   end Make_Final_Call;
9173
9174   --------------------------------
9175   -- Make_Finalize_Address_Body --
9176   --------------------------------
9177
9178   procedure Make_Finalize_Address_Body (Typ : Entity_Id) is
9179      Is_Task : constant Boolean :=
9180                  Ekind (Typ) = E_Record_Type
9181                    and then Is_Concurrent_Record_Type (Typ)
9182                    and then Ekind (Corresponding_Concurrent_Type (Typ)) =
9183                                                                 E_Task_Type;
9184      Loc     : constant Source_Ptr := Sloc (Typ);
9185      Proc_Id : Entity_Id;
9186      Stmts   : List_Id;
9187
9188   begin
9189      --  The corresponding records of task types are not controlled by design.
9190      --  For the sake of completeness, create an empty Finalize_Address to be
9191      --  used in task class-wide allocations.
9192
9193      if Is_Task then
9194         null;
9195
9196      --  Nothing to do if the type is not controlled or it already has a
9197      --  TSS entry for Finalize_Address. Skip class-wide subtypes which do not
9198      --  come from source. These are usually generated for completeness and
9199      --  do not need the Finalize_Address primitive.
9200
9201      elsif not Needs_Finalization (Typ)
9202        or else Present (TSS (Typ, TSS_Finalize_Address))
9203        or else
9204          (Is_Class_Wide_Type (Typ)
9205            and then Ekind (Root_Type (Typ)) = E_Record_Subtype
9206            and then not Comes_From_Source (Root_Type (Typ)))
9207      then
9208         return;
9209      end if;
9210
9211      --  Do not generate Finalize_Address routine for CodePeer
9212
9213      if CodePeer_Mode then
9214         return;
9215      end if;
9216
9217      Proc_Id :=
9218        Make_Defining_Identifier (Loc,
9219          Make_TSS_Name (Typ, TSS_Finalize_Address));
9220
9221      --  Generate:
9222
9223      --    procedure <Typ>FD (V : System.Address) is
9224      --    begin
9225      --       null;                            --  for tasks
9226
9227      --       declare                          --  for all other types
9228      --          type Pnn is access all Typ;
9229      --          for Pnn'Storage_Size use 0;
9230      --       begin
9231      --          [Deep_]Finalize (Pnn (V).all);
9232      --       end;
9233      --    end TypFD;
9234
9235      if Is_Task then
9236         Stmts := New_List (Make_Null_Statement (Loc));
9237      else
9238         Stmts := Make_Finalize_Address_Stmts (Typ);
9239      end if;
9240
9241      Discard_Node (
9242        Make_Subprogram_Body (Loc,
9243          Specification =>
9244            Make_Procedure_Specification (Loc,
9245              Defining_Unit_Name => Proc_Id,
9246
9247              Parameter_Specifications => New_List (
9248                Make_Parameter_Specification (Loc,
9249                  Defining_Identifier =>
9250                    Make_Defining_Identifier (Loc, Name_V),
9251                  Parameter_Type =>
9252                    New_Occurrence_Of (RTE (RE_Address), Loc)))),
9253
9254          Declarations => No_List,
9255
9256          Handled_Statement_Sequence =>
9257            Make_Handled_Sequence_Of_Statements (Loc,
9258              Statements => Stmts)));
9259
9260      Set_TSS (Typ, Proc_Id);
9261   end Make_Finalize_Address_Body;
9262
9263   ---------------------------------
9264   -- Make_Finalize_Address_Stmts --
9265   ---------------------------------
9266
9267   function Make_Finalize_Address_Stmts (Typ : Entity_Id) return List_Id is
9268      Loc : constant Source_Ptr := Sloc (Typ);
9269
9270      Decls     : List_Id;
9271      Desig_Typ : Entity_Id;
9272      Fin_Block : Node_Id;
9273      Fin_Call  : Node_Id;
9274      Obj_Expr  : Node_Id;
9275      Ptr_Typ   : Entity_Id;
9276
9277   begin
9278      if Is_Array_Type (Typ) then
9279         if Is_Constrained (First_Subtype (Typ)) then
9280            Desig_Typ := First_Subtype (Typ);
9281         else
9282            Desig_Typ := Base_Type (Typ);
9283         end if;
9284
9285      --  Class-wide types of constrained root types
9286
9287      elsif Is_Class_Wide_Type (Typ)
9288        and then Has_Discriminants (Root_Type (Typ))
9289        and then not
9290          Is_Empty_Elmt_List (Discriminant_Constraint (Root_Type (Typ)))
9291      then
9292         declare
9293            Parent_Typ : Entity_Id;
9294
9295         begin
9296            --  Climb the parent type chain looking for a non-constrained type
9297
9298            Parent_Typ := Root_Type (Typ);
9299            while Parent_Typ /= Etype (Parent_Typ)
9300              and then Has_Discriminants (Parent_Typ)
9301              and then not
9302                Is_Empty_Elmt_List (Discriminant_Constraint (Parent_Typ))
9303            loop
9304               Parent_Typ := Etype (Parent_Typ);
9305            end loop;
9306
9307            --  Handle views created for tagged types with unknown
9308            --  discriminants.
9309
9310            if Is_Underlying_Record_View (Parent_Typ) then
9311               Parent_Typ := Underlying_Record_View (Parent_Typ);
9312            end if;
9313
9314            Desig_Typ := Class_Wide_Type (Underlying_Type (Parent_Typ));
9315         end;
9316
9317      --  General case
9318
9319      else
9320         Desig_Typ := Typ;
9321      end if;
9322
9323      --  Generate:
9324      --    type Ptr_Typ is access all Typ;
9325      --    for Ptr_Typ'Storage_Size use 0;
9326
9327      Ptr_Typ := Make_Temporary (Loc, 'P');
9328
9329      Decls := New_List (
9330        Make_Full_Type_Declaration (Loc,
9331          Defining_Identifier => Ptr_Typ,
9332          Type_Definition     =>
9333            Make_Access_To_Object_Definition (Loc,
9334              All_Present        => True,
9335              Subtype_Indication => New_Occurrence_Of (Desig_Typ, Loc))),
9336
9337        Make_Attribute_Definition_Clause (Loc,
9338          Name       => New_Occurrence_Of (Ptr_Typ, Loc),
9339          Chars      => Name_Storage_Size,
9340          Expression => Make_Integer_Literal (Loc, 0)));
9341
9342      Obj_Expr := Make_Identifier (Loc, Name_V);
9343
9344      --  Unconstrained arrays require special processing in order to retrieve
9345      --  the elements. To achieve this, we have to skip the dope vector which
9346      --  lays in front of the elements and then use a thin pointer to perform
9347      --  the address-to-access conversion.
9348
9349      if Is_Array_Type (Typ)
9350        and then not Is_Constrained (First_Subtype (Typ))
9351      then
9352         declare
9353            Dope_Id : Entity_Id;
9354
9355         begin
9356            --  Ensure that Ptr_Typ is a thin pointer; generate:
9357            --    for Ptr_Typ'Size use System.Address'Size;
9358
9359            Append_To (Decls,
9360              Make_Attribute_Definition_Clause (Loc,
9361                Name       => New_Occurrence_Of (Ptr_Typ, Loc),
9362                Chars      => Name_Size,
9363                Expression =>
9364                  Make_Integer_Literal (Loc, System_Address_Size)));
9365
9366            --  Generate:
9367            --    Dnn : constant Storage_Offset :=
9368            --            Desig_Typ'Descriptor_Size / Storage_Unit;
9369
9370            Dope_Id := Make_Temporary (Loc, 'D');
9371
9372            Append_To (Decls,
9373              Make_Object_Declaration (Loc,
9374                Defining_Identifier => Dope_Id,
9375                Constant_Present    => True,
9376                Object_Definition   =>
9377                  New_Occurrence_Of (RTE (RE_Storage_Offset), Loc),
9378                Expression          =>
9379                  Make_Op_Divide (Loc,
9380                    Left_Opnd  =>
9381                      Make_Attribute_Reference (Loc,
9382                        Prefix         => New_Occurrence_Of (Desig_Typ, Loc),
9383                        Attribute_Name => Name_Descriptor_Size),
9384                    Right_Opnd =>
9385                      Make_Integer_Literal (Loc, System_Storage_Unit))));
9386
9387            --  Shift the address from the start of the dope vector to the
9388            --  start of the elements:
9389            --
9390            --    V + Dnn
9391            --
9392            --  Note that this is done through a wrapper routine since RTSfind
9393            --  cannot retrieve operations with string names of the form "+".
9394
9395            Obj_Expr :=
9396              Make_Function_Call (Loc,
9397                Name                   =>
9398                  New_Occurrence_Of (RTE (RE_Add_Offset_To_Address), Loc),
9399                Parameter_Associations => New_List (
9400                  Obj_Expr,
9401                  New_Occurrence_Of (Dope_Id, Loc)));
9402         end;
9403      end if;
9404
9405      Fin_Call :=
9406        Make_Final_Call (
9407          Obj_Ref =>
9408            Make_Explicit_Dereference (Loc,
9409              Prefix => Unchecked_Convert_To (Ptr_Typ, Obj_Expr)),
9410          Typ     => Desig_Typ);
9411
9412      if Present (Fin_Call) then
9413         Fin_Block :=
9414           Make_Block_Statement (Loc,
9415             Declarations               => Decls,
9416             Handled_Statement_Sequence =>
9417               Make_Handled_Sequence_Of_Statements (Loc,
9418                 Statements => New_List (Fin_Call)));
9419
9420      --  Otherwise previous errors or a missing full view may prevent the
9421      --  proper freezing of the designated type. If this is the case, there
9422      --  is no [Deep_]Finalize primitive to call.
9423
9424      else
9425         Fin_Block := Make_Null_Statement (Loc);
9426      end if;
9427
9428      return New_List (Fin_Block);
9429   end Make_Finalize_Address_Stmts;
9430
9431   -------------------------------------
9432   -- Make_Handler_For_Ctrl_Operation --
9433   -------------------------------------
9434
9435   --  Generate:
9436
9437   --    when E : others =>
9438   --      Raise_From_Controlled_Operation (E);
9439
9440   --  or:
9441
9442   --    when others =>
9443   --      raise Program_Error [finalize raised exception];
9444
9445   --  depending on whether Raise_From_Controlled_Operation is available
9446
9447   function Make_Handler_For_Ctrl_Operation
9448     (Loc : Source_Ptr) return Node_Id
9449   is
9450      E_Occ : Entity_Id;
9451      --  Choice parameter (for the first case above)
9452
9453      Raise_Node : Node_Id;
9454      --  Procedure call or raise statement
9455
9456   begin
9457      --  Standard run-time: add choice parameter E and pass it to
9458      --  Raise_From_Controlled_Operation so that the original exception
9459      --  name and message can be recorded in the exception message for
9460      --  Program_Error.
9461
9462      if RTE_Available (RE_Raise_From_Controlled_Operation) then
9463         E_Occ := Make_Defining_Identifier (Loc, Name_E);
9464         Raise_Node :=
9465           Make_Procedure_Call_Statement (Loc,
9466             Name                   =>
9467               New_Occurrence_Of
9468                 (RTE (RE_Raise_From_Controlled_Operation), Loc),
9469             Parameter_Associations => New_List (
9470               New_Occurrence_Of (E_Occ, Loc)));
9471
9472      --  Restricted run-time: exception messages are not supported
9473
9474      else
9475         E_Occ := Empty;
9476         Raise_Node :=
9477           Make_Raise_Program_Error (Loc,
9478             Reason => PE_Finalize_Raised_Exception);
9479      end if;
9480
9481      return
9482        Make_Implicit_Exception_Handler (Loc,
9483          Exception_Choices => New_List (Make_Others_Choice (Loc)),
9484          Choice_Parameter  => E_Occ,
9485          Statements        => New_List (Raise_Node));
9486   end Make_Handler_For_Ctrl_Operation;
9487
9488   --------------------
9489   -- Make_Init_Call --
9490   --------------------
9491
9492   function Make_Init_Call
9493     (Obj_Ref : Node_Id;
9494      Typ     : Entity_Id) return Node_Id
9495   is
9496      Loc     : constant Source_Ptr := Sloc (Obj_Ref);
9497      Is_Conc : Boolean;
9498      Proc    : Entity_Id;
9499      Ref     : Node_Id;
9500      Utyp    : Entity_Id;
9501
9502   begin
9503      Ref := Obj_Ref;
9504
9505      --  Deal with the type and object reference. Depending on the context, an
9506      --  object reference may need several conversions.
9507
9508      if Is_Concurrent_Type (Typ) then
9509         Is_Conc := True;
9510         Utyp    := Corresponding_Record_Type (Typ);
9511         Ref     := Convert_Concurrent (Ref, Typ);
9512
9513      elsif Is_Private_Type (Typ)
9514        and then Present (Full_View (Typ))
9515        and then Is_Concurrent_Type (Underlying_Type (Typ))
9516      then
9517         Is_Conc := True;
9518         Utyp    := Corresponding_Record_Type (Underlying_Type (Typ));
9519         Ref     := Convert_Concurrent (Ref, Underlying_Type (Typ));
9520
9521      else
9522         Is_Conc := False;
9523         Utyp    := Typ;
9524      end if;
9525
9526      Utyp := Underlying_Type (Base_Type (Utyp));
9527      Set_Assignment_OK (Ref);
9528
9529      --  Deal with untagged derivation of private views
9530
9531      if Is_Untagged_Derivation (Typ) and then not Is_Conc then
9532         Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
9533         Ref  := Unchecked_Convert_To (Utyp, Ref);
9534
9535         --  The following is to prevent problems with UC see 1.156 RH ???
9536
9537         Set_Assignment_OK (Ref);
9538      end if;
9539
9540      --  If the underlying_type is a subtype, then we are dealing with the
9541      --  completion of a private type. We need to access the base type and
9542      --  generate a conversion to it.
9543
9544      if Present (Utyp) and then Utyp /= Base_Type (Utyp) then
9545         pragma Assert (Is_Private_Type (Typ));
9546         Utyp := Base_Type (Utyp);
9547         Ref  := Unchecked_Convert_To (Utyp, Ref);
9548      end if;
9549
9550      --  The underlying type may not be present due to a missing full view.
9551      --  In this case freezing did not take place and there is no suitable
9552      --  [Deep_]Initialize primitive to call.
9553      --  If Typ is protected then no additional processing is needed either.
9554
9555      if No (Utyp)
9556        or else Is_Protected_Type (Typ)
9557      then
9558         return Empty;
9559      end if;
9560
9561      --  Select the appropriate version of initialize
9562
9563      if Has_Controlled_Component (Utyp) then
9564         Proc := TSS (Utyp, Deep_Name_Of (Initialize_Case));
9565      else
9566         Proc := Find_Prim_Op (Utyp, Name_Of (Initialize_Case));
9567         Check_Visibly_Controlled (Initialize_Case, Typ, Proc, Ref);
9568      end if;
9569
9570      --  If initialization procedure for an array of controlled objects is
9571      --  trivial, do not generate a useless call to it.
9572      --  The initialization procedure may be missing altogether in the case
9573      --  of a derived container whose components have trivial initialization.
9574
9575      if No (Proc)
9576        or else (Is_Array_Type (Utyp) and then Is_Trivial_Subprogram (Proc))
9577        or else
9578          (not Comes_From_Source (Proc)
9579            and then Present (Alias (Proc))
9580            and then Is_Trivial_Subprogram (Alias (Proc)))
9581      then
9582         return Empty;
9583      end if;
9584
9585      --  The object reference may need another conversion depending on the
9586      --  type of the formal and that of the actual.
9587
9588      Ref := Convert_View (Proc, Ref);
9589
9590      --  Generate:
9591      --    [Deep_]Initialize (Ref);
9592
9593      return
9594        Make_Procedure_Call_Statement (Loc,
9595          Name                   => New_Occurrence_Of (Proc, Loc),
9596          Parameter_Associations => New_List (Ref));
9597   end Make_Init_Call;
9598
9599   ------------------------------
9600   -- Make_Local_Deep_Finalize --
9601   ------------------------------
9602
9603   function Make_Local_Deep_Finalize
9604     (Typ : Entity_Id;
9605      Nam : Entity_Id) return Node_Id
9606   is
9607      Loc : constant Source_Ptr := Sloc (Typ);
9608      Formals : List_Id;
9609
9610   begin
9611      Formals := New_List (
9612
9613         --  V : in out Typ
9614
9615        Make_Parameter_Specification (Loc,
9616          Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
9617          In_Present          => True,
9618          Out_Present         => True,
9619          Parameter_Type      => New_Occurrence_Of (Typ, Loc)),
9620
9621         --  F : Boolean := True
9622
9623        Make_Parameter_Specification (Loc,
9624          Defining_Identifier => Make_Defining_Identifier (Loc, Name_F),
9625          Parameter_Type      => New_Occurrence_Of (Standard_Boolean, Loc),
9626          Expression          => New_Occurrence_Of (Standard_True, Loc)));
9627
9628      --  Add the necessary number of counters to represent the initialization
9629      --  state of an object.
9630
9631      return
9632        Make_Subprogram_Body (Loc,
9633          Specification =>
9634            Make_Procedure_Specification (Loc,
9635              Defining_Unit_Name       => Nam,
9636              Parameter_Specifications => Formals),
9637
9638          Declarations => No_List,
9639
9640          Handled_Statement_Sequence =>
9641            Make_Handled_Sequence_Of_Statements (Loc,
9642              Statements => Make_Deep_Record_Body (Finalize_Case, Typ, True)));
9643   end Make_Local_Deep_Finalize;
9644
9645   ------------------------------------
9646   -- Make_Set_Finalize_Address_Call --
9647   ------------------------------------
9648
9649   function Make_Set_Finalize_Address_Call
9650     (Loc     : Source_Ptr;
9651      Ptr_Typ : Entity_Id) return Node_Id
9652   is
9653      --  It is possible for Ptr_Typ to be a partial view, if the access type
9654      --  is a full view declared in the private part of a nested package, and
9655      --  the finalization actions take place when completing analysis of the
9656      --  enclosing unit. For this reason use Underlying_Type twice below.
9657
9658      Desig_Typ : constant Entity_Id :=
9659                    Available_View
9660                      (Designated_Type (Underlying_Type (Ptr_Typ)));
9661      Fin_Addr  : constant Entity_Id := Finalize_Address (Desig_Typ);
9662      Fin_Mas   : constant Entity_Id :=
9663                    Finalization_Master (Underlying_Type (Ptr_Typ));
9664
9665   begin
9666      --  Both the finalization master and primitive Finalize_Address must be
9667      --  available.
9668
9669      pragma Assert (Present (Fin_Addr) and Present (Fin_Mas));
9670
9671      --  Generate:
9672      --    Set_Finalize_Address
9673      --      (<Ptr_Typ>FM, <Desig_Typ>FD'Unrestricted_Access);
9674
9675      return
9676        Make_Procedure_Call_Statement (Loc,
9677          Name                   =>
9678            New_Occurrence_Of (RTE (RE_Set_Finalize_Address), Loc),
9679          Parameter_Associations => New_List (
9680            New_Occurrence_Of (Fin_Mas, Loc),
9681
9682            Make_Attribute_Reference (Loc,
9683              Prefix         => New_Occurrence_Of (Fin_Addr, Loc),
9684              Attribute_Name => Name_Unrestricted_Access)));
9685   end Make_Set_Finalize_Address_Call;
9686
9687   --------------------------
9688   -- Make_Transient_Block --
9689   --------------------------
9690
9691   function Make_Transient_Block
9692     (Loc    : Source_Ptr;
9693      Action : Node_Id;
9694      Par    : Node_Id) return Node_Id
9695   is
9696      function Manages_Sec_Stack (Id : Entity_Id) return Boolean;
9697      --  Determine whether scoping entity Id manages the secondary stack
9698
9699      function Within_Loop_Statement (N : Node_Id) return Boolean;
9700      --  Return True when N appears within a loop and no block is containing N
9701
9702      -----------------------
9703      -- Manages_Sec_Stack --
9704      -----------------------
9705
9706      function Manages_Sec_Stack (Id : Entity_Id) return Boolean is
9707      begin
9708         case Ekind (Id) is
9709
9710            --  An exception handler with a choice parameter utilizes a dummy
9711            --  block to provide a declarative region. Such a block should not
9712            --  be considered because it never manifests in the tree and can
9713            --  never release the secondary stack.
9714
9715            when E_Block =>
9716               return
9717                 Uses_Sec_Stack (Id) and then not Is_Exception_Handler (Id);
9718
9719            when E_Entry
9720               | E_Entry_Family
9721               | E_Function
9722               | E_Procedure
9723            =>
9724               return Uses_Sec_Stack (Id);
9725
9726            when others =>
9727               return False;
9728         end case;
9729      end Manages_Sec_Stack;
9730
9731      ---------------------------
9732      -- Within_Loop_Statement --
9733      ---------------------------
9734
9735      function Within_Loop_Statement (N : Node_Id) return Boolean is
9736         Par : Node_Id := Parent (N);
9737
9738      begin
9739         while Nkind (Par) not in
9740           N_Handled_Sequence_Of_Statements | N_Loop_Statement |
9741           N_Package_Specification          | N_Proper_Body
9742         loop
9743            pragma Assert (Present (Par));
9744            Par := Parent (Par);
9745         end loop;
9746
9747         return Nkind (Par) = N_Loop_Statement;
9748      end Within_Loop_Statement;
9749
9750      --  Local variables
9751
9752      Decls    : constant List_Id   := New_List;
9753      Instrs   : constant List_Id   := New_List (Action);
9754      Trans_Id : constant Entity_Id := Current_Scope;
9755
9756      Block  : Node_Id;
9757      Insert : Node_Id;
9758      Scop   : Entity_Id;
9759
9760   --  Start of processing for Make_Transient_Block
9761
9762   begin
9763      --  Even though the transient block is tasked with managing the secondary
9764      --  stack, the block may forgo this functionality depending on how the
9765      --  secondary stack is managed by enclosing scopes.
9766
9767      if Manages_Sec_Stack (Trans_Id) then
9768
9769         --  Determine whether an enclosing scope already manages the secondary
9770         --  stack.
9771
9772         Scop := Scope (Trans_Id);
9773         while Present (Scop) loop
9774
9775            --  It should not be possible to reach Standard without hitting one
9776            --  of the other cases first unless Standard was manually pushed.
9777
9778            if Scop = Standard_Standard then
9779               exit;
9780
9781            --  The transient block is within a function which returns on the
9782            --  secondary stack. Take a conservative approach and assume that
9783            --  the value on the secondary stack is part of the result. Note
9784            --  that it is not possible to detect this dependency without flow
9785            --  analysis which the compiler does not have. Letting the object
9786            --  live longer than the transient block will not leak any memory
9787            --  because the caller will reclaim the total storage used by the
9788            --  function.
9789
9790            elsif Ekind (Scop) = E_Function
9791              and then Sec_Stack_Needed_For_Return (Scop)
9792            then
9793               Set_Uses_Sec_Stack (Trans_Id, False);
9794               exit;
9795
9796            --  The transient block must manage the secondary stack when the
9797            --  block appears within a loop in order to reclaim the memory at
9798            --  each iteration.
9799
9800            elsif Ekind (Scop) = E_Loop then
9801               exit;
9802
9803            --  Ditto when the block appears without a block that does not
9804            --  manage the secondary stack and is located within a loop.
9805
9806            elsif Ekind (Scop) = E_Block
9807              and then not Manages_Sec_Stack (Scop)
9808              and then Present (Block_Node (Scop))
9809              and then Within_Loop_Statement (Block_Node (Scop))
9810            then
9811               exit;
9812
9813            --  The transient block does not need to manage the secondary stack
9814            --  when there is an enclosing construct which already does that.
9815            --  This optimization saves on SS_Mark and SS_Release calls but may
9816            --  allow objects to live a little longer than required.
9817
9818            --  The transient block must manage the secondary stack when switch
9819            --  -gnatd.s (strict management) is in effect.
9820
9821            elsif Manages_Sec_Stack (Scop) and then not Debug_Flag_Dot_S then
9822               Set_Uses_Sec_Stack (Trans_Id, False);
9823               exit;
9824
9825            --  Prevent the search from going too far because transient blocks
9826            --  are bounded by packages and subprogram scopes.
9827
9828            elsif Ekind (Scop) in E_Entry
9829                                | E_Entry_Family
9830                                | E_Function
9831                                | E_Package
9832                                | E_Procedure
9833                                | E_Subprogram_Body
9834            then
9835               exit;
9836            end if;
9837
9838            Scop := Scope (Scop);
9839         end loop;
9840      end if;
9841
9842      --  Create the transient block. Set the parent now since the block itself
9843      --  is not part of the tree. The current scope is the E_Block entity that
9844      --  has been pushed by Establish_Transient_Scope.
9845
9846      pragma Assert (Ekind (Trans_Id) = E_Block);
9847
9848      Block :=
9849        Make_Block_Statement (Loc,
9850          Identifier                 => New_Occurrence_Of (Trans_Id, Loc),
9851          Declarations               => Decls,
9852          Handled_Statement_Sequence =>
9853            Make_Handled_Sequence_Of_Statements (Loc, Statements => Instrs),
9854          Has_Created_Identifier     => True);
9855      Set_Parent (Block, Par);
9856
9857      --  Insert actions stuck in the transient scopes as well as all freezing
9858      --  nodes needed by those actions. Do not insert cleanup actions here,
9859      --  they will be transferred to the newly created block.
9860
9861      Insert_Actions_In_Scope_Around
9862        (Action, Clean => False, Manage_SS => False);
9863
9864      Insert := Prev (Action);
9865
9866      if Present (Insert) then
9867         Freeze_All (First_Entity (Trans_Id), Insert);
9868      end if;
9869
9870      --  Transfer cleanup actions to the newly created block
9871
9872      declare
9873         Cleanup_Actions : List_Id
9874           renames Scope_Stack.Table (Scope_Stack.Last).
9875                     Actions_To_Be_Wrapped (Cleanup);
9876      begin
9877         Set_Cleanup_Actions (Block, Cleanup_Actions);
9878         Cleanup_Actions := No_List;
9879      end;
9880
9881      --  When the transient scope was established, we pushed the entry for the
9882      --  transient scope onto the scope stack, so that the scope was active
9883      --  for the installation of finalizable entities etc. Now we must remove
9884      --  this entry, since we have constructed a proper block.
9885
9886      Pop_Scope;
9887
9888      return Block;
9889   end Make_Transient_Block;
9890
9891   ------------------------
9892   -- Node_To_Be_Wrapped --
9893   ------------------------
9894
9895   function Node_To_Be_Wrapped return Node_Id is
9896   begin
9897      return Scope_Stack.Table (Scope_Stack.Last).Node_To_Be_Wrapped;
9898   end Node_To_Be_Wrapped;
9899
9900   ----------------------------
9901   -- Store_Actions_In_Scope --
9902   ----------------------------
9903
9904   procedure Store_Actions_In_Scope (AK : Scope_Action_Kind; L : List_Id) is
9905      SE      : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
9906      Actions : List_Id renames SE.Actions_To_Be_Wrapped (AK);
9907
9908   begin
9909      if Is_Empty_List (Actions) then
9910         Actions := L;
9911
9912         if Is_List_Member (SE.Node_To_Be_Wrapped) then
9913            Set_Parent (L, Parent (SE.Node_To_Be_Wrapped));
9914         else
9915            Set_Parent (L, SE.Node_To_Be_Wrapped);
9916         end if;
9917
9918         Analyze_List (L);
9919
9920      elsif AK = Before then
9921         Insert_List_After_And_Analyze (Last (Actions), L);
9922
9923      else
9924         Insert_List_Before_And_Analyze (First (Actions), L);
9925      end if;
9926   end Store_Actions_In_Scope;
9927
9928   ----------------------------------
9929   -- Store_After_Actions_In_Scope --
9930   ----------------------------------
9931
9932   procedure Store_After_Actions_In_Scope (L : List_Id) is
9933   begin
9934      Store_Actions_In_Scope (After, L);
9935   end Store_After_Actions_In_Scope;
9936
9937   -----------------------------------
9938   -- Store_Before_Actions_In_Scope --
9939   -----------------------------------
9940
9941   procedure Store_Before_Actions_In_Scope (L : List_Id) is
9942   begin
9943      Store_Actions_In_Scope (Before, L);
9944   end Store_Before_Actions_In_Scope;
9945
9946   -----------------------------------
9947   -- Store_Cleanup_Actions_In_Scope --
9948   -----------------------------------
9949
9950   procedure Store_Cleanup_Actions_In_Scope (L : List_Id) is
9951   begin
9952      Store_Actions_In_Scope (Cleanup, L);
9953   end Store_Cleanup_Actions_In_Scope;
9954
9955   ------------------
9956   -- Unnest_Block --
9957   ------------------
9958
9959   procedure Unnest_Block (Decl : Node_Id) is
9960      Loc        : constant Source_Ptr := Sloc (Decl);
9961      Ent        : Entity_Id;
9962      Local_Body : Node_Id;
9963      Local_Call : Node_Id;
9964      Local_Proc : Entity_Id;
9965      Local_Scop : Entity_Id;
9966
9967   begin
9968      Local_Scop := Entity (Identifier (Decl));
9969      Ent := First_Entity (Local_Scop);
9970
9971      Local_Proc :=
9972        Make_Defining_Identifier (Loc,
9973          Chars => New_Internal_Name ('P'));
9974
9975      Local_Body :=
9976        Make_Subprogram_Body (Loc,
9977          Specification              =>
9978            Make_Procedure_Specification (Loc,
9979              Defining_Unit_Name => Local_Proc),
9980              Declarations       => Declarations (Decl),
9981          Handled_Statement_Sequence =>
9982            Handled_Statement_Sequence (Decl));
9983
9984      --  Handlers in the block may contain nested subprograms that require
9985      --  unnesting.
9986
9987      Check_Unnesting_In_Handlers (Local_Body);
9988
9989      Rewrite (Decl, Local_Body);
9990      Analyze (Decl);
9991      Set_Has_Nested_Subprogram (Local_Proc);
9992
9993      Local_Call :=
9994        Make_Procedure_Call_Statement (Loc,
9995          Name => New_Occurrence_Of (Local_Proc, Loc));
9996
9997      Insert_After (Decl, Local_Call);
9998      Analyze (Local_Call);
9999
10000      --  The new subprogram has the same scope as the original block
10001
10002      Set_Scope (Local_Proc, Scope (Local_Scop));
10003
10004      --  And the entity list of the new procedure is that of the block
10005
10006      Set_First_Entity (Local_Proc, Ent);
10007
10008      --  Reset the scopes of all the entities to the new procedure
10009
10010      while Present (Ent) loop
10011         Set_Scope (Ent, Local_Proc);
10012         Next_Entity (Ent);
10013      end loop;
10014   end Unnest_Block;
10015
10016   -------------------------
10017   -- Unnest_If_Statement --
10018   -------------------------
10019
10020   procedure Unnest_If_Statement (If_Stmt : Node_Id) is
10021
10022      procedure Check_Stmts_For_Subp_Unnesting (Stmts : in out List_Id);
10023      --  A list of statements (that may be a list associated with a then,
10024      --  elsif, or else part of an if-statement) is traversed at the top
10025      --  level to determine whether it contains a subprogram body, and if so,
10026      --  the statements will be replaced with a new procedure body containing
10027      --  the statements followed by a call to the procedure. The individual
10028      --  statements may also be blocks, loops, or other if statements that
10029      --  themselves may require contain nested subprograms needing unnesting.
10030
10031      procedure Check_Stmts_For_Subp_Unnesting (Stmts : in out List_Id) is
10032         Subp_Found : Boolean := False;
10033
10034      begin
10035         if Is_Empty_List (Stmts) then
10036            return;
10037         end if;
10038
10039         declare
10040            Stmt : Node_Id := First (Stmts);
10041         begin
10042            while Present (Stmt) loop
10043               if Nkind (Stmt) = N_Subprogram_Body then
10044                  Subp_Found := True;
10045                  exit;
10046               end if;
10047
10048               Next (Stmt);
10049            end loop;
10050         end;
10051
10052         --  The statements themselves may be blocks, loops, etc. that in turn
10053         --  contain nested subprograms requiring an unnesting transformation.
10054         --  We perform this traversal after looking for subprogram bodies, to
10055         --  avoid considering procedures created for one of those statements
10056         --  (such as a block rewritten as a procedure) as a nested subprogram
10057         --  of the statement list (which could result in an unneeded wrapper
10058         --  procedure).
10059
10060         Check_Unnesting_In_Decls_Or_Stmts (Stmts);
10061
10062         --  If there was a top-level subprogram body in the statement list,
10063         --  then perform an unnesting transformation on the list by replacing
10064         --  the statements with a wrapper procedure body containing the
10065         --  original statements followed by a call to that procedure.
10066
10067         if Subp_Found then
10068            Unnest_Statement_List (Stmts);
10069         end if;
10070      end Check_Stmts_For_Subp_Unnesting;
10071
10072      --  Local variables
10073
10074      Then_Stmts : List_Id := Then_Statements (If_Stmt);
10075      Else_Stmts : List_Id := Else_Statements (If_Stmt);
10076
10077   --  Start of processing for Unnest_If_Statement
10078
10079   begin
10080      Check_Stmts_For_Subp_Unnesting (Then_Stmts);
10081      Set_Then_Statements (If_Stmt, Then_Stmts);
10082
10083      if not Is_Empty_List (Elsif_Parts (If_Stmt)) then
10084         declare
10085            Elsif_Part  : Node_Id :=
10086                            First (Elsif_Parts (If_Stmt));
10087            Elsif_Stmts : List_Id;
10088         begin
10089            while Present (Elsif_Part) loop
10090               Elsif_Stmts := Then_Statements (Elsif_Part);
10091
10092               Check_Stmts_For_Subp_Unnesting (Elsif_Stmts);
10093               Set_Then_Statements (Elsif_Part, Elsif_Stmts);
10094
10095               Next (Elsif_Part);
10096            end loop;
10097         end;
10098      end if;
10099
10100      Check_Stmts_For_Subp_Unnesting (Else_Stmts);
10101      Set_Else_Statements (If_Stmt, Else_Stmts);
10102   end Unnest_If_Statement;
10103
10104   -----------------
10105   -- Unnest_Loop --
10106   -----------------
10107
10108   procedure Unnest_Loop (Loop_Stmt : Node_Id) is
10109      Loc        : constant Source_Ptr := Sloc (Loop_Stmt);
10110      Ent        : Entity_Id;
10111      Local_Body : Node_Id;
10112      Local_Call : Node_Id;
10113      Local_Proc : Entity_Id;
10114      Local_Scop : Entity_Id;
10115      Loop_Copy  : constant Node_Id :=
10116                     Relocate_Node (Loop_Stmt);
10117   begin
10118      Local_Scop := Entity (Identifier (Loop_Stmt));
10119      Ent := First_Entity (Local_Scop);
10120
10121      Local_Proc :=
10122        Make_Defining_Identifier (Loc,
10123          Chars => New_Internal_Name ('P'));
10124
10125      Local_Body :=
10126        Make_Subprogram_Body (Loc,
10127          Specification              =>
10128            Make_Procedure_Specification (Loc,
10129              Defining_Unit_Name => Local_Proc),
10130              Declarations       => Empty_List,
10131          Handled_Statement_Sequence =>
10132            Make_Handled_Sequence_Of_Statements (Loc,
10133              Statements => New_List (Loop_Copy)));
10134
10135      Set_First_Real_Statement
10136        (Handled_Statement_Sequence (Local_Body), Loop_Copy);
10137
10138      Rewrite (Loop_Stmt, Local_Body);
10139      Analyze (Loop_Stmt);
10140
10141      Set_Has_Nested_Subprogram (Local_Proc);
10142
10143      Local_Call :=
10144        Make_Procedure_Call_Statement (Loc,
10145          Name => New_Occurrence_Of (Local_Proc, Loc));
10146
10147      Insert_After (Loop_Stmt, Local_Call);
10148      Analyze (Local_Call);
10149
10150      --  New procedure has the same scope as the original loop, and the scope
10151      --  of the loop is the new procedure.
10152
10153      Set_Scope (Local_Proc, Scope (Local_Scop));
10154      Set_Scope (Local_Scop, Local_Proc);
10155
10156      --  The entity list of the new procedure is that of the loop
10157
10158      Set_First_Entity (Local_Proc, Ent);
10159
10160      --  Note that the entities associated with the loop don't need to have
10161      --  their Scope fields reset, since they're still associated with the
10162      --  same loop entity that now belongs to the copied loop statement.
10163   end Unnest_Loop;
10164
10165   ---------------------------
10166   -- Unnest_Statement_List --
10167   ---------------------------
10168
10169   procedure Unnest_Statement_List (Stmts : in out List_Id) is
10170      Loc        : constant Source_Ptr := Sloc (First (Stmts));
10171      Local_Body : Node_Id;
10172      Local_Call : Node_Id;
10173      Local_Proc : Entity_Id;
10174      New_Stmts  : constant List_Id := Empty_List;
10175
10176   begin
10177      Local_Proc :=
10178        Make_Defining_Identifier (Loc,
10179          Chars => New_Internal_Name ('P'));
10180
10181      Local_Body :=
10182        Make_Subprogram_Body (Loc,
10183          Specification              =>
10184            Make_Procedure_Specification (Loc,
10185              Defining_Unit_Name => Local_Proc),
10186          Declarations               => Empty_List,
10187          Handled_Statement_Sequence =>
10188            Make_Handled_Sequence_Of_Statements (Loc,
10189              Statements => Stmts));
10190
10191      Append_To (New_Stmts, Local_Body);
10192
10193      Analyze (Local_Body);
10194
10195      Set_Has_Nested_Subprogram (Local_Proc);
10196
10197      Local_Call :=
10198        Make_Procedure_Call_Statement (Loc,
10199          Name => New_Occurrence_Of (Local_Proc, Loc));
10200
10201      Append_To (New_Stmts, Local_Call);
10202      Analyze (Local_Call);
10203
10204      --  Traverse the statements, and for any that are declarations or
10205      --  subprogram bodies that have entities, set the Scope of those
10206      --  entities to the new procedure's Entity_Id.
10207
10208      declare
10209         Stmt : Node_Id := First (Stmts);
10210
10211      begin
10212         while Present (Stmt) loop
10213            case Nkind (Stmt) is
10214               when N_Declaration
10215                  | N_Renaming_Declaration
10216               =>
10217                  Set_Scope (Defining_Identifier (Stmt), Local_Proc);
10218
10219               when N_Subprogram_Body =>
10220                  Set_Scope
10221                    (Defining_Unit_Name (Specification (Stmt)), Local_Proc);
10222
10223               when others =>
10224                  null;
10225            end case;
10226
10227            Next (Stmt);
10228         end loop;
10229      end;
10230
10231      Stmts := New_Stmts;
10232   end Unnest_Statement_List;
10233
10234   --------------------------------
10235   -- Wrap_Transient_Declaration --
10236   --------------------------------
10237
10238   --  If a transient scope has been established during the processing of the
10239   --  Expression of an Object_Declaration, it is not possible to wrap the
10240   --  declaration into a transient block as usual case, otherwise the object
10241   --  would be itself declared in the wrong scope. Therefore, all entities (if
10242   --  any) defined in the transient block are moved to the proper enclosing
10243   --  scope. Furthermore, if they are controlled variables they are finalized
10244   --  right after the declaration. The finalization list of the transient
10245   --  scope is defined as a renaming of the enclosing one so during their
10246   --  initialization they will be attached to the proper finalization list.
10247   --  For instance, the following declaration :
10248
10249   --        X : Typ := F (G (A), G (B));
10250
10251   --  (where G(A) and G(B) return controlled values, expanded as _v1 and _v2)
10252   --  is expanded into :
10253
10254   --    X : Typ := [ complex Expression-Action ];
10255   --    [Deep_]Finalize (_v1);
10256   --    [Deep_]Finalize (_v2);
10257
10258   procedure Wrap_Transient_Declaration (N : Node_Id) is
10259      Curr_S : Entity_Id;
10260      Encl_S : Entity_Id;
10261
10262   begin
10263      Curr_S := Current_Scope;
10264      Encl_S := Scope (Curr_S);
10265
10266      --  Insert all actions including cleanup generated while analyzing or
10267      --  expanding the transient context back into the tree. Manage the
10268      --  secondary stack when the object declaration appears in a library
10269      --  level package [body].
10270
10271      Insert_Actions_In_Scope_Around
10272        (N         => N,
10273         Clean     => True,
10274         Manage_SS =>
10275           Uses_Sec_Stack (Curr_S)
10276             and then Nkind (N) = N_Object_Declaration
10277             and then Ekind (Encl_S) in E_Package | E_Package_Body
10278             and then Is_Library_Level_Entity (Encl_S));
10279      Pop_Scope;
10280
10281      --  Relocate local entities declared within the transient scope to the
10282      --  enclosing scope. This action sets their Is_Public flag accordingly.
10283
10284      Transfer_Entities (Curr_S, Encl_S);
10285
10286      --  Mark the enclosing dynamic scope to ensure that the secondary stack
10287      --  is properly released upon exiting the said scope.
10288
10289      if Uses_Sec_Stack (Curr_S) then
10290         Curr_S := Enclosing_Dynamic_Scope (Curr_S);
10291
10292         --  Do not mark a function that returns on the secondary stack as the
10293         --  reclamation is done by the caller.
10294
10295         if Ekind (Curr_S) = E_Function
10296           and then Requires_Transient_Scope (Etype (Curr_S))
10297         then
10298            null;
10299
10300         --  Otherwise mark the enclosing dynamic scope
10301
10302         else
10303            Set_Uses_Sec_Stack (Curr_S);
10304            Check_Restriction (No_Secondary_Stack, N);
10305         end if;
10306      end if;
10307   end Wrap_Transient_Declaration;
10308
10309   -------------------------------
10310   -- Wrap_Transient_Expression --
10311   -------------------------------
10312
10313   procedure Wrap_Transient_Expression (N : Node_Id) is
10314      Loc  : constant Source_Ptr := Sloc (N);
10315      Expr : Node_Id             := Relocate_Node (N);
10316      Temp : constant Entity_Id  := Make_Temporary (Loc, 'E', N);
10317      Typ  : constant Entity_Id  := Etype (N);
10318
10319   begin
10320      --  Generate:
10321
10322      --    Temp : Typ;
10323      --    declare
10324      --       M : constant Mark_Id := SS_Mark;
10325      --       procedure Finalizer is ...  (See Build_Finalizer)
10326
10327      --    begin
10328      --       Temp := <Expr>;                           --  general case
10329      --       Temp := (if <Expr> then True else False); --  boolean case
10330
10331      --    at end
10332      --       Finalizer;
10333      --    end;
10334
10335      --  A special case is made for Boolean expressions so that the back end
10336      --  knows to generate a conditional branch instruction, if running with
10337      --  -fpreserve-control-flow. This ensures that a control-flow change
10338      --  signaling the decision outcome occurs before the cleanup actions.
10339
10340      if Opt.Suppress_Control_Flow_Optimizations
10341        and then Is_Boolean_Type (Typ)
10342      then
10343         Expr :=
10344           Make_If_Expression (Loc,
10345             Expressions => New_List (
10346               Expr,
10347               New_Occurrence_Of (Standard_True, Loc),
10348               New_Occurrence_Of (Standard_False, Loc)));
10349      end if;
10350
10351      Insert_Actions (N, New_List (
10352        Make_Object_Declaration (Loc,
10353          Defining_Identifier => Temp,
10354          Object_Definition   => New_Occurrence_Of (Typ, Loc)),
10355
10356        Make_Transient_Block (Loc,
10357          Action =>
10358            Make_Assignment_Statement (Loc,
10359              Name       => New_Occurrence_Of (Temp, Loc),
10360              Expression => Expr),
10361          Par    => Parent (N))));
10362
10363      if Debug_Generated_Code then
10364         Set_Debug_Info_Needed (Temp);
10365      end if;
10366
10367      Rewrite (N, New_Occurrence_Of (Temp, Loc));
10368      Analyze_And_Resolve (N, Typ);
10369   end Wrap_Transient_Expression;
10370
10371   ------------------------------
10372   -- Wrap_Transient_Statement --
10373   ------------------------------
10374
10375   procedure Wrap_Transient_Statement (N : Node_Id) is
10376      Loc      : constant Source_Ptr := Sloc (N);
10377      New_Stmt : constant Node_Id    := Relocate_Node (N);
10378
10379   begin
10380      --  Generate:
10381      --    declare
10382      --       M : constant Mark_Id := SS_Mark;
10383      --       procedure Finalizer is ...  (See Build_Finalizer)
10384      --
10385      --    begin
10386      --       <New_Stmt>;
10387      --
10388      --    at end
10389      --       Finalizer;
10390      --    end;
10391
10392      Rewrite (N,
10393        Make_Transient_Block (Loc,
10394          Action => New_Stmt,
10395          Par    => Parent (N)));
10396
10397      --  With the scope stack back to normal, we can call analyze on the
10398      --  resulting block. At this point, the transient scope is being
10399      --  treated like a perfectly normal scope, so there is nothing
10400      --  special about it.
10401
10402      --  Note: Wrap_Transient_Statement is called with the node already
10403      --  analyzed (i.e. Analyzed (N) is True). This is important, since
10404      --  otherwise we would get a recursive processing of the node when
10405      --  we do this Analyze call.
10406
10407      Analyze (N);
10408   end Wrap_Transient_Statement;
10409
10410end Exp_Ch7;
10411