cfgloopmanip.c (copy_loop_info): New function.
[official-gcc.git] / gcc / ada / exp_ch7.adb
blob78ad5d27d674ce1534259dc350ef8da6068e25f3
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-2012, 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 ------------------------------------------------------------------------------
26 -- This package contains virtually all expansion mechanisms related to
27 -- - controlled types
28 -- - transient scopes
30 with Atree; use Atree;
31 with Debug; use Debug;
32 with Einfo; use Einfo;
33 with Elists; use Elists;
34 with Errout; use Errout;
35 with Exp_Ch6; use Exp_Ch6;
36 with Exp_Ch9; use Exp_Ch9;
37 with Exp_Ch11; use Exp_Ch11;
38 with Exp_Dbug; use Exp_Dbug;
39 with Exp_Dist; use Exp_Dist;
40 with Exp_Disp; use Exp_Disp;
41 with Exp_Tss; use Exp_Tss;
42 with Exp_Util; use Exp_Util;
43 with Freeze; use Freeze;
44 with Lib; use Lib;
45 with Nlists; use Nlists;
46 with Nmake; use Nmake;
47 with Opt; use Opt;
48 with Output; use Output;
49 with Restrict; use Restrict;
50 with Rident; use Rident;
51 with Rtsfind; use Rtsfind;
52 with Sinfo; use Sinfo;
53 with Sem; use Sem;
54 with Sem_Aux; use Sem_Aux;
55 with Sem_Ch3; use Sem_Ch3;
56 with Sem_Ch7; use Sem_Ch7;
57 with Sem_Ch8; use Sem_Ch8;
58 with Sem_Res; use Sem_Res;
59 with Sem_Util; use Sem_Util;
60 with Snames; use Snames;
61 with Stand; use Stand;
62 with Targparm; use Targparm;
63 with Tbuild; use Tbuild;
64 with Ttypes; use Ttypes;
65 with Uintp; use Uintp;
67 package body Exp_Ch7 is
69 --------------------------------
70 -- Transient Scope Management --
71 --------------------------------
73 -- A transient scope is created when temporary objects are created by the
74 -- compiler. These temporary objects are allocated on the secondary stack
75 -- and the transient scope is responsible for finalizing the object when
76 -- appropriate and reclaiming the memory at the right time. The temporary
77 -- objects are generally the objects allocated to store the result of a
78 -- function returning an unconstrained or a tagged value. Expressions
79 -- needing to be wrapped in a transient scope (functions calls returning
80 -- unconstrained or tagged values) may appear in 3 different contexts which
81 -- lead to 3 different kinds of transient scope expansion:
83 -- 1. In a simple statement (procedure call, assignment, ...). In this
84 -- case the instruction is wrapped into a transient block. See
85 -- Wrap_Transient_Statement for details.
87 -- 2. In an expression of a control structure (test in a IF statement,
88 -- expression in a CASE statement, ...). See Wrap_Transient_Expression
89 -- for details.
91 -- 3. In a expression of an object_declaration. No wrapping is possible
92 -- here, so the finalization actions, if any, are done right after the
93 -- declaration and the secondary stack deallocation is done in the
94 -- proper enclosing scope. See Wrap_Transient_Declaration for details.
96 -- Note about functions returning tagged types: it has been decided to
97 -- always allocate their result in the secondary stack, even though is not
98 -- absolutely mandatory when the tagged type is constrained because the
99 -- caller knows the size of the returned object and thus could allocate the
100 -- result in the primary stack. An exception to this is when the function
101 -- builds its result in place, as is done for functions with inherently
102 -- limited result types for Ada 2005. In that case, certain callers may
103 -- pass the address of a constrained object as the target object for the
104 -- function result.
106 -- By allocating tagged results in the secondary stack a number of
107 -- implementation difficulties are avoided:
109 -- - If it is a dispatching function call, the computation of the size of
110 -- the result is possible but complex from the outside.
112 -- - If the returned type is controlled, the assignment of the returned
113 -- value to the anonymous object involves an Adjust, and we have no
114 -- easy way to access the anonymous object created by the back end.
116 -- - If the returned type is class-wide, this is an unconstrained type
117 -- anyway.
119 -- Furthermore, the small loss in efficiency which is the result of this
120 -- decision is not such a big deal because functions returning tagged types
121 -- are not as common in practice compared to functions returning access to
122 -- a tagged type.
124 --------------------------------------------------
125 -- Transient Blocks and Finalization Management --
126 --------------------------------------------------
128 function Find_Node_To_Be_Wrapped (N : Node_Id) return Node_Id;
129 -- N is a node which may generate a transient scope. Loop over the parent
130 -- pointers of N until it find the appropriate node to wrap. If it returns
131 -- Empty, it means that no transient scope is needed in this context.
133 procedure Insert_Actions_In_Scope_Around (N : Node_Id);
134 -- Insert the before-actions kept in the scope stack before N, and the
135 -- after-actions after N, which must be a member of a list.
137 function Make_Transient_Block
138 (Loc : Source_Ptr;
139 Action : Node_Id;
140 Par : Node_Id) return Node_Id;
141 -- Action is a single statement or object declaration. Par is the proper
142 -- parent of the generated block. Create a transient block whose name is
143 -- the current scope and the only handled statement is Action. If Action
144 -- involves controlled objects or secondary stack usage, the corresponding
145 -- cleanup actions are performed at the end of the block.
147 procedure Set_Node_To_Be_Wrapped (N : Node_Id);
148 -- Set the field Node_To_Be_Wrapped of the current scope
150 -- ??? The entire comment needs to be rewritten
152 -----------------------------
153 -- Finalization Management --
154 -----------------------------
156 -- This part describe how Initialization/Adjustment/Finalization procedures
157 -- are generated and called. Two cases must be considered, types that are
158 -- Controlled (Is_Controlled flag set) and composite types that contain
159 -- controlled components (Has_Controlled_Component flag set). In the first
160 -- case the procedures to call are the user-defined primitive operations
161 -- Initialize/Adjust/Finalize. In the second case, GNAT generates
162 -- Deep_Initialize, Deep_Adjust and Deep_Finalize that are in charge
163 -- of calling the former procedures on the controlled components.
165 -- For records with Has_Controlled_Component set, a hidden "controller"
166 -- component is inserted. This controller component contains its own
167 -- finalization list on which all controlled components are attached
168 -- creating an indirection on the upper-level Finalization list. This
169 -- technique facilitates the management of objects whose number of
170 -- controlled components changes during execution. This controller
171 -- component is itself controlled and is attached to the upper-level
172 -- finalization chain. Its adjust primitive is in charge of calling adjust
173 -- on the components and adjusting the finalization pointer to match their
174 -- new location (see a-finali.adb).
176 -- It is not possible to use a similar technique for arrays that have
177 -- Has_Controlled_Component set. In this case, deep procedures are
178 -- generated that call initialize/adjust/finalize + attachment or
179 -- detachment on the finalization list for all component.
181 -- Initialize calls: they are generated for declarations or dynamic
182 -- allocations of Controlled objects with no initial value. They are always
183 -- followed by an attachment to the current Finalization Chain. For the
184 -- dynamic allocation case this the chain attached to the scope of the
185 -- access type definition otherwise, this is the chain of the current
186 -- scope.
188 -- Adjust Calls: They are generated on 2 occasions: (1) for declarations
189 -- or dynamic allocations of Controlled objects with an initial value.
190 -- (2) after an assignment. In the first case they are followed by an
191 -- attachment to the final chain, in the second case they are not.
193 -- Finalization Calls: They are generated on (1) scope exit, (2)
194 -- assignments, (3) unchecked deallocations. In case (3) they have to
195 -- be detached from the final chain, in case (2) they must not and in
196 -- case (1) this is not important since we are exiting the scope anyway.
198 -- Other details:
200 -- Type extensions will have a new record controller at each derivation
201 -- level containing controlled components. The record controller for
202 -- the parent/ancestor is attached to the finalization list of the
203 -- extension's record controller (i.e. the parent is like a component
204 -- of the extension).
206 -- For types that are both Is_Controlled and Has_Controlled_Components,
207 -- the record controller and the object itself are handled separately.
208 -- It could seem simpler to attach the object at the end of its record
209 -- controller but this would not tackle view conversions properly.
211 -- A classwide type can always potentially have controlled components
212 -- but the record controller of the corresponding actual type may not
213 -- be known at compile time so the dispatch table contains a special
214 -- field that allows to compute the offset of the record controller
215 -- dynamically. See s-finimp.Deep_Tag_Attach and a-tags.RC_Offset.
217 -- Here is a simple example of the expansion of a controlled block :
219 -- declare
220 -- X : Controlled;
221 -- Y : Controlled := Init;
223 -- type R is record
224 -- C : Controlled;
225 -- end record;
226 -- W : R;
227 -- Z : R := (C => X);
229 -- begin
230 -- X := Y;
231 -- W := Z;
232 -- end;
234 -- is expanded into
236 -- declare
237 -- _L : System.FI.Finalizable_Ptr;
239 -- procedure _Clean is
240 -- begin
241 -- Abort_Defer;
242 -- System.FI.Finalize_List (_L);
243 -- Abort_Undefer;
244 -- end _Clean;
246 -- X : Controlled;
247 -- begin
248 -- Abort_Defer;
249 -- Initialize (X);
250 -- Attach_To_Final_List (_L, Finalizable (X), 1);
251 -- at end: Abort_Undefer;
252 -- Y : Controlled := Init;
253 -- Adjust (Y);
254 -- Attach_To_Final_List (_L, Finalizable (Y), 1);
256 -- type R is record
257 -- C : Controlled;
258 -- end record;
259 -- W : R;
260 -- begin
261 -- Abort_Defer;
262 -- Deep_Initialize (W, _L, 1);
263 -- at end: Abort_Under;
264 -- Z : R := (C => X);
265 -- Deep_Adjust (Z, _L, 1);
267 -- begin
268 -- _Assign (X, Y);
269 -- Deep_Finalize (W, False);
270 -- <save W's final pointers>
271 -- W := Z;
272 -- <restore W's final pointers>
273 -- Deep_Adjust (W, _L, 0);
274 -- at end
275 -- _Clean;
276 -- end;
278 type Final_Primitives is
279 (Initialize_Case, Adjust_Case, Finalize_Case, Address_Case);
280 -- This enumeration type is defined in order to ease sharing code for
281 -- building finalization procedures for composite types.
283 Name_Of : constant array (Final_Primitives) of Name_Id :=
284 (Initialize_Case => Name_Initialize,
285 Adjust_Case => Name_Adjust,
286 Finalize_Case => Name_Finalize,
287 Address_Case => Name_Finalize_Address);
288 Deep_Name_Of : constant array (Final_Primitives) of TSS_Name_Type :=
289 (Initialize_Case => TSS_Deep_Initialize,
290 Adjust_Case => TSS_Deep_Adjust,
291 Finalize_Case => TSS_Deep_Finalize,
292 Address_Case => TSS_Finalize_Address);
294 procedure Build_Array_Deep_Procs (Typ : Entity_Id);
295 -- Build the deep Initialize/Adjust/Finalize for a record Typ with
296 -- Has_Controlled_Component set and store them using the TSS mechanism.
298 function Build_Cleanup_Statements (N : Node_Id) return List_Id;
299 -- Create the clean up calls for an asynchronous call block, task master,
300 -- protected subprogram body, task allocation block or task body. If the
301 -- context does not contain the above constructs, the routine returns an
302 -- empty list.
304 procedure Build_Finalizer
305 (N : Node_Id;
306 Clean_Stmts : List_Id;
307 Mark_Id : Entity_Id;
308 Top_Decls : List_Id;
309 Defer_Abort : Boolean;
310 Fin_Id : out Entity_Id);
311 -- N may denote an accept statement, block, entry body, package body,
312 -- package spec, protected body, subprogram body, and a task body. Create
313 -- a procedure which contains finalization calls for all controlled objects
314 -- declared in the declarative or statement region of N. The calls are
315 -- built in reverse order relative to the original declarations. In the
316 -- case of a tack body, the routine delays the creation of the finalizer
317 -- until all statements have been moved to the task body procedure.
318 -- Clean_Stmts may contain additional context-dependent code used to abort
319 -- asynchronous calls or complete tasks (see Build_Cleanup_Statements).
320 -- Mark_Id is the secondary stack used in the current context or Empty if
321 -- missing. Top_Decls is the list on which the declaration of the finalizer
322 -- is attached in the non-package case. Defer_Abort indicates that the
323 -- statements passed in perform actions that require abort to be deferred,
324 -- such as for task termination. Fin_Id is the finalizer declaration
325 -- entity.
327 procedure Build_Finalizer_Call (N : Node_Id; Fin_Id : Entity_Id);
328 -- N is a construct which contains a handled sequence of statements, Fin_Id
329 -- is the entity of a finalizer. Create an At_End handler which covers the
330 -- statements of N and calls Fin_Id. If the handled statement sequence has
331 -- an exception handler, the statements will be wrapped in a block to avoid
332 -- unwanted interaction with the new At_End handler.
334 procedure Build_Record_Deep_Procs (Typ : Entity_Id);
335 -- Build the deep Initialize/Adjust/Finalize for a record Typ with
336 -- Has_Component_Component set and store them using the TSS mechanism.
338 procedure Check_Visibly_Controlled
339 (Prim : Final_Primitives;
340 Typ : Entity_Id;
341 E : in out Entity_Id;
342 Cref : in out Node_Id);
343 -- The controlled operation declared for a derived type may not be
344 -- overriding, if the controlled operations of the parent type are hidden,
345 -- for example when the parent is a private type whose full view is
346 -- controlled. For other primitive operations we modify the name of the
347 -- operation to indicate that it is not overriding, but this is not
348 -- possible for Initialize, etc. because they have to be retrievable by
349 -- name. Before generating the proper call to one of these operations we
350 -- check whether Typ is known to be controlled at the point of definition.
351 -- If it is not then we must retrieve the hidden operation of the parent
352 -- and use it instead. This is one case that might be solved more cleanly
353 -- once Overriding pragmas or declarations are in place.
355 function Convert_View
356 (Proc : Entity_Id;
357 Arg : Node_Id;
358 Ind : Pos := 1) return Node_Id;
359 -- Proc is one of the Initialize/Adjust/Finalize operations, and Arg is the
360 -- argument being passed to it. Ind indicates which formal of procedure
361 -- Proc we are trying to match. This function will, if necessary, generate
362 -- a conversion between the partial and full view of Arg to match the type
363 -- of the formal of Proc, or force a conversion to the class-wide type in
364 -- the case where the operation is abstract.
366 function Enclosing_Function (E : Entity_Id) return Entity_Id;
367 -- Given an arbitrary entity, traverse the scope chain looking for the
368 -- first enclosing function. Return Empty if no function was found.
370 function Make_Call
371 (Loc : Source_Ptr;
372 Proc_Id : Entity_Id;
373 Param : Node_Id;
374 For_Parent : Boolean := False) return Node_Id;
375 -- Subsidiary to Make_Adjust_Call and Make_Final_Call. Given the entity of
376 -- routine [Deep_]Adjust / Finalize and an object parameter, create an
377 -- adjust / finalization call. Flag For_Parent should be set when field
378 -- _parent is being processed.
380 function Make_Deep_Proc
381 (Prim : Final_Primitives;
382 Typ : Entity_Id;
383 Stmts : List_Id) return Node_Id;
384 -- This function generates the tree for Deep_Initialize, Deep_Adjust or
385 -- Deep_Finalize procedures according to the first parameter, these
386 -- procedures operate on the type Typ. The Stmts parameter gives the body
387 -- of the procedure.
389 function Make_Deep_Array_Body
390 (Prim : Final_Primitives;
391 Typ : Entity_Id) return List_Id;
392 -- This function generates the list of statements for implementing
393 -- Deep_Initialize, Deep_Adjust or Deep_Finalize procedures according to
394 -- the first parameter, these procedures operate on the array type Typ.
396 function Make_Deep_Record_Body
397 (Prim : Final_Primitives;
398 Typ : Entity_Id;
399 Is_Local : Boolean := False) return List_Id;
400 -- This function generates the list of statements for implementing
401 -- Deep_Initialize, Deep_Adjust or Deep_Finalize procedures according to
402 -- the first parameter, these procedures operate on the record type Typ.
403 -- Flag Is_Local is used in conjunction with Deep_Finalize to designate
404 -- whether the inner logic should be dictated by state counters.
406 function Make_Finalize_Address_Stmts (Typ : Entity_Id) return List_Id;
407 -- Subsidiary to Make_Finalize_Address_Body, Make_Deep_Array_Body and
408 -- Make_Deep_Record_Body. Generate the following statements:
410 -- declare
411 -- type Acc_Typ is access all Typ;
412 -- for Acc_Typ'Storage_Size use 0;
413 -- begin
414 -- [Deep_]Finalize (Acc_Typ (V).all);
415 -- end;
417 ----------------------------
418 -- Build_Array_Deep_Procs --
419 ----------------------------
421 procedure Build_Array_Deep_Procs (Typ : Entity_Id) is
422 begin
423 Set_TSS (Typ,
424 Make_Deep_Proc
425 (Prim => Initialize_Case,
426 Typ => Typ,
427 Stmts => Make_Deep_Array_Body (Initialize_Case, Typ)));
429 if not Is_Immutably_Limited_Type (Typ) then
430 Set_TSS (Typ,
431 Make_Deep_Proc
432 (Prim => Adjust_Case,
433 Typ => Typ,
434 Stmts => Make_Deep_Array_Body (Adjust_Case, Typ)));
435 end if;
437 -- Do not generate Deep_Finalize and Finalize_Address if finalization is
438 -- suppressed since these routine will not be used.
440 if not Restriction_Active (No_Finalization) then
441 Set_TSS (Typ,
442 Make_Deep_Proc
443 (Prim => Finalize_Case,
444 Typ => Typ,
445 Stmts => Make_Deep_Array_Body (Finalize_Case, Typ)));
447 -- Create TSS primitive Finalize_Address for non-VM targets. JVM and
448 -- .NET do not support address arithmetic and unchecked conversions.
450 if VM_Target = No_VM then
451 Set_TSS (Typ,
452 Make_Deep_Proc
453 (Prim => Address_Case,
454 Typ => Typ,
455 Stmts => Make_Deep_Array_Body (Address_Case, Typ)));
456 end if;
457 end if;
458 end Build_Array_Deep_Procs;
460 ------------------------------
461 -- Build_Cleanup_Statements --
462 ------------------------------
464 function Build_Cleanup_Statements (N : Node_Id) return List_Id is
465 Is_Asynchronous_Call : constant Boolean :=
466 Nkind (N) = N_Block_Statement
467 and then Is_Asynchronous_Call_Block (N);
468 Is_Master : constant Boolean :=
469 Nkind (N) /= N_Entry_Body
470 and then Is_Task_Master (N);
471 Is_Protected_Body : constant Boolean :=
472 Nkind (N) = N_Subprogram_Body
473 and then Is_Protected_Subprogram_Body (N);
474 Is_Task_Allocation : constant Boolean :=
475 Nkind (N) = N_Block_Statement
476 and then Is_Task_Allocation_Block (N);
477 Is_Task_Body : constant Boolean :=
478 Nkind (Original_Node (N)) = N_Task_Body;
480 Loc : constant Source_Ptr := Sloc (N);
481 Stmts : constant List_Id := New_List;
483 begin
484 if Is_Task_Body then
485 if Restricted_Profile then
486 Append_To (Stmts,
487 Build_Runtime_Call (Loc, RE_Complete_Restricted_Task));
488 else
489 Append_To (Stmts, Build_Runtime_Call (Loc, RE_Complete_Task));
490 end if;
492 elsif Is_Master then
493 if Restriction_Active (No_Task_Hierarchy) = False then
494 Append_To (Stmts, Build_Runtime_Call (Loc, RE_Complete_Master));
495 end if;
497 -- Add statements to unlock the protected object parameter and to
498 -- undefer abort. If the context is a protected procedure and the object
499 -- has entries, call the entry service routine.
501 -- NOTE: The generated code references _object, a parameter to the
502 -- procedure.
504 elsif Is_Protected_Body then
505 declare
506 Spec : constant Node_Id := Parent (Corresponding_Spec (N));
507 Conc_Typ : Entity_Id;
508 Nam : Node_Id;
509 Param : Node_Id;
510 Param_Typ : Entity_Id;
512 begin
513 -- Find the _object parameter representing the protected object
515 Param := First (Parameter_Specifications (Spec));
516 loop
517 Param_Typ := Etype (Parameter_Type (Param));
519 if Ekind (Param_Typ) = E_Record_Type then
520 Conc_Typ := Corresponding_Concurrent_Type (Param_Typ);
521 end if;
523 exit when No (Param) or else Present (Conc_Typ);
524 Next (Param);
525 end loop;
527 pragma Assert (Present (Param));
529 -- If the associated protected object has entries, a protected
530 -- procedure has to service entry queues. In this case generate:
532 -- Service_Entries (_object._object'Access);
534 if Nkind (Specification (N)) = N_Procedure_Specification
535 and then Has_Entries (Conc_Typ)
536 then
537 case Corresponding_Runtime_Package (Conc_Typ) is
538 when System_Tasking_Protected_Objects_Entries =>
539 Nam := New_Reference_To (RTE (RE_Service_Entries), Loc);
541 when System_Tasking_Protected_Objects_Single_Entry =>
542 Nam := New_Reference_To (RTE (RE_Service_Entry), Loc);
544 when others =>
545 raise Program_Error;
546 end case;
548 Append_To (Stmts,
549 Make_Procedure_Call_Statement (Loc,
550 Name => Nam,
551 Parameter_Associations => New_List (
552 Make_Attribute_Reference (Loc,
553 Prefix =>
554 Make_Selected_Component (Loc,
555 Prefix => New_Reference_To (
556 Defining_Identifier (Param), Loc),
557 Selector_Name =>
558 Make_Identifier (Loc, Name_uObject)),
559 Attribute_Name => Name_Unchecked_Access))));
561 else
562 -- Generate:
563 -- Unlock (_object._object'Access);
565 case Corresponding_Runtime_Package (Conc_Typ) is
566 when System_Tasking_Protected_Objects_Entries =>
567 Nam := New_Reference_To (RTE (RE_Unlock_Entries), Loc);
569 when System_Tasking_Protected_Objects_Single_Entry =>
570 Nam := New_Reference_To (RTE (RE_Unlock_Entry), Loc);
572 when System_Tasking_Protected_Objects =>
573 Nam := New_Reference_To (RTE (RE_Unlock), Loc);
575 when others =>
576 raise Program_Error;
577 end case;
579 Append_To (Stmts,
580 Make_Procedure_Call_Statement (Loc,
581 Name => Nam,
582 Parameter_Associations => New_List (
583 Make_Attribute_Reference (Loc,
584 Prefix =>
585 Make_Selected_Component (Loc,
586 Prefix =>
587 New_Reference_To
588 (Defining_Identifier (Param), Loc),
589 Selector_Name =>
590 Make_Identifier (Loc, Name_uObject)),
591 Attribute_Name => Name_Unchecked_Access))));
592 end if;
594 -- Generate:
595 -- Abort_Undefer;
597 if Abort_Allowed then
598 Append_To (Stmts,
599 Make_Procedure_Call_Statement (Loc,
600 Name =>
601 New_Reference_To (RTE (RE_Abort_Undefer), Loc),
602 Parameter_Associations => Empty_List));
603 end if;
604 end;
606 -- Add a call to Expunge_Unactivated_Tasks for dynamically allocated
607 -- tasks. Other unactivated tasks are completed by Complete_Task or
608 -- Complete_Master.
610 -- NOTE: The generated code references _chain, a local object
612 elsif Is_Task_Allocation then
614 -- Generate:
615 -- Expunge_Unactivated_Tasks (_chain);
617 -- where _chain is the list of tasks created by the allocator but not
618 -- yet activated. This list will be empty unless the block completes
619 -- abnormally.
621 Append_To (Stmts,
622 Make_Procedure_Call_Statement (Loc,
623 Name =>
624 New_Reference_To
625 (RTE (RE_Expunge_Unactivated_Tasks), Loc),
626 Parameter_Associations => New_List (
627 New_Reference_To (Activation_Chain_Entity (N), Loc))));
629 -- Attempt to cancel an asynchronous entry call whenever the block which
630 -- contains the abortable part is exited.
632 -- NOTE: The generated code references Cnn, a local object
634 elsif Is_Asynchronous_Call then
635 declare
636 Cancel_Param : constant Entity_Id :=
637 Entry_Cancel_Parameter (Entity (Identifier (N)));
639 begin
640 -- If it is of type Communication_Block, this must be a protected
641 -- entry call. Generate:
643 -- if Enqueued (Cancel_Param) then
644 -- Cancel_Protected_Entry_Call (Cancel_Param);
645 -- end if;
647 if Is_RTE (Etype (Cancel_Param), RE_Communication_Block) then
648 Append_To (Stmts,
649 Make_If_Statement (Loc,
650 Condition =>
651 Make_Function_Call (Loc,
652 Name =>
653 New_Reference_To (RTE (RE_Enqueued), Loc),
654 Parameter_Associations => New_List (
655 New_Reference_To (Cancel_Param, Loc))),
657 Then_Statements => New_List (
658 Make_Procedure_Call_Statement (Loc,
659 Name =>
660 New_Reference_To
661 (RTE (RE_Cancel_Protected_Entry_Call), Loc),
662 Parameter_Associations => New_List (
663 New_Reference_To (Cancel_Param, Loc))))));
665 -- Asynchronous delay, generate:
666 -- Cancel_Async_Delay (Cancel_Param);
668 elsif Is_RTE (Etype (Cancel_Param), RE_Delay_Block) then
669 Append_To (Stmts,
670 Make_Procedure_Call_Statement (Loc,
671 Name =>
672 New_Reference_To (RTE (RE_Cancel_Async_Delay), Loc),
673 Parameter_Associations => New_List (
674 Make_Attribute_Reference (Loc,
675 Prefix =>
676 New_Reference_To (Cancel_Param, Loc),
677 Attribute_Name => Name_Unchecked_Access))));
679 -- Task entry call, generate:
680 -- Cancel_Task_Entry_Call (Cancel_Param);
682 else
683 Append_To (Stmts,
684 Make_Procedure_Call_Statement (Loc,
685 Name =>
686 New_Reference_To (RTE (RE_Cancel_Task_Entry_Call), Loc),
687 Parameter_Associations => New_List (
688 New_Reference_To (Cancel_Param, Loc))));
689 end if;
690 end;
691 end if;
693 return Stmts;
694 end Build_Cleanup_Statements;
696 -----------------------------
697 -- Build_Controlling_Procs --
698 -----------------------------
700 procedure Build_Controlling_Procs (Typ : Entity_Id) is
701 begin
702 if Is_Array_Type (Typ) then
703 Build_Array_Deep_Procs (Typ);
704 else pragma Assert (Is_Record_Type (Typ));
705 Build_Record_Deep_Procs (Typ);
706 end if;
707 end Build_Controlling_Procs;
709 -----------------------------
710 -- Build_Exception_Handler --
711 -----------------------------
713 function Build_Exception_Handler
714 (Data : Finalization_Exception_Data;
715 For_Library : Boolean := False) return Node_Id
717 Actuals : List_Id;
718 Proc_To_Call : Entity_Id;
719 Except : Node_Id;
720 Stmts : List_Id;
722 begin
723 pragma Assert (Present (Data.Raised_Id));
725 if Exception_Extra_Info
726 or else (For_Library and not Restricted_Profile)
727 then
728 if Exception_Extra_Info then
730 -- Generate:
732 -- Get_Current_Excep.all
734 Except :=
735 Make_Function_Call (Data.Loc,
736 Name =>
737 Make_Explicit_Dereference (Data.Loc,
738 Prefix =>
739 New_Reference_To
740 (RTE (RE_Get_Current_Excep), Data.Loc)));
742 else
743 -- Generate:
745 -- null
747 Except := Make_Null (Data.Loc);
748 end if;
750 if For_Library and then not Restricted_Profile then
751 Proc_To_Call := RTE (RE_Save_Library_Occurrence);
752 Actuals := New_List (Except);
754 else
755 Proc_To_Call := RTE (RE_Save_Occurrence);
757 -- The dereference occurs only when Exception_Extra_Info is true,
758 -- and therefore Except is not null.
760 Actuals :=
761 New_List (
762 New_Reference_To (Data.E_Id, Data.Loc),
763 Make_Explicit_Dereference (Data.Loc, Except));
764 end if;
766 -- Generate:
768 -- when others =>
769 -- if not Raised_Id then
770 -- Raised_Id := True;
772 -- Save_Occurrence (E_Id, Get_Current_Excep.all.all);
773 -- or
774 -- Save_Library_Occurrence (Get_Current_Excep.all);
775 -- end if;
777 Stmts :=
778 New_List (
779 Make_If_Statement (Data.Loc,
780 Condition =>
781 Make_Op_Not (Data.Loc,
782 Right_Opnd => New_Reference_To (Data.Raised_Id, Data.Loc)),
784 Then_Statements => New_List (
785 Make_Assignment_Statement (Data.Loc,
786 Name => New_Reference_To (Data.Raised_Id, Data.Loc),
787 Expression => New_Reference_To (Standard_True, Data.Loc)),
789 Make_Procedure_Call_Statement (Data.Loc,
790 Name =>
791 New_Reference_To (Proc_To_Call, Data.Loc),
792 Parameter_Associations => Actuals))));
794 else
795 -- Generate:
797 -- Raised_Id := True;
799 Stmts := New_List (
800 Make_Assignment_Statement (Data.Loc,
801 Name => New_Reference_To (Data.Raised_Id, Data.Loc),
802 Expression => New_Reference_To (Standard_True, Data.Loc)));
803 end if;
805 -- Generate:
807 -- when others =>
809 return
810 Make_Exception_Handler (Data.Loc,
811 Exception_Choices => New_List (Make_Others_Choice (Data.Loc)),
812 Statements => Stmts);
813 end Build_Exception_Handler;
815 -------------------------------
816 -- Build_Finalization_Master --
817 -------------------------------
819 procedure Build_Finalization_Master
820 (Typ : Entity_Id;
821 Ins_Node : Node_Id := Empty;
822 Encl_Scope : Entity_Id := Empty)
824 Desig_Typ : constant Entity_Id := Directly_Designated_Type (Typ);
825 Ptr_Typ : Entity_Id := Root_Type (Base_Type (Typ));
827 function In_Deallocation_Instance (E : Entity_Id) return Boolean;
828 -- Determine whether entity E is inside a wrapper package created for
829 -- an instance of Ada.Unchecked_Deallocation.
831 ------------------------------
832 -- In_Deallocation_Instance --
833 ------------------------------
835 function In_Deallocation_Instance (E : Entity_Id) return Boolean is
836 Pkg : constant Entity_Id := Scope (E);
837 Par : Node_Id := Empty;
839 begin
840 if Ekind (Pkg) = E_Package
841 and then Present (Related_Instance (Pkg))
842 and then Ekind (Related_Instance (Pkg)) = E_Procedure
843 then
844 Par := Generic_Parent (Parent (Related_Instance (Pkg)));
846 return
847 Present (Par)
848 and then Chars (Par) = Name_Unchecked_Deallocation
849 and then Chars (Scope (Par)) = Name_Ada
850 and then Scope (Scope (Par)) = Standard_Standard;
851 end if;
853 return False;
854 end In_Deallocation_Instance;
856 -- Start of processing for Build_Finalization_Master
858 begin
859 if Is_Private_Type (Ptr_Typ)
860 and then Present (Full_View (Ptr_Typ))
861 then
862 Ptr_Typ := Full_View (Ptr_Typ);
863 end if;
865 -- Certain run-time configurations and targets do not provide support
866 -- for controlled types.
868 if Restriction_Active (No_Finalization) then
869 return;
871 -- Do not process C, C++, CIL and Java types since it is assumend that
872 -- the non-Ada side will handle their clean up.
874 elsif Convention (Desig_Typ) = Convention_C
875 or else Convention (Desig_Typ) = Convention_CIL
876 or else Convention (Desig_Typ) = Convention_CPP
877 or else Convention (Desig_Typ) = Convention_Java
878 then
879 return;
881 -- Various machinery such as freezing may have already created a
882 -- finalization master.
884 elsif Present (Finalization_Master (Ptr_Typ)) then
885 return;
887 -- Do not process types that return on the secondary stack
889 elsif Present (Associated_Storage_Pool (Ptr_Typ))
890 and then Is_RTE (Associated_Storage_Pool (Ptr_Typ), RE_SS_Pool)
891 then
892 return;
894 -- Do not process types which may never allocate an object
896 elsif No_Pool_Assigned (Ptr_Typ) then
897 return;
899 -- Do not process access types coming from Ada.Unchecked_Deallocation
900 -- instances. Even though the designated type may be controlled, the
901 -- access type will never participate in allocation.
903 elsif In_Deallocation_Instance (Ptr_Typ) then
904 return;
906 -- Ignore the general use of anonymous access types unless the context
907 -- requires a finalization master.
909 elsif Ekind (Ptr_Typ) = E_Anonymous_Access_Type
910 and then No (Ins_Node)
911 then
912 return;
914 -- Do not process non-library access types when restriction No_Nested_
915 -- Finalization is in effect since masters are controlled objects.
917 elsif Restriction_Active (No_Nested_Finalization)
918 and then not Is_Library_Level_Entity (Ptr_Typ)
919 then
920 return;
922 -- For .NET/JVM targets, allow the processing of access-to-controlled
923 -- types where the designated type is explicitly derived from [Limited_]
924 -- Controlled.
926 elsif VM_Target /= No_VM
927 and then not Is_Controlled (Desig_Typ)
928 then
929 return;
931 -- Do not create finalization masters in Alfa mode because they result
932 -- in unwanted expansion.
934 elsif Alfa_Mode then
935 return;
936 end if;
938 declare
939 Loc : constant Source_Ptr := Sloc (Ptr_Typ);
940 Actions : constant List_Id := New_List;
941 Fin_Mas_Id : Entity_Id;
942 Pool_Id : Entity_Id;
944 begin
945 -- Generate:
946 -- Fnn : aliased Finalization_Master;
948 -- Source access types use fixed master names since the master is
949 -- inserted in the same source unit only once. The only exception to
950 -- this are instances using the same access type as generic actual.
952 if Comes_From_Source (Ptr_Typ)
953 and then not Inside_A_Generic
954 then
955 Fin_Mas_Id :=
956 Make_Defining_Identifier (Loc,
957 Chars => New_External_Name (Chars (Ptr_Typ), "FM"));
959 -- Internally generated access types use temporaries as their names
960 -- due to possible collision with identical names coming from other
961 -- packages.
963 else
964 Fin_Mas_Id := Make_Temporary (Loc, 'F');
965 end if;
967 Append_To (Actions,
968 Make_Object_Declaration (Loc,
969 Defining_Identifier => Fin_Mas_Id,
970 Aliased_Present => True,
971 Object_Definition =>
972 New_Reference_To (RTE (RE_Finalization_Master), Loc)));
974 -- Storage pool selection and attribute decoration of the generated
975 -- master. Since .NET/JVM compilers do not support pools, this step
976 -- is skipped.
978 if VM_Target = No_VM then
980 -- If the access type has a user-defined pool, use it as the base
981 -- storage medium for the finalization pool.
983 if Present (Associated_Storage_Pool (Ptr_Typ)) then
984 Pool_Id := Associated_Storage_Pool (Ptr_Typ);
986 -- The default choice is the global pool
988 else
989 Pool_Id := Get_Global_Pool_For_Access_Type (Ptr_Typ);
990 Set_Associated_Storage_Pool (Ptr_Typ, Pool_Id);
991 end if;
993 -- Generate:
994 -- Set_Base_Pool (Fnn, Pool_Id'Unchecked_Access);
996 Append_To (Actions,
997 Make_Procedure_Call_Statement (Loc,
998 Name =>
999 New_Reference_To (RTE (RE_Set_Base_Pool), Loc),
1000 Parameter_Associations => New_List (
1001 New_Reference_To (Fin_Mas_Id, Loc),
1002 Make_Attribute_Reference (Loc,
1003 Prefix => New_Reference_To (Pool_Id, Loc),
1004 Attribute_Name => Name_Unrestricted_Access))));
1005 end if;
1007 Set_Finalization_Master (Ptr_Typ, Fin_Mas_Id);
1009 -- A finalization master created for an anonymous access type must be
1010 -- inserted before a context-dependent node.
1012 if Present (Ins_Node) then
1013 Push_Scope (Encl_Scope);
1015 -- Treat use clauses as declarations and insert directly in front
1016 -- of them.
1018 if Nkind_In (Ins_Node, N_Use_Package_Clause,
1019 N_Use_Type_Clause)
1020 then
1021 Insert_List_Before_And_Analyze (Ins_Node, Actions);
1022 else
1023 Insert_Actions (Ins_Node, Actions);
1024 end if;
1026 Pop_Scope;
1028 elsif Ekind (Desig_Typ) = E_Incomplete_Type
1029 and then Has_Completion_In_Body (Desig_Typ)
1030 then
1031 Insert_Actions (Parent (Ptr_Typ), Actions);
1033 -- If the designated type is not yet frozen, then append the actions
1034 -- to that type's freeze actions. The actions need to be appended to
1035 -- whichever type is frozen later, similarly to what Freeze_Type does
1036 -- for appending the storage pool declaration for an access type.
1037 -- Otherwise, the call to Set_Storage_Pool_Ptr might reference the
1038 -- pool object before it's declared. However, it's not clear that
1039 -- this is exactly the right test to accomplish that here. ???
1041 elsif Present (Freeze_Node (Desig_Typ))
1042 and then not Analyzed (Freeze_Node (Desig_Typ))
1043 then
1044 Append_Freeze_Actions (Desig_Typ, Actions);
1046 elsif Present (Freeze_Node (Ptr_Typ))
1047 and then not Analyzed (Freeze_Node (Ptr_Typ))
1048 then
1049 Append_Freeze_Actions (Ptr_Typ, Actions);
1051 -- If there's a pool created locally for the access type, then we
1052 -- need to ensure that the master gets created after the pool object,
1053 -- because otherwise we can have a forward reference, so we force the
1054 -- master actions to be inserted and analyzed after the pool entity.
1055 -- Note that both the access type and its designated type may have
1056 -- already been frozen and had their freezing actions analyzed at
1057 -- this point. (This seems a little unclean.???)
1059 elsif VM_Target = No_VM
1060 and then Scope (Pool_Id) = Scope (Ptr_Typ)
1061 then
1062 Insert_List_After_And_Analyze (Parent (Pool_Id), Actions);
1064 else
1065 Insert_Actions (Parent (Ptr_Typ), Actions);
1066 end if;
1067 end;
1068 end Build_Finalization_Master;
1070 ---------------------
1071 -- Build_Finalizer --
1072 ---------------------
1074 procedure Build_Finalizer
1075 (N : Node_Id;
1076 Clean_Stmts : List_Id;
1077 Mark_Id : Entity_Id;
1078 Top_Decls : List_Id;
1079 Defer_Abort : Boolean;
1080 Fin_Id : out Entity_Id)
1082 Acts_As_Clean : constant Boolean :=
1083 Present (Mark_Id)
1084 or else
1085 (Present (Clean_Stmts)
1086 and then Is_Non_Empty_List (Clean_Stmts));
1087 Exceptions_OK : constant Boolean :=
1088 not Restriction_Active (No_Exception_Propagation);
1089 For_Package_Body : constant Boolean := Nkind (N) = N_Package_Body;
1090 For_Package_Spec : constant Boolean := Nkind (N) = N_Package_Declaration;
1091 For_Package : constant Boolean :=
1092 For_Package_Body or else For_Package_Spec;
1093 Loc : constant Source_Ptr := Sloc (N);
1095 -- NOTE: Local variable declarations are conservative and do not create
1096 -- structures right from the start. Entities and lists are created once
1097 -- it has been established that N has at least one controlled object.
1099 Components_Built : Boolean := False;
1100 -- A flag used to avoid double initialization of entities and lists. If
1101 -- the flag is set then the following variables have been initialized:
1102 -- Counter_Id
1103 -- Finalizer_Decls
1104 -- Finalizer_Stmts
1105 -- Jump_Alts
1107 Counter_Id : Entity_Id := Empty;
1108 Counter_Val : Int := 0;
1109 -- Name and value of the state counter
1111 Decls : List_Id := No_List;
1112 -- Declarative region of N (if available). If N is a package declaration
1113 -- Decls denotes the visible declarations.
1115 Finalizer_Data : Finalization_Exception_Data;
1116 -- Data for the exception
1118 Finalizer_Decls : List_Id := No_List;
1119 -- Local variable declarations. This list holds the label declarations
1120 -- of all jump block alternatives as well as the declaration of the
1121 -- local exception occurence and the raised flag:
1122 -- E : Exception_Occurrence;
1123 -- Raised : Boolean := False;
1124 -- L<counter value> : label;
1126 Finalizer_Insert_Nod : Node_Id := Empty;
1127 -- Insertion point for the finalizer body. Depending on the context
1128 -- (Nkind of N) and the individual grouping of controlled objects, this
1129 -- node may denote a package declaration or body, package instantiation,
1130 -- block statement or a counter update statement.
1132 Finalizer_Stmts : List_Id := No_List;
1133 -- The statement list of the finalizer body. It contains the following:
1135 -- Abort_Defer; -- Added if abort is allowed
1136 -- <call to Prev_At_End> -- Added if exists
1137 -- <cleanup statements> -- Added if Acts_As_Clean
1138 -- <jump block> -- Added if Has_Ctrl_Objs
1139 -- <finalization statements> -- Added if Has_Ctrl_Objs
1140 -- <stack release> -- Added if Mark_Id exists
1141 -- Abort_Undefer; -- Added if abort is allowed
1143 Has_Ctrl_Objs : Boolean := False;
1144 -- A general flag which denotes whether N has at least one controlled
1145 -- object.
1147 Has_Tagged_Types : Boolean := False;
1148 -- A general flag which indicates whether N has at least one library-
1149 -- level tagged type declaration.
1151 HSS : Node_Id := Empty;
1152 -- The sequence of statements of N (if available)
1154 Jump_Alts : List_Id := No_List;
1155 -- Jump block alternatives. Depending on the value of the state counter,
1156 -- the control flow jumps to a sequence of finalization statements. This
1157 -- list contains the following:
1159 -- when <counter value> =>
1160 -- goto L<counter value>;
1162 Jump_Block_Insert_Nod : Node_Id := Empty;
1163 -- Specific point in the finalizer statements where the jump block is
1164 -- inserted.
1166 Last_Top_Level_Ctrl_Construct : Node_Id := Empty;
1167 -- The last controlled construct encountered when processing the top
1168 -- level lists of N. This can be a nested package, an instantiation or
1169 -- an object declaration.
1171 Prev_At_End : Entity_Id := Empty;
1172 -- The previous at end procedure of the handled statements block of N
1174 Priv_Decls : List_Id := No_List;
1175 -- The private declarations of N if N is a package declaration
1177 Spec_Id : Entity_Id := Empty;
1178 Spec_Decls : List_Id := Top_Decls;
1179 Stmts : List_Id := No_List;
1181 Tagged_Type_Stmts : List_Id := No_List;
1182 -- Contains calls to Ada.Tags.Unregister_Tag for all library-level
1183 -- tagged types found in N.
1185 -----------------------
1186 -- Local subprograms --
1187 -----------------------
1189 procedure Build_Components;
1190 -- Create all entites and initialize all lists used in the creation of
1191 -- the finalizer.
1193 procedure Create_Finalizer;
1194 -- Create the spec and body of the finalizer and insert them in the
1195 -- proper place in the tree depending on the context.
1197 procedure Process_Declarations
1198 (Decls : List_Id;
1199 Preprocess : Boolean := False;
1200 Top_Level : Boolean := False);
1201 -- Inspect a list of declarations or statements which may contain
1202 -- objects that need finalization. When flag Preprocess is set, the
1203 -- routine will simply count the total number of controlled objects in
1204 -- Decls. Flag Top_Level denotes whether the processing is done for
1205 -- objects in nested package declarations or instances.
1207 procedure Process_Object_Declaration
1208 (Decl : Node_Id;
1209 Has_No_Init : Boolean := False;
1210 Is_Protected : Boolean := False);
1211 -- Generate all the machinery associated with the finalization of a
1212 -- single object. Flag Has_No_Init is used to denote certain contexts
1213 -- where Decl does not have initialization call(s). Flag Is_Protected
1214 -- is set when Decl denotes a simple protected object.
1216 procedure Process_Tagged_Type_Declaration (Decl : Node_Id);
1217 -- Generate all the code necessary to unregister the external tag of a
1218 -- tagged type.
1220 ----------------------
1221 -- Build_Components --
1222 ----------------------
1224 procedure Build_Components is
1225 Counter_Decl : Node_Id;
1226 Counter_Typ : Entity_Id;
1227 Counter_Typ_Decl : Node_Id;
1229 begin
1230 pragma Assert (Present (Decls));
1232 -- This routine might be invoked several times when dealing with
1233 -- constructs that have two lists (either two declarative regions
1234 -- or declarations and statements). Avoid double initialization.
1236 if Components_Built then
1237 return;
1238 end if;
1240 Components_Built := True;
1242 if Has_Ctrl_Objs then
1244 -- Create entities for the counter, its type, the local exception
1245 -- and the raised flag.
1247 Counter_Id := Make_Temporary (Loc, 'C');
1248 Counter_Typ := Make_Temporary (Loc, 'T');
1250 Finalizer_Decls := New_List;
1252 Build_Object_Declarations
1253 (Finalizer_Data, Finalizer_Decls, Loc, For_Package);
1255 -- Since the total number of controlled objects is always known,
1256 -- build a subtype of Natural with precise bounds. This allows
1257 -- the backend to optimize the case statement. Generate:
1259 -- subtype Tnn is Natural range 0 .. Counter_Val;
1261 Counter_Typ_Decl :=
1262 Make_Subtype_Declaration (Loc,
1263 Defining_Identifier => Counter_Typ,
1264 Subtype_Indication =>
1265 Make_Subtype_Indication (Loc,
1266 Subtype_Mark => New_Reference_To (Standard_Natural, Loc),
1267 Constraint =>
1268 Make_Range_Constraint (Loc,
1269 Range_Expression =>
1270 Make_Range (Loc,
1271 Low_Bound =>
1272 Make_Integer_Literal (Loc, Uint_0),
1273 High_Bound =>
1274 Make_Integer_Literal (Loc, Counter_Val)))));
1276 -- Generate the declaration of the counter itself:
1278 -- Counter : Integer := 0;
1280 Counter_Decl :=
1281 Make_Object_Declaration (Loc,
1282 Defining_Identifier => Counter_Id,
1283 Object_Definition => New_Reference_To (Counter_Typ, Loc),
1284 Expression => Make_Integer_Literal (Loc, 0));
1286 -- Set the type of the counter explicitly to prevent errors when
1287 -- examining object declarations later on.
1289 Set_Etype (Counter_Id, Counter_Typ);
1291 -- The counter and its type are inserted before the source
1292 -- declarations of N.
1294 Prepend_To (Decls, Counter_Decl);
1295 Prepend_To (Decls, Counter_Typ_Decl);
1297 -- The counter and its associated type must be manually analized
1298 -- since N has already been analyzed. Use the scope of the spec
1299 -- when inserting in a package.
1301 if For_Package then
1302 Push_Scope (Spec_Id);
1303 Analyze (Counter_Typ_Decl);
1304 Analyze (Counter_Decl);
1305 Pop_Scope;
1307 else
1308 Analyze (Counter_Typ_Decl);
1309 Analyze (Counter_Decl);
1310 end if;
1312 Jump_Alts := New_List;
1313 end if;
1315 -- If the context requires additional clean up, the finalization
1316 -- machinery is added after the clean up code.
1318 if Acts_As_Clean then
1319 Finalizer_Stmts := Clean_Stmts;
1320 Jump_Block_Insert_Nod := Last (Finalizer_Stmts);
1321 else
1322 Finalizer_Stmts := New_List;
1323 end if;
1325 if Has_Tagged_Types then
1326 Tagged_Type_Stmts := New_List;
1327 end if;
1328 end Build_Components;
1330 ----------------------
1331 -- Create_Finalizer --
1332 ----------------------
1334 procedure Create_Finalizer is
1335 Body_Id : Entity_Id;
1336 Fin_Body : Node_Id;
1337 Fin_Spec : Node_Id;
1338 Jump_Block : Node_Id;
1339 Label : Node_Id;
1340 Label_Id : Entity_Id;
1342 function New_Finalizer_Name return Name_Id;
1343 -- Create a fully qualified name of a package spec or body finalizer.
1344 -- The generated name is of the form: xx__yy__finalize_[spec|body].
1346 ------------------------
1347 -- New_Finalizer_Name --
1348 ------------------------
1350 function New_Finalizer_Name return Name_Id is
1351 procedure New_Finalizer_Name (Id : Entity_Id);
1352 -- Place "__<name-of-Id>" in the name buffer. If the identifier
1353 -- has a non-standard scope, process the scope first.
1355 ------------------------
1356 -- New_Finalizer_Name --
1357 ------------------------
1359 procedure New_Finalizer_Name (Id : Entity_Id) is
1360 begin
1361 if Scope (Id) = Standard_Standard then
1362 Get_Name_String (Chars (Id));
1364 else
1365 New_Finalizer_Name (Scope (Id));
1366 Add_Str_To_Name_Buffer ("__");
1367 Add_Str_To_Name_Buffer (Get_Name_String (Chars (Id)));
1368 end if;
1369 end New_Finalizer_Name;
1371 -- Start of processing for New_Finalizer_Name
1373 begin
1374 -- Create the fully qualified name of the enclosing scope
1376 New_Finalizer_Name (Spec_Id);
1378 -- Generate:
1379 -- __finalize_[spec|body]
1381 Add_Str_To_Name_Buffer ("__finalize_");
1383 if For_Package_Spec then
1384 Add_Str_To_Name_Buffer ("spec");
1385 else
1386 Add_Str_To_Name_Buffer ("body");
1387 end if;
1389 return Name_Find;
1390 end New_Finalizer_Name;
1392 -- Start of processing for Create_Finalizer
1394 begin
1395 -- Step 1: Creation of the finalizer name
1397 -- Packages must use a distinct name for their finalizers since the
1398 -- binder will have to generate calls to them by name. The name is
1399 -- of the following form:
1401 -- xx__yy__finalize_[spec|body]
1403 if For_Package then
1404 Fin_Id := Make_Defining_Identifier (Loc, New_Finalizer_Name);
1405 Set_Has_Qualified_Name (Fin_Id);
1406 Set_Has_Fully_Qualified_Name (Fin_Id);
1408 -- The default name is _finalizer
1410 else
1411 Fin_Id :=
1412 Make_Defining_Identifier (Loc,
1413 Chars => New_External_Name (Name_uFinalizer));
1415 -- The visibility semantics of AT_END handlers force a strange
1416 -- separation of spec and body for stack-related finalizers:
1418 -- declare : Enclosing_Scope
1419 -- procedure _finalizer;
1420 -- begin
1421 -- <controlled objects>
1422 -- procedure _finalizer is
1423 -- ...
1424 -- at end
1425 -- _finalizer;
1426 -- end;
1428 -- Both spec and body are within the same construct and scope, but
1429 -- the body is part of the handled sequence of statements. This
1430 -- placement confuses the elaboration mechanism on targets where
1431 -- AT_END handlers are expanded into "when all others" handlers:
1433 -- exception
1434 -- when all others =>
1435 -- _finalizer; -- appears to require elab checks
1436 -- at end
1437 -- _finalizer;
1438 -- end;
1440 -- Since the compiler guarantees that the body of a _finalizer is
1441 -- always inserted in the same construct where the AT_END handler
1442 -- resides, there is no need for elaboration checks.
1444 Set_Kill_Elaboration_Checks (Fin_Id);
1445 end if;
1447 -- Step 2: Creation of the finalizer specification
1449 -- Generate:
1450 -- procedure Fin_Id;
1452 Fin_Spec :=
1453 Make_Subprogram_Declaration (Loc,
1454 Specification =>
1455 Make_Procedure_Specification (Loc,
1456 Defining_Unit_Name => Fin_Id));
1458 -- Step 3: Creation of the finalizer body
1460 if Has_Ctrl_Objs then
1462 -- Add L0, the default destination to the jump block
1464 Label_Id := Make_Identifier (Loc, New_External_Name ('L', 0));
1465 Set_Entity (Label_Id,
1466 Make_Defining_Identifier (Loc, Chars (Label_Id)));
1467 Label := Make_Label (Loc, Label_Id);
1469 -- Generate:
1470 -- L0 : label;
1472 Prepend_To (Finalizer_Decls,
1473 Make_Implicit_Label_Declaration (Loc,
1474 Defining_Identifier => Entity (Label_Id),
1475 Label_Construct => Label));
1477 -- Generate:
1478 -- when others =>
1479 -- goto L0;
1481 Append_To (Jump_Alts,
1482 Make_Case_Statement_Alternative (Loc,
1483 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
1484 Statements => New_List (
1485 Make_Goto_Statement (Loc,
1486 Name => New_Reference_To (Entity (Label_Id), Loc)))));
1488 -- Generate:
1489 -- <<L0>>
1491 Append_To (Finalizer_Stmts, Label);
1493 -- Create the jump block which controls the finalization flow
1494 -- depending on the value of the state counter.
1496 Jump_Block :=
1497 Make_Case_Statement (Loc,
1498 Expression => Make_Identifier (Loc, Chars (Counter_Id)),
1499 Alternatives => Jump_Alts);
1501 if Acts_As_Clean
1502 and then Present (Jump_Block_Insert_Nod)
1503 then
1504 Insert_After (Jump_Block_Insert_Nod, Jump_Block);
1505 else
1506 Prepend_To (Finalizer_Stmts, Jump_Block);
1507 end if;
1508 end if;
1510 -- Add the library-level tagged type unregistration machinery before
1511 -- the jump block circuitry. This ensures that external tags will be
1512 -- removed even if a finalization exception occurs at some point.
1514 if Has_Tagged_Types then
1515 Prepend_List_To (Finalizer_Stmts, Tagged_Type_Stmts);
1516 end if;
1518 -- Add a call to the previous At_End handler if it exists. The call
1519 -- must always precede the jump block.
1521 if Present (Prev_At_End) then
1522 Prepend_To (Finalizer_Stmts,
1523 Make_Procedure_Call_Statement (Loc, Prev_At_End));
1525 -- Clear the At_End handler since we have already generated the
1526 -- proper replacement call for it.
1528 Set_At_End_Proc (HSS, Empty);
1529 end if;
1531 -- Release the secondary stack mark
1533 if Present (Mark_Id) then
1534 Append_To (Finalizer_Stmts,
1535 Make_Procedure_Call_Statement (Loc,
1536 Name =>
1537 New_Reference_To (RTE (RE_SS_Release), Loc),
1538 Parameter_Associations => New_List (
1539 New_Reference_To (Mark_Id, Loc))));
1540 end if;
1542 -- Protect the statements with abort defer/undefer. This is only when
1543 -- aborts are allowed and the clean up statements require deferral or
1544 -- there are controlled objects to be finalized.
1546 if Abort_Allowed
1547 and then
1548 (Defer_Abort or else Has_Ctrl_Objs)
1549 then
1550 Prepend_To (Finalizer_Stmts,
1551 Make_Procedure_Call_Statement (Loc,
1552 Name => New_Reference_To (RTE (RE_Abort_Defer), Loc)));
1554 Append_To (Finalizer_Stmts,
1555 Make_Procedure_Call_Statement (Loc,
1556 Name => New_Reference_To (RTE (RE_Abort_Undefer), Loc)));
1557 end if;
1559 -- The local exception does not need to be reraised for library-level
1560 -- finalizers. Note that this action must be carried out after object
1561 -- clean up, secondary stack release and abort undeferral. Generate:
1563 -- if Raised and then not Abort then
1564 -- Raise_From_Controlled_Operation (E);
1565 -- end if;
1567 if Has_Ctrl_Objs
1568 and then Exceptions_OK
1569 and then not For_Package
1570 then
1571 Append_To (Finalizer_Stmts,
1572 Build_Raise_Statement (Finalizer_Data));
1573 end if;
1575 -- Generate:
1576 -- procedure Fin_Id is
1577 -- Abort : constant Boolean := Triggered_By_Abort;
1578 -- <or>
1579 -- Abort : constant Boolean := False; -- no abort
1581 -- E : Exception_Occurrence; -- All added if flag
1582 -- Raised : Boolean := False; -- Has_Ctrl_Objs is set
1583 -- L0 : label;
1584 -- ...
1585 -- Lnn : label;
1587 -- begin
1588 -- Abort_Defer; -- Added if abort is allowed
1589 -- <call to Prev_At_End> -- Added if exists
1590 -- <cleanup statements> -- Added if Acts_As_Clean
1591 -- <jump block> -- Added if Has_Ctrl_Objs
1592 -- <finalization statements> -- Added if Has_Ctrl_Objs
1593 -- <stack release> -- Added if Mark_Id exists
1594 -- Abort_Undefer; -- Added if abort is allowed
1595 -- <exception propagation> -- Added if Has_Ctrl_Objs
1596 -- end Fin_Id;
1598 -- Create the body of the finalizer
1600 Body_Id := Make_Defining_Identifier (Loc, Chars (Fin_Id));
1602 if For_Package then
1603 Set_Has_Qualified_Name (Body_Id);
1604 Set_Has_Fully_Qualified_Name (Body_Id);
1605 end if;
1607 Fin_Body :=
1608 Make_Subprogram_Body (Loc,
1609 Specification =>
1610 Make_Procedure_Specification (Loc,
1611 Defining_Unit_Name => Body_Id),
1612 Declarations => Finalizer_Decls,
1613 Handled_Statement_Sequence =>
1614 Make_Handled_Sequence_Of_Statements (Loc, Finalizer_Stmts));
1616 -- Step 4: Spec and body insertion, analysis
1618 if For_Package then
1620 -- If the package spec has private declarations, the finalizer
1621 -- body must be added to the end of the list in order to have
1622 -- visibility of all private controlled objects.
1624 if For_Package_Spec then
1625 if Present (Priv_Decls) then
1626 Append_To (Priv_Decls, Fin_Spec);
1627 Append_To (Priv_Decls, Fin_Body);
1628 else
1629 Append_To (Decls, Fin_Spec);
1630 Append_To (Decls, Fin_Body);
1631 end if;
1633 -- For package bodies, both the finalizer spec and body are
1634 -- inserted at the end of the package declarations.
1636 else
1637 Append_To (Decls, Fin_Spec);
1638 Append_To (Decls, Fin_Body);
1639 end if;
1641 -- Push the name of the package
1643 Push_Scope (Spec_Id);
1644 Analyze (Fin_Spec);
1645 Analyze (Fin_Body);
1646 Pop_Scope;
1648 -- Non-package case
1650 else
1651 -- Create the spec for the finalizer. The At_End handler must be
1652 -- able to call the body which resides in a nested structure.
1654 -- Generate:
1655 -- declare
1656 -- procedure Fin_Id; -- Spec
1657 -- begin
1658 -- <objects and possibly statements>
1659 -- procedure Fin_Id is ... -- Body
1660 -- <statements>
1661 -- at end
1662 -- Fin_Id; -- At_End handler
1663 -- end;
1665 pragma Assert (Present (Spec_Decls));
1667 Append_To (Spec_Decls, Fin_Spec);
1668 Analyze (Fin_Spec);
1670 -- When the finalizer acts solely as a clean up routine, the body
1671 -- is inserted right after the spec.
1673 if Acts_As_Clean
1674 and then not Has_Ctrl_Objs
1675 then
1676 Insert_After (Fin_Spec, Fin_Body);
1678 -- In all other cases the body is inserted after either:
1680 -- 1) The counter update statement of the last controlled object
1681 -- 2) The last top level nested controlled package
1682 -- 3) The last top level controlled instantiation
1684 else
1685 -- Manually freeze the spec. This is somewhat of a hack because
1686 -- a subprogram is frozen when its body is seen and the freeze
1687 -- node appears right before the body. However, in this case,
1688 -- the spec must be frozen earlier since the At_End handler
1689 -- must be able to call it.
1691 -- declare
1692 -- procedure Fin_Id; -- Spec
1693 -- [Fin_Id] -- Freeze node
1694 -- begin
1695 -- ...
1696 -- at end
1697 -- Fin_Id; -- At_End handler
1698 -- end;
1700 Ensure_Freeze_Node (Fin_Id);
1701 Insert_After (Fin_Spec, Freeze_Node (Fin_Id));
1702 Set_Is_Frozen (Fin_Id);
1704 -- In the case where the last construct to contain a controlled
1705 -- object is either a nested package, an instantiation or a
1706 -- freeze node, the body must be inserted directly after the
1707 -- construct.
1709 if Nkind_In (Last_Top_Level_Ctrl_Construct,
1710 N_Freeze_Entity,
1711 N_Package_Declaration,
1712 N_Package_Body)
1713 then
1714 Finalizer_Insert_Nod := Last_Top_Level_Ctrl_Construct;
1715 end if;
1717 Insert_After (Finalizer_Insert_Nod, Fin_Body);
1718 end if;
1720 Analyze (Fin_Body);
1721 end if;
1722 end Create_Finalizer;
1724 --------------------------
1725 -- Process_Declarations --
1726 --------------------------
1728 procedure Process_Declarations
1729 (Decls : List_Id;
1730 Preprocess : Boolean := False;
1731 Top_Level : Boolean := False)
1733 Decl : Node_Id;
1734 Expr : Node_Id;
1735 Obj_Id : Entity_Id;
1736 Obj_Typ : Entity_Id;
1737 Pack_Id : Entity_Id;
1738 Spec : Node_Id;
1739 Typ : Entity_Id;
1741 Old_Counter_Val : Int;
1742 -- This variable is used to determine whether a nested package or
1743 -- instance contains at least one controlled object.
1745 procedure Processing_Actions
1746 (Has_No_Init : Boolean := False;
1747 Is_Protected : Boolean := False);
1748 -- Depending on the mode of operation of Process_Declarations, either
1749 -- increment the controlled object counter, set the controlled object
1750 -- flag and store the last top level construct or process the current
1751 -- declaration. Flag Has_No_Init is used to propagate scenarios where
1752 -- the current declaration may not have initialization proc(s). Flag
1753 -- Is_Protected should be set when the current declaration denotes a
1754 -- simple protected object.
1756 ------------------------
1757 -- Processing_Actions --
1758 ------------------------
1760 procedure Processing_Actions
1761 (Has_No_Init : Boolean := False;
1762 Is_Protected : Boolean := False)
1764 begin
1765 -- Library-level tagged type
1767 if Nkind (Decl) = N_Full_Type_Declaration then
1768 if Preprocess then
1769 Has_Tagged_Types := True;
1771 if Top_Level
1772 and then No (Last_Top_Level_Ctrl_Construct)
1773 then
1774 Last_Top_Level_Ctrl_Construct := Decl;
1775 end if;
1777 else
1778 Process_Tagged_Type_Declaration (Decl);
1779 end if;
1781 -- Controlled object declaration
1783 else
1784 if Preprocess then
1785 Counter_Val := Counter_Val + 1;
1786 Has_Ctrl_Objs := True;
1788 if Top_Level
1789 and then No (Last_Top_Level_Ctrl_Construct)
1790 then
1791 Last_Top_Level_Ctrl_Construct := Decl;
1792 end if;
1794 else
1795 Process_Object_Declaration (Decl, Has_No_Init, Is_Protected);
1796 end if;
1797 end if;
1798 end Processing_Actions;
1800 -- Start of processing for Process_Declarations
1802 begin
1803 if No (Decls) or else Is_Empty_List (Decls) then
1804 return;
1805 end if;
1807 -- Process all declarations in reverse order
1809 Decl := Last_Non_Pragma (Decls);
1810 while Present (Decl) loop
1812 -- Library-level tagged types
1814 if Nkind (Decl) = N_Full_Type_Declaration then
1815 Typ := Defining_Identifier (Decl);
1817 if Is_Tagged_Type (Typ)
1818 and then Is_Library_Level_Entity (Typ)
1819 and then Convention (Typ) = Convention_Ada
1820 and then Present (Access_Disp_Table (Typ))
1821 and then RTE_Available (RE_Register_Tag)
1822 and then not No_Run_Time_Mode
1823 and then not Is_Abstract_Type (Typ)
1824 then
1825 Processing_Actions;
1826 end if;
1828 -- Regular object declarations
1830 elsif Nkind (Decl) = N_Object_Declaration then
1831 Obj_Id := Defining_Identifier (Decl);
1832 Obj_Typ := Base_Type (Etype (Obj_Id));
1833 Expr := Expression (Decl);
1835 -- Bypass any form of processing for objects which have their
1836 -- finalization disabled. This applies only to objects at the
1837 -- library level.
1839 if For_Package
1840 and then Finalize_Storage_Only (Obj_Typ)
1841 then
1842 null;
1844 -- Transient variables are treated separately in order to
1845 -- minimize the size of the generated code. For details, see
1846 -- Process_Transient_Objects.
1848 elsif Is_Processed_Transient (Obj_Id) then
1849 null;
1851 -- The object is of the form:
1852 -- Obj : Typ [:= Expr];
1854 -- Do not process the incomplete view of a deferred constant.
1855 -- Do not consider tag-to-class-wide conversions.
1857 elsif not Is_Imported (Obj_Id)
1858 and then Needs_Finalization (Obj_Typ)
1859 and then not (Ekind (Obj_Id) = E_Constant
1860 and then not Has_Completion (Obj_Id))
1861 and then not Is_Tag_To_Class_Wide_Conversion (Obj_Id)
1862 then
1863 Processing_Actions;
1865 -- The object is of the form:
1866 -- Obj : Access_Typ := Non_BIP_Function_Call'reference;
1868 -- Obj : Access_Typ :=
1869 -- BIP_Function_Call (BIPalloc => 2, ...)'reference;
1871 elsif Is_Access_Type (Obj_Typ)
1872 and then Needs_Finalization
1873 (Available_View (Designated_Type (Obj_Typ)))
1874 and then Present (Expr)
1875 and then
1876 (Is_Secondary_Stack_BIP_Func_Call (Expr)
1877 or else
1878 (Is_Non_BIP_Func_Call (Expr)
1879 and then not Is_Related_To_Func_Return (Obj_Id)))
1880 then
1881 Processing_Actions (Has_No_Init => True);
1883 -- Processing for "hook" objects generated for controlled
1884 -- transients declared inside an Expression_With_Actions.
1886 elsif Is_Access_Type (Obj_Typ)
1887 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
1888 and then Nkind (Status_Flag_Or_Transient_Decl (Obj_Id)) =
1889 N_Object_Declaration
1890 and then Is_Finalizable_Transient
1891 (Status_Flag_Or_Transient_Decl (Obj_Id), Decl)
1892 then
1893 Processing_Actions (Has_No_Init => True);
1895 -- Process intermediate results of an if expression with one
1896 -- of the alternatives using a controlled function call.
1898 elsif Is_Access_Type (Obj_Typ)
1899 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
1900 and then Nkind (Status_Flag_Or_Transient_Decl (Obj_Id)) =
1901 N_Defining_Identifier
1902 and then Present (Expr)
1903 and then Nkind (Expr) = N_Null
1904 then
1905 Processing_Actions (Has_No_Init => True);
1907 -- Simple protected objects which use type System.Tasking.
1908 -- Protected_Objects.Protection to manage their locks should
1909 -- be treated as controlled since they require manual cleanup.
1910 -- The only exception is illustrated in the following example:
1912 -- package Pkg is
1913 -- type Ctrl is new Controlled ...
1914 -- procedure Finalize (Obj : in out Ctrl);
1915 -- Lib_Obj : Ctrl;
1916 -- end Pkg;
1918 -- package body Pkg is
1919 -- protected Prot is
1920 -- procedure Do_Something (Obj : in out Ctrl);
1921 -- end Prot;
1923 -- protected body Prot is
1924 -- procedure Do_Something (Obj : in out Ctrl) is ...
1925 -- end Prot;
1927 -- procedure Finalize (Obj : in out Ctrl) is
1928 -- begin
1929 -- Prot.Do_Something (Obj);
1930 -- end Finalize;
1931 -- end Pkg;
1933 -- Since for the most part entities in package bodies depend on
1934 -- those in package specs, Prot's lock should be cleaned up
1935 -- first. The subsequent cleanup of the spec finalizes Lib_Obj.
1936 -- This act however attempts to invoke Do_Something and fails
1937 -- because the lock has disappeared.
1939 elsif Ekind (Obj_Id) = E_Variable
1940 and then not In_Library_Level_Package_Body (Obj_Id)
1941 and then
1942 (Is_Simple_Protected_Type (Obj_Typ)
1943 or else Has_Simple_Protected_Object (Obj_Typ))
1944 then
1945 Processing_Actions (Is_Protected => True);
1946 end if;
1948 -- Specific cases of object renamings
1950 elsif Nkind (Decl) = N_Object_Renaming_Declaration then
1951 Obj_Id := Defining_Identifier (Decl);
1952 Obj_Typ := Base_Type (Etype (Obj_Id));
1954 -- Bypass any form of processing for objects which have their
1955 -- finalization disabled. This applies only to objects at the
1956 -- library level.
1958 if For_Package
1959 and then Finalize_Storage_Only (Obj_Typ)
1960 then
1961 null;
1963 -- Return object of a build-in-place function. This case is
1964 -- recognized and marked by the expansion of an extended return
1965 -- statement (see Expand_N_Extended_Return_Statement).
1967 elsif Needs_Finalization (Obj_Typ)
1968 and then Is_Return_Object (Obj_Id)
1969 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
1970 then
1971 Processing_Actions (Has_No_Init => True);
1973 -- Detect a case where a source object has been initialized by
1974 -- a controlled function call or another object which was later
1975 -- rewritten as a class-wide conversion of Ada.Tags.Displace.
1977 -- Obj1 : CW_Type := Src_Obj;
1978 -- Obj2 : CW_Type := Function_Call (...);
1980 -- Obj1 : CW_Type renames (... Ada.Tags.Displace (Src_Obj));
1981 -- Tmp : ... := Function_Call (...)'reference;
1982 -- Obj2 : CW_Type renames (... Ada.Tags.Displace (Tmp));
1984 elsif Is_Displacement_Of_Object_Or_Function_Result (Obj_Id) then
1985 Processing_Actions (Has_No_Init => True);
1986 end if;
1988 -- Inspect the freeze node of an access-to-controlled type and
1989 -- look for a delayed finalization master. This case arises when
1990 -- the freeze actions are inserted at a later time than the
1991 -- expansion of the context. Since Build_Finalizer is never called
1992 -- on a single construct twice, the master will be ultimately
1993 -- left out and never finalized. This is also needed for freeze
1994 -- actions of designated types themselves, since in some cases the
1995 -- finalization master is associated with a designated type's
1996 -- freeze node rather than that of the access type (see handling
1997 -- for freeze actions in Build_Finalization_Master).
1999 elsif Nkind (Decl) = N_Freeze_Entity
2000 and then Present (Actions (Decl))
2001 then
2002 Typ := Entity (Decl);
2004 if (Is_Access_Type (Typ)
2005 and then not Is_Access_Subprogram_Type (Typ)
2006 and then Needs_Finalization
2007 (Available_View (Designated_Type (Typ))))
2008 or else (Is_Type (Typ) and then Needs_Finalization (Typ))
2009 then
2010 Old_Counter_Val := Counter_Val;
2012 -- Freeze nodes are considered to be identical to packages
2013 -- and blocks in terms of nesting. The difference is that
2014 -- a finalization master created inside the freeze node is
2015 -- at the same nesting level as the node itself.
2017 Process_Declarations (Actions (Decl), Preprocess);
2019 -- The freeze node contains a finalization master
2021 if Preprocess
2022 and then Top_Level
2023 and then No (Last_Top_Level_Ctrl_Construct)
2024 and then Counter_Val > Old_Counter_Val
2025 then
2026 Last_Top_Level_Ctrl_Construct := Decl;
2027 end if;
2028 end if;
2030 -- Nested package declarations, avoid generics
2032 elsif Nkind (Decl) = N_Package_Declaration then
2033 Spec := Specification (Decl);
2034 Pack_Id := Defining_Unit_Name (Spec);
2036 if Nkind (Pack_Id) = N_Defining_Program_Unit_Name then
2037 Pack_Id := Defining_Identifier (Pack_Id);
2038 end if;
2040 if Ekind (Pack_Id) /= E_Generic_Package then
2041 Old_Counter_Val := Counter_Val;
2042 Process_Declarations
2043 (Private_Declarations (Spec), Preprocess);
2044 Process_Declarations
2045 (Visible_Declarations (Spec), Preprocess);
2047 -- Either the visible or the private declarations contain a
2048 -- controlled object. The nested package declaration is the
2049 -- last such construct.
2051 if Preprocess
2052 and then Top_Level
2053 and then No (Last_Top_Level_Ctrl_Construct)
2054 and then Counter_Val > Old_Counter_Val
2055 then
2056 Last_Top_Level_Ctrl_Construct := Decl;
2057 end if;
2058 end if;
2060 -- Nested package bodies, avoid generics
2062 elsif Nkind (Decl) = N_Package_Body then
2063 Spec := Corresponding_Spec (Decl);
2065 if Ekind (Spec) /= E_Generic_Package then
2066 Old_Counter_Val := Counter_Val;
2067 Process_Declarations (Declarations (Decl), Preprocess);
2069 -- The nested package body is the last construct to contain
2070 -- a controlled object.
2072 if Preprocess
2073 and then Top_Level
2074 and then No (Last_Top_Level_Ctrl_Construct)
2075 and then Counter_Val > Old_Counter_Val
2076 then
2077 Last_Top_Level_Ctrl_Construct := Decl;
2078 end if;
2079 end if;
2081 -- Handle a rare case caused by a controlled transient variable
2082 -- created as part of a record init proc. The variable is wrapped
2083 -- in a block, but the block is not associated with a transient
2084 -- scope.
2086 elsif Nkind (Decl) = N_Block_Statement
2087 and then Inside_Init_Proc
2088 then
2089 Old_Counter_Val := Counter_Val;
2091 if Present (Handled_Statement_Sequence (Decl)) then
2092 Process_Declarations
2093 (Statements (Handled_Statement_Sequence (Decl)),
2094 Preprocess);
2095 end if;
2097 Process_Declarations (Declarations (Decl), Preprocess);
2099 -- Either the declaration or statement list of the block has a
2100 -- controlled object.
2102 if Preprocess
2103 and then Top_Level
2104 and then No (Last_Top_Level_Ctrl_Construct)
2105 and then Counter_Val > Old_Counter_Val
2106 then
2107 Last_Top_Level_Ctrl_Construct := Decl;
2108 end if;
2110 -- Handle the case where the original context has been wrapped in
2111 -- a block to avoid interference between exception handlers and
2112 -- At_End handlers. Treat the block as transparent and process its
2113 -- contents.
2115 elsif Nkind (Decl) = N_Block_Statement
2116 and then Is_Finalization_Wrapper (Decl)
2117 then
2118 if Present (Handled_Statement_Sequence (Decl)) then
2119 Process_Declarations
2120 (Statements (Handled_Statement_Sequence (Decl)),
2121 Preprocess);
2122 end if;
2124 Process_Declarations (Declarations (Decl), Preprocess);
2125 end if;
2127 Prev_Non_Pragma (Decl);
2128 end loop;
2129 end Process_Declarations;
2131 --------------------------------
2132 -- Process_Object_Declaration --
2133 --------------------------------
2135 procedure Process_Object_Declaration
2136 (Decl : Node_Id;
2137 Has_No_Init : Boolean := False;
2138 Is_Protected : Boolean := False)
2140 Obj_Id : constant Entity_Id := Defining_Identifier (Decl);
2141 Loc : constant Source_Ptr := Sloc (Decl);
2142 Body_Ins : Node_Id;
2143 Count_Ins : Node_Id;
2144 Fin_Call : Node_Id;
2145 Fin_Stmts : List_Id;
2146 Inc_Decl : Node_Id;
2147 Label : Node_Id;
2148 Label_Id : Entity_Id;
2149 Obj_Ref : Node_Id;
2150 Obj_Typ : Entity_Id;
2152 function Build_BIP_Cleanup_Stmts (Func_Id : Entity_Id) return Node_Id;
2153 -- Once it has been established that the current object is in fact a
2154 -- return object of build-in-place function Func_Id, generate the
2155 -- following cleanup code:
2157 -- if BIPallocfrom > Secondary_Stack'Pos
2158 -- and then BIPfinalizationmaster /= null
2159 -- then
2160 -- declare
2161 -- type Ptr_Typ is access Obj_Typ;
2162 -- for Ptr_Typ'Storage_Pool
2163 -- use Base_Pool (BIPfinalizationmaster);
2164 -- begin
2165 -- Free (Ptr_Typ (Temp));
2166 -- end;
2167 -- end if;
2169 -- Obj_Typ is the type of the current object, Temp is the original
2170 -- allocation which Obj_Id renames.
2172 procedure Find_Last_Init
2173 (Decl : Node_Id;
2174 Typ : Entity_Id;
2175 Last_Init : out Node_Id;
2176 Body_Insert : out Node_Id);
2177 -- An object declaration has at least one and at most two init calls:
2178 -- that of the type and the user-defined initialize. Given an object
2179 -- declaration, Last_Init denotes the last initialization call which
2180 -- follows the declaration. Body_Insert denotes the place where the
2181 -- finalizer body could be potentially inserted.
2183 -----------------------------
2184 -- Build_BIP_Cleanup_Stmts --
2185 -----------------------------
2187 function Build_BIP_Cleanup_Stmts
2188 (Func_Id : Entity_Id) return Node_Id
2190 Decls : constant List_Id := New_List;
2191 Fin_Mas_Id : constant Entity_Id :=
2192 Build_In_Place_Formal
2193 (Func_Id, BIP_Finalization_Master);
2194 Obj_Typ : constant Entity_Id := Etype (Func_Id);
2195 Temp_Id : constant Entity_Id :=
2196 Entity (Prefix (Name (Parent (Obj_Id))));
2198 Cond : Node_Id;
2199 Free_Blk : Node_Id;
2200 Free_Stmt : Node_Id;
2201 Pool_Id : Entity_Id;
2202 Ptr_Typ : Entity_Id;
2204 begin
2205 -- Generate:
2206 -- Pool_Id renames Base_Pool (BIPfinalizationmaster.all).all;
2208 Pool_Id := Make_Temporary (Loc, 'P');
2210 Append_To (Decls,
2211 Make_Object_Renaming_Declaration (Loc,
2212 Defining_Identifier => Pool_Id,
2213 Subtype_Mark =>
2214 New_Reference_To (RTE (RE_Root_Storage_Pool), Loc),
2215 Name =>
2216 Make_Explicit_Dereference (Loc,
2217 Prefix =>
2218 Make_Function_Call (Loc,
2219 Name =>
2220 New_Reference_To (RTE (RE_Base_Pool), Loc),
2221 Parameter_Associations => New_List (
2222 Make_Explicit_Dereference (Loc,
2223 Prefix => New_Reference_To (Fin_Mas_Id, Loc)))))));
2225 -- Create an access type which uses the storage pool of the
2226 -- caller's finalization master.
2228 -- Generate:
2229 -- type Ptr_Typ is access Obj_Typ;
2231 Ptr_Typ := Make_Temporary (Loc, 'P');
2233 Append_To (Decls,
2234 Make_Full_Type_Declaration (Loc,
2235 Defining_Identifier => Ptr_Typ,
2236 Type_Definition =>
2237 Make_Access_To_Object_Definition (Loc,
2238 Subtype_Indication => New_Reference_To (Obj_Typ, Loc))));
2240 -- Perform minor decoration in order to set the master and the
2241 -- storage pool attributes.
2243 Set_Ekind (Ptr_Typ, E_Access_Type);
2244 Set_Finalization_Master (Ptr_Typ, Fin_Mas_Id);
2245 Set_Associated_Storage_Pool (Ptr_Typ, Pool_Id);
2247 -- Create an explicit free statement. Note that the free uses the
2248 -- caller's pool expressed as a renaming.
2250 Free_Stmt :=
2251 Make_Free_Statement (Loc,
2252 Expression =>
2253 Unchecked_Convert_To (Ptr_Typ,
2254 New_Reference_To (Temp_Id, Loc)));
2256 Set_Storage_Pool (Free_Stmt, Pool_Id);
2258 -- Create a block to house the dummy type and the instantiation as
2259 -- well as to perform the cleanup the temporary.
2261 -- Generate:
2262 -- declare
2263 -- <Decls>
2264 -- begin
2265 -- Free (Ptr_Typ (Temp_Id));
2266 -- end;
2268 Free_Blk :=
2269 Make_Block_Statement (Loc,
2270 Declarations => Decls,
2271 Handled_Statement_Sequence =>
2272 Make_Handled_Sequence_Of_Statements (Loc,
2273 Statements => New_List (Free_Stmt)));
2275 -- Generate:
2276 -- if BIPfinalizationmaster /= null then
2278 Cond :=
2279 Make_Op_Ne (Loc,
2280 Left_Opnd => New_Reference_To (Fin_Mas_Id, Loc),
2281 Right_Opnd => Make_Null (Loc));
2283 -- For constrained or tagged results escalate the condition to
2284 -- include the allocation format. Generate:
2286 -- if BIPallocform > Secondary_Stack'Pos
2287 -- and then BIPfinalizationmaster /= null
2288 -- then
2290 if not Is_Constrained (Obj_Typ)
2291 or else Is_Tagged_Type (Obj_Typ)
2292 then
2293 declare
2294 Alloc : constant Entity_Id :=
2295 Build_In_Place_Formal (Func_Id, BIP_Alloc_Form);
2296 begin
2297 Cond :=
2298 Make_And_Then (Loc,
2299 Left_Opnd =>
2300 Make_Op_Gt (Loc,
2301 Left_Opnd => New_Reference_To (Alloc, Loc),
2302 Right_Opnd =>
2303 Make_Integer_Literal (Loc,
2304 UI_From_Int
2305 (BIP_Allocation_Form'Pos (Secondary_Stack)))),
2307 Right_Opnd => Cond);
2308 end;
2309 end if;
2311 -- Generate:
2312 -- if <Cond> then
2313 -- <Free_Blk>
2314 -- end if;
2316 return
2317 Make_If_Statement (Loc,
2318 Condition => Cond,
2319 Then_Statements => New_List (Free_Blk));
2320 end Build_BIP_Cleanup_Stmts;
2322 --------------------
2323 -- Find_Last_Init --
2324 --------------------
2326 procedure Find_Last_Init
2327 (Decl : Node_Id;
2328 Typ : Entity_Id;
2329 Last_Init : out Node_Id;
2330 Body_Insert : out Node_Id)
2332 Nod_1 : Node_Id := Empty;
2333 Nod_2 : Node_Id := Empty;
2334 Utyp : Entity_Id;
2336 function Is_Init_Call
2337 (N : Node_Id;
2338 Typ : Entity_Id) return Boolean;
2339 -- Given an arbitrary node, determine whether N is a procedure
2340 -- call and if it is, try to match the name of the call with the
2341 -- [Deep_]Initialize proc of Typ.
2343 function Next_Suitable_Statement (Stmt : Node_Id) return Node_Id;
2344 -- Given a statement which is part of a list, return the next
2345 -- real statement while skipping over dynamic elab checks.
2347 ------------------
2348 -- Is_Init_Call --
2349 ------------------
2351 function Is_Init_Call
2352 (N : Node_Id;
2353 Typ : Entity_Id) return Boolean
2355 begin
2356 -- A call to [Deep_]Initialize is always direct
2358 if Nkind (N) = N_Procedure_Call_Statement
2359 and then Nkind (Name (N)) = N_Identifier
2360 then
2361 declare
2362 Call_Ent : constant Entity_Id := Entity (Name (N));
2363 Deep_Init : constant Entity_Id :=
2364 TSS (Typ, TSS_Deep_Initialize);
2365 Init : Entity_Id := Empty;
2367 begin
2368 -- A type may have controlled components but not be
2369 -- controlled.
2371 if Is_Controlled (Typ) then
2372 Init := Find_Prim_Op (Typ, Name_Initialize);
2374 if Present (Init) then
2375 Init := Ultimate_Alias (Init);
2376 end if;
2377 end if;
2379 return
2380 (Present (Deep_Init) and then Call_Ent = Deep_Init)
2381 or else
2382 (Present (Init) and then Call_Ent = Init);
2383 end;
2384 end if;
2386 return False;
2387 end Is_Init_Call;
2389 -----------------------------
2390 -- Next_Suitable_Statement --
2391 -----------------------------
2393 function Next_Suitable_Statement (Stmt : Node_Id) return Node_Id is
2394 Result : Node_Id := Next (Stmt);
2396 begin
2397 -- Skip over access-before-elaboration checks
2399 if Dynamic_Elaboration_Checks
2400 and then Nkind (Result) = N_Raise_Program_Error
2401 then
2402 Result := Next (Result);
2403 end if;
2405 return Result;
2406 end Next_Suitable_Statement;
2408 -- Start of processing for Find_Last_Init
2410 begin
2411 Last_Init := Decl;
2412 Body_Insert := Empty;
2414 -- Object renamings and objects associated with controlled
2415 -- function results do not have initialization calls.
2417 if Has_No_Init then
2418 return;
2419 end if;
2421 if Is_Concurrent_Type (Typ) then
2422 Utyp := Corresponding_Record_Type (Typ);
2423 else
2424 Utyp := Typ;
2425 end if;
2427 if Is_Private_Type (Utyp)
2428 and then Present (Full_View (Utyp))
2429 then
2430 Utyp := Full_View (Utyp);
2431 end if;
2433 -- The init procedures are arranged as follows:
2435 -- Object : Controlled_Type;
2436 -- Controlled_TypeIP (Object);
2437 -- [[Deep_]Initialize (Object);]
2439 -- where the user-defined initialize may be optional or may appear
2440 -- inside a block when abort deferral is needed.
2442 Nod_1 := Next_Suitable_Statement (Decl);
2443 if Present (Nod_1) then
2444 Nod_2 := Next_Suitable_Statement (Nod_1);
2446 -- The statement following an object declaration is always a
2447 -- call to the type init proc.
2449 Last_Init := Nod_1;
2450 end if;
2452 -- Optional user-defined init or deep init processing
2454 if Present (Nod_2) then
2456 -- The statement following the type init proc may be a block
2457 -- statement in cases where abort deferral is required.
2459 if Nkind (Nod_2) = N_Block_Statement then
2460 declare
2461 HSS : constant Node_Id :=
2462 Handled_Statement_Sequence (Nod_2);
2463 Stmt : Node_Id;
2465 begin
2466 if Present (HSS)
2467 and then Present (Statements (HSS))
2468 then
2469 Stmt := First (Statements (HSS));
2471 -- Examine individual block statements and locate the
2472 -- call to [Deep_]Initialze.
2474 while Present (Stmt) loop
2475 if Is_Init_Call (Stmt, Utyp) then
2476 Last_Init := Stmt;
2477 Body_Insert := Nod_2;
2479 exit;
2480 end if;
2482 Next (Stmt);
2483 end loop;
2484 end if;
2485 end;
2487 elsif Is_Init_Call (Nod_2, Utyp) then
2488 Last_Init := Nod_2;
2489 end if;
2490 end if;
2491 end Find_Last_Init;
2493 -- Start of processing for Process_Object_Declaration
2495 begin
2496 Obj_Ref := New_Reference_To (Obj_Id, Loc);
2497 Obj_Typ := Base_Type (Etype (Obj_Id));
2499 -- Handle access types
2501 if Is_Access_Type (Obj_Typ) then
2502 Obj_Ref := Make_Explicit_Dereference (Loc, Obj_Ref);
2503 Obj_Typ := Directly_Designated_Type (Obj_Typ);
2504 end if;
2506 Set_Etype (Obj_Ref, Obj_Typ);
2508 -- Set a new value for the state counter and insert the statement
2509 -- after the object declaration. Generate:
2511 -- Counter := <value>;
2513 Inc_Decl :=
2514 Make_Assignment_Statement (Loc,
2515 Name => New_Reference_To (Counter_Id, Loc),
2516 Expression => Make_Integer_Literal (Loc, Counter_Val));
2518 -- Insert the counter after all initialization has been done. The
2519 -- place of insertion depends on the context. When dealing with a
2520 -- controlled function, the counter is inserted directly after the
2521 -- declaration because such objects lack init calls.
2523 Find_Last_Init (Decl, Obj_Typ, Count_Ins, Body_Ins);
2525 Insert_After (Count_Ins, Inc_Decl);
2526 Analyze (Inc_Decl);
2528 -- If the current declaration is the last in the list, the finalizer
2529 -- body needs to be inserted after the set counter statement for the
2530 -- current object declaration. This is complicated by the fact that
2531 -- the set counter statement may appear in abort deferred block. In
2532 -- that case, the proper insertion place is after the block.
2534 if No (Finalizer_Insert_Nod) then
2536 -- Insertion after an abort deffered block
2538 if Present (Body_Ins) then
2539 Finalizer_Insert_Nod := Body_Ins;
2540 else
2541 Finalizer_Insert_Nod := Inc_Decl;
2542 end if;
2543 end if;
2545 -- Create the associated label with this object, generate:
2547 -- L<counter> : label;
2549 Label_Id :=
2550 Make_Identifier (Loc, New_External_Name ('L', Counter_Val));
2551 Set_Entity
2552 (Label_Id, Make_Defining_Identifier (Loc, Chars (Label_Id)));
2553 Label := Make_Label (Loc, Label_Id);
2555 Prepend_To (Finalizer_Decls,
2556 Make_Implicit_Label_Declaration (Loc,
2557 Defining_Identifier => Entity (Label_Id),
2558 Label_Construct => Label));
2560 -- Create the associated jump with this object, generate:
2562 -- when <counter> =>
2563 -- goto L<counter>;
2565 Prepend_To (Jump_Alts,
2566 Make_Case_Statement_Alternative (Loc,
2567 Discrete_Choices => New_List (
2568 Make_Integer_Literal (Loc, Counter_Val)),
2569 Statements => New_List (
2570 Make_Goto_Statement (Loc,
2571 Name => New_Reference_To (Entity (Label_Id), Loc)))));
2573 -- Insert the jump destination, generate:
2575 -- <<L<counter>>>
2577 Append_To (Finalizer_Stmts, Label);
2579 -- Processing for simple protected objects. Such objects require
2580 -- manual finalization of their lock managers.
2582 if Is_Protected then
2583 Fin_Stmts := No_List;
2585 if Is_Simple_Protected_Type (Obj_Typ) then
2586 Fin_Call := Cleanup_Protected_Object (Decl, Obj_Ref);
2588 if Present (Fin_Call) then
2589 Fin_Stmts := New_List (Fin_Call);
2590 end if;
2592 elsif Has_Simple_Protected_Object (Obj_Typ) then
2593 if Is_Record_Type (Obj_Typ) then
2594 Fin_Stmts := Cleanup_Record (Decl, Obj_Ref, Obj_Typ);
2595 elsif Is_Array_Type (Obj_Typ) then
2596 Fin_Stmts := Cleanup_Array (Decl, Obj_Ref, Obj_Typ);
2597 end if;
2598 end if;
2600 -- Generate:
2601 -- begin
2602 -- System.Tasking.Protected_Objects.Finalize_Protection
2603 -- (Obj._object);
2605 -- exception
2606 -- when others =>
2607 -- null;
2608 -- end;
2610 if Present (Fin_Stmts) then
2611 Append_To (Finalizer_Stmts,
2612 Make_Block_Statement (Loc,
2613 Handled_Statement_Sequence =>
2614 Make_Handled_Sequence_Of_Statements (Loc,
2615 Statements => Fin_Stmts,
2617 Exception_Handlers => New_List (
2618 Make_Exception_Handler (Loc,
2619 Exception_Choices => New_List (
2620 Make_Others_Choice (Loc)),
2622 Statements => New_List (
2623 Make_Null_Statement (Loc)))))));
2624 end if;
2626 -- Processing for regular controlled objects
2628 else
2629 -- Generate:
2630 -- [Deep_]Finalize (Obj); -- No_Exception_Propagation
2632 -- begin -- Exception handlers allowed
2633 -- [Deep_]Finalize (Obj);
2635 -- exception
2636 -- when Id : others =>
2637 -- if not Raised then
2638 -- Raised := True;
2639 -- Save_Occurrence (E, Id);
2640 -- end if;
2641 -- end;
2643 Fin_Call :=
2644 Make_Final_Call (
2645 Obj_Ref => Obj_Ref,
2646 Typ => Obj_Typ);
2648 -- For CodePeer, the exception handlers normally generated here
2649 -- generate complex flowgraphs which result in capacity problems.
2650 -- Omitting these handlers for CodePeer is justified as follows:
2652 -- If a handler is dead, then omitting it is surely ok
2654 -- If a handler is live, then CodePeer should flag the
2655 -- potentially-exception-raising construct that causes it
2656 -- to be live. That is what we are interested in, not what
2657 -- happens after the exception is raised.
2659 if Exceptions_OK and not CodePeer_Mode then
2660 Fin_Stmts := New_List (
2661 Make_Block_Statement (Loc,
2662 Handled_Statement_Sequence =>
2663 Make_Handled_Sequence_Of_Statements (Loc,
2664 Statements => New_List (Fin_Call),
2666 Exception_Handlers => New_List (
2667 Build_Exception_Handler
2668 (Finalizer_Data, For_Package)))));
2670 -- When exception handlers are prohibited, the finalization call
2671 -- appears unprotected. Any exception raised during finalization
2672 -- will bypass the circuitry which ensures the cleanup of all
2673 -- remaining objects.
2675 else
2676 Fin_Stmts := New_List (Fin_Call);
2677 end if;
2679 -- If we are dealing with a return object of a build-in-place
2680 -- function, generate the following cleanup statements:
2682 -- if BIPallocfrom > Secondary_Stack'Pos
2683 -- and then BIPfinalizationmaster /= null
2684 -- then
2685 -- declare
2686 -- type Ptr_Typ is access Obj_Typ;
2687 -- for Ptr_Typ'Storage_Pool use
2688 -- Base_Pool (BIPfinalizationmaster.all).all;
2689 -- begin
2690 -- Free (Ptr_Typ (Temp));
2691 -- end;
2692 -- end if;
2694 -- The generated code effectively detaches the temporary from the
2695 -- caller finalization master and deallocates the object. This is
2696 -- disabled on .NET/JVM because pools are not supported.
2698 if VM_Target = No_VM and then Is_Return_Object (Obj_Id) then
2699 declare
2700 Func_Id : constant Entity_Id := Enclosing_Function (Obj_Id);
2701 begin
2702 if Is_Build_In_Place_Function (Func_Id)
2703 and then Needs_BIP_Finalization_Master (Func_Id)
2704 then
2705 Append_To (Fin_Stmts, Build_BIP_Cleanup_Stmts (Func_Id));
2706 end if;
2707 end;
2708 end if;
2710 if Ekind_In (Obj_Id, E_Constant, E_Variable)
2711 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
2712 then
2713 -- Temporaries created for the purpose of "exporting" a
2714 -- controlled transient out of an Expression_With_Actions (EWA)
2715 -- need guards. The following illustrates the usage of such
2716 -- temporaries.
2718 -- Access_Typ : access [all] Obj_Typ;
2719 -- Temp : Access_Typ := null;
2720 -- <Counter> := ...;
2722 -- do
2723 -- Ctrl_Trans : [access [all]] Obj_Typ := ...;
2724 -- Temp := Access_Typ (Ctrl_Trans); -- when a pointer
2725 -- <or>
2726 -- Temp := Ctrl_Trans'Unchecked_Access;
2727 -- in ... end;
2729 -- The finalization machinery does not process EWA nodes as
2730 -- this may lead to premature finalization of expressions. Note
2731 -- that Temp is marked as being properly initialized regardless
2732 -- of whether the initialization of Ctrl_Trans succeeded. Since
2733 -- a failed initialization may leave Temp with a value of null,
2734 -- add a guard to handle this case:
2736 -- if Obj /= null then
2737 -- <object finalization statements>
2738 -- end if;
2740 if Nkind (Status_Flag_Or_Transient_Decl (Obj_Id)) =
2741 N_Object_Declaration
2742 then
2743 Fin_Stmts := New_List (
2744 Make_If_Statement (Loc,
2745 Condition =>
2746 Make_Op_Ne (Loc,
2747 Left_Opnd => New_Reference_To (Obj_Id, Loc),
2748 Right_Opnd => Make_Null (Loc)),
2749 Then_Statements => Fin_Stmts));
2751 -- Return objects use a flag to aid in processing their
2752 -- potential finalization when the enclosing function fails
2753 -- to return properly. Generate:
2755 -- if not Flag then
2756 -- <object finalization statements>
2757 -- end if;
2759 else
2760 Fin_Stmts := New_List (
2761 Make_If_Statement (Loc,
2762 Condition =>
2763 Make_Op_Not (Loc,
2764 Right_Opnd =>
2765 New_Reference_To
2766 (Status_Flag_Or_Transient_Decl (Obj_Id), Loc)),
2768 Then_Statements => Fin_Stmts));
2769 end if;
2770 end if;
2771 end if;
2773 Append_List_To (Finalizer_Stmts, Fin_Stmts);
2775 -- Since the declarations are examined in reverse, the state counter
2776 -- must be decremented in order to keep with the true position of
2777 -- objects.
2779 Counter_Val := Counter_Val - 1;
2780 end Process_Object_Declaration;
2782 -------------------------------------
2783 -- Process_Tagged_Type_Declaration --
2784 -------------------------------------
2786 procedure Process_Tagged_Type_Declaration (Decl : Node_Id) is
2787 Typ : constant Entity_Id := Defining_Identifier (Decl);
2788 DT_Ptr : constant Entity_Id :=
2789 Node (First_Elmt (Access_Disp_Table (Typ)));
2790 begin
2791 -- Generate:
2792 -- Ada.Tags.Unregister_Tag (<Typ>P);
2794 Append_To (Tagged_Type_Stmts,
2795 Make_Procedure_Call_Statement (Loc,
2796 Name =>
2797 New_Reference_To (RTE (RE_Unregister_Tag), Loc),
2798 Parameter_Associations => New_List (
2799 New_Reference_To (DT_Ptr, Loc))));
2800 end Process_Tagged_Type_Declaration;
2802 -- Start of processing for Build_Finalizer
2804 begin
2805 Fin_Id := Empty;
2807 -- Do not perform this expansion in Alfa mode because it is not
2808 -- necessary.
2810 if Alfa_Mode then
2811 return;
2812 end if;
2814 -- Step 1: Extract all lists which may contain controlled objects or
2815 -- library-level tagged types.
2817 if For_Package_Spec then
2818 Decls := Visible_Declarations (Specification (N));
2819 Priv_Decls := Private_Declarations (Specification (N));
2821 -- Retrieve the package spec id
2823 Spec_Id := Defining_Unit_Name (Specification (N));
2825 if Nkind (Spec_Id) = N_Defining_Program_Unit_Name then
2826 Spec_Id := Defining_Identifier (Spec_Id);
2827 end if;
2829 -- Accept statement, block, entry body, package body, protected body,
2830 -- subprogram body or task body.
2832 else
2833 Decls := Declarations (N);
2834 HSS := Handled_Statement_Sequence (N);
2836 if Present (HSS) then
2837 if Present (Statements (HSS)) then
2838 Stmts := Statements (HSS);
2839 end if;
2841 if Present (At_End_Proc (HSS)) then
2842 Prev_At_End := At_End_Proc (HSS);
2843 end if;
2844 end if;
2846 -- Retrieve the package spec id for package bodies
2848 if For_Package_Body then
2849 Spec_Id := Corresponding_Spec (N);
2850 end if;
2851 end if;
2853 -- Do not process nested packages since those are handled by the
2854 -- enclosing scope's finalizer. Do not process non-expanded package
2855 -- instantiations since those will be re-analyzed and re-expanded.
2857 if For_Package
2858 and then
2859 (not Is_Library_Level_Entity (Spec_Id)
2861 -- Nested packages are considered to be library level entities,
2862 -- but do not need to be processed separately. True library level
2863 -- packages have a scope value of 1.
2865 or else Scope_Depth_Value (Spec_Id) /= Uint_1
2866 or else (Is_Generic_Instance (Spec_Id)
2867 and then Package_Instantiation (Spec_Id) /= N))
2868 then
2869 return;
2870 end if;
2872 -- Step 2: Object [pre]processing
2874 if For_Package then
2876 -- Preprocess the visible declarations now in order to obtain the
2877 -- correct number of controlled object by the time the private
2878 -- declarations are processed.
2880 Process_Declarations (Decls, Preprocess => True, Top_Level => True);
2882 -- From all the possible contexts, only package specifications may
2883 -- have private declarations.
2885 if For_Package_Spec then
2886 Process_Declarations
2887 (Priv_Decls, Preprocess => True, Top_Level => True);
2888 end if;
2890 -- The current context may lack controlled objects, but require some
2891 -- other form of completion (task termination for instance). In such
2892 -- cases, the finalizer must be created and carry the additional
2893 -- statements.
2895 if Acts_As_Clean or Has_Ctrl_Objs or Has_Tagged_Types then
2896 Build_Components;
2897 end if;
2899 -- The preprocessing has determined that the context has controlled
2900 -- objects or library-level tagged types.
2902 if Has_Ctrl_Objs or Has_Tagged_Types then
2904 -- Private declarations are processed first in order to preserve
2905 -- possible dependencies between public and private objects.
2907 if For_Package_Spec then
2908 Process_Declarations (Priv_Decls);
2909 end if;
2911 Process_Declarations (Decls);
2912 end if;
2914 -- Non-package case
2916 else
2917 -- Preprocess both declarations and statements
2919 Process_Declarations (Decls, Preprocess => True, Top_Level => True);
2920 Process_Declarations (Stmts, Preprocess => True, Top_Level => True);
2922 -- At this point it is known that N has controlled objects. Ensure
2923 -- that N has a declarative list since the finalizer spec will be
2924 -- attached to it.
2926 if Has_Ctrl_Objs and then No (Decls) then
2927 Set_Declarations (N, New_List);
2928 Decls := Declarations (N);
2929 Spec_Decls := Decls;
2930 end if;
2932 -- The current context may lack controlled objects, but require some
2933 -- other form of completion (task termination for instance). In such
2934 -- cases, the finalizer must be created and carry the additional
2935 -- statements.
2937 if Acts_As_Clean or Has_Ctrl_Objs or Has_Tagged_Types then
2938 Build_Components;
2939 end if;
2941 if Has_Ctrl_Objs or Has_Tagged_Types then
2942 Process_Declarations (Stmts);
2943 Process_Declarations (Decls);
2944 end if;
2945 end if;
2947 -- Step 3: Finalizer creation
2949 if Acts_As_Clean or Has_Ctrl_Objs or Has_Tagged_Types then
2950 Create_Finalizer;
2951 end if;
2952 end Build_Finalizer;
2954 --------------------------
2955 -- Build_Finalizer_Call --
2956 --------------------------
2958 procedure Build_Finalizer_Call (N : Node_Id; Fin_Id : Entity_Id) is
2959 Is_Prot_Body : constant Boolean :=
2960 Nkind (N) = N_Subprogram_Body
2961 and then Is_Protected_Subprogram_Body (N);
2962 -- Determine whether N denotes the protected version of a subprogram
2963 -- which belongs to a protected type.
2965 Loc : constant Source_Ptr := Sloc (N);
2966 HSS : Node_Id;
2968 begin
2969 -- Do not perform this expansion in Alfa mode because we do not create
2970 -- finalizers in the first place.
2972 if Alfa_Mode then
2973 return;
2974 end if;
2976 -- The At_End handler should have been assimilated by the finalizer
2978 HSS := Handled_Statement_Sequence (N);
2979 pragma Assert (No (At_End_Proc (HSS)));
2981 -- If the construct to be cleaned up is a protected subprogram body, the
2982 -- finalizer call needs to be associated with the block which wraps the
2983 -- unprotected version of the subprogram. The following illustrates this
2984 -- scenario:
2986 -- procedure Prot_SubpP is
2987 -- procedure finalizer is
2988 -- begin
2989 -- Service_Entries (Prot_Obj);
2990 -- Abort_Undefer;
2991 -- end finalizer;
2993 -- begin
2994 -- . . .
2995 -- begin
2996 -- Prot_SubpN (Prot_Obj);
2997 -- at end
2998 -- finalizer;
2999 -- end;
3000 -- end Prot_SubpP;
3002 if Is_Prot_Body then
3003 HSS := Handled_Statement_Sequence (Last (Statements (HSS)));
3005 -- An At_End handler and regular exception handlers cannot coexist in
3006 -- the same statement sequence. Wrap the original statements in a block.
3008 elsif Present (Exception_Handlers (HSS)) then
3009 declare
3010 End_Lab : constant Node_Id := End_Label (HSS);
3011 Block : Node_Id;
3013 begin
3014 Block :=
3015 Make_Block_Statement (Loc, Handled_Statement_Sequence => HSS);
3017 Set_Handled_Statement_Sequence (N,
3018 Make_Handled_Sequence_Of_Statements (Loc, New_List (Block)));
3020 HSS := Handled_Statement_Sequence (N);
3021 Set_End_Label (HSS, End_Lab);
3022 end;
3023 end if;
3025 Set_At_End_Proc (HSS, New_Reference_To (Fin_Id, Loc));
3027 Analyze (At_End_Proc (HSS));
3028 Expand_At_End_Handler (HSS, Empty);
3029 end Build_Finalizer_Call;
3031 ---------------------
3032 -- Build_Late_Proc --
3033 ---------------------
3035 procedure Build_Late_Proc (Typ : Entity_Id; Nam : Name_Id) is
3036 begin
3037 for Final_Prim in Name_Of'Range loop
3038 if Name_Of (Final_Prim) = Nam then
3039 Set_TSS (Typ,
3040 Make_Deep_Proc
3041 (Prim => Final_Prim,
3042 Typ => Typ,
3043 Stmts => Make_Deep_Record_Body (Final_Prim, Typ)));
3044 end if;
3045 end loop;
3046 end Build_Late_Proc;
3048 -------------------------------
3049 -- Build_Object_Declarations --
3050 -------------------------------
3052 procedure Build_Object_Declarations
3053 (Data : out Finalization_Exception_Data;
3054 Decls : List_Id;
3055 Loc : Source_Ptr;
3056 For_Package : Boolean := False)
3058 A_Expr : Node_Id;
3059 E_Decl : Node_Id;
3061 begin
3062 pragma Assert (Decls /= No_List);
3064 -- Always set the proper location as it may be needed even when
3065 -- exception propagation is forbidden.
3067 Data.Loc := Loc;
3069 if Restriction_Active (No_Exception_Propagation) then
3070 Data.Abort_Id := Empty;
3071 Data.E_Id := Empty;
3072 Data.Raised_Id := Empty;
3073 return;
3074 end if;
3076 Data.Raised_Id := Make_Temporary (Loc, 'R');
3078 -- In certain scenarios, finalization can be triggered by an abort. If
3079 -- the finalization itself fails and raises an exception, the resulting
3080 -- Program_Error must be supressed and replaced by an abort signal. In
3081 -- order to detect this scenario, save the state of entry into the
3082 -- finalization code.
3084 -- No need to do this for VM case, since VM version of Ada.Exceptions
3085 -- does not include routine Raise_From_Controlled_Operation which is the
3086 -- the sole user of flag Abort.
3088 -- This is not needed for library-level finalizers as they are called
3089 -- by the environment task and cannot be aborted.
3091 if Abort_Allowed
3092 and then VM_Target = No_VM
3093 and then not For_Package
3094 then
3095 Data.Abort_Id := Make_Temporary (Loc, 'A');
3097 A_Expr := New_Reference_To (RTE (RE_Triggered_By_Abort), Loc);
3099 -- Generate:
3101 -- Abort_Id : constant Boolean := <A_Expr>;
3103 Append_To (Decls,
3104 Make_Object_Declaration (Loc,
3105 Defining_Identifier => Data.Abort_Id,
3106 Constant_Present => True,
3107 Object_Definition => New_Reference_To (Standard_Boolean, Loc),
3108 Expression => A_Expr));
3110 else
3111 -- No abort, .NET/JVM or library-level finalizers
3113 Data.Abort_Id := Empty;
3114 end if;
3116 if Exception_Extra_Info then
3117 Data.E_Id := Make_Temporary (Loc, 'E');
3119 -- Generate:
3121 -- E_Id : Exception_Occurrence;
3123 E_Decl :=
3124 Make_Object_Declaration (Loc,
3125 Defining_Identifier => Data.E_Id,
3126 Object_Definition =>
3127 New_Reference_To (RTE (RE_Exception_Occurrence), Loc));
3128 Set_No_Initialization (E_Decl);
3130 Append_To (Decls, E_Decl);
3132 else
3133 Data.E_Id := Empty;
3134 end if;
3136 -- Generate:
3138 -- Raised_Id : Boolean := False;
3140 Append_To (Decls,
3141 Make_Object_Declaration (Loc,
3142 Defining_Identifier => Data.Raised_Id,
3143 Object_Definition => New_Reference_To (Standard_Boolean, Loc),
3144 Expression => New_Reference_To (Standard_False, Loc)));
3145 end Build_Object_Declarations;
3147 ---------------------------
3148 -- Build_Raise_Statement --
3149 ---------------------------
3151 function Build_Raise_Statement
3152 (Data : Finalization_Exception_Data) return Node_Id
3154 Stmt : Node_Id;
3155 Expr : Node_Id;
3157 begin
3158 -- Standard run-time and .NET/JVM targets use the specialized routine
3159 -- Raise_From_Controlled_Operation.
3161 if Exception_Extra_Info
3162 and then RTE_Available (RE_Raise_From_Controlled_Operation)
3163 then
3164 Stmt :=
3165 Make_Procedure_Call_Statement (Data.Loc,
3166 Name =>
3167 New_Reference_To
3168 (RTE (RE_Raise_From_Controlled_Operation), Data.Loc),
3169 Parameter_Associations =>
3170 New_List (New_Reference_To (Data.E_Id, Data.Loc)));
3172 -- Restricted run-time: exception messages are not supported and hence
3173 -- Raise_From_Controlled_Operation is not supported. Raise Program_Error
3174 -- instead.
3176 else
3177 Stmt :=
3178 Make_Raise_Program_Error (Data.Loc,
3179 Reason => PE_Finalize_Raised_Exception);
3180 end if;
3182 -- Generate:
3184 -- Raised_Id and then not Abort_Id
3185 -- <or>
3186 -- Raised_Id
3188 Expr := New_Reference_To (Data.Raised_Id, Data.Loc);
3190 if Present (Data.Abort_Id) then
3191 Expr := Make_And_Then (Data.Loc,
3192 Left_Opnd => Expr,
3193 Right_Opnd =>
3194 Make_Op_Not (Data.Loc,
3195 Right_Opnd => New_Reference_To (Data.Abort_Id, Data.Loc)));
3196 end if;
3198 -- Generate:
3200 -- if Raised_Id and then not Abort_Id then
3201 -- Raise_From_Controlled_Operation (E_Id);
3202 -- <or>
3203 -- raise Program_Error; -- restricted runtime
3204 -- end if;
3206 return
3207 Make_If_Statement (Data.Loc,
3208 Condition => Expr,
3209 Then_Statements => New_List (Stmt));
3210 end Build_Raise_Statement;
3212 -----------------------------
3213 -- Build_Record_Deep_Procs --
3214 -----------------------------
3216 procedure Build_Record_Deep_Procs (Typ : Entity_Id) is
3217 begin
3218 Set_TSS (Typ,
3219 Make_Deep_Proc
3220 (Prim => Initialize_Case,
3221 Typ => Typ,
3222 Stmts => Make_Deep_Record_Body (Initialize_Case, Typ)));
3224 if not Is_Immutably_Limited_Type (Typ) then
3225 Set_TSS (Typ,
3226 Make_Deep_Proc
3227 (Prim => Adjust_Case,
3228 Typ => Typ,
3229 Stmts => Make_Deep_Record_Body (Adjust_Case, Typ)));
3230 end if;
3232 -- Do not generate Deep_Finalize and Finalize_Address if finalization is
3233 -- suppressed since these routine will not be used.
3235 if not Restriction_Active (No_Finalization) then
3236 Set_TSS (Typ,
3237 Make_Deep_Proc
3238 (Prim => Finalize_Case,
3239 Typ => Typ,
3240 Stmts => Make_Deep_Record_Body (Finalize_Case, Typ)));
3242 -- Create TSS primitive Finalize_Address for non-VM targets. JVM and
3243 -- .NET do not support address arithmetic and unchecked conversions.
3245 if VM_Target = No_VM then
3246 Set_TSS (Typ,
3247 Make_Deep_Proc
3248 (Prim => Address_Case,
3249 Typ => Typ,
3250 Stmts => Make_Deep_Record_Body (Address_Case, Typ)));
3251 end if;
3252 end if;
3253 end Build_Record_Deep_Procs;
3255 -------------------
3256 -- Cleanup_Array --
3257 -------------------
3259 function Cleanup_Array
3260 (N : Node_Id;
3261 Obj : Node_Id;
3262 Typ : Entity_Id) return List_Id
3264 Loc : constant Source_Ptr := Sloc (N);
3265 Index_List : constant List_Id := New_List;
3267 function Free_Component return List_Id;
3268 -- Generate the code to finalize the task or protected subcomponents
3269 -- of a single component of the array.
3271 function Free_One_Dimension (Dim : Int) return List_Id;
3272 -- Generate a loop over one dimension of the array
3274 --------------------
3275 -- Free_Component --
3276 --------------------
3278 function Free_Component return List_Id is
3279 Stmts : List_Id := New_List;
3280 Tsk : Node_Id;
3281 C_Typ : constant Entity_Id := Component_Type (Typ);
3283 begin
3284 -- Component type is known to contain tasks or protected objects
3286 Tsk :=
3287 Make_Indexed_Component (Loc,
3288 Prefix => Duplicate_Subexpr_No_Checks (Obj),
3289 Expressions => Index_List);
3291 Set_Etype (Tsk, C_Typ);
3293 if Is_Task_Type (C_Typ) then
3294 Append_To (Stmts, Cleanup_Task (N, Tsk));
3296 elsif Is_Simple_Protected_Type (C_Typ) then
3297 Append_To (Stmts, Cleanup_Protected_Object (N, Tsk));
3299 elsif Is_Record_Type (C_Typ) then
3300 Stmts := Cleanup_Record (N, Tsk, C_Typ);
3302 elsif Is_Array_Type (C_Typ) then
3303 Stmts := Cleanup_Array (N, Tsk, C_Typ);
3304 end if;
3306 return Stmts;
3307 end Free_Component;
3309 ------------------------
3310 -- Free_One_Dimension --
3311 ------------------------
3313 function Free_One_Dimension (Dim : Int) return List_Id is
3314 Index : Entity_Id;
3316 begin
3317 if Dim > Number_Dimensions (Typ) then
3318 return Free_Component;
3320 -- Here we generate the required loop
3322 else
3323 Index := Make_Temporary (Loc, 'J');
3324 Append (New_Reference_To (Index, Loc), Index_List);
3326 return New_List (
3327 Make_Implicit_Loop_Statement (N,
3328 Identifier => Empty,
3329 Iteration_Scheme =>
3330 Make_Iteration_Scheme (Loc,
3331 Loop_Parameter_Specification =>
3332 Make_Loop_Parameter_Specification (Loc,
3333 Defining_Identifier => Index,
3334 Discrete_Subtype_Definition =>
3335 Make_Attribute_Reference (Loc,
3336 Prefix => Duplicate_Subexpr (Obj),
3337 Attribute_Name => Name_Range,
3338 Expressions => New_List (
3339 Make_Integer_Literal (Loc, Dim))))),
3340 Statements => Free_One_Dimension (Dim + 1)));
3341 end if;
3342 end Free_One_Dimension;
3344 -- Start of processing for Cleanup_Array
3346 begin
3347 return Free_One_Dimension (1);
3348 end Cleanup_Array;
3350 --------------------
3351 -- Cleanup_Record --
3352 --------------------
3354 function Cleanup_Record
3355 (N : Node_Id;
3356 Obj : Node_Id;
3357 Typ : Entity_Id) return List_Id
3359 Loc : constant Source_Ptr := Sloc (N);
3360 Tsk : Node_Id;
3361 Comp : Entity_Id;
3362 Stmts : constant List_Id := New_List;
3363 U_Typ : constant Entity_Id := Underlying_Type (Typ);
3365 begin
3366 if Has_Discriminants (U_Typ)
3367 and then Nkind (Parent (U_Typ)) = N_Full_Type_Declaration
3368 and then
3369 Nkind (Type_Definition (Parent (U_Typ))) = N_Record_Definition
3370 and then
3371 Present
3372 (Variant_Part (Component_List (Type_Definition (Parent (U_Typ)))))
3373 then
3374 -- For now, do not attempt to free a component that may appear in a
3375 -- variant, and instead issue a warning. Doing this "properly" would
3376 -- require building a case statement and would be quite a mess. Note
3377 -- that the RM only requires that free "work" for the case of a task
3378 -- access value, so already we go way beyond this in that we deal
3379 -- with the array case and non-discriminated record cases.
3381 Error_Msg_N
3382 ("task/protected object in variant record will not be freed?", N);
3383 return New_List (Make_Null_Statement (Loc));
3384 end if;
3386 Comp := First_Component (Typ);
3387 while Present (Comp) loop
3388 if Has_Task (Etype (Comp))
3389 or else Has_Simple_Protected_Object (Etype (Comp))
3390 then
3391 Tsk :=
3392 Make_Selected_Component (Loc,
3393 Prefix => Duplicate_Subexpr_No_Checks (Obj),
3394 Selector_Name => New_Occurrence_Of (Comp, Loc));
3395 Set_Etype (Tsk, Etype (Comp));
3397 if Is_Task_Type (Etype (Comp)) then
3398 Append_To (Stmts, Cleanup_Task (N, Tsk));
3400 elsif Is_Simple_Protected_Type (Etype (Comp)) then
3401 Append_To (Stmts, Cleanup_Protected_Object (N, Tsk));
3403 elsif Is_Record_Type (Etype (Comp)) then
3405 -- Recurse, by generating the prefix of the argument to
3406 -- the eventual cleanup call.
3408 Append_List_To (Stmts, Cleanup_Record (N, Tsk, Etype (Comp)));
3410 elsif Is_Array_Type (Etype (Comp)) then
3411 Append_List_To (Stmts, Cleanup_Array (N, Tsk, Etype (Comp)));
3412 end if;
3413 end if;
3415 Next_Component (Comp);
3416 end loop;
3418 return Stmts;
3419 end Cleanup_Record;
3421 ------------------------------
3422 -- Cleanup_Protected_Object --
3423 ------------------------------
3425 function Cleanup_Protected_Object
3426 (N : Node_Id;
3427 Ref : Node_Id) return Node_Id
3429 Loc : constant Source_Ptr := Sloc (N);
3431 begin
3432 -- For restricted run-time libraries (Ravenscar), tasks are
3433 -- non-terminating, and protected objects can only appear at library
3434 -- level, so we do not want finalization of protected objects.
3436 if Restricted_Profile then
3437 return Empty;
3439 else
3440 return
3441 Make_Procedure_Call_Statement (Loc,
3442 Name =>
3443 New_Reference_To (RTE (RE_Finalize_Protection), Loc),
3444 Parameter_Associations => New_List (Concurrent_Ref (Ref)));
3445 end if;
3446 end Cleanup_Protected_Object;
3448 ------------------
3449 -- Cleanup_Task --
3450 ------------------
3452 function Cleanup_Task
3453 (N : Node_Id;
3454 Ref : Node_Id) return Node_Id
3456 Loc : constant Source_Ptr := Sloc (N);
3458 begin
3459 -- For restricted run-time libraries (Ravenscar), tasks are
3460 -- non-terminating and they can only appear at library level, so we do
3461 -- not want finalization of task objects.
3463 if Restricted_Profile then
3464 return Empty;
3466 else
3467 return
3468 Make_Procedure_Call_Statement (Loc,
3469 Name =>
3470 New_Reference_To (RTE (RE_Free_Task), Loc),
3471 Parameter_Associations => New_List (Concurrent_Ref (Ref)));
3472 end if;
3473 end Cleanup_Task;
3475 ------------------------------
3476 -- Check_Visibly_Controlled --
3477 ------------------------------
3479 procedure Check_Visibly_Controlled
3480 (Prim : Final_Primitives;
3481 Typ : Entity_Id;
3482 E : in out Entity_Id;
3483 Cref : in out Node_Id)
3485 Parent_Type : Entity_Id;
3486 Op : Entity_Id;
3488 begin
3489 if Is_Derived_Type (Typ)
3490 and then Comes_From_Source (E)
3491 and then not Present (Overridden_Operation (E))
3492 then
3493 -- We know that the explicit operation on the type does not override
3494 -- the inherited operation of the parent, and that the derivation
3495 -- is from a private type that is not visibly controlled.
3497 Parent_Type := Etype (Typ);
3498 Op := Find_Prim_Op (Parent_Type, Name_Of (Prim));
3500 if Present (Op) then
3501 E := Op;
3503 -- Wrap the object to be initialized into the proper
3504 -- unchecked conversion, to be compatible with the operation
3505 -- to be called.
3507 if Nkind (Cref) = N_Unchecked_Type_Conversion then
3508 Cref := Unchecked_Convert_To (Parent_Type, Expression (Cref));
3509 else
3510 Cref := Unchecked_Convert_To (Parent_Type, Cref);
3511 end if;
3512 end if;
3513 end if;
3514 end Check_Visibly_Controlled;
3516 -------------------------------
3517 -- CW_Or_Has_Controlled_Part --
3518 -------------------------------
3520 function CW_Or_Has_Controlled_Part (T : Entity_Id) return Boolean is
3521 begin
3522 return Is_Class_Wide_Type (T) or else Needs_Finalization (T);
3523 end CW_Or_Has_Controlled_Part;
3525 ------------------
3526 -- Convert_View --
3527 ------------------
3529 function Convert_View
3530 (Proc : Entity_Id;
3531 Arg : Node_Id;
3532 Ind : Pos := 1) return Node_Id
3534 Fent : Entity_Id := First_Entity (Proc);
3535 Ftyp : Entity_Id;
3536 Atyp : Entity_Id;
3538 begin
3539 for J in 2 .. Ind loop
3540 Next_Entity (Fent);
3541 end loop;
3543 Ftyp := Etype (Fent);
3545 if Nkind_In (Arg, N_Type_Conversion, N_Unchecked_Type_Conversion) then
3546 Atyp := Entity (Subtype_Mark (Arg));
3547 else
3548 Atyp := Etype (Arg);
3549 end if;
3551 if Is_Abstract_Subprogram (Proc) and then Is_Tagged_Type (Ftyp) then
3552 return Unchecked_Convert_To (Class_Wide_Type (Ftyp), Arg);
3554 elsif Ftyp /= Atyp
3555 and then Present (Atyp)
3556 and then (Is_Private_Type (Ftyp) or else Is_Private_Type (Atyp))
3557 and then Base_Type (Underlying_Type (Atyp)) =
3558 Base_Type (Underlying_Type (Ftyp))
3559 then
3560 return Unchecked_Convert_To (Ftyp, Arg);
3562 -- If the argument is already a conversion, as generated by
3563 -- Make_Init_Call, set the target type to the type of the formal
3564 -- directly, to avoid spurious typing problems.
3566 elsif Nkind_In (Arg, N_Unchecked_Type_Conversion, N_Type_Conversion)
3567 and then not Is_Class_Wide_Type (Atyp)
3568 then
3569 Set_Subtype_Mark (Arg, New_Occurrence_Of (Ftyp, Sloc (Arg)));
3570 Set_Etype (Arg, Ftyp);
3571 return Arg;
3573 else
3574 return Arg;
3575 end if;
3576 end Convert_View;
3578 ------------------------
3579 -- Enclosing_Function --
3580 ------------------------
3582 function Enclosing_Function (E : Entity_Id) return Entity_Id is
3583 Func_Id : Entity_Id;
3585 begin
3586 Func_Id := E;
3587 while Present (Func_Id)
3588 and then Func_Id /= Standard_Standard
3589 loop
3590 if Ekind (Func_Id) = E_Function then
3591 return Func_Id;
3592 end if;
3594 Func_Id := Scope (Func_Id);
3595 end loop;
3597 return Empty;
3598 end Enclosing_Function;
3600 -------------------------------
3601 -- Establish_Transient_Scope --
3602 -------------------------------
3604 -- This procedure is called each time a transient block has to be inserted
3605 -- that is to say for each call to a function with unconstrained or tagged
3606 -- result. It creates a new scope on the stack scope in order to enclose
3607 -- all transient variables generated
3609 procedure Establish_Transient_Scope (N : Node_Id; Sec_Stack : Boolean) is
3610 Loc : constant Source_Ptr := Sloc (N);
3611 Wrap_Node : Node_Id;
3613 begin
3614 -- Do not create a transient scope if we are already inside one
3616 for S in reverse Scope_Stack.First .. Scope_Stack.Last loop
3617 if Scope_Stack.Table (S).Is_Transient then
3618 if Sec_Stack then
3619 Set_Uses_Sec_Stack (Scope_Stack.Table (S).Entity);
3620 end if;
3622 return;
3624 -- If we have encountered Standard there are no enclosing
3625 -- transient scopes.
3627 elsif Scope_Stack.Table (S).Entity = Standard_Standard then
3628 exit;
3629 end if;
3630 end loop;
3632 Wrap_Node := Find_Node_To_Be_Wrapped (N);
3634 -- Case of no wrap node, false alert, no transient scope needed
3636 if No (Wrap_Node) then
3637 null;
3639 -- If the node to wrap is an iteration_scheme, the expression is
3640 -- one of the bounds, and the expansion will make an explicit
3641 -- declaration for it (see Analyze_Iteration_Scheme, sem_ch5.adb),
3642 -- so do not apply any transformations here. Same for an Ada 2012
3643 -- iterator specification, where a block is created for the expression
3644 -- that build the container.
3646 elsif Nkind_In (Wrap_Node, N_Iteration_Scheme,
3647 N_Iterator_Specification)
3648 then
3649 null;
3651 -- In formal verification mode, if the node to wrap is a pragma check,
3652 -- this node and enclosed expression are not expanded, so do not apply
3653 -- any transformations here.
3655 elsif Alfa_Mode
3656 and then Nkind (Wrap_Node) = N_Pragma
3657 and then Get_Pragma_Id (Wrap_Node) = Pragma_Check
3658 then
3659 null;
3661 else
3662 Push_Scope (New_Internal_Entity (E_Block, Current_Scope, Loc, 'B'));
3663 Set_Scope_Is_Transient;
3665 if Sec_Stack then
3666 Set_Uses_Sec_Stack (Current_Scope);
3667 Check_Restriction (No_Secondary_Stack, N);
3668 end if;
3670 Set_Etype (Current_Scope, Standard_Void_Type);
3671 Set_Node_To_Be_Wrapped (Wrap_Node);
3673 if Debug_Flag_W then
3674 Write_Str (" <Transient>");
3675 Write_Eol;
3676 end if;
3677 end if;
3678 end Establish_Transient_Scope;
3680 ----------------------------
3681 -- Expand_Cleanup_Actions --
3682 ----------------------------
3684 procedure Expand_Cleanup_Actions (N : Node_Id) is
3685 Scop : constant Entity_Id := Current_Scope;
3687 Is_Asynchronous_Call : constant Boolean :=
3688 Nkind (N) = N_Block_Statement
3689 and then Is_Asynchronous_Call_Block (N);
3690 Is_Master : constant Boolean :=
3691 Nkind (N) /= N_Entry_Body
3692 and then Is_Task_Master (N);
3693 Is_Protected_Body : constant Boolean :=
3694 Nkind (N) = N_Subprogram_Body
3695 and then Is_Protected_Subprogram_Body (N);
3696 Is_Task_Allocation : constant Boolean :=
3697 Nkind (N) = N_Block_Statement
3698 and then Is_Task_Allocation_Block (N);
3699 Is_Task_Body : constant Boolean :=
3700 Nkind (Original_Node (N)) = N_Task_Body;
3701 Needs_Sec_Stack_Mark : constant Boolean :=
3702 Uses_Sec_Stack (Scop)
3703 and then
3704 not Sec_Stack_Needed_For_Return (Scop)
3705 and then VM_Target = No_VM;
3707 Actions_Required : constant Boolean :=
3708 Requires_Cleanup_Actions (N, True)
3709 or else Is_Asynchronous_Call
3710 or else Is_Master
3711 or else Is_Protected_Body
3712 or else Is_Task_Allocation
3713 or else Is_Task_Body
3714 or else Needs_Sec_Stack_Mark;
3716 HSS : Node_Id := Handled_Statement_Sequence (N);
3717 Loc : Source_Ptr;
3719 procedure Wrap_HSS_In_Block;
3720 -- Move HSS inside a new block along with the original exception
3721 -- handlers. Make the newly generated block the sole statement of HSS.
3723 -----------------------
3724 -- Wrap_HSS_In_Block --
3725 -----------------------
3727 procedure Wrap_HSS_In_Block is
3728 Block : Node_Id;
3729 End_Lab : Node_Id;
3731 begin
3732 -- Preserve end label to provide proper cross-reference information
3734 End_Lab := End_Label (HSS);
3735 Block :=
3736 Make_Block_Statement (Loc,
3737 Handled_Statement_Sequence => HSS);
3739 -- Signal the finalization machinery that this particular block
3740 -- contains the original context.
3742 Set_Is_Finalization_Wrapper (Block);
3744 Set_Handled_Statement_Sequence (N,
3745 Make_Handled_Sequence_Of_Statements (Loc, New_List (Block)));
3746 HSS := Handled_Statement_Sequence (N);
3748 Set_First_Real_Statement (HSS, Block);
3749 Set_End_Label (HSS, End_Lab);
3751 -- Comment needed here, see RH for 1.306 ???
3753 if Nkind (N) = N_Subprogram_Body then
3754 Set_Has_Nested_Block_With_Handler (Scop);
3755 end if;
3756 end Wrap_HSS_In_Block;
3758 -- Start of processing for Expand_Cleanup_Actions
3760 begin
3761 -- The current construct does not need any form of servicing
3763 if not Actions_Required then
3764 return;
3766 -- If the current node is a rewritten task body and the descriptors have
3767 -- not been delayed (due to some nested instantiations), do not generate
3768 -- redundant cleanup actions.
3770 elsif Is_Task_Body
3771 and then Nkind (N) = N_Subprogram_Body
3772 and then not Delay_Subprogram_Descriptors (Corresponding_Spec (N))
3773 then
3774 return;
3775 end if;
3777 declare
3778 Decls : List_Id := Declarations (N);
3779 Fin_Id : Entity_Id;
3780 Mark : Entity_Id := Empty;
3781 New_Decls : List_Id;
3782 Old_Poll : Boolean;
3784 begin
3785 -- If we are generating expanded code for debugging purposes, use the
3786 -- Sloc of the point of insertion for the cleanup code. The Sloc will
3787 -- be updated subsequently to reference the proper line in .dg files.
3788 -- If we are not debugging generated code, use No_Location instead,
3789 -- so that no debug information is generated for the cleanup code.
3790 -- This makes the behavior of the NEXT command in GDB monotonic, and
3791 -- makes the placement of breakpoints more accurate.
3793 if Debug_Generated_Code then
3794 Loc := Sloc (Scop);
3795 else
3796 Loc := No_Location;
3797 end if;
3799 -- Set polling off. The finalization and cleanup code is executed
3800 -- with aborts deferred.
3802 Old_Poll := Polling_Required;
3803 Polling_Required := False;
3805 -- A task activation call has already been built for a task
3806 -- allocation block.
3808 if not Is_Task_Allocation then
3809 Build_Task_Activation_Call (N);
3810 end if;
3812 if Is_Master then
3813 Establish_Task_Master (N);
3814 end if;
3816 New_Decls := New_List;
3818 -- If secondary stack is in use, generate:
3820 -- Mnn : constant Mark_Id := SS_Mark;
3822 -- Suppress calls to SS_Mark and SS_Release if VM_Target, since the
3823 -- secondary stack is never used on a VM.
3825 if Needs_Sec_Stack_Mark then
3826 Mark := Make_Temporary (Loc, 'M');
3828 Append_To (New_Decls,
3829 Make_Object_Declaration (Loc,
3830 Defining_Identifier => Mark,
3831 Object_Definition =>
3832 New_Reference_To (RTE (RE_Mark_Id), Loc),
3833 Expression =>
3834 Make_Function_Call (Loc,
3835 Name => New_Reference_To (RTE (RE_SS_Mark), Loc))));
3837 Set_Uses_Sec_Stack (Scop, False);
3838 end if;
3840 -- If exception handlers are present, wrap the sequence of statements
3841 -- in a block since it is not possible to have exception handlers and
3842 -- an At_End handler in the same construct.
3844 if Present (Exception_Handlers (HSS)) then
3845 Wrap_HSS_In_Block;
3847 -- Ensure that the First_Real_Statement field is set
3849 elsif No (First_Real_Statement (HSS)) then
3850 Set_First_Real_Statement (HSS, First (Statements (HSS)));
3851 end if;
3853 -- Do not move the Activation_Chain declaration in the context of
3854 -- task allocation blocks. Task allocation blocks use _chain in their
3855 -- cleanup handlers and gigi complains if it is declared in the
3856 -- sequence of statements of the scope that declares the handler.
3858 if Is_Task_Allocation then
3859 declare
3860 Chain : constant Entity_Id := Activation_Chain_Entity (N);
3861 Decl : Node_Id;
3863 begin
3864 Decl := First (Decls);
3865 while Nkind (Decl) /= N_Object_Declaration
3866 or else Defining_Identifier (Decl) /= Chain
3867 loop
3868 Next (Decl);
3870 -- A task allocation block should always include a _chain
3871 -- declaration.
3873 pragma Assert (Present (Decl));
3874 end loop;
3876 Remove (Decl);
3877 Prepend_To (New_Decls, Decl);
3878 end;
3879 end if;
3881 -- Ensure the presence of a declaration list in order to successfully
3882 -- append all original statements to it.
3884 if No (Decls) then
3885 Set_Declarations (N, New_List);
3886 Decls := Declarations (N);
3887 end if;
3889 -- Move the declarations into the sequence of statements in order to
3890 -- have them protected by the At_End handler. It may seem weird to
3891 -- put declarations in the sequence of statement but in fact nothing
3892 -- forbids that at the tree level.
3894 Append_List_To (Decls, Statements (HSS));
3895 Set_Statements (HSS, Decls);
3897 -- Reset the Sloc of the handled statement sequence to properly
3898 -- reflect the new initial "statement" in the sequence.
3900 Set_Sloc (HSS, Sloc (First (Decls)));
3902 -- The declarations of finalizer spec and auxiliary variables replace
3903 -- the old declarations that have been moved inward.
3905 Set_Declarations (N, New_Decls);
3906 Analyze_Declarations (New_Decls);
3908 -- Generate finalization calls for all controlled objects appearing
3909 -- in the statements of N. Add context specific cleanup for various
3910 -- constructs.
3912 Build_Finalizer
3913 (N => N,
3914 Clean_Stmts => Build_Cleanup_Statements (N),
3915 Mark_Id => Mark,
3916 Top_Decls => New_Decls,
3917 Defer_Abort => Nkind (Original_Node (N)) = N_Task_Body
3918 or else Is_Master,
3919 Fin_Id => Fin_Id);
3921 if Present (Fin_Id) then
3922 Build_Finalizer_Call (N, Fin_Id);
3923 end if;
3925 -- Restore saved polling mode
3927 Polling_Required := Old_Poll;
3928 end;
3929 end Expand_Cleanup_Actions;
3931 ---------------------------
3932 -- Expand_N_Package_Body --
3933 ---------------------------
3935 -- Add call to Activate_Tasks if body is an activator (actual processing
3936 -- is in chapter 9).
3938 -- Generate subprogram descriptor for elaboration routine
3940 -- Encode entity names in package body
3942 procedure Expand_N_Package_Body (N : Node_Id) is
3943 Spec_Ent : constant Entity_Id := Corresponding_Spec (N);
3944 Fin_Id : Entity_Id;
3946 begin
3947 -- This is done only for non-generic packages
3949 if Ekind (Spec_Ent) = E_Package then
3950 Push_Scope (Corresponding_Spec (N));
3952 -- Build dispatch tables of library level tagged types
3954 if Tagged_Type_Expansion
3955 and then Is_Library_Level_Entity (Spec_Ent)
3956 then
3957 Build_Static_Dispatch_Tables (N);
3958 end if;
3960 Build_Task_Activation_Call (N);
3961 Pop_Scope;
3962 end if;
3964 Set_Elaboration_Flag (N, Corresponding_Spec (N));
3965 Set_In_Package_Body (Spec_Ent, False);
3967 -- Set to encode entity names in package body before gigi is called
3969 Qualify_Entity_Names (N);
3971 if Ekind (Spec_Ent) /= E_Generic_Package then
3972 Build_Finalizer
3973 (N => N,
3974 Clean_Stmts => No_List,
3975 Mark_Id => Empty,
3976 Top_Decls => No_List,
3977 Defer_Abort => False,
3978 Fin_Id => Fin_Id);
3980 if Present (Fin_Id) then
3981 declare
3982 Body_Ent : Node_Id := Defining_Unit_Name (N);
3984 begin
3985 if Nkind (Body_Ent) = N_Defining_Program_Unit_Name then
3986 Body_Ent := Defining_Identifier (Body_Ent);
3987 end if;
3989 Set_Finalizer (Body_Ent, Fin_Id);
3990 end;
3991 end if;
3992 end if;
3993 end Expand_N_Package_Body;
3995 ----------------------------------
3996 -- Expand_N_Package_Declaration --
3997 ----------------------------------
3999 -- Add call to Activate_Tasks if there are tasks declared and the package
4000 -- has no body. Note that in Ada 83 this may result in premature activation
4001 -- of some tasks, given that we cannot tell whether a body will eventually
4002 -- appear.
4004 procedure Expand_N_Package_Declaration (N : Node_Id) is
4005 Id : constant Entity_Id := Defining_Entity (N);
4006 Spec : constant Node_Id := Specification (N);
4007 Decls : List_Id;
4008 Fin_Id : Entity_Id;
4010 No_Body : Boolean := False;
4011 -- True in the case of a package declaration that is a compilation
4012 -- unit and for which no associated body will be compiled in this
4013 -- compilation.
4015 begin
4016 -- Case of a package declaration other than a compilation unit
4018 if Nkind (Parent (N)) /= N_Compilation_Unit then
4019 null;
4021 -- Case of a compilation unit that does not require a body
4023 elsif not Body_Required (Parent (N))
4024 and then not Unit_Requires_Body (Id)
4025 then
4026 No_Body := True;
4028 -- Special case of generating calling stubs for a remote call interface
4029 -- package: even though the package declaration requires one, the body
4030 -- won't be processed in this compilation (so any stubs for RACWs
4031 -- declared in the package must be generated here, along with the spec).
4033 elsif Parent (N) = Cunit (Main_Unit)
4034 and then Is_Remote_Call_Interface (Id)
4035 and then Distribution_Stub_Mode = Generate_Caller_Stub_Body
4036 then
4037 No_Body := True;
4038 end if;
4040 -- For a nested instance, delay processing until freeze point
4042 if Has_Delayed_Freeze (Id)
4043 and then Nkind (Parent (N)) /= N_Compilation_Unit
4044 then
4045 return;
4046 end if;
4048 -- For a package declaration that implies no associated body, generate
4049 -- task activation call and RACW supporting bodies now (since we won't
4050 -- have a specific separate compilation unit for that).
4052 if No_Body then
4053 Push_Scope (Id);
4055 if Has_RACW (Id) then
4057 -- Generate RACW subprogram bodies
4059 Decls := Private_Declarations (Spec);
4061 if No (Decls) then
4062 Decls := Visible_Declarations (Spec);
4063 end if;
4065 if No (Decls) then
4066 Decls := New_List;
4067 Set_Visible_Declarations (Spec, Decls);
4068 end if;
4070 Append_RACW_Bodies (Decls, Id);
4071 Analyze_List (Decls);
4072 end if;
4074 if Present (Activation_Chain_Entity (N)) then
4076 -- Generate task activation call as last step of elaboration
4078 Build_Task_Activation_Call (N);
4079 end if;
4081 Pop_Scope;
4082 end if;
4084 -- Build dispatch tables of library level tagged types
4086 if Tagged_Type_Expansion
4087 and then (Is_Compilation_Unit (Id)
4088 or else (Is_Generic_Instance (Id)
4089 and then Is_Library_Level_Entity (Id)))
4090 then
4091 Build_Static_Dispatch_Tables (N);
4092 end if;
4094 -- Note: it is not necessary to worry about generating a subprogram
4095 -- descriptor, since the only way to get exception handlers into a
4096 -- package spec is to include instantiations, and that would cause
4097 -- generation of subprogram descriptors to be delayed in any case.
4099 -- Set to encode entity names in package spec before gigi is called
4101 Qualify_Entity_Names (N);
4103 if Ekind (Id) /= E_Generic_Package then
4104 Build_Finalizer
4105 (N => N,
4106 Clean_Stmts => No_List,
4107 Mark_Id => Empty,
4108 Top_Decls => No_List,
4109 Defer_Abort => False,
4110 Fin_Id => Fin_Id);
4112 Set_Finalizer (Id, Fin_Id);
4113 end if;
4114 end Expand_N_Package_Declaration;
4116 -----------------------------
4117 -- Find_Node_To_Be_Wrapped --
4118 -----------------------------
4120 function Find_Node_To_Be_Wrapped (N : Node_Id) return Node_Id is
4121 P : Node_Id;
4122 The_Parent : Node_Id;
4124 begin
4125 The_Parent := N;
4126 loop
4127 P := The_Parent;
4128 pragma Assert (P /= Empty);
4129 The_Parent := Parent (P);
4131 case Nkind (The_Parent) is
4133 -- Simple statement can be wrapped
4135 when N_Pragma =>
4136 return The_Parent;
4138 -- Usually assignments are good candidate for wrapping except
4139 -- when they have been generated as part of a controlled aggregate
4140 -- where the wrapping should take place more globally.
4142 when N_Assignment_Statement =>
4143 if No_Ctrl_Actions (The_Parent) then
4144 null;
4145 else
4146 return The_Parent;
4147 end if;
4149 -- An entry call statement is a special case if it occurs in the
4150 -- context of a Timed_Entry_Call. In this case we wrap the entire
4151 -- timed entry call.
4153 when N_Entry_Call_Statement |
4154 N_Procedure_Call_Statement =>
4155 if Nkind (Parent (The_Parent)) = N_Entry_Call_Alternative
4156 and then Nkind_In (Parent (Parent (The_Parent)),
4157 N_Timed_Entry_Call,
4158 N_Conditional_Entry_Call)
4159 then
4160 return Parent (Parent (The_Parent));
4161 else
4162 return The_Parent;
4163 end if;
4165 -- Object declarations are also a boundary for the transient scope
4166 -- even if they are not really wrapped. For further details, see
4167 -- Wrap_Transient_Declaration.
4169 when N_Object_Declaration |
4170 N_Object_Renaming_Declaration |
4171 N_Subtype_Declaration =>
4172 return The_Parent;
4174 -- The expression itself is to be wrapped if its parent is a
4175 -- compound statement or any other statement where the expression
4176 -- is known to be scalar
4178 when N_Accept_Alternative |
4179 N_Attribute_Definition_Clause |
4180 N_Case_Statement |
4181 N_Code_Statement |
4182 N_Delay_Alternative |
4183 N_Delay_Until_Statement |
4184 N_Delay_Relative_Statement |
4185 N_Discriminant_Association |
4186 N_Elsif_Part |
4187 N_Entry_Body_Formal_Part |
4188 N_Exit_Statement |
4189 N_If_Statement |
4190 N_Iteration_Scheme |
4191 N_Terminate_Alternative =>
4192 return P;
4194 when N_Attribute_Reference =>
4196 if Is_Procedure_Attribute_Name
4197 (Attribute_Name (The_Parent))
4198 then
4199 return The_Parent;
4200 end if;
4202 -- A raise statement can be wrapped. This will arise when the
4203 -- expression in a raise_with_expression uses the secondary
4204 -- stack, for example.
4206 when N_Raise_Statement =>
4207 return The_Parent;
4209 -- If the expression is within the iteration scheme of a loop,
4210 -- we must create a declaration for it, followed by an assignment
4211 -- in order to have a usable statement to wrap.
4213 when N_Loop_Parameter_Specification =>
4214 return Parent (The_Parent);
4216 -- The following nodes contains "dummy calls" which don't need to
4217 -- be wrapped.
4219 when N_Parameter_Specification |
4220 N_Discriminant_Specification |
4221 N_Component_Declaration =>
4222 return Empty;
4224 -- The return statement is not to be wrapped when the function
4225 -- itself needs wrapping at the outer-level
4227 when N_Simple_Return_Statement =>
4228 declare
4229 Applies_To : constant Entity_Id :=
4230 Return_Applies_To
4231 (Return_Statement_Entity (The_Parent));
4232 Return_Type : constant Entity_Id := Etype (Applies_To);
4233 begin
4234 if Requires_Transient_Scope (Return_Type) then
4235 return Empty;
4236 else
4237 return The_Parent;
4238 end if;
4239 end;
4241 -- If we leave a scope without having been able to find a node to
4242 -- wrap, something is going wrong but this can happen in error
4243 -- situation that are not detected yet (such as a dynamic string
4244 -- in a pragma export)
4246 when N_Subprogram_Body |
4247 N_Package_Declaration |
4248 N_Package_Body |
4249 N_Block_Statement =>
4250 return Empty;
4252 -- Otherwise continue the search
4254 when others =>
4255 null;
4256 end case;
4257 end loop;
4258 end Find_Node_To_Be_Wrapped;
4260 -------------------------------------
4261 -- Get_Global_Pool_For_Access_Type --
4262 -------------------------------------
4264 function Get_Global_Pool_For_Access_Type (T : Entity_Id) return Entity_Id is
4265 begin
4266 -- Access types whose size is smaller than System.Address size can exist
4267 -- only on VMS. We can't use the usual global pool which returns an
4268 -- object of type Address as truncation will make it invalid. To handle
4269 -- this case, VMS has a dedicated global pool that returns addresses
4270 -- that fit into 32 bit accesses.
4272 if Opt.True_VMS_Target and then Esize (T) = 32 then
4273 return RTE (RE_Global_Pool_32_Object);
4274 else
4275 return RTE (RE_Global_Pool_Object);
4276 end if;
4277 end Get_Global_Pool_For_Access_Type;
4279 ----------------------------------
4280 -- Has_New_Controlled_Component --
4281 ----------------------------------
4283 function Has_New_Controlled_Component (E : Entity_Id) return Boolean is
4284 Comp : Entity_Id;
4286 begin
4287 if not Is_Tagged_Type (E) then
4288 return Has_Controlled_Component (E);
4289 elsif not Is_Derived_Type (E) then
4290 return Has_Controlled_Component (E);
4291 end if;
4293 Comp := First_Component (E);
4294 while Present (Comp) loop
4295 if Chars (Comp) = Name_uParent then
4296 null;
4298 elsif Scope (Original_Record_Component (Comp)) = E
4299 and then Needs_Finalization (Etype (Comp))
4300 then
4301 return True;
4302 end if;
4304 Next_Component (Comp);
4305 end loop;
4307 return False;
4308 end Has_New_Controlled_Component;
4310 ---------------------------------
4311 -- Has_Simple_Protected_Object --
4312 ---------------------------------
4314 function Has_Simple_Protected_Object (T : Entity_Id) return Boolean is
4315 begin
4316 if Has_Task (T) then
4317 return False;
4319 elsif Is_Simple_Protected_Type (T) then
4320 return True;
4322 elsif Is_Array_Type (T) then
4323 return Has_Simple_Protected_Object (Component_Type (T));
4325 elsif Is_Record_Type (T) then
4326 declare
4327 Comp : Entity_Id;
4329 begin
4330 Comp := First_Component (T);
4331 while Present (Comp) loop
4332 if Has_Simple_Protected_Object (Etype (Comp)) then
4333 return True;
4334 end if;
4336 Next_Component (Comp);
4337 end loop;
4339 return False;
4340 end;
4342 else
4343 return False;
4344 end if;
4345 end Has_Simple_Protected_Object;
4347 ------------------------------------
4348 -- Insert_Actions_In_Scope_Around --
4349 ------------------------------------
4351 procedure Insert_Actions_In_Scope_Around (N : Node_Id) is
4352 After : constant List_Id :=
4353 Scope_Stack.Table (Scope_Stack.Last).Actions_To_Be_Wrapped_After;
4354 Before : constant List_Id :=
4355 Scope_Stack.Table (Scope_Stack.Last).Actions_To_Be_Wrapped_Before;
4356 -- Note: We used to use renamings of Scope_Stack.Table (Scope_Stack.
4357 -- Last), but this was incorrect as Process_Transient_Object may
4358 -- introduce new scopes and cause a reallocation of Scope_Stack.Table.
4360 procedure Process_Transient_Objects
4361 (First_Object : Node_Id;
4362 Last_Object : Node_Id;
4363 Related_Node : Node_Id);
4364 -- First_Object and Last_Object define a list which contains potential
4365 -- controlled transient objects. Finalization flags are inserted before
4366 -- First_Object and finalization calls are inserted after Last_Object.
4367 -- Related_Node is the node for which transient objects have been
4368 -- created.
4370 -------------------------------
4371 -- Process_Transient_Objects --
4372 -------------------------------
4374 procedure Process_Transient_Objects
4375 (First_Object : Node_Id;
4376 Last_Object : Node_Id;
4377 Related_Node : Node_Id)
4379 function Requires_Hooking return Boolean;
4380 -- Determine whether the context requires transient variable export
4381 -- to the outer finalizer. This scenario arises when the context may
4382 -- raise an exception.
4384 ----------------------
4385 -- Requires_Hooking --
4386 ----------------------
4388 function Requires_Hooking return Boolean is
4389 begin
4390 -- The context is either a procedure or function call or an object
4391 -- declaration initialized by a function call. Note that in the
4392 -- latter case, a function call that returns on the secondary
4393 -- stack is usually rewritten into something else. Its proper
4394 -- detection requires examination of the original initialization
4395 -- expression.
4397 return Nkind (N) in N_Subprogram_Call
4398 or else (Nkind (N) = N_Object_Declaration
4399 and then Nkind (Original_Node (Expression (N))) =
4400 N_Function_Call);
4401 end Requires_Hooking;
4403 -- Local variables
4405 Must_Hook : constant Boolean := Requires_Hooking;
4406 Built : Boolean := False;
4407 Desig_Typ : Entity_Id;
4408 Fin_Block : Node_Id;
4409 Fin_Data : Finalization_Exception_Data;
4410 Fin_Decls : List_Id;
4411 Last_Fin : Node_Id := Empty;
4412 Loc : Source_Ptr;
4413 Obj_Id : Entity_Id;
4414 Obj_Ref : Node_Id;
4415 Obj_Typ : Entity_Id;
4416 Prev_Fin : Node_Id := Empty;
4417 Stmt : Node_Id;
4418 Stmts : List_Id;
4419 Temp_Id : Entity_Id;
4421 -- Start of processing for Process_Transient_Objects
4423 begin
4424 -- Examine all objects in the list First_Object .. Last_Object
4426 Stmt := First_Object;
4427 while Present (Stmt) loop
4428 if Nkind (Stmt) = N_Object_Declaration
4429 and then Analyzed (Stmt)
4430 and then Is_Finalizable_Transient (Stmt, N)
4432 -- Do not process the node to be wrapped since it will be
4433 -- handled by the enclosing finalizer.
4435 and then Stmt /= Related_Node
4436 then
4437 Loc := Sloc (Stmt);
4438 Obj_Id := Defining_Identifier (Stmt);
4439 Obj_Typ := Base_Type (Etype (Obj_Id));
4440 Desig_Typ := Obj_Typ;
4442 Set_Is_Processed_Transient (Obj_Id);
4444 -- Handle access types
4446 if Is_Access_Type (Desig_Typ) then
4447 Desig_Typ := Available_View (Designated_Type (Desig_Typ));
4448 end if;
4450 -- Create the necessary entities and declarations the first
4451 -- time around.
4453 if not Built then
4454 Fin_Decls := New_List;
4456 Build_Object_Declarations (Fin_Data, Fin_Decls, Loc);
4458 Built := True;
4459 end if;
4461 -- Transient variables associated with subprogram calls need
4462 -- extra processing. These variables are usually created right
4463 -- before the call and finalized immediately after the call.
4464 -- If an exception occurs during the call, the clean up code
4465 -- is skipped due to the sudden change in control and the
4466 -- transient is never finalized.
4468 -- To handle this case, such variables are "exported" to the
4469 -- enclosing sequence of statements where their corresponding
4470 -- "hooks" are picked up by the finalization machinery.
4472 if Must_Hook then
4473 declare
4474 Expr : Node_Id;
4475 Ptr_Id : Entity_Id;
4477 begin
4478 -- Step 1: Create an access type which provides a
4479 -- reference to the transient object. Generate:
4481 -- Ann : access [all] <Desig_Typ>;
4483 Ptr_Id := Make_Temporary (Loc, 'A');
4485 Insert_Action (Stmt,
4486 Make_Full_Type_Declaration (Loc,
4487 Defining_Identifier => Ptr_Id,
4488 Type_Definition =>
4489 Make_Access_To_Object_Definition (Loc,
4490 All_Present =>
4491 Ekind (Obj_Typ) = E_General_Access_Type,
4492 Subtype_Indication =>
4493 New_Reference_To (Desig_Typ, Loc))));
4495 -- Step 2: Create a temporary which acts as a hook to
4496 -- the transient object. Generate:
4498 -- Temp : Ptr_Id := null;
4500 Temp_Id := Make_Temporary (Loc, 'T');
4502 Insert_Action (Stmt,
4503 Make_Object_Declaration (Loc,
4504 Defining_Identifier => Temp_Id,
4505 Object_Definition =>
4506 New_Reference_To (Ptr_Id, Loc)));
4508 -- Mark the temporary as a transient hook. This signals
4509 -- the machinery in Build_Finalizer to recognize this
4510 -- special case.
4512 Set_Status_Flag_Or_Transient_Decl (Temp_Id, Stmt);
4514 -- Step 3: Hook the transient object to the temporary
4516 if Is_Access_Type (Obj_Typ) then
4517 Expr :=
4518 Convert_To (Ptr_Id, New_Reference_To (Obj_Id, Loc));
4519 else
4520 Expr :=
4521 Make_Attribute_Reference (Loc,
4522 Prefix => New_Reference_To (Obj_Id, Loc),
4523 Attribute_Name => Name_Unrestricted_Access);
4524 end if;
4526 -- Generate:
4527 -- Temp := Ptr_Id (Obj_Id);
4528 -- <or>
4529 -- Temp := Obj_Id'Unrestricted_Access;
4531 Insert_After_And_Analyze (Stmt,
4532 Make_Assignment_Statement (Loc,
4533 Name => New_Reference_To (Temp_Id, Loc),
4534 Expression => Expr));
4535 end;
4536 end if;
4538 Stmts := New_List;
4540 -- The transient object is about to be finalized by the clean
4541 -- up code following the subprogram call. In order to avoid
4542 -- double finalization, clear the hook.
4544 -- Generate:
4545 -- Temp := null;
4547 if Must_Hook then
4548 Append_To (Stmts,
4549 Make_Assignment_Statement (Loc,
4550 Name => New_Reference_To (Temp_Id, Loc),
4551 Expression => Make_Null (Loc)));
4552 end if;
4554 -- Generate:
4555 -- [Deep_]Finalize (Obj_Ref);
4557 Obj_Ref := New_Reference_To (Obj_Id, Loc);
4559 if Is_Access_Type (Obj_Typ) then
4560 Obj_Ref := Make_Explicit_Dereference (Loc, Obj_Ref);
4561 end if;
4563 Append_To (Stmts,
4564 Make_Final_Call (Obj_Ref => Obj_Ref, Typ => Desig_Typ));
4566 -- Generate:
4567 -- [Temp := null;]
4568 -- begin
4569 -- [Deep_]Finalize (Obj_Ref);
4571 -- exception
4572 -- when others =>
4573 -- if not Raised then
4574 -- Raised := True;
4575 -- Save_Occurrence
4576 -- (Enn, Get_Current_Excep.all.all);
4577 -- end if;
4578 -- end;
4580 Fin_Block :=
4581 Make_Block_Statement (Loc,
4582 Handled_Statement_Sequence =>
4583 Make_Handled_Sequence_Of_Statements (Loc,
4584 Statements => Stmts,
4585 Exception_Handlers => New_List (
4586 Build_Exception_Handler (Fin_Data))));
4588 -- The single raise statement must be inserted after all the
4589 -- finalization blocks, and we put everything into a wrapper
4590 -- block to clearly expose the construct to the back-end.
4592 if Present (Prev_Fin) then
4593 Insert_Before_And_Analyze (Prev_Fin, Fin_Block);
4594 else
4595 Insert_After_And_Analyze (Last_Object,
4596 Make_Block_Statement (Loc,
4597 Declarations => Fin_Decls,
4598 Handled_Statement_Sequence =>
4599 Make_Handled_Sequence_Of_Statements (Loc,
4600 Statements => New_List (Fin_Block))));
4602 Last_Fin := Fin_Block;
4603 end if;
4605 Prev_Fin := Fin_Block;
4606 end if;
4608 -- Terminate the scan after the last object has been processed to
4609 -- avoid touching unrelated code.
4611 if Stmt = Last_Object then
4612 exit;
4613 end if;
4615 Next (Stmt);
4616 end loop;
4618 -- Generate:
4619 -- if Raised and then not Abort then
4620 -- Raise_From_Controlled_Operation (E);
4621 -- end if;
4623 if Built
4624 and then Present (Last_Fin)
4625 then
4626 Insert_After_And_Analyze (Last_Fin,
4627 Build_Raise_Statement (Fin_Data));
4628 end if;
4629 end Process_Transient_Objects;
4631 -- Start of processing for Insert_Actions_In_Scope_Around
4633 begin
4634 if No (Before) and then No (After) then
4635 return;
4636 end if;
4638 declare
4639 Node_To_Wrap : constant Node_Id := Node_To_Be_Wrapped;
4640 First_Obj : Node_Id;
4641 Last_Obj : Node_Id;
4642 Target : Node_Id;
4644 begin
4645 -- If the node to be wrapped is the trigger of an asynchronous
4646 -- select, it is not part of a statement list. The actions must be
4647 -- inserted before the select itself, which is part of some list of
4648 -- statements. Note that the triggering alternative includes the
4649 -- triggering statement and an optional statement list. If the node
4650 -- to be wrapped is part of that list, the normal insertion applies.
4652 if Nkind (Parent (Node_To_Wrap)) = N_Triggering_Alternative
4653 and then not Is_List_Member (Node_To_Wrap)
4654 then
4655 Target := Parent (Parent (Node_To_Wrap));
4656 else
4657 Target := N;
4658 end if;
4660 First_Obj := Target;
4661 Last_Obj := Target;
4663 -- Add all actions associated with a transient scope into the main
4664 -- tree. There are several scenarios here:
4666 -- +--- Before ----+ +----- After ---+
4667 -- 1) First_Obj ....... Target ........ Last_Obj
4669 -- 2) First_Obj ....... Target
4671 -- 3) Target ........ Last_Obj
4673 if Present (Before) then
4675 -- Flag declarations are inserted before the first object
4677 First_Obj := First (Before);
4679 Insert_List_Before (Target, Before);
4680 end if;
4682 if Present (After) then
4684 -- Finalization calls are inserted after the last object
4686 Last_Obj := Last (After);
4688 Insert_List_After (Target, After);
4689 end if;
4691 -- Check for transient controlled objects associated with Target and
4692 -- generate the appropriate finalization actions for them.
4694 Process_Transient_Objects
4695 (First_Object => First_Obj,
4696 Last_Object => Last_Obj,
4697 Related_Node => Target);
4699 -- Reset the action lists
4701 if Present (Before) then
4702 Scope_Stack.Table (Scope_Stack.Last).
4703 Actions_To_Be_Wrapped_Before := No_List;
4704 end if;
4706 if Present (After) then
4707 Scope_Stack.Table (Scope_Stack.Last).
4708 Actions_To_Be_Wrapped_After := No_List;
4709 end if;
4710 end;
4711 end Insert_Actions_In_Scope_Around;
4713 ------------------------------
4714 -- Is_Simple_Protected_Type --
4715 ------------------------------
4717 function Is_Simple_Protected_Type (T : Entity_Id) return Boolean is
4718 begin
4719 return
4720 Is_Protected_Type (T)
4721 and then not Uses_Lock_Free (T)
4722 and then not Has_Entries (T)
4723 and then Is_RTE (Find_Protection_Type (T), RE_Protection);
4724 end Is_Simple_Protected_Type;
4726 -----------------------
4727 -- Make_Adjust_Call --
4728 -----------------------
4730 function Make_Adjust_Call
4731 (Obj_Ref : Node_Id;
4732 Typ : Entity_Id;
4733 For_Parent : Boolean := False) return Node_Id
4735 Loc : constant Source_Ptr := Sloc (Obj_Ref);
4736 Adj_Id : Entity_Id := Empty;
4737 Ref : Node_Id := Obj_Ref;
4738 Utyp : Entity_Id;
4740 begin
4741 -- Recover the proper type which contains Deep_Adjust
4743 if Is_Class_Wide_Type (Typ) then
4744 Utyp := Root_Type (Typ);
4745 else
4746 Utyp := Typ;
4747 end if;
4749 Utyp := Underlying_Type (Base_Type (Utyp));
4750 Set_Assignment_OK (Ref);
4752 -- Deal with non-tagged derivation of private views
4754 if Is_Untagged_Derivation (Typ) then
4755 Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
4756 Ref := Unchecked_Convert_To (Utyp, Ref);
4757 Set_Assignment_OK (Ref);
4758 end if;
4760 -- When dealing with the completion of a private type, use the base
4761 -- type instead.
4763 if Utyp /= Base_Type (Utyp) then
4764 pragma Assert (Is_Private_Type (Typ));
4766 Utyp := Base_Type (Utyp);
4767 Ref := Unchecked_Convert_To (Utyp, Ref);
4768 end if;
4770 -- Select the appropriate version of adjust
4772 if For_Parent then
4773 if Has_Controlled_Component (Utyp) then
4774 Adj_Id := Find_Prim_Op (Utyp, TSS_Deep_Adjust);
4775 end if;
4777 -- Class-wide types, interfaces and types with controlled components
4779 elsif Is_Class_Wide_Type (Typ)
4780 or else Is_Interface (Typ)
4781 or else Has_Controlled_Component (Utyp)
4782 then
4783 if Is_Tagged_Type (Utyp) then
4784 Adj_Id := Find_Prim_Op (Utyp, TSS_Deep_Adjust);
4785 else
4786 Adj_Id := TSS (Utyp, TSS_Deep_Adjust);
4787 end if;
4789 -- Derivations from [Limited_]Controlled
4791 elsif Is_Controlled (Utyp) then
4792 if Has_Controlled_Component (Utyp) then
4793 Adj_Id := Find_Prim_Op (Utyp, TSS_Deep_Adjust);
4794 else
4795 Adj_Id := Find_Prim_Op (Utyp, Name_Of (Adjust_Case));
4796 end if;
4798 -- Tagged types
4800 elsif Is_Tagged_Type (Utyp) then
4801 Adj_Id := Find_Prim_Op (Utyp, TSS_Deep_Adjust);
4803 else
4804 raise Program_Error;
4805 end if;
4807 if Present (Adj_Id) then
4809 -- If the object is unanalyzed, set its expected type for use in
4810 -- Convert_View in case an additional conversion is needed.
4812 if No (Etype (Ref))
4813 and then Nkind (Ref) /= N_Unchecked_Type_Conversion
4814 then
4815 Set_Etype (Ref, Typ);
4816 end if;
4818 -- The object reference may need another conversion depending on the
4819 -- type of the formal and that of the actual.
4821 if not Is_Class_Wide_Type (Typ) then
4822 Ref := Convert_View (Adj_Id, Ref);
4823 end if;
4825 return Make_Call (Loc, Adj_Id, New_Copy_Tree (Ref), For_Parent);
4826 else
4827 return Empty;
4828 end if;
4829 end Make_Adjust_Call;
4831 ----------------------
4832 -- Make_Attach_Call --
4833 ----------------------
4835 function Make_Attach_Call
4836 (Obj_Ref : Node_Id;
4837 Ptr_Typ : Entity_Id) return Node_Id
4839 pragma Assert (VM_Target /= No_VM);
4841 Loc : constant Source_Ptr := Sloc (Obj_Ref);
4842 begin
4843 return
4844 Make_Procedure_Call_Statement (Loc,
4845 Name =>
4846 New_Reference_To (RTE (RE_Attach), Loc),
4847 Parameter_Associations => New_List (
4848 New_Reference_To (Finalization_Master (Ptr_Typ), Loc),
4849 Unchecked_Convert_To (RTE (RE_Root_Controlled_Ptr), Obj_Ref)));
4850 end Make_Attach_Call;
4852 ----------------------
4853 -- Make_Detach_Call --
4854 ----------------------
4856 function Make_Detach_Call (Obj_Ref : Node_Id) return Node_Id is
4857 Loc : constant Source_Ptr := Sloc (Obj_Ref);
4859 begin
4860 return
4861 Make_Procedure_Call_Statement (Loc,
4862 Name =>
4863 New_Reference_To (RTE (RE_Detach), Loc),
4864 Parameter_Associations => New_List (
4865 Unchecked_Convert_To (RTE (RE_Root_Controlled_Ptr), Obj_Ref)));
4866 end Make_Detach_Call;
4868 ---------------
4869 -- Make_Call --
4870 ---------------
4872 function Make_Call
4873 (Loc : Source_Ptr;
4874 Proc_Id : Entity_Id;
4875 Param : Node_Id;
4876 For_Parent : Boolean := False) return Node_Id
4878 Params : constant List_Id := New_List (Param);
4880 begin
4881 -- When creating a call to Deep_Finalize for a _parent field of a
4882 -- derived type, disable the invocation of the nested Finalize by giving
4883 -- the corresponding flag a False value.
4885 if For_Parent then
4886 Append_To (Params, New_Reference_To (Standard_False, Loc));
4887 end if;
4889 return
4890 Make_Procedure_Call_Statement (Loc,
4891 Name => New_Reference_To (Proc_Id, Loc),
4892 Parameter_Associations => Params);
4893 end Make_Call;
4895 --------------------------
4896 -- Make_Deep_Array_Body --
4897 --------------------------
4899 function Make_Deep_Array_Body
4900 (Prim : Final_Primitives;
4901 Typ : Entity_Id) return List_Id
4903 function Build_Adjust_Or_Finalize_Statements
4904 (Typ : Entity_Id) return List_Id;
4905 -- Create the statements necessary to adjust or finalize an array of
4906 -- controlled elements. Generate:
4908 -- declare
4909 -- Abort : constant Boolean := Triggered_By_Abort;
4910 -- <or>
4911 -- Abort : constant Boolean := False; -- no abort
4913 -- E : Exception_Occurrence;
4914 -- Raised : Boolean := False;
4916 -- begin
4917 -- for J1 in [reverse] Typ'First (1) .. Typ'Last (1) loop
4918 -- ^-- in the finalization case
4919 -- ...
4920 -- for Jn in [reverse] Typ'First (n) .. Typ'Last (n) loop
4921 -- begin
4922 -- [Deep_]Adjust / Finalize (V (J1, ..., Jn));
4924 -- exception
4925 -- when others =>
4926 -- if not Raised then
4927 -- Raised := True;
4928 -- Save_Occurrence (E, Get_Current_Excep.all.all);
4929 -- end if;
4930 -- end;
4931 -- end loop;
4932 -- ...
4933 -- end loop;
4935 -- if Raised and then not Abort then
4936 -- Raise_From_Controlled_Operation (E);
4937 -- end if;
4938 -- end;
4940 function Build_Initialize_Statements (Typ : Entity_Id) return List_Id;
4941 -- Create the statements necessary to initialize an array of controlled
4942 -- elements. Include a mechanism to carry out partial finalization if an
4943 -- exception occurs. Generate:
4945 -- declare
4946 -- Counter : Integer := 0;
4948 -- begin
4949 -- for J1 in V'Range (1) loop
4950 -- ...
4951 -- for JN in V'Range (N) loop
4952 -- begin
4953 -- [Deep_]Initialize (V (J1, ..., JN));
4955 -- Counter := Counter + 1;
4957 -- exception
4958 -- when others =>
4959 -- declare
4960 -- Abort : constant Boolean := Triggered_By_Abort;
4961 -- <or>
4962 -- Abort : constant Boolean := False; -- no abort
4963 -- E : Exception_Occurence;
4964 -- Raised : Boolean := False;
4966 -- begin
4967 -- Counter :=
4968 -- V'Length (1) *
4969 -- V'Length (2) *
4970 -- ...
4971 -- V'Length (N) - Counter;
4973 -- for F1 in reverse V'Range (1) loop
4974 -- ...
4975 -- for FN in reverse V'Range (N) loop
4976 -- if Counter > 0 then
4977 -- Counter := Counter - 1;
4978 -- else
4979 -- begin
4980 -- [Deep_]Finalize (V (F1, ..., FN));
4982 -- exception
4983 -- when others =>
4984 -- if not Raised then
4985 -- Raised := True;
4986 -- Save_Occurrence (E,
4987 -- Get_Current_Excep.all.all);
4988 -- end if;
4989 -- end;
4990 -- end if;
4991 -- end loop;
4992 -- ...
4993 -- end loop;
4994 -- end;
4996 -- if Raised and then not Abort then
4997 -- Raise_From_Controlled_Operation (E);
4998 -- end if;
5000 -- raise;
5001 -- end;
5002 -- end loop;
5003 -- end loop;
5004 -- end;
5006 function New_References_To
5007 (L : List_Id;
5008 Loc : Source_Ptr) return List_Id;
5009 -- Given a list of defining identifiers, return a list of references to
5010 -- the original identifiers, in the same order as they appear.
5012 -----------------------------------------
5013 -- Build_Adjust_Or_Finalize_Statements --
5014 -----------------------------------------
5016 function Build_Adjust_Or_Finalize_Statements
5017 (Typ : Entity_Id) return List_Id
5019 Comp_Typ : constant Entity_Id := Component_Type (Typ);
5020 Index_List : constant List_Id := New_List;
5021 Loc : constant Source_Ptr := Sloc (Typ);
5022 Num_Dims : constant Int := Number_Dimensions (Typ);
5023 Finalizer_Decls : List_Id := No_List;
5024 Finalizer_Data : Finalization_Exception_Data;
5025 Call : Node_Id;
5026 Comp_Ref : Node_Id;
5027 Core_Loop : Node_Id;
5028 Dim : Int;
5029 J : Entity_Id;
5030 Loop_Id : Entity_Id;
5031 Stmts : List_Id;
5033 Exceptions_OK : constant Boolean :=
5034 not Restriction_Active (No_Exception_Propagation);
5036 procedure Build_Indices;
5037 -- Generate the indices used in the dimension loops
5039 -------------------
5040 -- Build_Indices --
5041 -------------------
5043 procedure Build_Indices is
5044 begin
5045 -- Generate the following identifiers:
5046 -- Jnn - for initialization
5048 for Dim in 1 .. Num_Dims loop
5049 Append_To (Index_List,
5050 Make_Defining_Identifier (Loc, New_External_Name ('J', Dim)));
5051 end loop;
5052 end Build_Indices;
5054 -- Start of processing for Build_Adjust_Or_Finalize_Statements
5056 begin
5057 Finalizer_Decls := New_List;
5059 Build_Indices;
5060 Build_Object_Declarations (Finalizer_Data, Finalizer_Decls, Loc);
5062 Comp_Ref :=
5063 Make_Indexed_Component (Loc,
5064 Prefix => Make_Identifier (Loc, Name_V),
5065 Expressions => New_References_To (Index_List, Loc));
5066 Set_Etype (Comp_Ref, Comp_Typ);
5068 -- Generate:
5069 -- [Deep_]Adjust (V (J1, ..., JN))
5071 if Prim = Adjust_Case then
5072 Call := Make_Adjust_Call (Obj_Ref => Comp_Ref, Typ => Comp_Typ);
5074 -- Generate:
5075 -- [Deep_]Finalize (V (J1, ..., JN))
5077 else pragma Assert (Prim = Finalize_Case);
5078 Call := Make_Final_Call (Obj_Ref => Comp_Ref, Typ => Comp_Typ);
5079 end if;
5081 -- Generate the block which houses the adjust or finalize call:
5083 -- <adjust or finalize call>; -- No_Exception_Propagation
5085 -- begin -- Exception handlers allowed
5086 -- <adjust or finalize call>
5088 -- exception
5089 -- when others =>
5090 -- if not Raised then
5091 -- Raised := True;
5092 -- Save_Occurrence (E, Get_Current_Excep.all.all);
5093 -- end if;
5094 -- end;
5096 if Exceptions_OK then
5097 Core_Loop :=
5098 Make_Block_Statement (Loc,
5099 Handled_Statement_Sequence =>
5100 Make_Handled_Sequence_Of_Statements (Loc,
5101 Statements => New_List (Call),
5102 Exception_Handlers => New_List (
5103 Build_Exception_Handler (Finalizer_Data))));
5104 else
5105 Core_Loop := Call;
5106 end if;
5108 -- Generate the dimension loops starting from the innermost one
5110 -- for Jnn in [reverse] V'Range (Dim) loop
5111 -- <core loop>
5112 -- end loop;
5114 J := Last (Index_List);
5115 Dim := Num_Dims;
5116 while Present (J) and then Dim > 0 loop
5117 Loop_Id := J;
5118 Prev (J);
5119 Remove (Loop_Id);
5121 Core_Loop :=
5122 Make_Loop_Statement (Loc,
5123 Iteration_Scheme =>
5124 Make_Iteration_Scheme (Loc,
5125 Loop_Parameter_Specification =>
5126 Make_Loop_Parameter_Specification (Loc,
5127 Defining_Identifier => Loop_Id,
5128 Discrete_Subtype_Definition =>
5129 Make_Attribute_Reference (Loc,
5130 Prefix => Make_Identifier (Loc, Name_V),
5131 Attribute_Name => Name_Range,
5132 Expressions => New_List (
5133 Make_Integer_Literal (Loc, Dim))),
5135 Reverse_Present => Prim = Finalize_Case)),
5137 Statements => New_List (Core_Loop),
5138 End_Label => Empty);
5140 Dim := Dim - 1;
5141 end loop;
5143 -- Generate the block which contains the core loop, the declarations
5144 -- of the abort flag, the exception occurrence, the raised flag and
5145 -- the conditional raise:
5147 -- declare
5148 -- Abort : constant Boolean := Triggered_By_Abort;
5149 -- <or>
5150 -- Abort : constant Boolean := False; -- no abort
5152 -- E : Exception_Occurrence;
5153 -- Raised : Boolean := False;
5155 -- begin
5156 -- <core loop>
5158 -- if Raised and then not Abort then -- Expection handlers OK
5159 -- Raise_From_Controlled_Operation (E);
5160 -- end if;
5161 -- end;
5163 Stmts := New_List (Core_Loop);
5165 if Exceptions_OK then
5166 Append_To (Stmts,
5167 Build_Raise_Statement (Finalizer_Data));
5168 end if;
5170 return
5171 New_List (
5172 Make_Block_Statement (Loc,
5173 Declarations =>
5174 Finalizer_Decls,
5175 Handled_Statement_Sequence =>
5176 Make_Handled_Sequence_Of_Statements (Loc, Stmts)));
5177 end Build_Adjust_Or_Finalize_Statements;
5179 ---------------------------------
5180 -- Build_Initialize_Statements --
5181 ---------------------------------
5183 function Build_Initialize_Statements (Typ : Entity_Id) return List_Id is
5184 Comp_Typ : constant Entity_Id := Component_Type (Typ);
5185 Final_List : constant List_Id := New_List;
5186 Index_List : constant List_Id := New_List;
5187 Loc : constant Source_Ptr := Sloc (Typ);
5188 Num_Dims : constant Int := Number_Dimensions (Typ);
5189 Counter_Id : Entity_Id;
5190 Dim : Int;
5191 F : Node_Id;
5192 Fin_Stmt : Node_Id;
5193 Final_Block : Node_Id;
5194 Final_Loop : Node_Id;
5195 Finalizer_Data : Finalization_Exception_Data;
5196 Finalizer_Decls : List_Id := No_List;
5197 Init_Loop : Node_Id;
5198 J : Node_Id;
5199 Loop_Id : Node_Id;
5200 Stmts : List_Id;
5202 Exceptions_OK : constant Boolean :=
5203 not Restriction_Active (No_Exception_Propagation);
5205 function Build_Counter_Assignment return Node_Id;
5206 -- Generate the following assignment:
5207 -- Counter := V'Length (1) *
5208 -- ...
5209 -- V'Length (N) - Counter;
5211 function Build_Finalization_Call return Node_Id;
5212 -- Generate a deep finalization call for an array element
5214 procedure Build_Indices;
5215 -- Generate the initialization and finalization indices used in the
5216 -- dimension loops.
5218 function Build_Initialization_Call return Node_Id;
5219 -- Generate a deep initialization call for an array element
5221 ------------------------------
5222 -- Build_Counter_Assignment --
5223 ------------------------------
5225 function Build_Counter_Assignment return Node_Id is
5226 Dim : Int;
5227 Expr : Node_Id;
5229 begin
5230 -- Start from the first dimension and generate:
5231 -- V'Length (1)
5233 Dim := 1;
5234 Expr :=
5235 Make_Attribute_Reference (Loc,
5236 Prefix => Make_Identifier (Loc, Name_V),
5237 Attribute_Name => Name_Length,
5238 Expressions => New_List (Make_Integer_Literal (Loc, Dim)));
5240 -- Process the rest of the dimensions, generate:
5241 -- Expr * V'Length (N)
5243 Dim := Dim + 1;
5244 while Dim <= Num_Dims loop
5245 Expr :=
5246 Make_Op_Multiply (Loc,
5247 Left_Opnd => Expr,
5248 Right_Opnd =>
5249 Make_Attribute_Reference (Loc,
5250 Prefix => Make_Identifier (Loc, Name_V),
5251 Attribute_Name => Name_Length,
5252 Expressions => New_List (
5253 Make_Integer_Literal (Loc, Dim))));
5255 Dim := Dim + 1;
5256 end loop;
5258 -- Generate:
5259 -- Counter := Expr - Counter;
5261 return
5262 Make_Assignment_Statement (Loc,
5263 Name => New_Reference_To (Counter_Id, Loc),
5264 Expression =>
5265 Make_Op_Subtract (Loc,
5266 Left_Opnd => Expr,
5267 Right_Opnd => New_Reference_To (Counter_Id, Loc)));
5268 end Build_Counter_Assignment;
5270 -----------------------------
5271 -- Build_Finalization_Call --
5272 -----------------------------
5274 function Build_Finalization_Call return Node_Id is
5275 Comp_Ref : constant Node_Id :=
5276 Make_Indexed_Component (Loc,
5277 Prefix => Make_Identifier (Loc, Name_V),
5278 Expressions => New_References_To (Final_List, Loc));
5280 begin
5281 Set_Etype (Comp_Ref, Comp_Typ);
5283 -- Generate:
5284 -- [Deep_]Finalize (V);
5286 return Make_Final_Call (Obj_Ref => Comp_Ref, Typ => Comp_Typ);
5287 end Build_Finalization_Call;
5289 -------------------
5290 -- Build_Indices --
5291 -------------------
5293 procedure Build_Indices is
5294 begin
5295 -- Generate the following identifiers:
5296 -- Jnn - for initialization
5297 -- Fnn - for finalization
5299 for Dim in 1 .. Num_Dims loop
5300 Append_To (Index_List,
5301 Make_Defining_Identifier (Loc, New_External_Name ('J', Dim)));
5303 Append_To (Final_List,
5304 Make_Defining_Identifier (Loc, New_External_Name ('F', Dim)));
5305 end loop;
5306 end Build_Indices;
5308 -------------------------------
5309 -- Build_Initialization_Call --
5310 -------------------------------
5312 function Build_Initialization_Call return Node_Id is
5313 Comp_Ref : constant Node_Id :=
5314 Make_Indexed_Component (Loc,
5315 Prefix => Make_Identifier (Loc, Name_V),
5316 Expressions => New_References_To (Index_List, Loc));
5318 begin
5319 Set_Etype (Comp_Ref, Comp_Typ);
5321 -- Generate:
5322 -- [Deep_]Initialize (V (J1, ..., JN));
5324 return Make_Init_Call (Obj_Ref => Comp_Ref, Typ => Comp_Typ);
5325 end Build_Initialization_Call;
5327 -- Start of processing for Build_Initialize_Statements
5329 begin
5330 Counter_Id := Make_Temporary (Loc, 'C');
5331 Finalizer_Decls := New_List;
5333 Build_Indices;
5334 Build_Object_Declarations (Finalizer_Data, Finalizer_Decls, Loc);
5336 -- Generate the block which houses the finalization call, the index
5337 -- guard and the handler which triggers Program_Error later on.
5339 -- if Counter > 0 then
5340 -- Counter := Counter - 1;
5341 -- else
5342 -- [Deep_]Finalize (V (F1, ..., FN)); -- No_Except_Propagation
5344 -- begin -- Exceptions allowed
5345 -- [Deep_]Finalize (V (F1, ..., FN));
5346 -- exception
5347 -- when others =>
5348 -- if not Raised then
5349 -- Raised := True;
5350 -- Save_Occurrence (E, Get_Current_Excep.all.all);
5351 -- end if;
5352 -- end;
5353 -- end if;
5355 if Exceptions_OK then
5356 Fin_Stmt :=
5357 Make_Block_Statement (Loc,
5358 Handled_Statement_Sequence =>
5359 Make_Handled_Sequence_Of_Statements (Loc,
5360 Statements => New_List (Build_Finalization_Call),
5361 Exception_Handlers => New_List (
5362 Build_Exception_Handler (Finalizer_Data))));
5363 else
5364 Fin_Stmt := Build_Finalization_Call;
5365 end if;
5367 -- This is the core of the loop, the dimension iterators are added
5368 -- one by one in reverse.
5370 Final_Loop :=
5371 Make_If_Statement (Loc,
5372 Condition =>
5373 Make_Op_Gt (Loc,
5374 Left_Opnd => New_Reference_To (Counter_Id, Loc),
5375 Right_Opnd => Make_Integer_Literal (Loc, 0)),
5377 Then_Statements => New_List (
5378 Make_Assignment_Statement (Loc,
5379 Name => New_Reference_To (Counter_Id, Loc),
5380 Expression =>
5381 Make_Op_Subtract (Loc,
5382 Left_Opnd => New_Reference_To (Counter_Id, Loc),
5383 Right_Opnd => Make_Integer_Literal (Loc, 1)))),
5385 Else_Statements => New_List (Fin_Stmt));
5387 -- Generate all finalization loops starting from the innermost
5388 -- dimension.
5390 -- for Fnn in reverse V'Range (Dim) loop
5391 -- <final loop>
5392 -- end loop;
5394 F := Last (Final_List);
5395 Dim := Num_Dims;
5396 while Present (F) and then Dim > 0 loop
5397 Loop_Id := F;
5398 Prev (F);
5399 Remove (Loop_Id);
5401 Final_Loop :=
5402 Make_Loop_Statement (Loc,
5403 Iteration_Scheme =>
5404 Make_Iteration_Scheme (Loc,
5405 Loop_Parameter_Specification =>
5406 Make_Loop_Parameter_Specification (Loc,
5407 Defining_Identifier => Loop_Id,
5408 Discrete_Subtype_Definition =>
5409 Make_Attribute_Reference (Loc,
5410 Prefix => Make_Identifier (Loc, Name_V),
5411 Attribute_Name => Name_Range,
5412 Expressions => New_List (
5413 Make_Integer_Literal (Loc, Dim))),
5415 Reverse_Present => True)),
5417 Statements => New_List (Final_Loop),
5418 End_Label => Empty);
5420 Dim := Dim - 1;
5421 end loop;
5423 -- Generate the block which contains the finalization loops, the
5424 -- declarations of the abort flag, the exception occurrence, the
5425 -- raised flag and the conditional raise.
5427 -- declare
5428 -- Abort : constant Boolean := Triggered_By_Abort;
5429 -- <or>
5430 -- Abort : constant Boolean := False; -- no abort
5432 -- E : Exception_Occurrence;
5433 -- Raised : Boolean := False;
5435 -- begin
5436 -- Counter :=
5437 -- V'Length (1) *
5438 -- ...
5439 -- V'Length (N) - Counter;
5441 -- <final loop>
5443 -- if Raised and then not Abort then -- Exception handlers OK
5444 -- Raise_From_Controlled_Operation (E);
5445 -- end if;
5447 -- raise; -- Exception handlers OK
5448 -- end;
5450 Stmts := New_List (Build_Counter_Assignment, Final_Loop);
5452 if Exceptions_OK then
5453 Append_To (Stmts,
5454 Build_Raise_Statement (Finalizer_Data));
5455 Append_To (Stmts, Make_Raise_Statement (Loc));
5456 end if;
5458 Final_Block :=
5459 Make_Block_Statement (Loc,
5460 Declarations =>
5461 Finalizer_Decls,
5462 Handled_Statement_Sequence =>
5463 Make_Handled_Sequence_Of_Statements (Loc, Statements => Stmts));
5465 -- Generate the block which contains the initialization call and
5466 -- the partial finalization code.
5468 -- begin
5469 -- [Deep_]Initialize (V (J1, ..., JN));
5471 -- Counter := Counter + 1;
5473 -- exception
5474 -- when others =>
5475 -- <finalization code>
5476 -- end;
5478 Init_Loop :=
5479 Make_Block_Statement (Loc,
5480 Handled_Statement_Sequence =>
5481 Make_Handled_Sequence_Of_Statements (Loc,
5482 Statements => New_List (Build_Initialization_Call),
5483 Exception_Handlers => New_List (
5484 Make_Exception_Handler (Loc,
5485 Exception_Choices => New_List (Make_Others_Choice (Loc)),
5486 Statements => New_List (Final_Block)))));
5488 Append_To (Statements (Handled_Statement_Sequence (Init_Loop)),
5489 Make_Assignment_Statement (Loc,
5490 Name => New_Reference_To (Counter_Id, Loc),
5491 Expression =>
5492 Make_Op_Add (Loc,
5493 Left_Opnd => New_Reference_To (Counter_Id, Loc),
5494 Right_Opnd => Make_Integer_Literal (Loc, 1))));
5496 -- Generate all initialization loops starting from the innermost
5497 -- dimension.
5499 -- for Jnn in V'Range (Dim) loop
5500 -- <init loop>
5501 -- end loop;
5503 J := Last (Index_List);
5504 Dim := Num_Dims;
5505 while Present (J) and then Dim > 0 loop
5506 Loop_Id := J;
5507 Prev (J);
5508 Remove (Loop_Id);
5510 Init_Loop :=
5511 Make_Loop_Statement (Loc,
5512 Iteration_Scheme =>
5513 Make_Iteration_Scheme (Loc,
5514 Loop_Parameter_Specification =>
5515 Make_Loop_Parameter_Specification (Loc,
5516 Defining_Identifier => Loop_Id,
5517 Discrete_Subtype_Definition =>
5518 Make_Attribute_Reference (Loc,
5519 Prefix => Make_Identifier (Loc, Name_V),
5520 Attribute_Name => Name_Range,
5521 Expressions => New_List (
5522 Make_Integer_Literal (Loc, Dim))))),
5524 Statements => New_List (Init_Loop),
5525 End_Label => Empty);
5527 Dim := Dim - 1;
5528 end loop;
5530 -- Generate the block which contains the counter variable and the
5531 -- initialization loops.
5533 -- declare
5534 -- Counter : Integer := 0;
5535 -- begin
5536 -- <init loop>
5537 -- end;
5539 return
5540 New_List (
5541 Make_Block_Statement (Loc,
5542 Declarations => New_List (
5543 Make_Object_Declaration (Loc,
5544 Defining_Identifier => Counter_Id,
5545 Object_Definition =>
5546 New_Reference_To (Standard_Integer, Loc),
5547 Expression => Make_Integer_Literal (Loc, 0))),
5549 Handled_Statement_Sequence =>
5550 Make_Handled_Sequence_Of_Statements (Loc,
5551 Statements => New_List (Init_Loop))));
5552 end Build_Initialize_Statements;
5554 -----------------------
5555 -- New_References_To --
5556 -----------------------
5558 function New_References_To
5559 (L : List_Id;
5560 Loc : Source_Ptr) return List_Id
5562 Refs : constant List_Id := New_List;
5563 Id : Node_Id;
5565 begin
5566 Id := First (L);
5567 while Present (Id) loop
5568 Append_To (Refs, New_Reference_To (Id, Loc));
5569 Next (Id);
5570 end loop;
5572 return Refs;
5573 end New_References_To;
5575 -- Start of processing for Make_Deep_Array_Body
5577 begin
5578 case Prim is
5579 when Address_Case =>
5580 return Make_Finalize_Address_Stmts (Typ);
5582 when Adjust_Case |
5583 Finalize_Case =>
5584 return Build_Adjust_Or_Finalize_Statements (Typ);
5586 when Initialize_Case =>
5587 return Build_Initialize_Statements (Typ);
5588 end case;
5589 end Make_Deep_Array_Body;
5591 --------------------
5592 -- Make_Deep_Proc --
5593 --------------------
5595 function Make_Deep_Proc
5596 (Prim : Final_Primitives;
5597 Typ : Entity_Id;
5598 Stmts : List_Id) return Entity_Id
5600 Loc : constant Source_Ptr := Sloc (Typ);
5601 Formals : List_Id;
5602 Proc_Id : Entity_Id;
5604 begin
5605 -- Create the object formal, generate:
5606 -- V : System.Address
5608 if Prim = Address_Case then
5609 Formals := New_List (
5610 Make_Parameter_Specification (Loc,
5611 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
5612 Parameter_Type => New_Reference_To (RTE (RE_Address), Loc)));
5614 -- Default case
5616 else
5617 -- V : in out Typ
5619 Formals := New_List (
5620 Make_Parameter_Specification (Loc,
5621 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
5622 In_Present => True,
5623 Out_Present => True,
5624 Parameter_Type => New_Reference_To (Typ, Loc)));
5626 -- F : Boolean := True
5628 if Prim = Adjust_Case
5629 or else Prim = Finalize_Case
5630 then
5631 Append_To (Formals,
5632 Make_Parameter_Specification (Loc,
5633 Defining_Identifier => Make_Defining_Identifier (Loc, Name_F),
5634 Parameter_Type =>
5635 New_Reference_To (Standard_Boolean, Loc),
5636 Expression =>
5637 New_Reference_To (Standard_True, Loc)));
5638 end if;
5639 end if;
5641 Proc_Id :=
5642 Make_Defining_Identifier (Loc,
5643 Chars => Make_TSS_Name (Typ, Deep_Name_Of (Prim)));
5645 -- Generate:
5646 -- procedure Deep_Initialize / Adjust / Finalize (V : in out <typ>) is
5647 -- begin
5648 -- <stmts>
5649 -- exception -- Finalize and Adjust cases only
5650 -- raise Program_Error;
5651 -- end Deep_Initialize / Adjust / Finalize;
5653 -- or
5655 -- procedure Finalize_Address (V : System.Address) is
5656 -- begin
5657 -- <stmts>
5658 -- end Finalize_Address;
5660 Discard_Node (
5661 Make_Subprogram_Body (Loc,
5662 Specification =>
5663 Make_Procedure_Specification (Loc,
5664 Defining_Unit_Name => Proc_Id,
5665 Parameter_Specifications => Formals),
5667 Declarations => Empty_List,
5669 Handled_Statement_Sequence =>
5670 Make_Handled_Sequence_Of_Statements (Loc, Statements => Stmts)));
5672 return Proc_Id;
5673 end Make_Deep_Proc;
5675 ---------------------------
5676 -- Make_Deep_Record_Body --
5677 ---------------------------
5679 function Make_Deep_Record_Body
5680 (Prim : Final_Primitives;
5681 Typ : Entity_Id;
5682 Is_Local : Boolean := False) return List_Id
5684 function Build_Adjust_Statements (Typ : Entity_Id) return List_Id;
5685 -- Build the statements necessary to adjust a record type. The type may
5686 -- have discriminants and contain variant parts. Generate:
5688 -- begin
5689 -- begin
5690 -- [Deep_]Adjust (V.Comp_1);
5691 -- exception
5692 -- when Id : others =>
5693 -- if not Raised then
5694 -- Raised := True;
5695 -- Save_Occurrence (E, Get_Current_Excep.all.all);
5696 -- end if;
5697 -- end;
5698 -- . . .
5699 -- begin
5700 -- [Deep_]Adjust (V.Comp_N);
5701 -- exception
5702 -- when Id : others =>
5703 -- if not Raised then
5704 -- Raised := True;
5705 -- Save_Occurrence (E, Get_Current_Excep.all.all);
5706 -- end if;
5707 -- end;
5709 -- begin
5710 -- Deep_Adjust (V._parent, False); -- If applicable
5711 -- exception
5712 -- when Id : others =>
5713 -- if not Raised then
5714 -- Raised := True;
5715 -- Save_Occurrence (E, Get_Current_Excep.all.all);
5716 -- end if;
5717 -- end;
5719 -- if F then
5720 -- begin
5721 -- Adjust (V); -- If applicable
5722 -- exception
5723 -- when others =>
5724 -- if not Raised then
5725 -- Raised := True;
5726 -- Save_Occurence (E, Get_Current_Excep.all.all);
5727 -- end if;
5728 -- end;
5729 -- end if;
5731 -- if Raised and then not Abort then
5732 -- Raise_From_Controlled_Operation (E);
5733 -- end if;
5734 -- end;
5736 function Build_Finalize_Statements (Typ : Entity_Id) return List_Id;
5737 -- Build the statements necessary to finalize a record type. The type
5738 -- may have discriminants and contain variant parts. Generate:
5740 -- declare
5741 -- Abort : constant Boolean := Triggered_By_Abort;
5742 -- <or>
5743 -- Abort : constant Boolean := False; -- no abort
5744 -- E : Exception_Occurence;
5745 -- Raised : Boolean := False;
5747 -- begin
5748 -- if F then
5749 -- begin
5750 -- Finalize (V); -- If applicable
5751 -- exception
5752 -- when others =>
5753 -- if not Raised then
5754 -- Raised := True;
5755 -- Save_Occurence (E, Get_Current_Excep.all.all);
5756 -- end if;
5757 -- end;
5758 -- end if;
5760 -- case Variant_1 is
5761 -- when Value_1 =>
5762 -- case State_Counter_N => -- If Is_Local is enabled
5763 -- when N => .
5764 -- goto LN; .
5765 -- ... .
5766 -- when 1 => .
5767 -- goto L1; .
5768 -- when others => .
5769 -- goto L0; .
5770 -- end case; .
5772 -- <<LN>> -- If Is_Local is enabled
5773 -- begin
5774 -- [Deep_]Finalize (V.Comp_N);
5775 -- exception
5776 -- when others =>
5777 -- if not Raised then
5778 -- Raised := True;
5779 -- Save_Occurence (E, Get_Current_Excep.all.all);
5780 -- end if;
5781 -- end;
5782 -- . . .
5783 -- <<L1>>
5784 -- begin
5785 -- [Deep_]Finalize (V.Comp_1);
5786 -- exception
5787 -- when others =>
5788 -- if not Raised then
5789 -- Raised := True;
5790 -- Save_Occurence (E, Get_Current_Excep.all.all);
5791 -- end if;
5792 -- end;
5793 -- <<L0>>
5794 -- end case;
5796 -- case State_Counter_1 => -- If Is_Local is enabled
5797 -- when M => .
5798 -- goto LM; .
5799 -- ...
5801 -- begin
5802 -- Deep_Finalize (V._parent, False); -- If applicable
5803 -- exception
5804 -- when Id : others =>
5805 -- if not Raised then
5806 -- Raised := True;
5807 -- Save_Occurrence (E, Get_Current_Excep.all.all);
5808 -- end if;
5809 -- end;
5811 -- if Raised and then not Abort then
5812 -- Raise_From_Controlled_Operation (E);
5813 -- end if;
5814 -- end;
5816 function Parent_Field_Type (Typ : Entity_Id) return Entity_Id;
5817 -- Given a derived tagged type Typ, traverse all components, find field
5818 -- _parent and return its type.
5820 procedure Preprocess_Components
5821 (Comps : Node_Id;
5822 Num_Comps : out Int;
5823 Has_POC : out Boolean);
5824 -- Examine all components in component list Comps, count all controlled
5825 -- components and determine whether at least one of them is per-object
5826 -- constrained. Component _parent is always skipped.
5828 -----------------------------
5829 -- Build_Adjust_Statements --
5830 -----------------------------
5832 function Build_Adjust_Statements (Typ : Entity_Id) return List_Id is
5833 Loc : constant Source_Ptr := Sloc (Typ);
5834 Typ_Def : constant Node_Id := Type_Definition (Parent (Typ));
5835 Bod_Stmts : List_Id;
5836 Finalizer_Data : Finalization_Exception_Data;
5837 Finalizer_Decls : List_Id := No_List;
5838 Rec_Def : Node_Id;
5839 Var_Case : Node_Id;
5841 Exceptions_OK : constant Boolean :=
5842 not Restriction_Active (No_Exception_Propagation);
5844 function Process_Component_List_For_Adjust
5845 (Comps : Node_Id) return List_Id;
5846 -- Build all necessary adjust statements for a single component list
5848 ---------------------------------------
5849 -- Process_Component_List_For_Adjust --
5850 ---------------------------------------
5852 function Process_Component_List_For_Adjust
5853 (Comps : Node_Id) return List_Id
5855 Stmts : constant List_Id := New_List;
5856 Decl : Node_Id;
5857 Decl_Id : Entity_Id;
5858 Decl_Typ : Entity_Id;
5859 Has_POC : Boolean;
5860 Num_Comps : Int;
5862 procedure Process_Component_For_Adjust (Decl : Node_Id);
5863 -- Process the declaration of a single controlled component
5865 ----------------------------------
5866 -- Process_Component_For_Adjust --
5867 ----------------------------------
5869 procedure Process_Component_For_Adjust (Decl : Node_Id) is
5870 Id : constant Entity_Id := Defining_Identifier (Decl);
5871 Typ : constant Entity_Id := Etype (Id);
5872 Adj_Stmt : Node_Id;
5874 begin
5875 -- Generate:
5876 -- [Deep_]Adjust (V.Id); -- No_Exception_Propagation
5878 -- begin -- Exception handlers allowed
5879 -- [Deep_]Adjust (V.Id);
5880 -- exception
5881 -- when others =>
5882 -- if not Raised then
5883 -- Raised := True;
5884 -- Save_Occurrence (E, Get_Current_Excep.all.all);
5885 -- end if;
5886 -- end;
5888 Adj_Stmt :=
5889 Make_Adjust_Call (
5890 Obj_Ref =>
5891 Make_Selected_Component (Loc,
5892 Prefix => Make_Identifier (Loc, Name_V),
5893 Selector_Name => Make_Identifier (Loc, Chars (Id))),
5894 Typ => Typ);
5896 if Exceptions_OK then
5897 Adj_Stmt :=
5898 Make_Block_Statement (Loc,
5899 Handled_Statement_Sequence =>
5900 Make_Handled_Sequence_Of_Statements (Loc,
5901 Statements => New_List (Adj_Stmt),
5902 Exception_Handlers => New_List (
5903 Build_Exception_Handler (Finalizer_Data))));
5904 end if;
5906 Append_To (Stmts, Adj_Stmt);
5907 end Process_Component_For_Adjust;
5909 -- Start of processing for Process_Component_List_For_Adjust
5911 begin
5912 -- Perform an initial check, determine the number of controlled
5913 -- components in the current list and whether at least one of them
5914 -- is per-object constrained.
5916 Preprocess_Components (Comps, Num_Comps, Has_POC);
5918 -- The processing in this routine is done in the following order:
5919 -- 1) Regular components
5920 -- 2) Per-object constrained components
5921 -- 3) Variant parts
5923 if Num_Comps > 0 then
5925 -- Process all regular components in order of declarations
5927 Decl := First_Non_Pragma (Component_Items (Comps));
5928 while Present (Decl) loop
5929 Decl_Id := Defining_Identifier (Decl);
5930 Decl_Typ := Etype (Decl_Id);
5932 -- Skip _parent as well as per-object constrained components
5934 if Chars (Decl_Id) /= Name_uParent
5935 and then Needs_Finalization (Decl_Typ)
5936 then
5937 if Has_Access_Constraint (Decl_Id)
5938 and then No (Expression (Decl))
5939 then
5940 null;
5941 else
5942 Process_Component_For_Adjust (Decl);
5943 end if;
5944 end if;
5946 Next_Non_Pragma (Decl);
5947 end loop;
5949 -- Process all per-object constrained components in order of
5950 -- declarations.
5952 if Has_POC then
5953 Decl := First_Non_Pragma (Component_Items (Comps));
5954 while Present (Decl) loop
5955 Decl_Id := Defining_Identifier (Decl);
5956 Decl_Typ := Etype (Decl_Id);
5958 -- Skip _parent
5960 if Chars (Decl_Id) /= Name_uParent
5961 and then Needs_Finalization (Decl_Typ)
5962 and then Has_Access_Constraint (Decl_Id)
5963 and then No (Expression (Decl))
5964 then
5965 Process_Component_For_Adjust (Decl);
5966 end if;
5968 Next_Non_Pragma (Decl);
5969 end loop;
5970 end if;
5971 end if;
5973 -- Process all variants, if any
5975 Var_Case := Empty;
5976 if Present (Variant_Part (Comps)) then
5977 declare
5978 Var_Alts : constant List_Id := New_List;
5979 Var : Node_Id;
5981 begin
5982 Var := First_Non_Pragma (Variants (Variant_Part (Comps)));
5983 while Present (Var) loop
5985 -- Generate:
5986 -- when <discrete choices> =>
5987 -- <adjust statements>
5989 Append_To (Var_Alts,
5990 Make_Case_Statement_Alternative (Loc,
5991 Discrete_Choices =>
5992 New_Copy_List (Discrete_Choices (Var)),
5993 Statements =>
5994 Process_Component_List_For_Adjust (
5995 Component_List (Var))));
5997 Next_Non_Pragma (Var);
5998 end loop;
6000 -- Generate:
6001 -- case V.<discriminant> is
6002 -- when <discrete choices 1> =>
6003 -- <adjust statements 1>
6004 -- ...
6005 -- when <discrete choices N> =>
6006 -- <adjust statements N>
6007 -- end case;
6009 Var_Case :=
6010 Make_Case_Statement (Loc,
6011 Expression =>
6012 Make_Selected_Component (Loc,
6013 Prefix => Make_Identifier (Loc, Name_V),
6014 Selector_Name =>
6015 Make_Identifier (Loc,
6016 Chars => Chars (Name (Variant_Part (Comps))))),
6017 Alternatives => Var_Alts);
6018 end;
6019 end if;
6021 -- Add the variant case statement to the list of statements
6023 if Present (Var_Case) then
6024 Append_To (Stmts, Var_Case);
6025 end if;
6027 -- If the component list did not have any controlled components
6028 -- nor variants, return null.
6030 if Is_Empty_List (Stmts) then
6031 Append_To (Stmts, Make_Null_Statement (Loc));
6032 end if;
6034 return Stmts;
6035 end Process_Component_List_For_Adjust;
6037 -- Start of processing for Build_Adjust_Statements
6039 begin
6040 Finalizer_Decls := New_List;
6041 Build_Object_Declarations (Finalizer_Data, Finalizer_Decls, Loc);
6043 if Nkind (Typ_Def) = N_Derived_Type_Definition then
6044 Rec_Def := Record_Extension_Part (Typ_Def);
6045 else
6046 Rec_Def := Typ_Def;
6047 end if;
6049 -- Create an adjust sequence for all record components
6051 if Present (Component_List (Rec_Def)) then
6052 Bod_Stmts :=
6053 Process_Component_List_For_Adjust (Component_List (Rec_Def));
6054 end if;
6056 -- A derived record type must adjust all inherited components. This
6057 -- action poses the following problem:
6059 -- procedure Deep_Adjust (Obj : in out Parent_Typ) is
6060 -- begin
6061 -- Adjust (Obj);
6062 -- ...
6064 -- procedure Deep_Adjust (Obj : in out Derived_Typ) is
6065 -- begin
6066 -- Deep_Adjust (Obj._parent);
6067 -- ...
6068 -- Adjust (Obj);
6069 -- ...
6071 -- Adjusting the derived type will invoke Adjust of the parent and
6072 -- then that of the derived type. This is undesirable because both
6073 -- routines may modify shared components. Only the Adjust of the
6074 -- derived type should be invoked.
6076 -- To prevent this double adjustment of shared components,
6077 -- Deep_Adjust uses a flag to control the invocation of Adjust:
6079 -- procedure Deep_Adjust
6080 -- (Obj : in out Some_Type;
6081 -- Flag : Boolean := True)
6082 -- is
6083 -- begin
6084 -- if Flag then
6085 -- Adjust (Obj);
6086 -- end if;
6087 -- ...
6089 -- When Deep_Adjust is invokes for field _parent, a value of False is
6090 -- provided for the flag:
6092 -- Deep_Adjust (Obj._parent, False);
6094 if Is_Tagged_Type (Typ) and then Is_Derived_Type (Typ) then
6095 declare
6096 Par_Typ : constant Entity_Id := Parent_Field_Type (Typ);
6097 Adj_Stmt : Node_Id;
6098 Call : Node_Id;
6100 begin
6101 if Needs_Finalization (Par_Typ) then
6102 Call :=
6103 Make_Adjust_Call
6104 (Obj_Ref =>
6105 Make_Selected_Component (Loc,
6106 Prefix => Make_Identifier (Loc, Name_V),
6107 Selector_Name =>
6108 Make_Identifier (Loc, Name_uParent)),
6109 Typ => Par_Typ,
6110 For_Parent => True);
6112 -- Generate:
6113 -- Deep_Adjust (V._parent, False); -- No_Except_Propagat
6115 -- begin -- Exceptions OK
6116 -- Deep_Adjust (V._parent, False);
6117 -- exception
6118 -- when Id : others =>
6119 -- if not Raised then
6120 -- Raised := True;
6121 -- Save_Occurrence (E,
6122 -- Get_Current_Excep.all.all);
6123 -- end if;
6124 -- end;
6126 if Present (Call) then
6127 Adj_Stmt := Call;
6129 if Exceptions_OK then
6130 Adj_Stmt :=
6131 Make_Block_Statement (Loc,
6132 Handled_Statement_Sequence =>
6133 Make_Handled_Sequence_Of_Statements (Loc,
6134 Statements => New_List (Adj_Stmt),
6135 Exception_Handlers => New_List (
6136 Build_Exception_Handler (Finalizer_Data))));
6137 end if;
6139 Prepend_To (Bod_Stmts, Adj_Stmt);
6140 end if;
6141 end if;
6142 end;
6143 end if;
6145 -- Adjust the object. This action must be performed last after all
6146 -- components have been adjusted.
6148 if Is_Controlled (Typ) then
6149 declare
6150 Adj_Stmt : Node_Id;
6151 Proc : Entity_Id;
6153 begin
6154 Proc := Find_Prim_Op (Typ, Name_Adjust);
6156 -- Generate:
6157 -- if F then
6158 -- Adjust (V); -- No_Exception_Propagation
6160 -- begin -- Exception handlers allowed
6161 -- Adjust (V);
6162 -- exception
6163 -- when others =>
6164 -- if not Raised then
6165 -- Raised := True;
6166 -- Save_Occurrence (E,
6167 -- Get_Current_Excep.all.all);
6168 -- end if;
6169 -- end;
6170 -- end if;
6172 if Present (Proc) then
6173 Adj_Stmt :=
6174 Make_Procedure_Call_Statement (Loc,
6175 Name => New_Reference_To (Proc, Loc),
6176 Parameter_Associations => New_List (
6177 Make_Identifier (Loc, Name_V)));
6179 if Exceptions_OK then
6180 Adj_Stmt :=
6181 Make_Block_Statement (Loc,
6182 Handled_Statement_Sequence =>
6183 Make_Handled_Sequence_Of_Statements (Loc,
6184 Statements => New_List (Adj_Stmt),
6185 Exception_Handlers => New_List (
6186 Build_Exception_Handler
6187 (Finalizer_Data))));
6188 end if;
6190 Append_To (Bod_Stmts,
6191 Make_If_Statement (Loc,
6192 Condition => Make_Identifier (Loc, Name_F),
6193 Then_Statements => New_List (Adj_Stmt)));
6194 end if;
6195 end;
6196 end if;
6198 -- At this point either all adjustment statements have been generated
6199 -- or the type is not controlled.
6201 if Is_Empty_List (Bod_Stmts) then
6202 Append_To (Bod_Stmts, Make_Null_Statement (Loc));
6204 return Bod_Stmts;
6206 -- Generate:
6207 -- declare
6208 -- Abort : constant Boolean := Triggered_By_Abort;
6209 -- <or>
6210 -- Abort : constant Boolean := False; -- no abort
6212 -- E : Exception_Occurence;
6213 -- Raised : Boolean := False;
6215 -- begin
6216 -- <adjust statements>
6218 -- if Raised and then not Abort then
6219 -- Raise_From_Controlled_Operation (E);
6220 -- end if;
6221 -- end;
6223 else
6224 if Exceptions_OK then
6225 Append_To (Bod_Stmts,
6226 Build_Raise_Statement (Finalizer_Data));
6227 end if;
6229 return
6230 New_List (
6231 Make_Block_Statement (Loc,
6232 Declarations =>
6233 Finalizer_Decls,
6234 Handled_Statement_Sequence =>
6235 Make_Handled_Sequence_Of_Statements (Loc, Bod_Stmts)));
6236 end if;
6237 end Build_Adjust_Statements;
6239 -------------------------------
6240 -- Build_Finalize_Statements --
6241 -------------------------------
6243 function Build_Finalize_Statements (Typ : Entity_Id) return List_Id is
6244 Loc : constant Source_Ptr := Sloc (Typ);
6245 Typ_Def : constant Node_Id := Type_Definition (Parent (Typ));
6246 Bod_Stmts : List_Id;
6247 Counter : Int := 0;
6248 Finalizer_Data : Finalization_Exception_Data;
6249 Finalizer_Decls : List_Id := No_List;
6250 Rec_Def : Node_Id;
6251 Var_Case : Node_Id;
6253 Exceptions_OK : constant Boolean :=
6254 not Restriction_Active (No_Exception_Propagation);
6256 function Process_Component_List_For_Finalize
6257 (Comps : Node_Id) return List_Id;
6258 -- Build all necessary finalization statements for a single component
6259 -- list. The statements may include a jump circuitry if flag Is_Local
6260 -- is enabled.
6262 -----------------------------------------
6263 -- Process_Component_List_For_Finalize --
6264 -----------------------------------------
6266 function Process_Component_List_For_Finalize
6267 (Comps : Node_Id) return List_Id
6269 Alts : List_Id;
6270 Counter_Id : Entity_Id;
6271 Decl : Node_Id;
6272 Decl_Id : Entity_Id;
6273 Decl_Typ : Entity_Id;
6274 Decls : List_Id;
6275 Has_POC : Boolean;
6276 Jump_Block : Node_Id;
6277 Label : Node_Id;
6278 Label_Id : Entity_Id;
6279 Num_Comps : Int;
6280 Stmts : List_Id;
6282 procedure Process_Component_For_Finalize
6283 (Decl : Node_Id;
6284 Alts : List_Id;
6285 Decls : List_Id;
6286 Stmts : List_Id);
6287 -- Process the declaration of a single controlled component. If
6288 -- flag Is_Local is enabled, create the corresponding label and
6289 -- jump circuitry. Alts is the list of case alternatives, Decls
6290 -- is the top level declaration list where labels are declared
6291 -- and Stmts is the list of finalization actions.
6293 ------------------------------------
6294 -- Process_Component_For_Finalize --
6295 ------------------------------------
6297 procedure Process_Component_For_Finalize
6298 (Decl : Node_Id;
6299 Alts : List_Id;
6300 Decls : List_Id;
6301 Stmts : List_Id)
6303 Id : constant Entity_Id := Defining_Identifier (Decl);
6304 Typ : constant Entity_Id := Etype (Id);
6305 Fin_Stmt : Node_Id;
6307 begin
6308 if Is_Local then
6309 declare
6310 Label : Node_Id;
6311 Label_Id : Entity_Id;
6313 begin
6314 -- Generate:
6315 -- LN : label;
6317 Label_Id :=
6318 Make_Identifier (Loc,
6319 Chars => New_External_Name ('L', Num_Comps));
6320 Set_Entity (Label_Id,
6321 Make_Defining_Identifier (Loc, Chars (Label_Id)));
6322 Label := Make_Label (Loc, Label_Id);
6324 Append_To (Decls,
6325 Make_Implicit_Label_Declaration (Loc,
6326 Defining_Identifier => Entity (Label_Id),
6327 Label_Construct => Label));
6329 -- Generate:
6330 -- when N =>
6331 -- goto LN;
6333 Append_To (Alts,
6334 Make_Case_Statement_Alternative (Loc,
6335 Discrete_Choices => New_List (
6336 Make_Integer_Literal (Loc, Num_Comps)),
6338 Statements => New_List (
6339 Make_Goto_Statement (Loc,
6340 Name =>
6341 New_Reference_To (Entity (Label_Id), Loc)))));
6343 -- Generate:
6344 -- <<LN>>
6346 Append_To (Stmts, Label);
6348 -- Decrease the number of components to be processed.
6349 -- This action yields a new Label_Id in future calls.
6351 Num_Comps := Num_Comps - 1;
6352 end;
6353 end if;
6355 -- Generate:
6356 -- [Deep_]Finalize (V.Id); -- No_Exception_Propagation
6358 -- begin -- Exception handlers allowed
6359 -- [Deep_]Finalize (V.Id);
6360 -- exception
6361 -- when others =>
6362 -- if not Raised then
6363 -- Raised := True;
6364 -- Save_Occurrence (E,
6365 -- Get_Current_Excep.all.all);
6366 -- end if;
6367 -- end;
6369 Fin_Stmt :=
6370 Make_Final_Call
6371 (Obj_Ref =>
6372 Make_Selected_Component (Loc,
6373 Prefix => Make_Identifier (Loc, Name_V),
6374 Selector_Name => Make_Identifier (Loc, Chars (Id))),
6375 Typ => Typ);
6377 if not Restriction_Active (No_Exception_Propagation) then
6378 Fin_Stmt :=
6379 Make_Block_Statement (Loc,
6380 Handled_Statement_Sequence =>
6381 Make_Handled_Sequence_Of_Statements (Loc,
6382 Statements => New_List (Fin_Stmt),
6383 Exception_Handlers => New_List (
6384 Build_Exception_Handler (Finalizer_Data))));
6385 end if;
6387 Append_To (Stmts, Fin_Stmt);
6388 end Process_Component_For_Finalize;
6390 -- Start of processing for Process_Component_List_For_Finalize
6392 begin
6393 -- Perform an initial check, look for controlled and per-object
6394 -- constrained components.
6396 Preprocess_Components (Comps, Num_Comps, Has_POC);
6398 -- Create a state counter to service the current component list.
6399 -- This step is performed before the variants are inspected in
6400 -- order to generate the same state counter names as those from
6401 -- Build_Initialize_Statements.
6403 if Num_Comps > 0
6404 and then Is_Local
6405 then
6406 Counter := Counter + 1;
6408 Counter_Id :=
6409 Make_Defining_Identifier (Loc,
6410 Chars => New_External_Name ('C', Counter));
6411 end if;
6413 -- Process the component in the following order:
6414 -- 1) Variants
6415 -- 2) Per-object constrained components
6416 -- 3) Regular components
6418 -- Start with the variant parts
6420 Var_Case := Empty;
6421 if Present (Variant_Part (Comps)) then
6422 declare
6423 Var_Alts : constant List_Id := New_List;
6424 Var : Node_Id;
6426 begin
6427 Var := First_Non_Pragma (Variants (Variant_Part (Comps)));
6428 while Present (Var) loop
6430 -- Generate:
6431 -- when <discrete choices> =>
6432 -- <finalize statements>
6434 Append_To (Var_Alts,
6435 Make_Case_Statement_Alternative (Loc,
6436 Discrete_Choices =>
6437 New_Copy_List (Discrete_Choices (Var)),
6438 Statements =>
6439 Process_Component_List_For_Finalize (
6440 Component_List (Var))));
6442 Next_Non_Pragma (Var);
6443 end loop;
6445 -- Generate:
6446 -- case V.<discriminant> is
6447 -- when <discrete choices 1> =>
6448 -- <finalize statements 1>
6449 -- ...
6450 -- when <discrete choices N> =>
6451 -- <finalize statements N>
6452 -- end case;
6454 Var_Case :=
6455 Make_Case_Statement (Loc,
6456 Expression =>
6457 Make_Selected_Component (Loc,
6458 Prefix => Make_Identifier (Loc, Name_V),
6459 Selector_Name =>
6460 Make_Identifier (Loc,
6461 Chars => Chars (Name (Variant_Part (Comps))))),
6462 Alternatives => Var_Alts);
6463 end;
6464 end if;
6466 -- The current component list does not have a single controlled
6467 -- component, however it may contain variants. Return the case
6468 -- statement for the variants or nothing.
6470 if Num_Comps = 0 then
6471 if Present (Var_Case) then
6472 return New_List (Var_Case);
6473 else
6474 return New_List (Make_Null_Statement (Loc));
6475 end if;
6476 end if;
6478 -- Prepare all lists
6480 Alts := New_List;
6481 Decls := New_List;
6482 Stmts := New_List;
6484 -- Process all per-object constrained components in reverse order
6486 if Has_POC then
6487 Decl := Last_Non_Pragma (Component_Items (Comps));
6488 while Present (Decl) loop
6489 Decl_Id := Defining_Identifier (Decl);
6490 Decl_Typ := Etype (Decl_Id);
6492 -- Skip _parent
6494 if Chars (Decl_Id) /= Name_uParent
6495 and then Needs_Finalization (Decl_Typ)
6496 and then Has_Access_Constraint (Decl_Id)
6497 and then No (Expression (Decl))
6498 then
6499 Process_Component_For_Finalize (Decl, Alts, Decls, Stmts);
6500 end if;
6502 Prev_Non_Pragma (Decl);
6503 end loop;
6504 end if;
6506 -- Process the rest of the components in reverse order
6508 Decl := Last_Non_Pragma (Component_Items (Comps));
6509 while Present (Decl) loop
6510 Decl_Id := Defining_Identifier (Decl);
6511 Decl_Typ := Etype (Decl_Id);
6513 -- Skip _parent
6515 if Chars (Decl_Id) /= Name_uParent
6516 and then Needs_Finalization (Decl_Typ)
6517 then
6518 -- Skip per-object constrained components since they were
6519 -- handled in the above step.
6521 if Has_Access_Constraint (Decl_Id)
6522 and then No (Expression (Decl))
6523 then
6524 null;
6525 else
6526 Process_Component_For_Finalize (Decl, Alts, Decls, Stmts);
6527 end if;
6528 end if;
6530 Prev_Non_Pragma (Decl);
6531 end loop;
6533 -- Generate:
6534 -- declare
6535 -- LN : label; -- If Is_Local is enabled
6536 -- ... .
6537 -- L0 : label; .
6539 -- begin .
6540 -- case CounterX is .
6541 -- when N => .
6542 -- goto LN; .
6543 -- ... .
6544 -- when 1 => .
6545 -- goto L1; .
6546 -- when others => .
6547 -- goto L0; .
6548 -- end case; .
6550 -- <<LN>> -- If Is_Local is enabled
6551 -- begin
6552 -- [Deep_]Finalize (V.CompY);
6553 -- exception
6554 -- when Id : others =>
6555 -- if not Raised then
6556 -- Raised := True;
6557 -- Save_Occurrence (E,
6558 -- Get_Current_Excep.all.all);
6559 -- end if;
6560 -- end;
6561 -- ...
6562 -- <<L0>> -- If Is_Local is enabled
6563 -- end;
6565 if Is_Local then
6567 -- Add the declaration of default jump location L0, its
6568 -- corresponding alternative and its place in the statements.
6570 Label_Id := Make_Identifier (Loc, New_External_Name ('L', 0));
6571 Set_Entity (Label_Id,
6572 Make_Defining_Identifier (Loc, Chars (Label_Id)));
6573 Label := Make_Label (Loc, Label_Id);
6575 Append_To (Decls, -- declaration
6576 Make_Implicit_Label_Declaration (Loc,
6577 Defining_Identifier => Entity (Label_Id),
6578 Label_Construct => Label));
6580 Append_To (Alts, -- alternative
6581 Make_Case_Statement_Alternative (Loc,
6582 Discrete_Choices => New_List (
6583 Make_Others_Choice (Loc)),
6585 Statements => New_List (
6586 Make_Goto_Statement (Loc,
6587 Name => New_Reference_To (Entity (Label_Id), Loc)))));
6589 Append_To (Stmts, Label); -- statement
6591 -- Create the jump block
6593 Prepend_To (Stmts,
6594 Make_Case_Statement (Loc,
6595 Expression => Make_Identifier (Loc, Chars (Counter_Id)),
6596 Alternatives => Alts));
6597 end if;
6599 Jump_Block :=
6600 Make_Block_Statement (Loc,
6601 Declarations => Decls,
6602 Handled_Statement_Sequence =>
6603 Make_Handled_Sequence_Of_Statements (Loc, Stmts));
6605 if Present (Var_Case) then
6606 return New_List (Var_Case, Jump_Block);
6607 else
6608 return New_List (Jump_Block);
6609 end if;
6610 end Process_Component_List_For_Finalize;
6612 -- Start of processing for Build_Finalize_Statements
6614 begin
6615 Finalizer_Decls := New_List;
6616 Build_Object_Declarations (Finalizer_Data, Finalizer_Decls, Loc);
6618 if Nkind (Typ_Def) = N_Derived_Type_Definition then
6619 Rec_Def := Record_Extension_Part (Typ_Def);
6620 else
6621 Rec_Def := Typ_Def;
6622 end if;
6624 -- Create a finalization sequence for all record components
6626 if Present (Component_List (Rec_Def)) then
6627 Bod_Stmts :=
6628 Process_Component_List_For_Finalize (Component_List (Rec_Def));
6629 end if;
6631 -- A derived record type must finalize all inherited components. This
6632 -- action poses the following problem:
6634 -- procedure Deep_Finalize (Obj : in out Parent_Typ) is
6635 -- begin
6636 -- Finalize (Obj);
6637 -- ...
6639 -- procedure Deep_Finalize (Obj : in out Derived_Typ) is
6640 -- begin
6641 -- Deep_Finalize (Obj._parent);
6642 -- ...
6643 -- Finalize (Obj);
6644 -- ...
6646 -- Finalizing the derived type will invoke Finalize of the parent and
6647 -- then that of the derived type. This is undesirable because both
6648 -- routines may modify shared components. Only the Finalize of the
6649 -- derived type should be invoked.
6651 -- To prevent this double adjustment of shared components,
6652 -- Deep_Finalize uses a flag to control the invocation of Finalize:
6654 -- procedure Deep_Finalize
6655 -- (Obj : in out Some_Type;
6656 -- Flag : Boolean := True)
6657 -- is
6658 -- begin
6659 -- if Flag then
6660 -- Finalize (Obj);
6661 -- end if;
6662 -- ...
6664 -- When Deep_Finalize is invokes for field _parent, a value of False
6665 -- is provided for the flag:
6667 -- Deep_Finalize (Obj._parent, False);
6669 if Is_Tagged_Type (Typ)
6670 and then Is_Derived_Type (Typ)
6671 then
6672 declare
6673 Par_Typ : constant Entity_Id := Parent_Field_Type (Typ);
6674 Call : Node_Id;
6675 Fin_Stmt : Node_Id;
6677 begin
6678 if Needs_Finalization (Par_Typ) then
6679 Call :=
6680 Make_Final_Call
6681 (Obj_Ref =>
6682 Make_Selected_Component (Loc,
6683 Prefix => Make_Identifier (Loc, Name_V),
6684 Selector_Name =>
6685 Make_Identifier (Loc, Name_uParent)),
6686 Typ => Par_Typ,
6687 For_Parent => True);
6689 -- Generate:
6690 -- Deep_Finalize (V._parent, False); -- No_Except_Propag
6692 -- begin -- Exceptions OK
6693 -- Deep_Finalize (V._parent, False);
6694 -- exception
6695 -- when Id : others =>
6696 -- if not Raised then
6697 -- Raised := True;
6698 -- Save_Occurrence (E,
6699 -- Get_Current_Excep.all.all);
6700 -- end if;
6701 -- end;
6703 if Present (Call) then
6704 Fin_Stmt := Call;
6706 if Exceptions_OK then
6707 Fin_Stmt :=
6708 Make_Block_Statement (Loc,
6709 Handled_Statement_Sequence =>
6710 Make_Handled_Sequence_Of_Statements (Loc,
6711 Statements => New_List (Fin_Stmt),
6712 Exception_Handlers => New_List (
6713 Build_Exception_Handler
6714 (Finalizer_Data))));
6715 end if;
6717 Append_To (Bod_Stmts, Fin_Stmt);
6718 end if;
6719 end if;
6720 end;
6721 end if;
6723 -- Finalize the object. This action must be performed first before
6724 -- all components have been finalized.
6726 if Is_Controlled (Typ)
6727 and then not Is_Local
6728 then
6729 declare
6730 Fin_Stmt : Node_Id;
6731 Proc : Entity_Id;
6733 begin
6734 Proc := Find_Prim_Op (Typ, Name_Finalize);
6736 -- Generate:
6737 -- if F then
6738 -- Finalize (V); -- No_Exception_Propagation
6740 -- begin
6741 -- Finalize (V);
6742 -- exception
6743 -- when others =>
6744 -- if not Raised then
6745 -- Raised := True;
6746 -- Save_Occurrence (E,
6747 -- Get_Current_Excep.all.all);
6748 -- end if;
6749 -- end;
6750 -- end if;
6752 if Present (Proc) then
6753 Fin_Stmt :=
6754 Make_Procedure_Call_Statement (Loc,
6755 Name => New_Reference_To (Proc, Loc),
6756 Parameter_Associations => New_List (
6757 Make_Identifier (Loc, Name_V)));
6759 if Exceptions_OK then
6760 Fin_Stmt :=
6761 Make_Block_Statement (Loc,
6762 Handled_Statement_Sequence =>
6763 Make_Handled_Sequence_Of_Statements (Loc,
6764 Statements => New_List (Fin_Stmt),
6765 Exception_Handlers => New_List (
6766 Build_Exception_Handler
6767 (Finalizer_Data))));
6768 end if;
6770 Prepend_To (Bod_Stmts,
6771 Make_If_Statement (Loc,
6772 Condition => Make_Identifier (Loc, Name_F),
6773 Then_Statements => New_List (Fin_Stmt)));
6774 end if;
6775 end;
6776 end if;
6778 -- At this point either all finalization statements have been
6779 -- generated or the type is not controlled.
6781 if No (Bod_Stmts) then
6782 return New_List (Make_Null_Statement (Loc));
6784 -- Generate:
6785 -- declare
6786 -- Abort : constant Boolean := Triggered_By_Abort;
6787 -- <or>
6788 -- Abort : constant Boolean := False; -- no abort
6790 -- E : Exception_Occurence;
6791 -- Raised : Boolean := False;
6793 -- begin
6794 -- <finalize statements>
6796 -- if Raised and then not Abort then
6797 -- Raise_From_Controlled_Operation (E);
6798 -- end if;
6799 -- end;
6801 else
6802 if Exceptions_OK then
6803 Append_To (Bod_Stmts,
6804 Build_Raise_Statement (Finalizer_Data));
6805 end if;
6807 return
6808 New_List (
6809 Make_Block_Statement (Loc,
6810 Declarations =>
6811 Finalizer_Decls,
6812 Handled_Statement_Sequence =>
6813 Make_Handled_Sequence_Of_Statements (Loc, Bod_Stmts)));
6814 end if;
6815 end Build_Finalize_Statements;
6817 -----------------------
6818 -- Parent_Field_Type --
6819 -----------------------
6821 function Parent_Field_Type (Typ : Entity_Id) return Entity_Id is
6822 Field : Entity_Id;
6824 begin
6825 Field := First_Entity (Typ);
6826 while Present (Field) loop
6827 if Chars (Field) = Name_uParent then
6828 return Etype (Field);
6829 end if;
6831 Next_Entity (Field);
6832 end loop;
6834 -- A derived tagged type should always have a parent field
6836 raise Program_Error;
6837 end Parent_Field_Type;
6839 ---------------------------
6840 -- Preprocess_Components --
6841 ---------------------------
6843 procedure Preprocess_Components
6844 (Comps : Node_Id;
6845 Num_Comps : out Int;
6846 Has_POC : out Boolean)
6848 Decl : Node_Id;
6849 Id : Entity_Id;
6850 Typ : Entity_Id;
6852 begin
6853 Num_Comps := 0;
6854 Has_POC := False;
6856 Decl := First_Non_Pragma (Component_Items (Comps));
6857 while Present (Decl) loop
6858 Id := Defining_Identifier (Decl);
6859 Typ := Etype (Id);
6861 -- Skip field _parent
6863 if Chars (Id) /= Name_uParent
6864 and then Needs_Finalization (Typ)
6865 then
6866 Num_Comps := Num_Comps + 1;
6868 if Has_Access_Constraint (Id)
6869 and then No (Expression (Decl))
6870 then
6871 Has_POC := True;
6872 end if;
6873 end if;
6875 Next_Non_Pragma (Decl);
6876 end loop;
6877 end Preprocess_Components;
6879 -- Start of processing for Make_Deep_Record_Body
6881 begin
6882 case Prim is
6883 when Address_Case =>
6884 return Make_Finalize_Address_Stmts (Typ);
6886 when Adjust_Case =>
6887 return Build_Adjust_Statements (Typ);
6889 when Finalize_Case =>
6890 return Build_Finalize_Statements (Typ);
6892 when Initialize_Case =>
6893 declare
6894 Loc : constant Source_Ptr := Sloc (Typ);
6896 begin
6897 if Is_Controlled (Typ) then
6898 return New_List (
6899 Make_Procedure_Call_Statement (Loc,
6900 Name =>
6901 New_Reference_To
6902 (Find_Prim_Op (Typ, Name_Of (Prim)), Loc),
6903 Parameter_Associations => New_List (
6904 Make_Identifier (Loc, Name_V))));
6905 else
6906 return Empty_List;
6907 end if;
6908 end;
6909 end case;
6910 end Make_Deep_Record_Body;
6912 ----------------------
6913 -- Make_Final_Call --
6914 ----------------------
6916 function Make_Final_Call
6917 (Obj_Ref : Node_Id;
6918 Typ : Entity_Id;
6919 For_Parent : Boolean := False) return Node_Id
6921 Loc : constant Source_Ptr := Sloc (Obj_Ref);
6922 Atyp : Entity_Id;
6923 Fin_Id : Entity_Id := Empty;
6924 Ref : Node_Id;
6925 Utyp : Entity_Id;
6927 begin
6928 -- Recover the proper type which contains [Deep_]Finalize
6930 if Is_Class_Wide_Type (Typ) then
6931 Utyp := Root_Type (Typ);
6932 Atyp := Utyp;
6933 Ref := Obj_Ref;
6935 elsif Is_Concurrent_Type (Typ) then
6936 Utyp := Corresponding_Record_Type (Typ);
6937 Atyp := Empty;
6938 Ref := Convert_Concurrent (Obj_Ref, Typ);
6940 elsif Is_Private_Type (Typ)
6941 and then Present (Full_View (Typ))
6942 and then Is_Concurrent_Type (Full_View (Typ))
6943 then
6944 Utyp := Corresponding_Record_Type (Full_View (Typ));
6945 Atyp := Typ;
6946 Ref := Convert_Concurrent (Obj_Ref, Full_View (Typ));
6948 else
6949 Utyp := Typ;
6950 Atyp := Typ;
6951 Ref := Obj_Ref;
6952 end if;
6954 Utyp := Underlying_Type (Base_Type (Utyp));
6955 Set_Assignment_OK (Ref);
6957 -- Deal with non-tagged derivation of private views. If the parent type
6958 -- is a protected type, Deep_Finalize is found on the corresponding
6959 -- record of the ancestor.
6961 if Is_Untagged_Derivation (Typ) then
6962 if Is_Protected_Type (Typ) then
6963 Utyp := Corresponding_Record_Type (Root_Type (Base_Type (Typ)));
6964 else
6965 Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
6967 if Is_Protected_Type (Utyp) then
6968 Utyp := Corresponding_Record_Type (Utyp);
6969 end if;
6970 end if;
6972 Ref := Unchecked_Convert_To (Utyp, Ref);
6973 Set_Assignment_OK (Ref);
6974 end if;
6976 -- Deal with derived private types which do not inherit primitives from
6977 -- their parents. In this case, [Deep_]Finalize can be found in the full
6978 -- view of the parent type.
6980 if Is_Tagged_Type (Utyp)
6981 and then Is_Derived_Type (Utyp)
6982 and then Is_Empty_Elmt_List (Primitive_Operations (Utyp))
6983 and then Is_Private_Type (Etype (Utyp))
6984 and then Present (Full_View (Etype (Utyp)))
6985 then
6986 Utyp := Full_View (Etype (Utyp));
6987 Ref := Unchecked_Convert_To (Utyp, Ref);
6988 Set_Assignment_OK (Ref);
6989 end if;
6991 -- When dealing with the completion of a private type, use the base type
6992 -- instead.
6994 if Utyp /= Base_Type (Utyp) then
6995 pragma Assert (Present (Atyp) and then Is_Private_Type (Atyp));
6997 Utyp := Base_Type (Utyp);
6998 Ref := Unchecked_Convert_To (Utyp, Ref);
6999 Set_Assignment_OK (Ref);
7000 end if;
7002 -- Select the appropriate version of Finalize
7004 if For_Parent then
7005 if Has_Controlled_Component (Utyp) then
7006 Fin_Id := Find_Prim_Op (Utyp, TSS_Deep_Finalize);
7007 end if;
7009 -- Class-wide types, interfaces and types with controlled components
7011 elsif Is_Class_Wide_Type (Typ)
7012 or else Is_Interface (Typ)
7013 or else Has_Controlled_Component (Utyp)
7014 then
7015 if Is_Tagged_Type (Utyp) then
7016 Fin_Id := Find_Prim_Op (Utyp, TSS_Deep_Finalize);
7017 else
7018 Fin_Id := TSS (Utyp, TSS_Deep_Finalize);
7019 end if;
7021 -- Derivations from [Limited_]Controlled
7023 elsif Is_Controlled (Utyp) then
7024 if Has_Controlled_Component (Utyp) then
7025 Fin_Id := Find_Prim_Op (Utyp, TSS_Deep_Finalize);
7026 else
7027 Fin_Id := Find_Prim_Op (Utyp, Name_Of (Finalize_Case));
7028 end if;
7030 -- Tagged types
7032 elsif Is_Tagged_Type (Utyp) then
7033 Fin_Id := Find_Prim_Op (Utyp, TSS_Deep_Finalize);
7035 else
7036 raise Program_Error;
7037 end if;
7039 if Present (Fin_Id) then
7041 -- When finalizing a class-wide object, do not convert to the root
7042 -- type in order to produce a dispatching call.
7044 if Is_Class_Wide_Type (Typ) then
7045 null;
7047 -- Ensure that a finalization routine is at least decorated in order
7048 -- to inspect the object parameter.
7050 elsif Analyzed (Fin_Id)
7051 or else Ekind (Fin_Id) = E_Procedure
7052 then
7053 -- In certain cases, such as the creation of Stream_Read, the
7054 -- visible entity of the type is its full view. Since Stream_Read
7055 -- will have to create an object of type Typ, the local object
7056 -- will be finalzed by the scope finalizer generated later on. The
7057 -- object parameter of Deep_Finalize will always use the private
7058 -- view of the type. To avoid such a clash between a private and a
7059 -- full view, perform an unchecked conversion of the object
7060 -- reference to the private view.
7062 declare
7063 Formal_Typ : constant Entity_Id :=
7064 Etype (First_Formal (Fin_Id));
7065 begin
7066 if Is_Private_Type (Formal_Typ)
7067 and then Present (Full_View (Formal_Typ))
7068 and then Full_View (Formal_Typ) = Utyp
7069 then
7070 Ref := Unchecked_Convert_To (Formal_Typ, Ref);
7071 end if;
7072 end;
7074 Ref := Convert_View (Fin_Id, Ref);
7075 end if;
7077 return Make_Call (Loc, Fin_Id, New_Copy_Tree (Ref), For_Parent);
7078 else
7079 return Empty;
7080 end if;
7081 end Make_Final_Call;
7083 --------------------------------
7084 -- Make_Finalize_Address_Body --
7085 --------------------------------
7087 procedure Make_Finalize_Address_Body (Typ : Entity_Id) is
7088 Is_Task : constant Boolean :=
7089 Ekind (Typ) = E_Record_Type
7090 and then Is_Concurrent_Record_Type (Typ)
7091 and then Ekind (Corresponding_Concurrent_Type (Typ)) =
7092 E_Task_Type;
7093 Loc : constant Source_Ptr := Sloc (Typ);
7094 Proc_Id : Entity_Id;
7095 Stmts : List_Id;
7097 begin
7098 -- The corresponding records of task types are not controlled by design.
7099 -- For the sake of completeness, create an empty Finalize_Address to be
7100 -- used in task class-wide allocations.
7102 if Is_Task then
7103 null;
7105 -- Nothing to do if the type is not controlled or it already has a
7106 -- TSS entry for Finalize_Address. Skip class-wide subtypes which do not
7107 -- come from source. These are usually generated for completeness and
7108 -- do not need the Finalize_Address primitive.
7110 elsif not Needs_Finalization (Typ)
7111 or else Is_Abstract_Type (Typ)
7112 or else Present (TSS (Typ, TSS_Finalize_Address))
7113 or else
7114 (Is_Class_Wide_Type (Typ)
7115 and then Ekind (Root_Type (Typ)) = E_Record_Subtype
7116 and then not Comes_From_Source (Root_Type (Typ)))
7117 then
7118 return;
7119 end if;
7121 Proc_Id :=
7122 Make_Defining_Identifier (Loc,
7123 Make_TSS_Name (Typ, TSS_Finalize_Address));
7125 -- Generate:
7127 -- procedure <Typ>FD (V : System.Address) is
7128 -- begin
7129 -- null; -- for tasks
7131 -- declare -- for all other types
7132 -- type Pnn is access all Typ;
7133 -- for Pnn'Storage_Size use 0;
7134 -- begin
7135 -- [Deep_]Finalize (Pnn (V).all);
7136 -- end;
7137 -- end TypFD;
7139 if Is_Task then
7140 Stmts := New_List (Make_Null_Statement (Loc));
7141 else
7142 Stmts := Make_Finalize_Address_Stmts (Typ);
7143 end if;
7145 Discard_Node (
7146 Make_Subprogram_Body (Loc,
7147 Specification =>
7148 Make_Procedure_Specification (Loc,
7149 Defining_Unit_Name => Proc_Id,
7151 Parameter_Specifications => New_List (
7152 Make_Parameter_Specification (Loc,
7153 Defining_Identifier =>
7154 Make_Defining_Identifier (Loc, Name_V),
7155 Parameter_Type =>
7156 New_Reference_To (RTE (RE_Address), Loc)))),
7158 Declarations => No_List,
7160 Handled_Statement_Sequence =>
7161 Make_Handled_Sequence_Of_Statements (Loc,
7162 Statements => Stmts)));
7164 Set_TSS (Typ, Proc_Id);
7165 end Make_Finalize_Address_Body;
7167 ---------------------------------
7168 -- Make_Finalize_Address_Stmts --
7169 ---------------------------------
7171 function Make_Finalize_Address_Stmts (Typ : Entity_Id) return List_Id is
7172 Loc : constant Source_Ptr := Sloc (Typ);
7173 Ptr_Typ : constant Entity_Id := Make_Temporary (Loc, 'P');
7174 Decls : List_Id;
7175 Desg_Typ : Entity_Id;
7176 Obj_Expr : Node_Id;
7178 begin
7179 if Is_Array_Type (Typ) then
7180 if Is_Constrained (First_Subtype (Typ)) then
7181 Desg_Typ := First_Subtype (Typ);
7182 else
7183 Desg_Typ := Base_Type (Typ);
7184 end if;
7186 -- Class-wide types of constrained root types
7188 elsif Is_Class_Wide_Type (Typ)
7189 and then Has_Discriminants (Root_Type (Typ))
7190 and then not
7191 Is_Empty_Elmt_List (Discriminant_Constraint (Root_Type (Typ)))
7192 then
7193 declare
7194 Parent_Typ : Entity_Id;
7196 begin
7197 -- Climb the parent type chain looking for a non-constrained type
7199 Parent_Typ := Root_Type (Typ);
7200 while Parent_Typ /= Etype (Parent_Typ)
7201 and then Has_Discriminants (Parent_Typ)
7202 and then not
7203 Is_Empty_Elmt_List (Discriminant_Constraint (Parent_Typ))
7204 loop
7205 Parent_Typ := Etype (Parent_Typ);
7206 end loop;
7208 -- Handle views created for tagged types with unknown
7209 -- discriminants.
7211 if Is_Underlying_Record_View (Parent_Typ) then
7212 Parent_Typ := Underlying_Record_View (Parent_Typ);
7213 end if;
7215 Desg_Typ := Class_Wide_Type (Underlying_Type (Parent_Typ));
7216 end;
7218 -- General case
7220 else
7221 Desg_Typ := Typ;
7222 end if;
7224 -- Generate:
7225 -- type Ptr_Typ is access all Typ;
7226 -- for Ptr_Typ'Storage_Size use 0;
7228 Decls := New_List (
7229 Make_Full_Type_Declaration (Loc,
7230 Defining_Identifier => Ptr_Typ,
7231 Type_Definition =>
7232 Make_Access_To_Object_Definition (Loc,
7233 All_Present => True,
7234 Subtype_Indication => New_Reference_To (Desg_Typ, Loc))),
7236 Make_Attribute_Definition_Clause (Loc,
7237 Name => New_Reference_To (Ptr_Typ, Loc),
7238 Chars => Name_Storage_Size,
7239 Expression => Make_Integer_Literal (Loc, 0)));
7241 Obj_Expr := Make_Identifier (Loc, Name_V);
7243 -- Unconstrained arrays require special processing in order to retrieve
7244 -- the elements. To achieve this, we have to skip the dope vector which
7245 -- lays in front of the elements and then use a thin pointer to perform
7246 -- the address-to-access conversion.
7248 if Is_Array_Type (Typ)
7249 and then not Is_Constrained (First_Subtype (Typ))
7250 then
7251 declare
7252 Dope_Id : Entity_Id;
7254 begin
7255 -- Ensure that Ptr_Typ a thin pointer, generate:
7256 -- for Ptr_Typ'Size use System.Address'Size;
7258 Append_To (Decls,
7259 Make_Attribute_Definition_Clause (Loc,
7260 Name => New_Reference_To (Ptr_Typ, Loc),
7261 Chars => Name_Size,
7262 Expression =>
7263 Make_Integer_Literal (Loc, System_Address_Size)));
7265 -- Generate:
7266 -- Dnn : constant Storage_Offset :=
7267 -- Desg_Typ'Descriptor_Size / Storage_Unit;
7269 Dope_Id := Make_Temporary (Loc, 'D');
7271 Append_To (Decls,
7272 Make_Object_Declaration (Loc,
7273 Defining_Identifier => Dope_Id,
7274 Constant_Present => True,
7275 Object_Definition =>
7276 New_Reference_To (RTE (RE_Storage_Offset), Loc),
7277 Expression =>
7278 Make_Op_Divide (Loc,
7279 Left_Opnd =>
7280 Make_Attribute_Reference (Loc,
7281 Prefix => New_Reference_To (Desg_Typ, Loc),
7282 Attribute_Name => Name_Descriptor_Size),
7283 Right_Opnd =>
7284 Make_Integer_Literal (Loc, System_Storage_Unit))));
7286 -- Shift the address from the start of the dope vector to the
7287 -- start of the elements:
7289 -- V + Dnn
7291 -- Note that this is done through a wrapper routine since RTSfind
7292 -- cannot retrieve operations with string names of the form "+".
7294 Obj_Expr :=
7295 Make_Function_Call (Loc,
7296 Name =>
7297 New_Reference_To (RTE (RE_Add_Offset_To_Address), Loc),
7298 Parameter_Associations => New_List (
7299 Obj_Expr,
7300 New_Reference_To (Dope_Id, Loc)));
7301 end;
7302 end if;
7304 -- Create the block and the finalization call
7306 return New_List (
7307 Make_Block_Statement (Loc,
7308 Declarations => Decls,
7310 Handled_Statement_Sequence =>
7311 Make_Handled_Sequence_Of_Statements (Loc,
7312 Statements => New_List (
7313 Make_Final_Call (
7314 Obj_Ref =>
7315 Make_Explicit_Dereference (Loc,
7316 Prefix => Unchecked_Convert_To (Ptr_Typ, Obj_Expr)),
7317 Typ => Desg_Typ)))));
7318 end Make_Finalize_Address_Stmts;
7320 -------------------------------------
7321 -- Make_Handler_For_Ctrl_Operation --
7322 -------------------------------------
7324 -- Generate:
7326 -- when E : others =>
7327 -- Raise_From_Controlled_Operation (E);
7329 -- or:
7331 -- when others =>
7332 -- raise Program_Error [finalize raised exception];
7334 -- depending on whether Raise_From_Controlled_Operation is available
7336 function Make_Handler_For_Ctrl_Operation
7337 (Loc : Source_Ptr) return Node_Id
7339 E_Occ : Entity_Id;
7340 -- Choice parameter (for the first case above)
7342 Raise_Node : Node_Id;
7343 -- Procedure call or raise statement
7345 begin
7346 -- Standard run-time, .NET/JVM targets: add choice parameter E and pass
7347 -- it to Raise_From_Controlled_Operation so that the original exception
7348 -- name and message can be recorded in the exception message for
7349 -- Program_Error.
7351 if RTE_Available (RE_Raise_From_Controlled_Operation) then
7352 E_Occ := Make_Defining_Identifier (Loc, Name_E);
7353 Raise_Node :=
7354 Make_Procedure_Call_Statement (Loc,
7355 Name =>
7356 New_Reference_To
7357 (RTE (RE_Raise_From_Controlled_Operation), Loc),
7358 Parameter_Associations => New_List (
7359 New_Reference_To (E_Occ, Loc)));
7361 -- Restricted run-time: exception messages are not supported
7363 else
7364 E_Occ := Empty;
7365 Raise_Node :=
7366 Make_Raise_Program_Error (Loc,
7367 Reason => PE_Finalize_Raised_Exception);
7368 end if;
7370 return
7371 Make_Implicit_Exception_Handler (Loc,
7372 Exception_Choices => New_List (Make_Others_Choice (Loc)),
7373 Choice_Parameter => E_Occ,
7374 Statements => New_List (Raise_Node));
7375 end Make_Handler_For_Ctrl_Operation;
7377 --------------------
7378 -- Make_Init_Call --
7379 --------------------
7381 function Make_Init_Call
7382 (Obj_Ref : Node_Id;
7383 Typ : Entity_Id) return Node_Id
7385 Loc : constant Source_Ptr := Sloc (Obj_Ref);
7386 Is_Conc : Boolean;
7387 Proc : Entity_Id;
7388 Ref : Node_Id;
7389 Utyp : Entity_Id;
7391 begin
7392 -- Deal with the type and object reference. Depending on the context, an
7393 -- object reference may need several conversions.
7395 if Is_Concurrent_Type (Typ) then
7396 Is_Conc := True;
7397 Utyp := Corresponding_Record_Type (Typ);
7398 Ref := Convert_Concurrent (Obj_Ref, Typ);
7400 elsif Is_Private_Type (Typ)
7401 and then Present (Full_View (Typ))
7402 and then Is_Concurrent_Type (Underlying_Type (Typ))
7403 then
7404 Is_Conc := True;
7405 Utyp := Corresponding_Record_Type (Underlying_Type (Typ));
7406 Ref := Convert_Concurrent (Obj_Ref, Underlying_Type (Typ));
7408 else
7409 Is_Conc := False;
7410 Utyp := Typ;
7411 Ref := Obj_Ref;
7412 end if;
7414 Set_Assignment_OK (Ref);
7416 Utyp := Underlying_Type (Base_Type (Utyp));
7418 -- Deal with non-tagged derivation of private views
7420 if Is_Untagged_Derivation (Typ)
7421 and then not Is_Conc
7422 then
7423 Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
7424 Ref := Unchecked_Convert_To (Utyp, Ref);
7426 -- The following is to prevent problems with UC see 1.156 RH ???
7428 Set_Assignment_OK (Ref);
7429 end if;
7431 -- If the underlying_type is a subtype, then we are dealing with the
7432 -- completion of a private type. We need to access the base type and
7433 -- generate a conversion to it.
7435 if Utyp /= Base_Type (Utyp) then
7436 pragma Assert (Is_Private_Type (Typ));
7437 Utyp := Base_Type (Utyp);
7438 Ref := Unchecked_Convert_To (Utyp, Ref);
7439 end if;
7441 -- Select the appropriate version of initialize
7443 if Has_Controlled_Component (Utyp) then
7444 Proc := TSS (Utyp, Deep_Name_Of (Initialize_Case));
7445 else
7446 Proc := Find_Prim_Op (Utyp, Name_Of (Initialize_Case));
7447 Check_Visibly_Controlled (Initialize_Case, Typ, Proc, Ref);
7448 end if;
7450 -- The object reference may need another conversion depending on the
7451 -- type of the formal and that of the actual.
7453 Ref := Convert_View (Proc, Ref);
7455 -- Generate:
7456 -- [Deep_]Initialize (Ref);
7458 return
7459 Make_Procedure_Call_Statement (Loc,
7460 Name =>
7461 New_Reference_To (Proc, Loc),
7462 Parameter_Associations => New_List (Ref));
7463 end Make_Init_Call;
7465 ------------------------------
7466 -- Make_Local_Deep_Finalize --
7467 ------------------------------
7469 function Make_Local_Deep_Finalize
7470 (Typ : Entity_Id;
7471 Nam : Entity_Id) return Node_Id
7473 Loc : constant Source_Ptr := Sloc (Typ);
7474 Formals : List_Id;
7476 begin
7477 Formals := New_List (
7479 -- V : in out Typ
7481 Make_Parameter_Specification (Loc,
7482 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
7483 In_Present => True,
7484 Out_Present => True,
7485 Parameter_Type => New_Reference_To (Typ, Loc)),
7487 -- F : Boolean := True
7489 Make_Parameter_Specification (Loc,
7490 Defining_Identifier => Make_Defining_Identifier (Loc, Name_F),
7491 Parameter_Type => New_Reference_To (Standard_Boolean, Loc),
7492 Expression => New_Reference_To (Standard_True, Loc)));
7494 -- Add the necessary number of counters to represent the initialization
7495 -- state of an object.
7497 return
7498 Make_Subprogram_Body (Loc,
7499 Specification =>
7500 Make_Procedure_Specification (Loc,
7501 Defining_Unit_Name => Nam,
7502 Parameter_Specifications => Formals),
7504 Declarations => No_List,
7506 Handled_Statement_Sequence =>
7507 Make_Handled_Sequence_Of_Statements (Loc,
7508 Statements => Make_Deep_Record_Body (Finalize_Case, Typ, True)));
7509 end Make_Local_Deep_Finalize;
7511 ------------------------------------
7512 -- Make_Set_Finalize_Address_Call --
7513 ------------------------------------
7515 function Make_Set_Finalize_Address_Call
7516 (Loc : Source_Ptr;
7517 Typ : Entity_Id;
7518 Ptr_Typ : Entity_Id) return Node_Id
7520 Desig_Typ : constant Entity_Id :=
7521 Available_View (Designated_Type (Ptr_Typ));
7522 Fin_Mas_Id : constant Entity_Id := Finalization_Master (Ptr_Typ);
7523 Fin_Mas_Ref : Node_Id;
7524 Utyp : Entity_Id;
7526 begin
7527 -- If the context is a class-wide allocator, we use the class-wide type
7528 -- to obtain the proper Finalize_Address routine.
7530 if Is_Class_Wide_Type (Desig_Typ) then
7531 Utyp := Desig_Typ;
7533 else
7534 Utyp := Typ;
7536 if Is_Private_Type (Utyp) and then Present (Full_View (Utyp)) then
7537 Utyp := Full_View (Utyp);
7538 end if;
7540 if Is_Concurrent_Type (Utyp) then
7541 Utyp := Corresponding_Record_Type (Utyp);
7542 end if;
7543 end if;
7545 Utyp := Underlying_Type (Base_Type (Utyp));
7547 -- Deal with non-tagged derivation of private views. If the parent is
7548 -- now known to be protected, the finalization routine is the one
7549 -- defined on the corresponding record of the ancestor (corresponding
7550 -- records do not automatically inherit operations, but maybe they
7551 -- should???)
7553 if Is_Untagged_Derivation (Typ) then
7554 if Is_Protected_Type (Typ) then
7555 Utyp := Corresponding_Record_Type (Root_Type (Base_Type (Typ)));
7556 else
7557 Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
7559 if Is_Protected_Type (Utyp) then
7560 Utyp := Corresponding_Record_Type (Utyp);
7561 end if;
7562 end if;
7563 end if;
7565 -- If the underlying_type is a subtype, we are dealing with the
7566 -- completion of a private type. We need to access the base type and
7567 -- generate a conversion to it.
7569 if Utyp /= Base_Type (Utyp) then
7570 pragma Assert (Is_Private_Type (Typ));
7572 Utyp := Base_Type (Utyp);
7573 end if;
7575 Fin_Mas_Ref := New_Occurrence_Of (Fin_Mas_Id, Loc);
7577 -- If the call is from a build-in-place function, the Master parameter
7578 -- is actually a pointer. Dereference it for the call.
7580 if Is_Access_Type (Etype (Fin_Mas_Id)) then
7581 Fin_Mas_Ref := Make_Explicit_Dereference (Loc, Fin_Mas_Ref);
7582 end if;
7584 -- Generate:
7585 -- Set_Finalize_Address (<Ptr_Typ>FM, <Utyp>FD'Unrestricted_Access);
7587 return
7588 Make_Procedure_Call_Statement (Loc,
7589 Name =>
7590 New_Reference_To (RTE (RE_Set_Finalize_Address), Loc),
7591 Parameter_Associations => New_List (
7592 Fin_Mas_Ref,
7593 Make_Attribute_Reference (Loc,
7594 Prefix =>
7595 New_Reference_To (TSS (Utyp, TSS_Finalize_Address), Loc),
7596 Attribute_Name => Name_Unrestricted_Access)));
7597 end Make_Set_Finalize_Address_Call;
7599 --------------------------
7600 -- Make_Transient_Block --
7601 --------------------------
7603 function Make_Transient_Block
7604 (Loc : Source_Ptr;
7605 Action : Node_Id;
7606 Par : Node_Id) return Node_Id
7608 Decls : constant List_Id := New_List;
7609 Instrs : constant List_Id := New_List (Action);
7610 Block : Node_Id;
7611 Insert : Node_Id;
7613 begin
7614 -- Case where only secondary stack use is involved
7616 if VM_Target = No_VM
7617 and then Uses_Sec_Stack (Current_Scope)
7618 and then Nkind (Action) /= N_Simple_Return_Statement
7619 and then Nkind (Par) /= N_Exception_Handler
7620 then
7621 declare
7622 S : Entity_Id;
7624 begin
7625 S := Scope (Current_Scope);
7626 loop
7627 -- At the outer level, no need to release the sec stack
7629 if S = Standard_Standard then
7630 Set_Uses_Sec_Stack (Current_Scope, False);
7631 exit;
7633 -- In a function, only release the sec stack if the function
7634 -- does not return on the sec stack otherwise the result may
7635 -- be lost. The caller is responsible for releasing.
7637 elsif Ekind (S) = E_Function then
7638 Set_Uses_Sec_Stack (Current_Scope, False);
7640 if not Requires_Transient_Scope (Etype (S)) then
7641 Set_Uses_Sec_Stack (S, True);
7642 Check_Restriction (No_Secondary_Stack, Action);
7643 end if;
7645 exit;
7647 -- In a loop or entry we should install a block encompassing
7648 -- all the construct. For now just release right away.
7650 elsif Ekind_In (S, E_Entry, E_Loop) then
7651 exit;
7653 -- In a procedure or a block, we release on exit of the
7654 -- procedure or block. ??? memory leak can be created by
7655 -- recursive calls.
7657 elsif Ekind_In (S, E_Block, E_Procedure) then
7658 Set_Uses_Sec_Stack (S, True);
7659 Check_Restriction (No_Secondary_Stack, Action);
7660 Set_Uses_Sec_Stack (Current_Scope, False);
7661 exit;
7663 else
7664 S := Scope (S);
7665 end if;
7666 end loop;
7667 end;
7668 end if;
7670 -- Create the transient block. Set the parent now since the block itself
7671 -- is not part of the tree.
7673 Block :=
7674 Make_Block_Statement (Loc,
7675 Identifier => New_Reference_To (Current_Scope, Loc),
7676 Declarations => Decls,
7677 Handled_Statement_Sequence =>
7678 Make_Handled_Sequence_Of_Statements (Loc, Statements => Instrs),
7679 Has_Created_Identifier => True);
7680 Set_Parent (Block, Par);
7682 -- Insert actions stuck in the transient scopes as well as all freezing
7683 -- nodes needed by those actions.
7685 Insert_Actions_In_Scope_Around (Action);
7687 Insert := Prev (Action);
7688 if Present (Insert) then
7689 Freeze_All (First_Entity (Current_Scope), Insert);
7690 end if;
7692 -- When the transient scope was established, we pushed the entry for the
7693 -- transient scope onto the scope stack, so that the scope was active
7694 -- for the installation of finalizable entities etc. Now we must remove
7695 -- this entry, since we have constructed a proper block.
7697 Pop_Scope;
7699 return Block;
7700 end Make_Transient_Block;
7702 ------------------------
7703 -- Node_To_Be_Wrapped --
7704 ------------------------
7706 function Node_To_Be_Wrapped return Node_Id is
7707 begin
7708 return Scope_Stack.Table (Scope_Stack.Last).Node_To_Be_Wrapped;
7709 end Node_To_Be_Wrapped;
7711 ----------------------------
7712 -- Set_Node_To_Be_Wrapped --
7713 ----------------------------
7715 procedure Set_Node_To_Be_Wrapped (N : Node_Id) is
7716 begin
7717 Scope_Stack.Table (Scope_Stack.Last).Node_To_Be_Wrapped := N;
7718 end Set_Node_To_Be_Wrapped;
7720 ----------------------------------
7721 -- Store_After_Actions_In_Scope --
7722 ----------------------------------
7724 procedure Store_After_Actions_In_Scope (L : List_Id) is
7725 SE : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
7727 begin
7728 if Present (SE.Actions_To_Be_Wrapped_After) then
7729 Insert_List_Before_And_Analyze (
7730 First (SE.Actions_To_Be_Wrapped_After), L);
7732 else
7733 SE.Actions_To_Be_Wrapped_After := L;
7735 if Is_List_Member (SE.Node_To_Be_Wrapped) then
7736 Set_Parent (L, Parent (SE.Node_To_Be_Wrapped));
7737 else
7738 Set_Parent (L, SE.Node_To_Be_Wrapped);
7739 end if;
7741 Analyze_List (L);
7742 end if;
7743 end Store_After_Actions_In_Scope;
7745 -----------------------------------
7746 -- Store_Before_Actions_In_Scope --
7747 -----------------------------------
7749 procedure Store_Before_Actions_In_Scope (L : List_Id) is
7750 SE : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
7752 begin
7753 if Present (SE.Actions_To_Be_Wrapped_Before) then
7754 Insert_List_After_And_Analyze (
7755 Last (SE.Actions_To_Be_Wrapped_Before), L);
7757 else
7758 SE.Actions_To_Be_Wrapped_Before := L;
7760 if Is_List_Member (SE.Node_To_Be_Wrapped) then
7761 Set_Parent (L, Parent (SE.Node_To_Be_Wrapped));
7762 else
7763 Set_Parent (L, SE.Node_To_Be_Wrapped);
7764 end if;
7766 Analyze_List (L);
7767 end if;
7768 end Store_Before_Actions_In_Scope;
7770 --------------------------------
7771 -- Wrap_Transient_Declaration --
7772 --------------------------------
7774 -- If a transient scope has been established during the processing of the
7775 -- Expression of an Object_Declaration, it is not possible to wrap the
7776 -- declaration into a transient block as usual case, otherwise the object
7777 -- would be itself declared in the wrong scope. Therefore, all entities (if
7778 -- any) defined in the transient block are moved to the proper enclosing
7779 -- scope, furthermore, if they are controlled variables they are finalized
7780 -- right after the declaration. The finalization list of the transient
7781 -- scope is defined as a renaming of the enclosing one so during their
7782 -- initialization they will be attached to the proper finalization list.
7783 -- For instance, the following declaration :
7785 -- X : Typ := F (G (A), G (B));
7787 -- (where G(A) and G(B) return controlled values, expanded as _v1 and _v2)
7788 -- is expanded into :
7790 -- X : Typ := [ complex Expression-Action ];
7791 -- [Deep_]Finalize (_v1);
7792 -- [Deep_]Finalize (_v2);
7794 procedure Wrap_Transient_Declaration (N : Node_Id) is
7795 Encl_S : Entity_Id;
7796 S : Entity_Id;
7797 Uses_SS : Boolean;
7799 begin
7800 S := Current_Scope;
7801 Encl_S := Scope (S);
7803 -- Insert Actions kept in the Scope stack
7805 Insert_Actions_In_Scope_Around (N);
7807 -- If the declaration is consuming some secondary stack, mark the
7808 -- enclosing scope appropriately.
7810 Uses_SS := Uses_Sec_Stack (S);
7811 Pop_Scope;
7813 -- Put the local entities back in the enclosing scope, and set the
7814 -- Is_Public flag appropriately.
7816 Transfer_Entities (S, Encl_S);
7818 -- Mark the enclosing dynamic scope so that the sec stack will be
7819 -- released upon its exit unless this is a function that returns on
7820 -- the sec stack in which case this will be done by the caller.
7822 if VM_Target = No_VM and then Uses_SS then
7823 S := Enclosing_Dynamic_Scope (S);
7825 if Ekind (S) = E_Function
7826 and then Requires_Transient_Scope (Etype (S))
7827 then
7828 null;
7829 else
7830 Set_Uses_Sec_Stack (S);
7831 Check_Restriction (No_Secondary_Stack, N);
7832 end if;
7833 end if;
7834 end Wrap_Transient_Declaration;
7836 -------------------------------
7837 -- Wrap_Transient_Expression --
7838 -------------------------------
7840 procedure Wrap_Transient_Expression (N : Node_Id) is
7841 Expr : constant Node_Id := Relocate_Node (N);
7842 Loc : constant Source_Ptr := Sloc (N);
7843 Temp : constant Entity_Id := Make_Temporary (Loc, 'E', N);
7844 Typ : constant Entity_Id := Etype (N);
7846 begin
7847 -- Generate:
7849 -- Temp : Typ;
7850 -- declare
7851 -- M : constant Mark_Id := SS_Mark;
7852 -- procedure Finalizer is ... (See Build_Finalizer)
7854 -- begin
7855 -- Temp := <Expr>;
7857 -- at end
7858 -- Finalizer;
7859 -- end;
7861 Insert_Actions (N, New_List (
7862 Make_Object_Declaration (Loc,
7863 Defining_Identifier => Temp,
7864 Object_Definition => New_Reference_To (Typ, Loc)),
7866 Make_Transient_Block (Loc,
7867 Action =>
7868 Make_Assignment_Statement (Loc,
7869 Name => New_Reference_To (Temp, Loc),
7870 Expression => Expr),
7871 Par => Parent (N))));
7873 Rewrite (N, New_Reference_To (Temp, Loc));
7874 Analyze_And_Resolve (N, Typ);
7875 end Wrap_Transient_Expression;
7877 ------------------------------
7878 -- Wrap_Transient_Statement --
7879 ------------------------------
7881 procedure Wrap_Transient_Statement (N : Node_Id) is
7882 Loc : constant Source_Ptr := Sloc (N);
7883 New_Stmt : constant Node_Id := Relocate_Node (N);
7885 begin
7886 -- Generate:
7887 -- declare
7888 -- M : constant Mark_Id := SS_Mark;
7889 -- procedure Finalizer is ... (See Build_Finalizer)
7891 -- begin
7892 -- <New_Stmt>;
7894 -- at end
7895 -- Finalizer;
7896 -- end;
7898 Rewrite (N,
7899 Make_Transient_Block (Loc,
7900 Action => New_Stmt,
7901 Par => Parent (N)));
7903 -- With the scope stack back to normal, we can call analyze on the
7904 -- resulting block. At this point, the transient scope is being
7905 -- treated like a perfectly normal scope, so there is nothing
7906 -- special about it.
7908 -- Note: Wrap_Transient_Statement is called with the node already
7909 -- analyzed (i.e. Analyzed (N) is True). This is important, since
7910 -- otherwise we would get a recursive processing of the node when
7911 -- we do this Analyze call.
7913 Analyze (N);
7914 end Wrap_Transient_Statement;
7916 end Exp_Ch7;