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