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