Add x prefix to v850e case for handling --with-cpu=v850e.
[official-gcc.git] / gcc / ada / exp_ch7.adb
blobc9132e019cc0c9735dc8079155c94b09ad9369dc
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- E X P _ C H 7 --
6 -- --
7 -- B o d y --
8 -- --
9 -- --
10 -- Copyright (C) 1992-2002, Free Software Foundation, Inc. --
11 -- --
12 -- GNAT is free software; you can redistribute it and/or modify it under --
13 -- terms of the GNU General Public License as published by the Free Soft- --
14 -- ware Foundation; either version 2, or (at your option) any later ver- --
15 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
16 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
17 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
18 -- for more details. You should have received a copy of the GNU General --
19 -- Public License distributed with GNAT; see file COPYING. If not, write --
20 -- to the Free Software Foundation, 59 Temple Place - Suite 330, Boston, --
21 -- MA 02111-1307, USA. --
22 -- --
23 -- GNAT was originally developed by the GNAT team at New York University. --
24 -- It is now maintained by Ada Core Technologies Inc (http://www.gnat.com). --
25 -- --
26 ------------------------------------------------------------------------------
28 -- This package contains virtually all expansion mechanisms related to
29 -- - controlled types
30 -- - transient scopes
32 with Atree; use Atree;
33 with Debug; use Debug;
34 with Einfo; use Einfo;
35 with Exp_Ch9; use Exp_Ch9;
36 with Exp_Ch11; use Exp_Ch11;
37 with Exp_Dbug; use Exp_Dbug;
38 with Exp_Tss; use Exp_Tss;
39 with Exp_Util; use Exp_Util;
40 with Freeze; use Freeze;
41 with Hostparm; use Hostparm;
42 with Lib; use Lib;
43 with Lib.Xref; use Lib.Xref;
44 with Nlists; use Nlists;
45 with Nmake; use Nmake;
46 with Opt; use Opt;
47 with Output; use Output;
48 with Restrict; use Restrict;
49 with Rtsfind; use Rtsfind;
50 with Targparm; use Targparm;
51 with Sinfo; use Sinfo;
52 with Sem; use Sem;
53 with Sem_Ch3; use Sem_Ch3;
54 with Sem_Ch7; use Sem_Ch7;
55 with Sem_Ch8; use Sem_Ch8;
56 with Sem_Res; use Sem_Res;
57 with Sem_Type; use Sem_Type;
58 with Sem_Util; use Sem_Util;
59 with Snames; use Snames;
60 with Stand; use Stand;
61 with Tbuild; use Tbuild;
62 with Uintp; use Uintp;
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 function returning tagged types: It has been decided to
94 -- always allocate their result in the secondary stack while it is not
95 -- absolutely mandatory when the tagged type is constrained because the
96 -- caller knows the size of the returned object and thus could allocate the
97 -- result in the primary stack. But, allocating them always in the
98 -- secondary stack simplifies many implementation hassles:
100 -- - If it is dispatching function call, the computation of the size of
101 -- the result is possible but complex from the outside.
103 -- - If the returned type is controlled, the assignment of the returned
104 -- value to the anonymous object involves an Adjust, and we have no
105 -- easy way to access the anonymous object created by the back-end
107 -- - If the returned type is class-wide, this is an unconstrained type
108 -- anyway
110 -- Furthermore, the little loss in efficiency which is the result of this
111 -- decision is not such a big deal because function returning tagged types
112 -- are not very much used in real life as opposed to functions returning
113 -- access to a tagged type
115 --------------------------------------------------
116 -- Transient Blocks and Finalization Management --
117 --------------------------------------------------
119 function Find_Node_To_Be_Wrapped (N : Node_Id) return Node_Id;
120 -- N is a node wich may generate a transient scope. Loop over the
121 -- parent pointers of N until it find the appropriate node to
122 -- wrap. It it returns Empty, it means that no transient scope is
123 -- needed in this context.
125 function Make_Clean
126 (N : Node_Id;
127 Clean : Entity_Id;
128 Mark : Entity_Id;
129 Flist : Entity_Id;
130 Is_Task : Boolean;
131 Is_Master : Boolean;
132 Is_Protected_Subprogram : Boolean;
133 Is_Task_Allocation_Block : Boolean;
134 Is_Asynchronous_Call_Block : Boolean)
135 return Node_Id;
136 -- Expand a the clean-up procedure for controlled and/or transient
137 -- block, and/or task master or task body, or blocks used to
138 -- implement task allocation or asynchronous entry calls, or
139 -- procedures used to implement protected procedures. Clean is the
140 -- entity for such a procedure. Mark is the entity for the secondary
141 -- stack mark, if empty only controlled block clean-up will be
142 -- performed. Flist is the entity for the local final list, if empty
143 -- only transient scope clean-up will be performed. The flags
144 -- Is_Task and Is_Master control the calls to the corresponding
145 -- finalization actions for a task body or for an entity that is a
146 -- task master.
148 procedure Set_Node_To_Be_Wrapped (N : Node_Id);
149 -- Set the field Node_To_Be_Wrapped of the current scope
151 procedure Insert_Actions_In_Scope_Around (N : Node_Id);
152 -- Insert the before-actions kept in the scope stack before N, and the
153 -- after after-actions, after N which must be a member of a list.
155 function Make_Transient_Block
156 (Loc : Source_Ptr;
157 Action : Node_Id)
158 return Node_Id;
159 -- Create a transient block whose name is Scope, which is also a
160 -- controlled block if Flist is not empty and whose only code is
161 -- Action (either a single statement or single declaration).
163 type Final_Primitives is (Initialize_Case, Adjust_Case, Finalize_Case);
164 -- This enumeration type is defined in order to ease sharing code for
165 -- building finalization procedures for composite types.
167 Name_Of : constant array (Final_Primitives) of Name_Id :=
168 (Initialize_Case => Name_Initialize,
169 Adjust_Case => Name_Adjust,
170 Finalize_Case => Name_Finalize);
172 Deep_Name_Of : constant array (Final_Primitives) of Name_Id :=
173 (Initialize_Case => Name_uDeep_Initialize,
174 Adjust_Case => Name_uDeep_Adjust,
175 Finalize_Case => Name_uDeep_Finalize);
177 procedure Build_Record_Deep_Procs (Typ : Entity_Id);
178 -- Build the deep Initialize/Adjust/Finalize for a record Typ with
179 -- Has_Component_Component set and store them using the TSS mechanism.
181 procedure Build_Array_Deep_Procs (Typ : Entity_Id);
182 -- Build the deep Initialize/Adjust/Finalize for a record Typ with
183 -- Has_Controlled_Component set and store them using the TSS mechanism.
185 function Make_Deep_Proc
186 (Prim : Final_Primitives;
187 Typ : Entity_Id;
188 Stmts : List_Id)
189 return Node_Id;
190 -- This function generates the tree for Deep_Initialize, Deep_Adjust
191 -- or Deep_Finalize procedures according to the first parameter,
192 -- these procedures operate on the type Typ. The Stmts parameter
193 -- gives the body of the procedure.
195 function Make_Deep_Array_Body
196 (Prim : Final_Primitives;
197 Typ : Entity_Id)
198 return List_Id;
199 -- This function generates the list of statements for implementing
200 -- Deep_Initialize, Deep_Adjust or Deep_Finalize procedures
201 -- according to the first parameter, these procedures operate on the
202 -- array type Typ.
204 function Make_Deep_Record_Body
205 (Prim : Final_Primitives;
206 Typ : Entity_Id)
207 return List_Id;
208 -- This function generates the list of statements for implementing
209 -- Deep_Initialize, Deep_Adjust or Deep_Finalize procedures
210 -- according to the first parameter, these procedures operate on the
211 -- record type Typ.
213 function Convert_View
214 (Proc : Entity_Id;
215 Arg : Node_Id;
216 Ind : Pos := 1)
217 return Node_Id;
218 -- Proc is one of the Initialize/Adjust/Finalize operations, and
219 -- Arg is the argument being passed to it. Ind indicates which
220 -- formal of procedure Proc we are trying to match. This function
221 -- will, if necessary, generate an conversion between the partial
222 -- and full view of Arg to match the type of the formal of Proc,
223 -- or force a conversion to the class-wide type in the case where
224 -- the operation is abstract.
226 -----------------------------
227 -- Finalization Management --
228 -----------------------------
230 -- This part describe how Initialization/Adjusment/Finalization procedures
231 -- are generated and called. Two cases must be considered, types that are
232 -- Controlled (Is_Controlled flag set) and composite types that contain
233 -- controlled components (Has_Controlled_Component flag set). In the first
234 -- case the procedures to call are the user-defined primitive operations
235 -- Initialize/Adjust/Finalize. In the second case, GNAT generates
236 -- Deep_Initialize, Deep_Adjust and Deep_Finalize that are in charge of
237 -- calling the former procedures on the controlled components.
239 -- For records with Has_Controlled_Component set, a hidden "controller"
240 -- component is inserted. This controller component contains its own
241 -- finalization list on which all controlled components are attached
242 -- creating an indirection on the upper-level Finalization list. This
243 -- technique facilitates the management of objects whose number of
244 -- controlled components changes during execution. This controller
245 -- component is itself controlled and is attached to the upper-level
246 -- finalization chain. Its adjust primitive is in charge of calling
247 -- adjust on the components and adusting the finalization pointer to
248 -- match their new location (see a-finali.adb)
250 -- It is not possible to use a similar technique for arrays that have
251 -- Has_Controlled_Component set. In this case, deep procedures are
252 -- generated that call initialize/adjust/finalize + attachment or
253 -- detachment on the finalization list for all component.
255 -- Initialize calls: they are generated for declarations or dynamic
256 -- allocations of Controlled objects with no initial value. They are
257 -- always followed by an attachment to the current Finalization
258 -- Chain. For the dynamic allocation case this the chain attached to
259 -- the scope of the access type definition otherwise, this is the chain
260 -- of the current scope.
262 -- Adjust Calls: They are generated on 2 occasions: (1) for
263 -- declarations or dynamic allocations of Controlled objects with an
264 -- initial value. (2) after an assignment. In the first case they are
265 -- followed by an attachment to the final chain, in the second case
266 -- they are not.
268 -- Finalization Calls: They are generated on (1) scope exit, (2)
269 -- assignments, (3) unchecked deallocations. In case (3) they have to
270 -- be detached from the final chain, in case (2) they must not and in
271 -- case (1) this is not important since we are exiting the scope
272 -- anyway.
274 -- Here is a simple example of the expansion of a controlled block :
276 -- declare
277 -- X : Controlled ;
278 -- Y : Controlled := Init;
280 -- type R is record
281 -- C : Controlled;
282 -- end record;
283 -- W : R;
284 -- Z : R := (C => X);
285 -- begin
286 -- X := Y;
287 -- W := Z;
288 -- end;
290 -- is expanded into
292 -- declare
293 -- _L : System.FI.Finalizable_Ptr;
295 -- procedure _Clean is
296 -- begin
297 -- Abort_Defer;
298 -- System.FI.Finalize_List (_L);
299 -- Abort_Undefer;
300 -- end _Clean;
302 -- X : Controlled;
303 -- Initialize (X);
304 -- Attach_To_Final_List (_L, Finalizable (X), 1);
305 -- Y : Controlled := Init;
306 -- Adjust (Y);
307 -- Attach_To_Final_List (_L, Finalizable (Y), 1);
309 -- type R is record
310 -- _C : Record_Controller;
311 -- C : Controlled;
312 -- end record;
313 -- W : R;
314 -- Deep_Initialize (W, _L, 1);
315 -- Z : R := (C => X);
316 -- Deep_Adjust (Z, _L, 1);
318 -- begin
319 -- Finalize (X);
320 -- X := Y;
321 -- Adjust (X);
323 -- Deep_Finalize (W, False);
324 -- W := Z;
325 -- Deep_Adjust (W, _L, 0);
326 -- at end
327 -- _Clean;
328 -- end;
330 function Global_Flist_Ref (Flist_Ref : Node_Id) return Boolean;
331 -- Return True if Flist_Ref refers to a global final list, either
332 -- the object GLobal_Final_List which is used to attach standalone
333 -- objects, or any of the list controllers associated with library
334 -- level access to controlled objects
336 ----------------------------
337 -- Build_Array_Deep_Procs --
338 ----------------------------
340 procedure Build_Array_Deep_Procs (Typ : Entity_Id) is
341 begin
342 Set_TSS (Typ,
343 Make_Deep_Proc (
344 Prim => Initialize_Case,
345 Typ => Typ,
346 Stmts => Make_Deep_Array_Body (Initialize_Case, Typ)));
348 if not Is_Return_By_Reference_Type (Typ) then
349 Set_TSS (Typ,
350 Make_Deep_Proc (
351 Prim => Adjust_Case,
352 Typ => Typ,
353 Stmts => Make_Deep_Array_Body (Adjust_Case, Typ)));
354 end if;
356 Set_TSS (Typ,
357 Make_Deep_Proc (
358 Prim => Finalize_Case,
359 Typ => Typ,
360 Stmts => Make_Deep_Array_Body (Finalize_Case, Typ)));
361 end Build_Array_Deep_Procs;
363 -----------------------------
364 -- Build_Controlling_Procs --
365 -----------------------------
367 procedure Build_Controlling_Procs (Typ : Entity_Id) is
368 begin
369 if Is_Array_Type (Typ) then
370 Build_Array_Deep_Procs (Typ);
372 else pragma Assert (Is_Record_Type (Typ));
373 Build_Record_Deep_Procs (Typ);
374 end if;
375 end Build_Controlling_Procs;
377 ----------------------
378 -- Build_Final_List --
379 ----------------------
381 procedure Build_Final_List (N : Node_Id; Typ : Entity_Id) is
382 Loc : constant Source_Ptr := Sloc (N);
383 Decl : Node_Id;
385 begin
386 Set_Associated_Final_Chain (Typ,
387 Make_Defining_Identifier (Loc,
388 New_External_Name (Chars (Typ), 'L')));
390 Decl :=
391 Make_Object_Declaration (Loc,
392 Defining_Identifier =>
393 Associated_Final_Chain (Typ),
394 Object_Definition =>
395 New_Reference_To
396 (RTE (RE_List_Controller), Loc));
398 -- The type may have been frozen already, and this is a late
399 -- freezing action, in which case the declaration must be elaborated
400 -- at once. If the call is for an allocator, the chain must also be
401 -- created now, because the freezing of the type does not build one.
402 -- Otherwise, the declaration is one of the freezing actions for a
403 -- user-defined type.
405 if Is_Frozen (Typ)
406 or else (Nkind (N) = N_Allocator
407 and then Ekind (Etype (N)) = E_Anonymous_Access_Type)
408 then
409 Insert_Action (N, Decl);
410 else
411 Append_Freeze_Action (Typ, Decl);
412 end if;
413 end Build_Final_List;
415 ---------------------
416 -- Build_Late_Proc --
417 ---------------------
419 procedure Build_Late_Proc (Typ : Entity_Id; Nam : Name_Id) is
420 begin
421 for Final_Prim in Name_Of'Range loop
422 if Name_Of (Final_Prim) = Nam then
423 Set_TSS (Typ,
424 Make_Deep_Proc (
425 Prim => Final_Prim,
426 Typ => Typ,
427 Stmts => Make_Deep_Record_Body (Final_Prim, Typ)));
428 end if;
429 end loop;
430 end Build_Late_Proc;
432 -----------------------------
433 -- Build_Record_Deep_Procs --
434 -----------------------------
436 procedure Build_Record_Deep_Procs (Typ : Entity_Id) is
437 begin
438 Set_TSS (Typ,
439 Make_Deep_Proc (
440 Prim => Initialize_Case,
441 Typ => Typ,
442 Stmts => Make_Deep_Record_Body (Initialize_Case, Typ)));
444 if not Is_Return_By_Reference_Type (Typ) then
445 Set_TSS (Typ,
446 Make_Deep_Proc (
447 Prim => Adjust_Case,
448 Typ => Typ,
449 Stmts => Make_Deep_Record_Body (Adjust_Case, Typ)));
450 end if;
452 Set_TSS (Typ,
453 Make_Deep_Proc (
454 Prim => Finalize_Case,
455 Typ => Typ,
456 Stmts => Make_Deep_Record_Body (Finalize_Case, Typ)));
457 end Build_Record_Deep_Procs;
459 ---------------------
460 -- Controlled_Type --
461 ---------------------
463 function Controlled_Type (T : Entity_Id) return Boolean is
465 function Has_Some_Controlled_Component (Rec : Entity_Id) return Boolean;
466 -- If type is not frozen yet, check explicitly among its components,
467 -- because flag is not necessarily set.
469 ------------------------------------
470 -- Has_Some_Controlled_Component --
471 ------------------------------------
473 function Has_Some_Controlled_Component (Rec : Entity_Id)
474 return Boolean
476 Comp : Entity_Id;
478 begin
479 if Has_Controlled_Component (Rec) then
480 return True;
482 elsif not Is_Frozen (Rec) then
483 if Is_Record_Type (Rec) then
484 Comp := First_Entity (Rec);
486 while Present (Comp) loop
487 if not Is_Type (Comp)
488 and then Controlled_Type (Etype (Comp))
489 then
490 return True;
491 end if;
493 Next_Entity (Comp);
494 end loop;
496 return False;
498 elsif Is_Array_Type (Rec) then
499 return Is_Controlled (Component_Type (Rec));
501 else
502 return Has_Controlled_Component (Rec);
503 end if;
504 else
505 return False;
506 end if;
507 end Has_Some_Controlled_Component;
509 -- Start of processing for Controlled_Type
511 begin
512 -- Class-wide types must be treated as controlled because they may
513 -- contain an extension that has controlled components
515 return (Is_Class_Wide_Type (T)
516 and then not No_Run_Time
517 and then not In_Finalization_Root (T))
518 or else Is_Controlled (T)
519 or else Has_Some_Controlled_Component (T)
520 or else (Is_Concurrent_Type (T)
521 and then Present (Corresponding_Record_Type (T))
522 and then Controlled_Type (Corresponding_Record_Type (T)));
523 end Controlled_Type;
525 --------------------------
526 -- Controller_Component --
527 --------------------------
529 function Controller_Component (Typ : Entity_Id) return Entity_Id is
530 T : Entity_Id := Base_Type (Typ);
531 Comp : Entity_Id;
532 Comp_Scop : Entity_Id;
533 Res : Entity_Id := Empty;
534 Res_Scop : Entity_Id := Empty;
536 begin
537 if Is_Class_Wide_Type (T) then
538 T := Root_Type (T);
539 end if;
541 if Is_Private_Type (T) then
542 T := Underlying_Type (T);
543 end if;
545 -- Fetch the outermost controller
547 Comp := First_Entity (T);
548 while Present (Comp) loop
549 if Chars (Comp) = Name_uController then
550 Comp_Scop := Scope (Original_Record_Component (Comp));
552 -- If this controller is at the outermost level, no need to
553 -- look for another one
555 if Comp_Scop = T then
556 return Comp;
558 -- Otherwise record the outermost one and continue looking
560 elsif Res = Empty or else Is_Ancestor (Res_Scop, Comp_Scop) then
561 Res := Comp;
562 Res_Scop := Comp_Scop;
563 end if;
564 end if;
566 Next_Entity (Comp);
567 end loop;
569 -- If we fall through the loop, there is no controller component
571 return Res;
572 end Controller_Component;
574 ------------------
575 -- Convert_View --
576 ------------------
578 function Convert_View
579 (Proc : Entity_Id;
580 Arg : Node_Id;
581 Ind : Pos := 1)
582 return Node_Id
584 Fent : Entity_Id := First_Entity (Proc);
585 Ftyp : Entity_Id;
586 Atyp : Entity_Id;
588 begin
589 for J in 2 .. Ind loop
590 Next_Entity (Fent);
591 end loop;
593 Ftyp := Etype (Fent);
595 if Nkind (Arg) = N_Type_Conversion
596 or else Nkind (Arg) = N_Unchecked_Type_Conversion
597 then
598 Atyp := Entity (Subtype_Mark (Arg));
599 else
600 Atyp := Etype (Arg);
601 end if;
603 if Is_Abstract (Proc) and then Is_Tagged_Type (Ftyp) then
604 return Unchecked_Convert_To (Class_Wide_Type (Ftyp), Arg);
606 elsif Ftyp /= Atyp
607 and then Present (Atyp)
608 and then
609 (Is_Private_Type (Ftyp) or else Is_Private_Type (Atyp))
610 and then Underlying_Type (Atyp) = Underlying_Type (Ftyp)
611 then
612 return Unchecked_Convert_To (Ftyp, Arg);
614 -- If the argument is already a conversion, as generated by
615 -- Make_Init_Call, set the target type to the type of the formal
616 -- directly, to avoid spurious typing problems.
618 elsif (Nkind (Arg) = N_Unchecked_Type_Conversion
619 or else Nkind (Arg) = N_Type_Conversion)
620 and then not Is_Class_Wide_Type (Atyp)
621 then
622 Set_Subtype_Mark (Arg, New_Occurrence_Of (Ftyp, Sloc (Arg)));
623 Set_Etype (Arg, Ftyp);
624 return Arg;
626 else
627 return Arg;
628 end if;
629 end Convert_View;
631 -------------------------------
632 -- Establish_Transient_Scope --
633 -------------------------------
635 -- This procedure is called each time a transient block has to be inserted
636 -- that is to say for each call to a function with unconstrained ot tagged
637 -- result. It creates a new scope on the stack scope in order to enclose
638 -- all transient variables generated
640 procedure Establish_Transient_Scope (N : Node_Id; Sec_Stack : Boolean) is
641 Loc : constant Source_Ptr := Sloc (N);
642 Wrap_Node : Node_Id;
644 Sec_Stk : constant Boolean :=
645 Sec_Stack and not Functions_Return_By_DSP_On_Target;
646 -- We never need a secondary stack if functions return by DSP
648 begin
649 -- Do not create a transient scope if we are already inside one
651 for S in reverse Scope_Stack.First .. Scope_Stack.Last loop
653 if Scope_Stack.Table (S).Is_Transient then
654 if Sec_Stk then
655 Set_Uses_Sec_Stack (Scope_Stack.Table (S).Entity);
656 end if;
658 return;
660 -- If we have encountered Standard there are no enclosing
661 -- transient scopes.
663 elsif Scope_Stack.Table (S).Entity = Standard_Standard then
664 exit;
666 end if;
667 end loop;
669 Wrap_Node := Find_Node_To_Be_Wrapped (N);
671 -- Case of no wrap node, false alert, no transient scope needed
673 if No (Wrap_Node) then
674 null;
676 -- Transient scope is required
678 else
679 New_Scope (New_Internal_Entity (E_Block, Current_Scope, Loc, 'B'));
680 Set_Scope_Is_Transient;
682 if Sec_Stk then
683 Set_Uses_Sec_Stack (Current_Scope);
684 Check_Restriction (No_Secondary_Stack, N);
685 end if;
687 Set_Etype (Current_Scope, Standard_Void_Type);
688 Set_Node_To_Be_Wrapped (Wrap_Node);
690 if Debug_Flag_W then
691 Write_Str (" <Transient>");
692 Write_Eol;
693 end if;
694 end if;
695 end Establish_Transient_Scope;
697 ----------------------------
698 -- Expand_Cleanup_Actions --
699 ----------------------------
701 procedure Expand_Cleanup_Actions (N : Node_Id) is
702 Loc : Source_Ptr;
703 S : constant Entity_Id :=
704 Current_Scope;
705 Flist : constant Entity_Id :=
706 Finalization_Chain_Entity (S);
707 Is_Task : constant Boolean :=
708 (Nkind (Original_Node (N)) = N_Task_Body);
709 Is_Master : constant Boolean :=
710 Nkind (N) /= N_Entry_Body
711 and then Is_Task_Master (N);
712 Is_Protected : constant Boolean :=
713 Nkind (N) = N_Subprogram_Body
714 and then Is_Protected_Subprogram_Body (N);
715 Is_Task_Allocation : constant Boolean :=
716 Nkind (N) = N_Block_Statement
717 and then Is_Task_Allocation_Block (N);
718 Is_Asynchronous_Call : constant Boolean :=
719 Nkind (N) = N_Block_Statement
720 and then Is_Asynchronous_Call_Block (N);
722 Clean : Entity_Id;
723 Mark : Entity_Id := Empty;
724 New_Decls : List_Id := New_List;
725 Blok : Node_Id;
726 Wrapped : Boolean;
727 Chain : Entity_Id := Empty;
728 Decl : Node_Id;
729 Old_Poll : Boolean;
731 begin
733 -- Compute a location that is not directly in the user code in
734 -- order to avoid to generate confusing debug info. A good
735 -- approximation is the name of the outer user-defined scope
737 declare
738 S1 : Entity_Id := S;
740 begin
741 while not Comes_From_Source (S1) and then S1 /= Standard_Standard loop
742 S1 := Scope (S1);
743 end loop;
745 Loc := Sloc (S1);
746 end;
748 -- There are cleanup actions only if the secondary stack needs
749 -- releasing or some finalizations are needed or in the context
750 -- of tasking
752 if Uses_Sec_Stack (Current_Scope)
753 and then not Sec_Stack_Needed_For_Return (Current_Scope)
754 then
755 null;
756 elsif No (Flist)
757 and then not Is_Master
758 and then not Is_Task
759 and then not Is_Protected
760 and then not Is_Task_Allocation
761 and then not Is_Asynchronous_Call
762 then
763 return;
764 end if;
766 -- Set polling off, since we don't need to poll during cleanup
767 -- actions, and indeed for the cleanup routine, which is executed
768 -- with aborts deferred, we don't want polling.
770 Old_Poll := Polling_Required;
771 Polling_Required := False;
773 -- Make sure we have a declaration list, since we will add to it
775 if No (Declarations (N)) then
776 Set_Declarations (N, New_List);
777 end if;
779 -- The task activation call has already been built for task
780 -- allocation blocks.
782 if not Is_Task_Allocation then
783 Build_Task_Activation_Call (N);
784 end if;
786 if Is_Master then
787 Establish_Task_Master (N);
788 end if;
790 -- If secondary stack is in use, expand:
791 -- _Mxx : constant Mark_Id := SS_Mark;
793 -- Suppress calls to SS_Mark and SS_Release if Java_VM,
794 -- since we never use the secondary stack on the JVM.
796 if Uses_Sec_Stack (Current_Scope)
797 and then not Sec_Stack_Needed_For_Return (Current_Scope)
798 and then not Java_VM
799 then
800 Mark := Make_Defining_Identifier (Loc, New_Internal_Name ('M'));
801 Append_To (New_Decls,
802 Make_Object_Declaration (Loc,
803 Defining_Identifier => Mark,
804 Object_Definition => New_Reference_To (RTE (RE_Mark_Id), Loc),
805 Expression =>
806 Make_Function_Call (Loc,
807 Name => New_Reference_To (RTE (RE_SS_Mark), Loc))));
809 Set_Uses_Sec_Stack (Current_Scope, False);
810 end if;
812 -- If finalization list is present then expand:
813 -- Local_Final_List : System.FI.Finalizable_Ptr;
815 if Present (Flist) then
816 Append_To (New_Decls,
817 Make_Object_Declaration (Loc,
818 Defining_Identifier => Flist,
819 Object_Definition =>
820 New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
821 end if;
823 -- Clean-up procedure definition
825 Clean := Make_Defining_Identifier (Loc, Name_uClean);
826 Set_Suppress_Elaboration_Warnings (Clean);
827 Append_To (New_Decls,
828 Make_Clean (N, Clean, Mark, Flist,
829 Is_Task,
830 Is_Master,
831 Is_Protected,
832 Is_Task_Allocation,
833 Is_Asynchronous_Call));
835 -- If exception handlers are present, wrap the Sequence of
836 -- statements in a block because it is not possible to get
837 -- exception handlers and an AT END call in the same scope.
839 if Present (Exception_Handlers (Handled_Statement_Sequence (N))) then
840 Blok :=
841 Make_Block_Statement (Loc,
842 Handled_Statement_Sequence => Handled_Statement_Sequence (N));
843 Set_Handled_Statement_Sequence (N,
844 Make_Handled_Sequence_Of_Statements (Loc, New_List (Blok)));
845 Wrapped := True;
847 -- Otherwise we do not wrap
849 else
850 Wrapped := False;
851 Blok := Empty;
852 end if;
854 -- Don't move the _chain Activation_Chain declaration in task
855 -- allocation blocks. Task allocation blocks use this object
856 -- in their cleanup handlers, and gigi complains if it is declared
857 -- in the sequence of statements of the scope that declares the
858 -- handler.
860 if Is_Task_Allocation then
861 Chain := Activation_Chain_Entity (N);
862 Decl := First (Declarations (N));
864 while Nkind (Decl) /= N_Object_Declaration
865 or else Defining_Identifier (Decl) /= Chain
866 loop
867 Next (Decl);
868 pragma Assert (Present (Decl));
869 end loop;
871 Remove (Decl);
872 Prepend_To (New_Decls, Decl);
873 end if;
875 -- Now we move the declarations into the Sequence of statements
876 -- in order to get them protected by the AT END call. It may seem
877 -- weird to put declarations in the sequence of statement but in
878 -- fact nothing forbids that at the tree level. We also set the
879 -- First_Real_Statement field so that we remember where the real
880 -- statements (i.e. original statements) begin. Note that if we
881 -- wrapped the statements, the first real statement is inside the
882 -- inner block. If the First_Real_Statement is already set (as is
883 -- the case for subprogram bodies that are expansions of task bodies)
884 -- then do not reset it, because its declarative part would migrate
885 -- to the statement part.
887 if not Wrapped then
888 if No (First_Real_Statement (Handled_Statement_Sequence (N))) then
889 Set_First_Real_Statement (Handled_Statement_Sequence (N),
890 First (Statements (Handled_Statement_Sequence (N))));
891 end if;
893 else
894 Set_First_Real_Statement (Handled_Statement_Sequence (N), Blok);
895 end if;
897 Append_List_To (Declarations (N),
898 Statements (Handled_Statement_Sequence (N)));
899 Set_Statements (Handled_Statement_Sequence (N), Declarations (N));
901 -- We need to reset the Sloc of the handled statement sequence to
902 -- properly reflect the new initial "statement" in the sequence.
904 Set_Sloc
905 (Handled_Statement_Sequence (N), Sloc (First (Declarations (N))));
907 -- The declarations of the _Clean procedure and finalization chain
908 -- replace the old declarations that have been moved inward
910 Set_Declarations (N, New_Decls);
911 Analyze_Declarations (New_Decls);
913 -- The At_End call is attached to the sequence of statements.
915 declare
916 HSS : Node_Id;
918 begin
919 -- If the construct is a protected subprogram, then the call to
920 -- the corresponding unprotected program appears in a block which
921 -- is the last statement in the body, and it is this block that
922 -- must be covered by the At_End handler.
924 if Is_Protected then
925 HSS := Handled_Statement_Sequence
926 (Last (Statements (Handled_Statement_Sequence (N))));
927 else
928 HSS := Handled_Statement_Sequence (N);
929 end if;
931 Set_At_End_Proc (HSS, New_Occurrence_Of (Clean, Loc));
932 Expand_At_End_Handler (HSS, Empty);
933 end;
935 -- Restore saved polling mode
937 Polling_Required := Old_Poll;
938 end Expand_Cleanup_Actions;
940 -------------------------------
941 -- Expand_Ctrl_Function_Call --
942 -------------------------------
944 procedure Expand_Ctrl_Function_Call (N : Node_Id) is
945 Loc : constant Source_Ptr := Sloc (N);
946 Rtype : constant Entity_Id := Etype (N);
947 Utype : constant Entity_Id := Underlying_Type (Rtype);
948 Ref : Node_Id;
949 Action : Node_Id;
951 Attach_Level : Uint := Uint_1;
952 Len_Ref : Node_Id := Empty;
954 function Last_Array_Component
955 (Ref : Node_Id;
956 Typ : Entity_Id)
957 return Node_Id;
958 -- Creates a reference to the last component of the array object
959 -- designated by Ref whose type is Typ.
961 function Last_Array_Component
962 (Ref : Node_Id;
963 Typ : Entity_Id)
964 return Node_Id
966 N : Int;
967 Index_List : List_Id := New_List;
969 begin
970 N := 1;
971 while N <= Number_Dimensions (Typ) loop
972 Append_To (Index_List,
973 Make_Attribute_Reference (Loc,
974 Prefix => Duplicate_Subexpr (Ref),
975 Attribute_Name => Name_Last,
976 Expressions => New_List (
977 Make_Integer_Literal (Loc, N))));
979 N := N + 1;
980 end loop;
982 return
983 Make_Indexed_Component (Loc,
984 Prefix => Duplicate_Subexpr (Ref),
985 Expressions => Index_List);
986 end Last_Array_Component;
988 -- Start of processing for Expand_Ctrl_Function_Call
990 begin
991 -- Optimization, if the returned value (which is on the sec-stack)
992 -- is returned again, no need to copy/readjust/finalize, we can just
993 -- pass the value thru (see Expand_N_Return_Statement), and thus no
994 -- attachment is needed
996 if Nkind (Parent (N)) = N_Return_Statement then
997 return;
998 end if;
1000 -- Resolution is now finished, make sure we don't start analysis again
1001 -- because of the duplication
1003 Set_Analyzed (N);
1004 Ref := Duplicate_Subexpr (N);
1006 -- Now we can generate the Attach Call, note that this value is
1007 -- always in the (secondary) stack and thus is attached to a singly
1008 -- linked final list:
1010 -- Resx := F (X)'reference;
1011 -- Attach_To_Final_List (_Lx, Resx.all, 1);
1012 -- or when there are controlled components
1013 -- Attach_To_Final_List (_Lx, Resx._controller, 1);
1014 -- or if it is an array with is_controlled components
1015 -- Attach_To_Final_List (_Lx, Resx (Resx'last), 3);
1016 -- An attach level of 3 means that a whole array is to be
1017 -- attached to the finalization list
1018 -- or if it is an array with has_controlled components
1019 -- Attach_To_Final_List (_Lx, Resx (Resx'last)._controller, 3);
1021 if Has_Controlled_Component (Rtype) then
1022 declare
1023 T1 : Entity_Id := Rtype;
1024 T2 : Entity_Id := Utype;
1026 begin
1027 if Is_Array_Type (T2) then
1028 Len_Ref :=
1029 Make_Attribute_Reference (Loc,
1030 Prefix => Duplicate_Subexpr (Unchecked_Convert_To (T2, Ref)),
1031 Attribute_Name => Name_Length);
1032 end if;
1034 while Is_Array_Type (T2) loop
1035 if T1 /= T2 then
1036 Ref := Unchecked_Convert_To (T2, Ref);
1037 end if;
1038 Ref := Last_Array_Component (Ref, T2);
1039 Attach_Level := Uint_3;
1040 T1 := Component_Type (T2);
1041 T2 := Underlying_Type (T1);
1042 end loop;
1044 if Has_Controlled_Component (T2) then
1045 if T1 /= T2 then
1046 Ref := Unchecked_Convert_To (T2, Ref);
1047 end if;
1048 Ref :=
1049 Make_Selected_Component (Loc,
1050 Prefix => Ref,
1051 Selector_Name => Make_Identifier (Loc, Name_uController));
1052 end if;
1053 end;
1055 -- Here we know that 'Ref' has a controller so we may as well
1056 -- attach it directly
1058 Action :=
1059 Make_Attach_Call (
1060 Obj_Ref => Ref,
1061 Flist_Ref => Find_Final_List (Current_Scope),
1062 With_Attach => Make_Integer_Literal (Loc, Attach_Level));
1064 else
1065 -- Here, we have a controlled type that does not seem to have
1066 -- controlled components but it could be a class wide type whose
1067 -- further derivations have controlled components. So we don't know
1068 -- if the object itself needs to be attached or if it
1069 -- has a record controller. We need to call a runtime function
1070 -- (Deep_Tag_Attach) which knows what to do thanks to the
1071 -- RC_Offset in the dispatch table.
1073 Action :=
1074 Make_Procedure_Call_Statement (Loc,
1075 Name => New_Reference_To (RTE (RE_Deep_Tag_Attach), Loc),
1076 Parameter_Associations => New_List (
1077 Find_Final_List (Current_Scope),
1079 Make_Attribute_Reference (Loc,
1080 Prefix => Ref,
1081 Attribute_Name => Name_Address),
1083 Make_Integer_Literal (Loc, Attach_Level)));
1084 end if;
1086 if Present (Len_Ref) then
1087 Action :=
1088 Make_Implicit_If_Statement (N,
1089 Condition => Make_Op_Gt (Loc,
1090 Left_Opnd => Len_Ref,
1091 Right_Opnd => Make_Integer_Literal (Loc, 0)),
1092 Then_Statements => New_List (Action));
1093 end if;
1095 Insert_Action (N, Action);
1096 end Expand_Ctrl_Function_Call;
1098 ---------------------------
1099 -- Expand_N_Package_Body --
1100 ---------------------------
1102 -- Add call to Activate_Tasks if body is an activator (actual
1103 -- processing is in chapter 9).
1105 -- Generate subprogram descriptor for elaboration routine
1107 -- ENcode entity names in package body
1109 procedure Expand_N_Package_Body (N : Node_Id) is
1110 Ent : Entity_Id := Corresponding_Spec (N);
1112 begin
1113 -- This is done only for non-generic packages
1115 if Ekind (Ent) = E_Package then
1116 New_Scope (Corresponding_Spec (N));
1117 Build_Task_Activation_Call (N);
1118 Pop_Scope;
1119 end if;
1121 Set_Elaboration_Flag (N, Corresponding_Spec (N));
1123 -- Generate a subprogram descriptor for the elaboration routine of
1124 -- a package body if the package body has no pending instantiations
1125 -- and it has generated at least one exception handler
1127 if Present (Handler_Records (Body_Entity (Ent)))
1128 and then Is_Compilation_Unit (Ent)
1129 and then not Delay_Subprogram_Descriptors (Body_Entity (Ent))
1130 then
1131 Generate_Subprogram_Descriptor_For_Package
1132 (N, Body_Entity (Ent));
1133 end if;
1135 Set_In_Package_Body (Ent, False);
1137 -- Set to encode entity names in package body before gigi is called
1139 Qualify_Entity_Names (N);
1140 end Expand_N_Package_Body;
1142 ----------------------------------
1143 -- Expand_N_Package_Declaration --
1144 ----------------------------------
1146 -- Add call to Activate_Tasks if there are tasks declared and the
1147 -- package has no body. Note that in Ada83, this may result in
1148 -- premature activation of some tasks, given that we cannot tell
1149 -- whether a body will eventually appear.
1151 procedure Expand_N_Package_Declaration (N : Node_Id) is
1152 begin
1153 if Nkind (Parent (N)) = N_Compilation_Unit
1154 and then not Body_Required (Parent (N))
1155 and then not Unit_Requires_Body (Defining_Entity (N))
1156 and then Present (Activation_Chain_Entity (N))
1157 then
1158 New_Scope (Defining_Entity (N));
1159 Build_Task_Activation_Call (N);
1160 Pop_Scope;
1161 end if;
1163 -- Note: it is not necessary to worry about generating a subprogram
1164 -- descriptor, since the only way to get exception handlers into a
1165 -- package spec is to include instantiations, and that would cause
1166 -- generation of subprogram descriptors to be delayed in any case.
1168 -- Set to encode entity names in package spec before gigi is called
1170 Qualify_Entity_Names (N);
1171 end Expand_N_Package_Declaration;
1173 ---------------------
1174 -- Find_Final_List --
1175 ---------------------
1177 function Find_Final_List
1178 (E : Entity_Id;
1179 Ref : Node_Id := Empty)
1180 return Node_Id
1182 Loc : constant Source_Ptr := Sloc (Ref);
1183 S : Entity_Id;
1184 Id : Entity_Id;
1185 R : Node_Id;
1187 begin
1188 -- Case of an internal component. The Final list is the record
1189 -- controller of the enclosing record
1191 if Present (Ref) then
1192 R := Ref;
1193 loop
1194 case Nkind (R) is
1195 when N_Unchecked_Type_Conversion | N_Type_Conversion =>
1196 R := Expression (R);
1198 when N_Indexed_Component | N_Explicit_Dereference =>
1199 R := Prefix (R);
1201 when N_Selected_Component =>
1202 R := Prefix (R);
1203 exit;
1205 when N_Identifier =>
1206 exit;
1208 when others =>
1209 raise Program_Error;
1210 end case;
1211 end loop;
1213 return
1214 Make_Selected_Component (Loc,
1215 Prefix =>
1216 Make_Selected_Component (Loc,
1217 Prefix => R,
1218 Selector_Name => Make_Identifier (Loc, Name_uController)),
1219 Selector_Name => Make_Identifier (Loc, Name_F));
1221 -- Case of a dynamically allocated object. The final list is the
1222 -- corresponding list controller (The next entity in the scope of
1223 -- the access type with the right type). If the type comes from a
1224 -- With_Type clause, no controller was created, and we use the
1225 -- global chain instead.
1227 elsif Is_Access_Type (E) then
1228 if not From_With_Type (E) then
1229 return
1230 Make_Selected_Component (Loc,
1231 Prefix =>
1232 New_Reference_To
1233 (Associated_Final_Chain (Base_Type (E)), Loc),
1234 Selector_Name => Make_Identifier (Loc, Name_F));
1235 else
1236 return New_Reference_To (RTE (RE_Global_Final_List), Sloc (E));
1237 end if;
1239 else
1240 if Is_Dynamic_Scope (E) then
1241 S := E;
1242 else
1243 S := Enclosing_Dynamic_Scope (E);
1244 end if;
1246 -- When the finalization chain entity is 'Error', it means that
1247 -- there should not be any chain at that level and that the
1248 -- enclosing one should be used
1250 -- This is a nasty kludge, see ??? note in exp_ch11
1252 while Finalization_Chain_Entity (S) = Error loop
1253 S := Enclosing_Dynamic_Scope (S);
1254 end loop;
1256 if S = Standard_Standard then
1257 return New_Reference_To (RTE (RE_Global_Final_List), Sloc (E));
1258 else
1259 if No (Finalization_Chain_Entity (S)) then
1261 Id := Make_Defining_Identifier (Sloc (S),
1262 New_Internal_Name ('F'));
1263 Set_Finalization_Chain_Entity (S, Id);
1265 -- Set momentarily some semantics attributes to allow normal
1266 -- analysis of expansions containing references to this chain.
1267 -- Will be fully decorated during the expansion of the scope
1268 -- itself
1270 Set_Ekind (Id, E_Variable);
1271 Set_Etype (Id, RTE (RE_Finalizable_Ptr));
1272 end if;
1274 return New_Reference_To (Finalization_Chain_Entity (S), Sloc (E));
1275 end if;
1276 end if;
1277 end Find_Final_List;
1279 -----------------------------
1280 -- Find_Node_To_Be_Wrapped --
1281 -----------------------------
1283 function Find_Node_To_Be_Wrapped (N : Node_Id) return Node_Id is
1284 P : Node_Id;
1285 The_Parent : Node_Id;
1287 begin
1288 The_Parent := N;
1289 loop
1290 P := The_Parent;
1291 pragma Assert (P /= Empty);
1292 The_Parent := Parent (P);
1294 case Nkind (The_Parent) is
1296 -- Simple statement can be wrapped
1298 when N_Pragma =>
1299 return The_Parent;
1301 -- Usually assignments are good candidate for wrapping
1302 -- except when they have been generated as part of a
1303 -- controlled aggregate where the wrapping should take
1304 -- place more globally.
1306 when N_Assignment_Statement =>
1307 if No_Ctrl_Actions (The_Parent) then
1308 null;
1309 else
1310 return The_Parent;
1311 end if;
1313 -- An entry call statement is a special case if it occurs in
1314 -- the context of a Timed_Entry_Call. In this case we wrap
1315 -- the entire timed entry call.
1317 when N_Entry_Call_Statement |
1318 N_Procedure_Call_Statement =>
1319 if Nkind (Parent (The_Parent)) = N_Entry_Call_Alternative
1320 and then
1321 Nkind (Parent (Parent (The_Parent))) = N_Timed_Entry_Call
1322 then
1323 return Parent (Parent (The_Parent));
1324 else
1325 return The_Parent;
1326 end if;
1328 -- Object declarations are also a boundary for the transient scope
1329 -- even if they are not really wrapped
1330 -- (see Wrap_Transient_Declaration)
1332 when N_Object_Declaration |
1333 N_Object_Renaming_Declaration |
1334 N_Subtype_Declaration =>
1335 return The_Parent;
1337 -- The expression itself is to be wrapped if its parent is a
1338 -- compound statement or any other statement where the expression
1339 -- is known to be scalar
1341 when N_Accept_Alternative |
1342 N_Attribute_Definition_Clause |
1343 N_Case_Statement |
1344 N_Code_Statement |
1345 N_Delay_Alternative |
1346 N_Delay_Until_Statement |
1347 N_Delay_Relative_Statement |
1348 N_Discriminant_Association |
1349 N_Elsif_Part |
1350 N_Entry_Body_Formal_Part |
1351 N_Exit_Statement |
1352 N_If_Statement |
1353 N_Iteration_Scheme |
1354 N_Terminate_Alternative =>
1355 return P;
1357 when N_Attribute_Reference =>
1359 if Is_Procedure_Attribute_Name
1360 (Attribute_Name (The_Parent))
1361 then
1362 return The_Parent;
1363 end if;
1365 -- ??? No scheme yet for "for I in Expression'Range loop"
1366 -- ??? the current scheme for Expression wrapping doesn't apply
1367 -- ??? because a RANGE is NOT an expression. Tricky problem...
1368 -- ??? while this problem is not solved we have a potential for
1369 -- ??? leak and unfinalized intermediate objects here.
1371 when N_Loop_Parameter_Specification =>
1372 return Empty;
1374 -- The following nodes contains "dummy calls" which don't
1375 -- need to be wrapped.
1377 when N_Parameter_Specification |
1378 N_Discriminant_Specification |
1379 N_Component_Declaration =>
1380 return Empty;
1382 -- The return statement is not to be wrapped when the function
1383 -- itself needs wrapping at the outer-level
1385 when N_Return_Statement =>
1386 if Requires_Transient_Scope (Return_Type (The_Parent)) then
1387 return Empty;
1388 else
1389 return The_Parent;
1390 end if;
1392 -- If we leave a scope without having been able to find a node to
1393 -- wrap, something is going wrong but this can happen in error
1394 -- situation that are not detected yet (such as a dynamic string
1395 -- in a pragma export)
1397 when N_Subprogram_Body |
1398 N_Package_Declaration |
1399 N_Package_Body |
1400 N_Block_Statement =>
1401 return Empty;
1403 -- otherwise continue the search
1405 when others =>
1406 null;
1407 end case;
1408 end loop;
1409 end Find_Node_To_Be_Wrapped;
1411 ----------------------
1412 -- Global_Flist_Ref --
1413 ----------------------
1415 function Global_Flist_Ref (Flist_Ref : Node_Id) return Boolean is
1416 Flist : Entity_Id;
1418 begin
1419 -- Look for the Global_Final_List
1421 if Is_Entity_Name (Flist_Ref) then
1422 Flist := Entity (Flist_Ref);
1424 -- Look for the final list associated with an access to controlled
1426 elsif Nkind (Flist_Ref) = N_Selected_Component
1427 and then Is_Entity_Name (Prefix (Flist_Ref))
1428 then
1429 Flist := Entity (Prefix (Flist_Ref));
1430 else
1431 return False;
1432 end if;
1434 return Present (Flist)
1435 and then Present (Scope (Flist))
1436 and then Enclosing_Dynamic_Scope (Flist) = Standard_Standard;
1437 end Global_Flist_Ref;
1439 ----------------------------------
1440 -- Has_New_Controlled_Component --
1441 ----------------------------------
1443 function Has_New_Controlled_Component (E : Entity_Id) return Boolean is
1444 Comp : Entity_Id;
1446 begin
1447 if not Is_Tagged_Type (E) then
1448 return Has_Controlled_Component (E);
1449 elsif not Is_Derived_Type (E) then
1450 return Has_Controlled_Component (E);
1451 end if;
1453 Comp := First_Component (E);
1454 while Present (Comp) loop
1456 if Chars (Comp) = Name_uParent then
1457 null;
1459 elsif Scope (Original_Record_Component (Comp)) = E
1460 and then Controlled_Type (Etype (Comp))
1461 then
1462 return True;
1463 end if;
1465 Next_Component (Comp);
1466 end loop;
1468 return False;
1469 end Has_New_Controlled_Component;
1471 --------------------------
1472 -- In_Finalization_Root --
1473 --------------------------
1475 -- It would seem simpler to test Scope (RTE (RE_Root_Controlled)) but
1476 -- the purpose of this function is to avoid a circular call to Rtsfind
1477 -- which would been caused by such a test.
1479 function In_Finalization_Root (E : Entity_Id) return Boolean is
1480 S : constant Entity_Id := Scope (E);
1482 begin
1483 return Chars (Scope (S)) = Name_System
1484 and then Chars (S) = Name_Finalization_Root
1485 and then Scope (Scope (S)) = Standard_Standard;
1486 end In_Finalization_Root;
1488 ------------------------------------
1489 -- Insert_Actions_In_Scope_Around --
1490 ------------------------------------
1492 procedure Insert_Actions_In_Scope_Around (N : Node_Id) is
1493 SE : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
1495 begin
1496 if Present (SE.Actions_To_Be_Wrapped_Before) then
1497 Insert_List_Before (N, SE.Actions_To_Be_Wrapped_Before);
1498 SE.Actions_To_Be_Wrapped_Before := No_List;
1499 end if;
1501 if Present (SE.Actions_To_Be_Wrapped_After) then
1502 Insert_List_After (N, SE.Actions_To_Be_Wrapped_After);
1503 SE.Actions_To_Be_Wrapped_After := No_List;
1504 end if;
1505 end Insert_Actions_In_Scope_Around;
1507 -----------------------
1508 -- Make_Adjust_Call --
1509 -----------------------
1511 function Make_Adjust_Call
1512 (Ref : Node_Id;
1513 Typ : Entity_Id;
1514 Flist_Ref : Node_Id;
1515 With_Attach : Node_Id)
1516 return List_Id
1518 Loc : constant Source_Ptr := Sloc (Ref);
1519 Res : constant List_Id := New_List;
1520 Utyp : Entity_Id;
1521 Proc : Entity_Id;
1522 Cref : Node_Id := Ref;
1523 Cref2 : Node_Id;
1524 Attach : Node_Id := With_Attach;
1526 begin
1527 if Is_Class_Wide_Type (Typ) then
1528 Utyp := Underlying_Type (Base_Type (Root_Type (Typ)));
1529 else
1530 Utyp := Underlying_Type (Base_Type (Typ));
1531 end if;
1533 Set_Assignment_OK (Cref);
1535 -- Deal with non-tagged derivation of private views
1537 if Is_Untagged_Derivation (Typ) then
1538 Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
1539 Cref := Unchecked_Convert_To (Utyp, Cref);
1540 Set_Assignment_OK (Cref);
1541 -- To prevent problems with UC see 1.156 RH ???
1542 end if;
1544 -- If the underlying_type is a subtype, we are dealing with
1545 -- the completion of a private type. We need to access
1546 -- the base type and generate a conversion to it.
1548 if Utyp /= Base_Type (Utyp) then
1549 pragma Assert (Is_Private_Type (Typ));
1550 Utyp := Base_Type (Utyp);
1551 Cref := Unchecked_Convert_To (Utyp, Cref);
1552 end if;
1554 -- We do not need to attach to one of the Global Final Lists
1555 -- the objects whose type is Finalize_Storage_Only
1557 if Finalize_Storage_Only (Typ)
1558 and then (Global_Flist_Ref (Flist_Ref)
1559 or else Entity (Constant_Value (RTE (RE_Garbage_Collected)))
1560 = Standard_True)
1561 then
1562 Attach := Make_Integer_Literal (Loc, 0);
1563 end if;
1565 -- Generate:
1566 -- Deep_Adjust (Flist_Ref, Ref, With_Attach);
1568 if Has_Controlled_Component (Utyp)
1569 or else Is_Class_Wide_Type (Typ)
1570 then
1571 if Is_Tagged_Type (Utyp) then
1572 Proc := Find_Prim_Op (Utyp, Deep_Name_Of (Adjust_Case));
1574 else
1575 Proc := TSS (Utyp, Deep_Name_Of (Adjust_Case));
1576 end if;
1578 Cref := Convert_View (Proc, Cref, 2);
1580 Append_To (Res,
1581 Make_Procedure_Call_Statement (Loc,
1582 Name => New_Reference_To (Proc, Loc),
1583 Parameter_Associations =>
1584 New_List (Flist_Ref, Cref, Attach)));
1586 -- Generate:
1587 -- if With_Attach then
1588 -- Attach_To_Final_List (Ref, Flist_Ref);
1589 -- end if;
1590 -- Adjust (Ref);
1592 else -- Is_Controlled (Utyp)
1594 Proc := Find_Prim_Op (Utyp, Name_Of (Adjust_Case));
1595 Cref := Convert_View (Proc, Cref);
1596 Cref2 := New_Copy_Tree (Cref);
1598 Append_To (Res,
1599 Make_Procedure_Call_Statement (Loc,
1600 Name => New_Reference_To (Proc, Loc),
1601 Parameter_Associations => New_List (Cref2)));
1603 Append_To (Res, Make_Attach_Call (Cref, Flist_Ref, Attach));
1605 -- Treat this as a reference to Adjust if the Adjust routine
1606 -- comes from source. The call is not explicit, but it is near
1607 -- enough, and we won't typically get explicit adjust calls.
1609 if Comes_From_Source (Proc) then
1610 Generate_Reference (Proc, Ref);
1611 end if;
1612 end if;
1614 return Res;
1615 end Make_Adjust_Call;
1617 ----------------------
1618 -- Make_Attach_Call --
1619 ----------------------
1621 -- Generate:
1622 -- System.FI.Attach_To_Final_List (Flist, Ref, Nb_Link)
1624 function Make_Attach_Call
1625 (Obj_Ref : Node_Id;
1626 Flist_Ref : Node_Id;
1627 With_Attach : Node_Id)
1628 return Node_Id
1630 Loc : constant Source_Ptr := Sloc (Obj_Ref);
1632 begin
1633 -- Optimization: If the number of links is statically '0', don't
1634 -- call the attach_proc.
1636 if Nkind (With_Attach) = N_Integer_Literal
1637 and then Intval (With_Attach) = Uint_0
1638 then
1639 return Make_Null_Statement (Loc);
1640 end if;
1642 return
1643 Make_Procedure_Call_Statement (Loc,
1644 Name => New_Reference_To (RTE (RE_Attach_To_Final_List), Loc),
1645 Parameter_Associations => New_List (
1646 Flist_Ref,
1647 OK_Convert_To (RTE (RE_Finalizable), Obj_Ref),
1648 With_Attach));
1649 end Make_Attach_Call;
1651 ----------------
1652 -- Make_Clean --
1653 ----------------
1655 function Make_Clean
1656 (N : Node_Id;
1657 Clean : Entity_Id;
1658 Mark : Entity_Id;
1659 Flist : Entity_Id;
1660 Is_Task : Boolean;
1661 Is_Master : Boolean;
1662 Is_Protected_Subprogram : Boolean;
1663 Is_Task_Allocation_Block : Boolean;
1664 Is_Asynchronous_Call_Block : Boolean)
1665 return Node_Id
1667 Loc : constant Source_Ptr := Sloc (Clean);
1669 Stmt : List_Id := New_List;
1670 Sbody : Node_Id;
1671 Spec : Node_Id;
1672 Name : Node_Id;
1673 Param : Node_Id;
1674 Unlock : Node_Id;
1675 Param_Type : Entity_Id;
1676 Pid : Entity_Id := Empty;
1677 Cancel_Param : Entity_Id;
1679 begin
1680 if Is_Task then
1681 if Restricted_Profile then
1682 Append_To
1683 (Stmt, Build_Runtime_Call (Loc, RE_Complete_Restricted_Task));
1684 else
1685 Append_To (Stmt, Build_Runtime_Call (Loc, RE_Complete_Task));
1686 end if;
1688 elsif Is_Master then
1689 if Restrictions (No_Task_Hierarchy) = False then
1690 Append_To (Stmt, Build_Runtime_Call (Loc, RE_Complete_Master));
1691 end if;
1693 elsif Is_Protected_Subprogram then
1695 -- Add statements to the cleanup handler of the (ordinary)
1696 -- subprogram expanded to implement a protected subprogram,
1697 -- unlocking the protected object parameter and undeferring abortion.
1698 -- If this is a protected procedure, and the object contains
1699 -- entries, this also calls the entry service routine.
1701 -- NOTE: This cleanup handler references _object, a parameter
1702 -- to the procedure.
1704 -- Find the _object parameter representing the protected object.
1706 Spec := Parent (Corresponding_Spec (N));
1708 Param := First (Parameter_Specifications (Spec));
1709 loop
1710 Param_Type := Etype (Parameter_Type (Param));
1712 if Ekind (Param_Type) = E_Record_Type then
1713 Pid := Corresponding_Concurrent_Type (Param_Type);
1714 end if;
1716 exit when not Present (Param) or else Present (Pid);
1717 Next (Param);
1718 end loop;
1720 pragma Assert (Present (Param));
1722 -- If the associated protected object declares entries,
1723 -- a protected procedure has to service entry queues.
1724 -- In this case, add
1726 -- Service_Entries (_object._object'Access);
1728 -- _object is the record used to implement the protected object.
1729 -- It is a parameter to the protected subprogram.
1731 if Nkind (Specification (N)) = N_Procedure_Specification
1732 and then Has_Entries (Pid)
1733 then
1734 if Abort_Allowed
1735 or else Restrictions (No_Entry_Queue) = False
1736 or else Number_Entries (Pid) > 1
1737 then
1738 Name := New_Reference_To (RTE (RE_Service_Entries), Loc);
1739 else
1740 Name := New_Reference_To (RTE (RE_Service_Entry), Loc);
1741 end if;
1743 Append_To (Stmt,
1744 Make_Procedure_Call_Statement (Loc,
1745 Name => Name,
1746 Parameter_Associations => New_List (
1747 Make_Attribute_Reference (Loc,
1748 Prefix =>
1749 Make_Selected_Component (Loc,
1750 Prefix => New_Reference_To (
1751 Defining_Identifier (Param), Loc),
1752 Selector_Name =>
1753 Make_Identifier (Loc, Name_uObject)),
1754 Attribute_Name => Name_Unchecked_Access))));
1755 end if;
1757 -- Unlock (_object._object'Access);
1759 -- _object is the record used to implement the protected object.
1760 -- It is a parameter to the protected subprogram.
1762 -- If the protected object is controlled (i.e it has entries or
1763 -- needs finalization for interrupt handling), call Unlock_Entries,
1764 -- except if the protected object follows the ravenscar profile, in
1765 -- which case call Unlock_Entry, otherwise call the simplified
1766 -- version, Unlock.
1768 if Has_Entries (Pid)
1769 or else Has_Interrupt_Handler (Pid)
1770 or else Has_Attach_Handler (Pid)
1771 then
1772 if Abort_Allowed
1773 or else Restrictions (No_Entry_Queue) = False
1774 or else Number_Entries (Pid) > 1
1775 then
1776 Unlock := New_Reference_To (RTE (RE_Unlock_Entries), Loc);
1777 else
1778 Unlock := New_Reference_To (RTE (RE_Unlock_Entry), Loc);
1779 end if;
1781 else
1782 Unlock := New_Reference_To (RTE (RE_Unlock), Loc);
1783 end if;
1785 Append_To (Stmt,
1786 Make_Procedure_Call_Statement (Loc,
1787 Name => Unlock,
1788 Parameter_Associations => New_List (
1789 Make_Attribute_Reference (Loc,
1790 Prefix =>
1791 Make_Selected_Component (Loc,
1792 Prefix =>
1793 New_Reference_To (Defining_Identifier (Param), Loc),
1794 Selector_Name =>
1795 Make_Identifier (Loc, Name_uObject)),
1796 Attribute_Name => Name_Unchecked_Access))));
1798 if Abort_Allowed then
1799 -- Abort_Undefer;
1801 Append_To (Stmt,
1802 Make_Procedure_Call_Statement (Loc,
1803 Name =>
1804 New_Reference_To (
1805 RTE (RE_Abort_Undefer), Loc),
1806 Parameter_Associations => Empty_List));
1807 end if;
1809 elsif Is_Task_Allocation_Block then
1811 -- Add a call to Expunge_Unactivated_Tasks to the cleanup
1812 -- handler of a block created for the dynamic allocation of
1813 -- tasks:
1815 -- Expunge_Unactivated_Tasks (_chain);
1817 -- where _chain is the list of tasks created by the allocator
1818 -- but not yet activated. This list will be empty unless
1819 -- the block completes abnormally.
1821 -- This only applies to dynamically allocated tasks;
1822 -- other unactivated tasks are completed by Complete_Task or
1823 -- Complete_Master.
1825 -- NOTE: This cleanup handler references _chain, a local
1826 -- object.
1828 Append_To (Stmt,
1829 Make_Procedure_Call_Statement (Loc,
1830 Name =>
1831 New_Reference_To (
1832 RTE (RE_Expunge_Unactivated_Tasks), Loc),
1833 Parameter_Associations => New_List (
1834 New_Reference_To (Activation_Chain_Entity (N), Loc))));
1836 elsif Is_Asynchronous_Call_Block then
1838 -- Add a call to attempt to cancel the asynchronous entry call
1839 -- whenever the block containing the abortable part is exited.
1841 -- NOTE: This cleanup handler references C, a local object
1843 -- Get the argument to the Cancel procedure
1844 Cancel_Param := Entry_Cancel_Parameter (Entity (Identifier (N)));
1846 -- If it is of type Communication_Block, this must be a
1847 -- protected entry call.
1849 if Is_RTE (Etype (Cancel_Param), RE_Communication_Block) then
1851 Append_To (Stmt,
1853 -- if Enqueued (Cancel_Parameter) then
1855 Make_Implicit_If_Statement (Clean,
1856 Condition => Make_Function_Call (Loc,
1857 Name => New_Reference_To (
1858 RTE (RE_Enqueued), Loc),
1859 Parameter_Associations => New_List (
1860 New_Reference_To (Cancel_Param, Loc))),
1861 Then_Statements => New_List (
1863 -- Cancel_Protected_Entry_Call (Cancel_Param);
1865 Make_Procedure_Call_Statement (Loc,
1866 Name => New_Reference_To (
1867 RTE (RE_Cancel_Protected_Entry_Call), Loc),
1868 Parameter_Associations => New_List (
1869 New_Reference_To (Cancel_Param, Loc))))));
1871 -- Asynchronous delay
1873 elsif Is_RTE (Etype (Cancel_Param), RE_Delay_Block) then
1874 Append_To (Stmt,
1875 Make_Procedure_Call_Statement (Loc,
1876 Name => New_Reference_To (RTE (RE_Cancel_Async_Delay), Loc),
1877 Parameter_Associations => New_List (
1878 Make_Attribute_Reference (Loc,
1879 Prefix => New_Reference_To (Cancel_Param, Loc),
1880 Attribute_Name => Name_Unchecked_Access))));
1882 -- Task entry call
1884 else
1885 -- Append call to Cancel_Task_Entry_Call (C);
1887 Append_To (Stmt,
1888 Make_Procedure_Call_Statement (Loc,
1889 Name => New_Reference_To (
1890 RTE (RE_Cancel_Task_Entry_Call),
1891 Loc),
1892 Parameter_Associations => New_List (
1893 New_Reference_To (Cancel_Param, Loc))));
1895 end if;
1896 end if;
1898 if Present (Flist) then
1899 Append_To (Stmt,
1900 Make_Procedure_Call_Statement (Loc,
1901 Name => New_Reference_To (RTE (RE_Finalize_List), Loc),
1902 Parameter_Associations => New_List (
1903 New_Reference_To (Flist, Loc))));
1904 end if;
1906 if Present (Mark) then
1907 Append_To (Stmt,
1908 Make_Procedure_Call_Statement (Loc,
1909 Name => New_Reference_To (RTE (RE_SS_Release), Loc),
1910 Parameter_Associations => New_List (
1911 New_Reference_To (Mark, Loc))));
1912 end if;
1914 Sbody :=
1915 Make_Subprogram_Body (Loc,
1916 Specification =>
1917 Make_Procedure_Specification (Loc,
1918 Defining_Unit_Name => Clean),
1920 Declarations => New_List,
1922 Handled_Statement_Sequence =>
1923 Make_Handled_Sequence_Of_Statements (Loc,
1924 Statements => Stmt));
1926 if Present (Flist) or else Is_Task or else Is_Master then
1927 Wrap_Cleanup_Procedure (Sbody);
1928 end if;
1930 -- We do not want debug information for _Clean routines,
1931 -- since it just confuses the debugging operation unless
1932 -- we are debugging generated code.
1934 if not Debug_Generated_Code then
1935 Set_Debug_Info_Off (Clean, True);
1936 end if;
1938 return Sbody;
1939 end Make_Clean;
1941 --------------------------
1942 -- Make_Deep_Array_Body --
1943 --------------------------
1945 -- Array components are initialized and adjusted in the normal order
1946 -- and finalized in the reverse order. Exceptions are handled and
1947 -- Program_Error is re-raise in the Adjust and Finalize case
1948 -- (RM 7.6.1(12)). Generate the following code :
1950 -- procedure Deep_<P> -- with <P> being Initialize or Adjust or Finalize
1951 -- (L : in out Finalizable_Ptr;
1952 -- V : in out Typ)
1953 -- is
1954 -- begin
1955 -- for J1 in Typ'First (1) .. Typ'Last (1) loop
1956 -- ^ reverse ^ -- in the finalization case
1957 -- ...
1958 -- for J2 in Typ'First (n) .. Typ'Last (n) loop
1959 -- Make_<P>_Call (Typ, V (J1, .. , Jn), L, V);
1960 -- end loop;
1961 -- ...
1962 -- end loop;
1963 -- exception -- not in the
1964 -- when others => raise Program_Error; -- Initialize case
1965 -- end Deep_<P>;
1967 function Make_Deep_Array_Body
1968 (Prim : Final_Primitives;
1969 Typ : Entity_Id)
1970 return List_Id
1972 Loc : constant Source_Ptr := Sloc (Typ);
1974 Index_List : constant List_Id := New_List;
1975 -- Stores the list of references to the indexes (one per dimension)
1977 function One_Component return List_Id;
1978 -- Create one statement to initialize/adjust/finalize one array
1979 -- component, designated by a full set of indices.
1981 function One_Dimension (N : Int) return List_Id;
1982 -- Create loop to deal with one dimension of the array. The single
1983 -- statement in the body of the loop initializes the inner dimensions if
1984 -- any, or else a single component.
1986 -------------------
1987 -- One_Component --
1988 -------------------
1990 function One_Component return List_Id is
1991 Comp_Typ : constant Entity_Id := Component_Type (Typ);
1992 Comp_Ref : constant Node_Id :=
1993 Make_Indexed_Component (Loc,
1994 Prefix => Make_Identifier (Loc, Name_V),
1995 Expressions => Index_List);
1997 begin
1998 -- Set the etype of the component Reference, which is used to
1999 -- determine whether a conversion to a parent type is needed.
2001 Set_Etype (Comp_Ref, Comp_Typ);
2003 case Prim is
2004 when Initialize_Case =>
2005 return Make_Init_Call (Comp_Ref, Comp_Typ,
2006 Make_Identifier (Loc, Name_L),
2007 Make_Identifier (Loc, Name_B));
2009 when Adjust_Case =>
2010 return Make_Adjust_Call (Comp_Ref, Comp_Typ,
2011 Make_Identifier (Loc, Name_L),
2012 Make_Identifier (Loc, Name_B));
2014 when Finalize_Case =>
2015 return Make_Final_Call (Comp_Ref, Comp_Typ,
2016 Make_Identifier (Loc, Name_B));
2017 end case;
2018 end One_Component;
2020 -------------------
2021 -- One_Dimension --
2022 -------------------
2024 function One_Dimension (N : Int) return List_Id is
2025 Index : Entity_Id;
2027 begin
2028 if N > Number_Dimensions (Typ) then
2029 return One_Component;
2031 else
2032 Index :=
2033 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
2035 Append_To (Index_List, New_Reference_To (Index, Loc));
2037 return New_List (
2038 Make_Implicit_Loop_Statement (Typ,
2039 Identifier => Empty,
2040 Iteration_Scheme =>
2041 Make_Iteration_Scheme (Loc,
2042 Loop_Parameter_Specification =>
2043 Make_Loop_Parameter_Specification (Loc,
2044 Defining_Identifier => Index,
2045 Discrete_Subtype_Definition =>
2046 Make_Attribute_Reference (Loc,
2047 Prefix => Make_Identifier (Loc, Name_V),
2048 Attribute_Name => Name_Range,
2049 Expressions => New_List (
2050 Make_Integer_Literal (Loc, N))),
2051 Reverse_Present => Prim = Finalize_Case)),
2052 Statements => One_Dimension (N + 1)));
2053 end if;
2054 end One_Dimension;
2056 -- Start of processing for Make_Deep_Array_Body
2058 begin
2059 return One_Dimension (1);
2060 end Make_Deep_Array_Body;
2062 --------------------
2063 -- Make_Deep_Proc --
2064 --------------------
2066 -- Generate:
2067 -- procedure DEEP_<prim>
2068 -- (L : IN OUT Finalizable_Ptr; -- not for Finalize
2069 -- V : IN OUT <typ>;
2070 -- B : IN Short_Short_Integer) is
2071 -- begin
2072 -- <stmts>;
2073 -- exception -- Finalize and Adjust Cases only
2074 -- raise Program_Error; -- idem
2075 -- end DEEP_<prim>;
2077 function Make_Deep_Proc
2078 (Prim : Final_Primitives;
2079 Typ : Entity_Id;
2080 Stmts : List_Id)
2081 return Entity_Id
2083 Loc : constant Source_Ptr := Sloc (Typ);
2084 Formals : List_Id;
2085 Proc_Name : Entity_Id;
2086 Handler : List_Id := No_List;
2087 Subp_Body : Node_Id;
2088 Type_B : Entity_Id;
2090 begin
2091 if Prim = Finalize_Case then
2092 Formals := New_List;
2093 Type_B := Standard_Boolean;
2095 else
2096 Formals := New_List (
2097 Make_Parameter_Specification (Loc,
2098 Defining_Identifier => Make_Defining_Identifier (Loc, Name_L),
2099 In_Present => True,
2100 Out_Present => True,
2101 Parameter_Type =>
2102 New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
2103 Type_B := Standard_Short_Short_Integer;
2104 end if;
2106 Append_To (Formals,
2107 Make_Parameter_Specification (Loc,
2108 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
2109 In_Present => True,
2110 Out_Present => True,
2111 Parameter_Type => New_Reference_To (Typ, Loc)));
2113 Append_To (Formals,
2114 Make_Parameter_Specification (Loc,
2115 Defining_Identifier => Make_Defining_Identifier (Loc, Name_B),
2116 Parameter_Type => New_Reference_To (Type_B, Loc)));
2118 if Prim = Finalize_Case or else Prim = Adjust_Case then
2119 Handler := New_List (
2120 Make_Exception_Handler (Loc,
2121 Exception_Choices => New_List (Make_Others_Choice (Loc)),
2122 Statements => New_List (
2123 Make_Raise_Program_Error (Loc,
2124 Reason => PE_Finalize_Raised_Exception))));
2125 end if;
2127 Proc_Name := Make_Defining_Identifier (Loc, Deep_Name_Of (Prim));
2129 Subp_Body :=
2130 Make_Subprogram_Body (Loc,
2131 Specification =>
2132 Make_Procedure_Specification (Loc,
2133 Defining_Unit_Name => Proc_Name,
2134 Parameter_Specifications => Formals),
2136 Declarations => Empty_List,
2137 Handled_Statement_Sequence =>
2138 Make_Handled_Sequence_Of_Statements (Loc,
2139 Statements => Stmts,
2140 Exception_Handlers => Handler));
2142 return Proc_Name;
2143 end Make_Deep_Proc;
2145 ---------------------------
2146 -- Make_Deep_Record_Body --
2147 ---------------------------
2149 -- The Deep procedures call the appropriate Controlling proc on the
2150 -- the controller component. In the init case, it also attach the
2151 -- controller to the current finalization list.
2153 function Make_Deep_Record_Body
2154 (Prim : Final_Primitives;
2155 Typ : Entity_Id)
2156 return List_Id
2158 Loc : constant Source_Ptr := Sloc (Typ);
2159 Controller_Typ : Entity_Id;
2160 Obj_Ref : constant Node_Id := Make_Identifier (Loc, Name_V);
2161 Controller_Ref : constant Node_Id :=
2162 Make_Selected_Component (Loc,
2163 Prefix => Obj_Ref,
2164 Selector_Name =>
2165 Make_Identifier (Loc, Name_uController));
2167 begin
2168 if Is_Return_By_Reference_Type (Typ) then
2169 Controller_Typ := RTE (RE_Limited_Record_Controller);
2170 else
2171 Controller_Typ := RTE (RE_Record_Controller);
2172 end if;
2174 case Prim is
2175 when Initialize_Case =>
2176 declare
2177 Res : constant List_Id := New_List;
2179 begin
2180 Append_List_To (Res,
2181 Make_Init_Call (
2182 Ref => Controller_Ref,
2183 Typ => Controller_Typ,
2184 Flist_Ref => Make_Identifier (Loc, Name_L),
2185 With_Attach => Make_Identifier (Loc, Name_B)));
2187 -- When the type is also a controlled type by itself,
2188 -- Initialize it and attach it at the end of the internal
2189 -- finalization chain
2191 if Is_Controlled (Typ) then
2192 Append_To (Res,
2193 Make_Procedure_Call_Statement (Loc,
2194 Name => New_Reference_To (
2195 Find_Prim_Op (Typ, Name_Of (Prim)), Loc),
2197 Parameter_Associations =>
2198 New_List (New_Copy_Tree (Obj_Ref))));
2200 Append_To (Res, Make_Attach_Call (
2201 Obj_Ref => New_Copy_Tree (Obj_Ref),
2202 Flist_Ref =>
2203 Make_Selected_Component (Loc,
2204 Prefix => New_Copy_Tree (Controller_Ref),
2205 Selector_Name => Make_Identifier (Loc, Name_F)),
2206 With_Attach => Make_Integer_Literal (Loc, 1)));
2207 end if;
2209 return Res;
2210 end;
2212 when Adjust_Case =>
2213 return
2214 Make_Adjust_Call (Controller_Ref, Controller_Typ,
2215 Make_Identifier (Loc, Name_L),
2216 Make_Identifier (Loc, Name_B));
2218 when Finalize_Case =>
2219 return
2220 Make_Final_Call (Controller_Ref, Controller_Typ,
2221 Make_Identifier (Loc, Name_B));
2222 end case;
2223 end Make_Deep_Record_Body;
2225 ----------------------
2226 -- Make_Final_Call --
2227 ----------------------
2229 function Make_Final_Call
2230 (Ref : Node_Id;
2231 Typ : Entity_Id;
2232 With_Detach : Node_Id)
2233 return List_Id
2235 Loc : constant Source_Ptr := Sloc (Ref);
2236 Res : constant List_Id := New_List;
2237 Cref : Node_Id;
2238 Cref2 : Node_Id;
2239 Proc : Entity_Id;
2240 Utyp : Entity_Id;
2242 begin
2243 if Is_Class_Wide_Type (Typ) then
2244 Utyp := Root_Type (Typ);
2245 Cref := Ref;
2247 elsif Is_Concurrent_Type (Typ) then
2248 Utyp := Corresponding_Record_Type (Typ);
2249 Cref := Convert_Concurrent (Ref, Typ);
2251 elsif Is_Private_Type (Typ)
2252 and then Present (Full_View (Typ))
2253 and then Is_Concurrent_Type (Full_View (Typ))
2254 then
2255 Utyp := Corresponding_Record_Type (Full_View (Typ));
2256 Cref := Convert_Concurrent (Ref, Full_View (Typ));
2257 else
2258 Utyp := Typ;
2259 Cref := Ref;
2260 end if;
2262 Utyp := Underlying_Type (Base_Type (Utyp));
2263 Set_Assignment_OK (Cref);
2265 -- Deal with non-tagged derivation of private views
2267 if Is_Untagged_Derivation (Typ) then
2268 Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
2269 Cref := Unchecked_Convert_To (Utyp, Cref);
2270 Set_Assignment_OK (Cref);
2271 -- To prevent problems with UC see 1.156 RH ???
2272 end if;
2274 -- If the underlying_type is a subtype, we are dealing with
2275 -- the completion of a private type. We need to access
2276 -- the base type and generate a conversion to it.
2278 if Utyp /= Base_Type (Utyp) then
2279 pragma Assert (Is_Private_Type (Typ));
2280 Utyp := Base_Type (Utyp);
2281 Cref := Unchecked_Convert_To (Utyp, Cref);
2282 end if;
2284 -- Generate:
2285 -- Deep_Finalize (Ref, With_Detach);
2287 if Has_Controlled_Component (Utyp)
2288 or else Is_Class_Wide_Type (Typ)
2289 then
2290 if Is_Tagged_Type (Utyp) then
2291 Proc := Find_Prim_Op (Utyp, Deep_Name_Of (Finalize_Case));
2292 else
2293 Proc := TSS (Utyp, Deep_Name_Of (Finalize_Case));
2294 end if;
2296 Cref := Convert_View (Proc, Cref);
2298 Append_To (Res,
2299 Make_Procedure_Call_Statement (Loc,
2300 Name => New_Reference_To (Proc, Loc),
2301 Parameter_Associations =>
2302 New_List (Cref, With_Detach)));
2304 -- Generate:
2305 -- if With_Detach then
2306 -- Finalize_One (Ref);
2307 -- else
2308 -- Finalize (Ref);
2309 -- end if;
2311 else
2312 Proc := Find_Prim_Op (Utyp, Name_Of (Finalize_Case));
2314 if Chars (With_Detach) = Chars (Standard_True) then
2315 Append_To (Res,
2316 Make_Procedure_Call_Statement (Loc,
2317 Name => New_Reference_To (RTE (RE_Finalize_One), Loc),
2318 Parameter_Associations => New_List (
2319 OK_Convert_To (RTE (RE_Finalizable), Cref))));
2321 elsif Chars (With_Detach) = Chars (Standard_False) then
2322 Append_To (Res,
2323 Make_Procedure_Call_Statement (Loc,
2324 Name => New_Reference_To (Proc, Loc),
2325 Parameter_Associations =>
2326 New_List (Convert_View (Proc, Cref))));
2328 else
2329 Cref2 := New_Copy_Tree (Cref);
2330 Append_To (Res,
2331 Make_Implicit_If_Statement (Ref,
2332 Condition => With_Detach,
2333 Then_Statements => New_List (
2334 Make_Procedure_Call_Statement (Loc,
2335 Name => New_Reference_To (RTE (RE_Finalize_One), Loc),
2336 Parameter_Associations => New_List (
2337 OK_Convert_To (RTE (RE_Finalizable), Cref)))),
2339 Else_Statements => New_List (
2340 Make_Procedure_Call_Statement (Loc,
2341 Name => New_Reference_To (Proc, Loc),
2342 Parameter_Associations =>
2343 New_List (Convert_View (Proc, Cref2))))));
2344 end if;
2345 end if;
2347 -- Treat this as a reference to Finalize if the Finalize routine
2348 -- comes from source. The call is not explicit, but it is near
2349 -- enough, and we won't typically get explicit adjust calls.
2351 if Comes_From_Source (Proc) then
2352 Generate_Reference (Proc, Ref);
2353 end if;
2354 return Res;
2355 end Make_Final_Call;
2357 --------------------
2358 -- Make_Init_Call --
2359 --------------------
2361 function Make_Init_Call
2362 (Ref : Node_Id;
2363 Typ : Entity_Id;
2364 Flist_Ref : Node_Id;
2365 With_Attach : Node_Id)
2366 return List_Id
2368 Loc : constant Source_Ptr := Sloc (Ref);
2369 Is_Conc : Boolean;
2370 Res : constant List_Id := New_List;
2371 Proc : Entity_Id;
2372 Utyp : Entity_Id;
2373 Cref : Node_Id;
2374 Cref2 : Node_Id;
2375 Attach : Node_Id := With_Attach;
2377 begin
2378 if Is_Concurrent_Type (Typ) then
2379 Is_Conc := True;
2380 Utyp := Corresponding_Record_Type (Typ);
2381 Cref := Convert_Concurrent (Ref, Typ);
2383 elsif Is_Private_Type (Typ)
2384 and then Present (Full_View (Typ))
2385 and then Is_Concurrent_Type (Underlying_Type (Typ))
2386 then
2387 Is_Conc := True;
2388 Utyp := Corresponding_Record_Type (Underlying_Type (Typ));
2389 Cref := Convert_Concurrent (Ref, Underlying_Type (Typ));
2391 else
2392 Is_Conc := False;
2393 Utyp := Typ;
2394 Cref := Ref;
2395 end if;
2397 Utyp := Underlying_Type (Base_Type (Utyp));
2399 Set_Assignment_OK (Cref);
2401 -- Deal with non-tagged derivation of private views
2403 if Is_Untagged_Derivation (Typ)
2404 and then not Is_Conc
2405 then
2406 Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
2407 Cref := Unchecked_Convert_To (Utyp, Cref);
2408 Set_Assignment_OK (Cref);
2409 -- To prevent problems with UC see 1.156 RH ???
2410 end if;
2412 -- If the underlying_type is a subtype, we are dealing with
2413 -- the completion of a private type. We need to access
2414 -- the base type and generate a conversion to it.
2416 if Utyp /= Base_Type (Utyp) then
2417 pragma Assert (Is_Private_Type (Typ));
2418 Utyp := Base_Type (Utyp);
2419 Cref := Unchecked_Convert_To (Utyp, Cref);
2420 end if;
2422 -- We do not need to attach to one of the Global Final Lists
2423 -- the objects whose type is Finalize_Storage_Only
2425 if Finalize_Storage_Only (Typ)
2426 and then (Global_Flist_Ref (Flist_Ref)
2427 or else Entity (Constant_Value (RTE (RE_Garbage_Collected)))
2428 = Standard_True)
2429 then
2430 Attach := Make_Integer_Literal (Loc, 0);
2431 end if;
2433 -- Generate:
2434 -- Deep_Initialize (Ref, Flist_Ref);
2436 if Has_Controlled_Component (Utyp) then
2437 Proc := TSS (Utyp, Deep_Name_Of (Initialize_Case));
2439 Cref := Convert_View (Proc, Cref, 2);
2441 Append_To (Res,
2442 Make_Procedure_Call_Statement (Loc,
2443 Name => New_Reference_To (Proc, Loc),
2444 Parameter_Associations => New_List (
2445 Node1 => Flist_Ref,
2446 Node2 => Cref,
2447 Node3 => Attach)));
2449 -- Generate:
2450 -- Attach_To_Final_List (Ref, Flist_Ref);
2451 -- Initialize (Ref);
2453 else -- Is_Controlled (Utyp)
2454 Proc := Find_Prim_Op (Utyp, Name_Of (Initialize_Case));
2455 Cref := Convert_View (Proc, Cref);
2456 Cref2 := New_Copy_Tree (Cref);
2458 Append_To (Res,
2459 Make_Procedure_Call_Statement (Loc,
2460 Name => New_Reference_To (Proc, Loc),
2461 Parameter_Associations => New_List (Cref2)));
2463 Append_To (Res,
2464 Make_Attach_Call (Cref, Flist_Ref, Attach));
2466 -- Treat this as a reference to Initialize if Initialize routine
2467 -- comes from source. The call is not explicit, but it is near
2468 -- enough, and we won't typically get explicit adjust calls.
2470 if Comes_From_Source (Proc) then
2471 Generate_Reference (Proc, Ref);
2472 end if;
2473 end if;
2475 return Res;
2476 end Make_Init_Call;
2478 --------------------------
2479 -- Make_Transient_Block --
2480 --------------------------
2482 -- If finalization is involved, this function just wraps the instruction
2483 -- into a block whose name is the transient block entity, and then
2484 -- Expand_Cleanup_Actions (called on the expansion of the handled
2485 -- sequence of statements will do the necessary expansions for
2486 -- cleanups).
2488 function Make_Transient_Block
2489 (Loc : Source_Ptr;
2490 Action : Node_Id)
2491 return Node_Id
2493 Flist : constant Entity_Id := Finalization_Chain_Entity (Current_Scope);
2494 Decls : constant List_Id := New_List;
2495 Par : constant Node_Id := Parent (Action);
2496 Instrs : constant List_Id := New_List (Action);
2497 Blk : Node_Id;
2499 begin
2500 -- Case where only secondary stack use is involved
2502 if Uses_Sec_Stack (Current_Scope)
2503 and then No (Flist)
2504 and then Nkind (Action) /= N_Return_Statement
2505 and then Nkind (Par) /= N_Exception_Handler
2506 then
2508 declare
2509 S : Entity_Id;
2510 K : Entity_Kind;
2511 begin
2512 S := Scope (Current_Scope);
2513 loop
2514 K := Ekind (S);
2516 -- At the outer level, no need to release the sec stack
2518 if S = Standard_Standard then
2519 Set_Uses_Sec_Stack (Current_Scope, False);
2520 exit;
2522 -- In a function, only release the sec stack if the
2523 -- function does not return on the sec stack otherwise
2524 -- the result may be lost. The caller is responsible for
2525 -- releasing.
2527 elsif K = E_Function then
2528 Set_Uses_Sec_Stack (Current_Scope, False);
2530 if not Requires_Transient_Scope (Etype (S)) then
2531 if not Functions_Return_By_DSP_On_Target then
2532 Set_Uses_Sec_Stack (S, True);
2533 Check_Restriction (No_Secondary_Stack, Action);
2534 end if;
2535 end if;
2537 exit;
2539 -- In a loop or entry we should install a block encompassing
2540 -- all the construct. For now just release right away.
2542 elsif K = E_Loop or else K = E_Entry then
2543 exit;
2545 -- In a procedure or a block, we release on exit of the
2546 -- procedure or block. ??? memory leak can be created by
2547 -- recursive calls.
2549 elsif K = E_Procedure
2550 or else K = E_Block
2551 then
2552 if not Functions_Return_By_DSP_On_Target then
2553 Set_Uses_Sec_Stack (S, True);
2554 Check_Restriction (No_Secondary_Stack, Action);
2555 end if;
2557 Set_Uses_Sec_Stack (Current_Scope, False);
2558 exit;
2560 else
2561 S := Scope (S);
2562 end if;
2563 end loop;
2564 end;
2565 end if;
2567 -- Insert actions stuck in the transient scopes as well as all
2568 -- freezing nodes needed by those actions
2570 Insert_Actions_In_Scope_Around (Action);
2572 declare
2573 Last_Inserted : Node_Id := Prev (Action);
2575 begin
2576 if Present (Last_Inserted) then
2577 Freeze_All (First_Entity (Current_Scope), Last_Inserted);
2578 end if;
2579 end;
2581 Blk :=
2582 Make_Block_Statement (Loc,
2583 Identifier => New_Reference_To (Current_Scope, Loc),
2584 Declarations => Decls,
2585 Handled_Statement_Sequence =>
2586 Make_Handled_Sequence_Of_Statements (Loc, Statements => Instrs),
2587 Has_Created_Identifier => True);
2589 -- When the transient scope was established, we pushed the entry for
2590 -- the transient scope onto the scope stack, so that the scope was
2591 -- active for the installation of finalizable entities etc. Now we
2592 -- must remove this entry, since we have constructed a proper block.
2594 Pop_Scope;
2596 return Blk;
2597 end Make_Transient_Block;
2599 ------------------------
2600 -- Node_To_Be_Wrapped --
2601 ------------------------
2603 function Node_To_Be_Wrapped return Node_Id is
2604 begin
2605 return Scope_Stack.Table (Scope_Stack.Last).Node_To_Be_Wrapped;
2606 end Node_To_Be_Wrapped;
2608 ----------------------------
2609 -- Set_Node_To_Be_Wrapped --
2610 ----------------------------
2612 procedure Set_Node_To_Be_Wrapped (N : Node_Id) is
2613 begin
2614 Scope_Stack.Table (Scope_Stack.Last).Node_To_Be_Wrapped := N;
2615 end Set_Node_To_Be_Wrapped;
2617 ----------------------------------
2618 -- Store_After_Actions_In_Scope --
2619 ----------------------------------
2621 procedure Store_After_Actions_In_Scope (L : List_Id) is
2622 SE : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
2624 begin
2625 if Present (SE.Actions_To_Be_Wrapped_After) then
2626 Insert_List_Before_And_Analyze (
2627 First (SE.Actions_To_Be_Wrapped_After), L);
2629 else
2630 SE.Actions_To_Be_Wrapped_After := L;
2632 if Is_List_Member (SE.Node_To_Be_Wrapped) then
2633 Set_Parent (L, Parent (SE.Node_To_Be_Wrapped));
2634 else
2635 Set_Parent (L, SE.Node_To_Be_Wrapped);
2636 end if;
2638 Analyze_List (L);
2639 end if;
2640 end Store_After_Actions_In_Scope;
2642 -----------------------------------
2643 -- Store_Before_Actions_In_Scope --
2644 -----------------------------------
2646 procedure Store_Before_Actions_In_Scope (L : List_Id) is
2647 SE : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
2649 begin
2650 if Present (SE.Actions_To_Be_Wrapped_Before) then
2651 Insert_List_After_And_Analyze (
2652 Last (SE.Actions_To_Be_Wrapped_Before), L);
2654 else
2655 SE.Actions_To_Be_Wrapped_Before := L;
2657 if Is_List_Member (SE.Node_To_Be_Wrapped) then
2658 Set_Parent (L, Parent (SE.Node_To_Be_Wrapped));
2659 else
2660 Set_Parent (L, SE.Node_To_Be_Wrapped);
2661 end if;
2663 Analyze_List (L);
2664 end if;
2665 end Store_Before_Actions_In_Scope;
2667 --------------------------------
2668 -- Wrap_Transient_Declaration --
2669 --------------------------------
2671 -- If a transient scope has been established during the processing of the
2672 -- Expression of an Object_Declaration, it is not possible to wrap the
2673 -- declaration into a transient block as usual case, otherwise the object
2674 -- would be itself declared in the wrong scope. Therefore, all entities (if
2675 -- any) defined in the transient block are moved to the proper enclosing
2676 -- scope, furthermore, if they are controlled variables they are finalized
2677 -- right after the declaration. The finalization list of the transient
2678 -- scope is defined as a renaming of the enclosing one so during their
2679 -- initialization they will be attached to the proper finalization
2680 -- list. For instance, the following declaration :
2682 -- X : Typ := F (G (A), G (B));
2684 -- (where G(A) and G(B) return controlled values, expanded as _v1 and _v2)
2685 -- is expanded into :
2687 -- _local_final_list_1 : Finalizable_Ptr;
2688 -- X : Typ := [ complex Expression-Action ];
2689 -- Finalize_One(_v1);
2690 -- Finalize_One (_v2);
2692 procedure Wrap_Transient_Declaration (N : Node_Id) is
2693 S : Entity_Id;
2694 LC : Entity_Id := Empty;
2695 Nodes : List_Id;
2696 Loc : constant Source_Ptr := Sloc (N);
2697 Enclosing_S : Entity_Id;
2698 Uses_SS : Boolean;
2699 Next_N : constant Node_Id := Next (N);
2701 begin
2702 S := Current_Scope;
2703 Enclosing_S := Scope (S);
2705 -- Insert Actions kept in the Scope stack
2707 Insert_Actions_In_Scope_Around (N);
2709 -- If the declaration is consuming some secondary stack, mark the
2710 -- Enclosing scope appropriately.
2712 Uses_SS := Uses_Sec_Stack (S);
2713 Pop_Scope;
2715 -- Create a List controller and rename the final list to be its
2716 -- internal final pointer:
2717 -- Lxxx : Simple_List_Controller;
2718 -- Fxxx : Finalizable_Ptr renames Lxxx.F;
2720 if Present (Finalization_Chain_Entity (S)) then
2721 LC := Make_Defining_Identifier (Loc, New_Internal_Name ('L'));
2723 Nodes := New_List (
2724 Make_Object_Declaration (Loc,
2725 Defining_Identifier => LC,
2726 Object_Definition =>
2727 New_Reference_To (RTE (RE_Simple_List_Controller), Loc)),
2729 Make_Object_Renaming_Declaration (Loc,
2730 Defining_Identifier => Finalization_Chain_Entity (S),
2731 Subtype_Mark => New_Reference_To (RTE (RE_Finalizable_Ptr), Loc),
2732 Name =>
2733 Make_Selected_Component (Loc,
2734 Prefix => New_Reference_To (LC, Loc),
2735 Selector_Name => Make_Identifier (Loc, Name_F))));
2737 -- Put the declaration at the beginning of the declaration part
2738 -- to make sure it will be before all other actions that have been
2739 -- inserted before N.
2741 Insert_List_Before_And_Analyze (First (List_Containing (N)), Nodes);
2743 -- Generate the Finalization calls by finalizing the list
2744 -- controller right away. It will be re-finalized on scope
2745 -- exit but it doesn't matter. It cannot be done when the
2746 -- call initializes a renaming object though because in this
2747 -- case, the object becomes a pointer to the temporary and thus
2748 -- increases its life span.
2750 if Nkind (N) = N_Object_Renaming_Declaration
2751 and then Controlled_Type (Etype (Defining_Identifier (N)))
2752 then
2753 null;
2755 else
2756 Nodes :=
2757 Make_Final_Call (
2758 Ref => New_Reference_To (LC, Loc),
2759 Typ => Etype (LC),
2760 With_Detach => New_Reference_To (Standard_False, Loc));
2761 if Present (Next_N) then
2762 Insert_List_Before_And_Analyze (Next_N, Nodes);
2763 else
2764 Append_List_To (List_Containing (N), Nodes);
2765 end if;
2766 end if;
2767 end if;
2769 -- Put the local entities back in the enclosing scope, and set the
2770 -- Is_Public flag appropriately.
2772 Transfer_Entities (S, Enclosing_S);
2774 -- Mark the enclosing dynamic scope so that the sec stack will be
2775 -- released upon its exit unless this is a function that returns on
2776 -- the sec stack in which case this will be done by the caller.
2778 if Uses_SS then
2779 S := Enclosing_Dynamic_Scope (S);
2781 if Ekind (S) = E_Function
2782 and then Requires_Transient_Scope (Etype (S))
2783 then
2784 null;
2785 else
2786 Set_Uses_Sec_Stack (S);
2787 Check_Restriction (No_Secondary_Stack, N);
2788 end if;
2789 end if;
2790 end Wrap_Transient_Declaration;
2792 -------------------------------
2793 -- Wrap_Transient_Expression --
2794 -------------------------------
2796 -- Insert actions before <Expression>:
2798 -- (lines marked with <CTRL> are expanded only in presence of Controlled
2799 -- objects needing finalization)
2801 -- _E : Etyp;
2802 -- declare
2803 -- _M : constant Mark_Id := SS_Mark;
2804 -- Local_Final_List : System.FI.Finalizable_Ptr; <CTRL>
2806 -- procedure _Clean is
2807 -- begin
2808 -- Abort_Defer;
2809 -- System.FI.Finalize_List (Local_Final_List); <CTRL>
2810 -- SS_Release (M);
2811 -- Abort_Undefer;
2812 -- end _Clean;
2814 -- begin
2815 -- _E := <Expression>;
2816 -- at end
2817 -- _Clean;
2818 -- end;
2820 -- then expression is replaced by _E
2822 procedure Wrap_Transient_Expression (N : Node_Id) is
2823 Loc : constant Source_Ptr := Sloc (N);
2824 E : constant Entity_Id :=
2825 Make_Defining_Identifier (Loc, New_Internal_Name ('E'));
2826 Etyp : Entity_Id := Etype (N);
2828 begin
2829 Insert_Actions (N, New_List (
2830 Make_Object_Declaration (Loc,
2831 Defining_Identifier => E,
2832 Object_Definition => New_Reference_To (Etyp, Loc)),
2834 Make_Transient_Block (Loc,
2835 Action =>
2836 Make_Assignment_Statement (Loc,
2837 Name => New_Reference_To (E, Loc),
2838 Expression => Relocate_Node (N)))));
2840 Rewrite (N, New_Reference_To (E, Loc));
2841 Analyze_And_Resolve (N, Etyp);
2842 end Wrap_Transient_Expression;
2844 ------------------------------
2845 -- Wrap_Transient_Statement --
2846 ------------------------------
2848 -- Transform <Instruction> into
2850 -- (lines marked with <CTRL> are expanded only in presence of Controlled
2851 -- objects needing finalization)
2853 -- declare
2854 -- _M : Mark_Id := SS_Mark;
2855 -- Local_Final_List : System.FI.Finalizable_Ptr ; <CTRL>
2857 -- procedure _Clean is
2858 -- begin
2859 -- Abort_Defer;
2860 -- System.FI.Finalize_List (Local_Final_List); <CTRL>
2861 -- SS_Release (_M);
2862 -- Abort_Undefer;
2863 -- end _Clean;
2865 -- begin
2866 -- <Instr uction>;
2867 -- at end
2868 -- _Clean;
2869 -- end;
2871 procedure Wrap_Transient_Statement (N : Node_Id) is
2872 Loc : constant Source_Ptr := Sloc (N);
2873 New_Statement : constant Node_Id := Relocate_Node (N);
2875 begin
2876 Rewrite (N, Make_Transient_Block (Loc, New_Statement));
2878 -- With the scope stack back to normal, we can call analyze on the
2879 -- resulting block. At this point, the transient scope is being
2880 -- treated like a perfectly normal scope, so there is nothing
2881 -- special about it.
2883 -- Note: Wrap_Transient_Statement is called with the node already
2884 -- analyzed (i.e. Analyzed (N) is True). This is important, since
2885 -- otherwise we would get a recursive processing of the node when
2886 -- we do this Analyze call.
2888 Analyze (N);
2889 end Wrap_Transient_Statement;
2891 end Exp_Ch7;