* Mainline merge as of 2006-02-16 (@111136).
[official-gcc.git] / gcc / ada / exp_ch7.adb
blob2535bb2c70c219da67455af21bf068b6e8b886b6
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-2006, 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, 51 Franklin Street, Fifth Floor, --
20 -- Boston, MA 02110-1301, 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) return Node_Id;
134 -- Expand a the clean-up procedure for controlled and/or transient
135 -- block, and/or task master or task body, or blocks used to
136 -- implement task allocation or asynchronous entry calls, or
137 -- procedures used to implement protected procedures. Clean is the
138 -- entity for such a procedure. Mark is the entity for the secondary
139 -- stack mark, if empty only controlled block clean-up will be
140 -- performed. Flist is the entity for the local final list, if empty
141 -- only transient scope clean-up will be performed. The flags
142 -- Is_Task and Is_Master control the calls to the corresponding
143 -- finalization actions for a task body or for an entity that is a
144 -- task master.
146 procedure Set_Node_To_Be_Wrapped (N : Node_Id);
147 -- Set the field Node_To_Be_Wrapped of the current scope
149 procedure Insert_Actions_In_Scope_Around (N : Node_Id);
150 -- Insert the before-actions kept in the scope stack before N, and the
151 -- after after-actions, after N which must be a member of a list.
153 function Make_Transient_Block
154 (Loc : Source_Ptr;
155 Action : Node_Id) return Node_Id;
156 -- Create a transient block whose name is Scope, which is also a
157 -- controlled block if Flist is not empty and whose only code is
158 -- Action (either a single statement or single declaration).
160 type Final_Primitives is (Initialize_Case, Adjust_Case, Finalize_Case);
161 -- This enumeration type is defined in order to ease sharing code for
162 -- building finalization procedures for composite types.
164 Name_Of : constant array (Final_Primitives) of Name_Id :=
165 (Initialize_Case => Name_Initialize,
166 Adjust_Case => Name_Adjust,
167 Finalize_Case => Name_Finalize);
169 Deep_Name_Of : constant array (Final_Primitives) of TSS_Name_Type :=
170 (Initialize_Case => TSS_Deep_Initialize,
171 Adjust_Case => TSS_Deep_Adjust,
172 Finalize_Case => TSS_Deep_Finalize);
174 procedure Build_Record_Deep_Procs (Typ : Entity_Id);
175 -- Build the deep Initialize/Adjust/Finalize for a record Typ with
176 -- Has_Component_Component set and store them using the TSS mechanism.
178 procedure Build_Array_Deep_Procs (Typ : Entity_Id);
179 -- Build the deep Initialize/Adjust/Finalize for a record Typ with
180 -- Has_Controlled_Component set and store them using the TSS mechanism.
182 function Make_Deep_Proc
183 (Prim : Final_Primitives;
184 Typ : Entity_Id;
185 Stmts : List_Id) return Node_Id;
186 -- This function generates the tree for Deep_Initialize, Deep_Adjust
187 -- or Deep_Finalize procedures according to the first parameter,
188 -- these procedures operate on the type Typ. The Stmts parameter
189 -- gives the body of the procedure.
191 function Make_Deep_Array_Body
192 (Prim : Final_Primitives;
193 Typ : Entity_Id) return List_Id;
194 -- This function generates the list of statements for implementing
195 -- Deep_Initialize, Deep_Adjust or Deep_Finalize procedures
196 -- according to the first parameter, these procedures operate on the
197 -- array type Typ.
199 function Make_Deep_Record_Body
200 (Prim : Final_Primitives;
201 Typ : Entity_Id) return List_Id;
202 -- This function generates the list of statements for implementing
203 -- Deep_Initialize, Deep_Adjust or Deep_Finalize procedures
204 -- according to the first parameter, these procedures operate on the
205 -- record type Typ.
207 procedure Check_Visibly_Controlled
208 (Prim : Final_Primitives;
209 Typ : Entity_Id;
210 E : in out Entity_Id;
211 Cref : in out Node_Id);
212 -- The controlled operation declared for a derived type may not be
213 -- overriding, if the controlled operations of the parent type are
214 -- hidden, for example when the parent is a private type whose full
215 -- view is controlled. For other primitive operations we modify the
216 -- name of the operation to indicate that it is not overriding, but
217 -- this is not possible for Initialize, etc. because they have to be
218 -- retrievable by name. Before generating the proper call to one of
219 -- these operations we check whether Typ is known to be controlled at
220 -- the point of definition. If it is not then we must retrieve the
221 -- hidden operation of the parent and use it instead. This is one
222 -- case that might be solved more cleanly once Overriding pragmas or
223 -- declarations are in place.
225 function Convert_View
226 (Proc : Entity_Id;
227 Arg : Node_Id;
228 Ind : Pos := 1) return Node_Id;
229 -- Proc is one of the Initialize/Adjust/Finalize operations, and
230 -- Arg is the argument being passed to it. Ind indicates which
231 -- formal of procedure Proc we are trying to match. This function
232 -- will, if necessary, generate an conversion between the partial
233 -- and full view of Arg to match the type of the formal of Proc,
234 -- or force a conversion to the class-wide type in the case where
235 -- the operation is abstract.
237 -----------------------------
238 -- Finalization Management --
239 -----------------------------
241 -- This part describe how Initialization/Adjusment/Finalization procedures
242 -- are generated and called. Two cases must be considered, types that are
243 -- Controlled (Is_Controlled flag set) and composite types that contain
244 -- controlled components (Has_Controlled_Component flag set). In the first
245 -- case the procedures to call are the user-defined primitive operations
246 -- Initialize/Adjust/Finalize. In the second case, GNAT generates
247 -- Deep_Initialize, Deep_Adjust and Deep_Finalize that are in charge of
248 -- calling the former procedures on the controlled components.
250 -- For records with Has_Controlled_Component set, a hidden "controller"
251 -- component is inserted. This controller component contains its own
252 -- finalization list on which all controlled components are attached
253 -- creating an indirection on the upper-level Finalization list. This
254 -- technique facilitates the management of objects whose number of
255 -- controlled components changes during execution. This controller
256 -- component is itself controlled and is attached to the upper-level
257 -- finalization chain. Its adjust primitive is in charge of calling
258 -- adjust on the components and adusting the finalization pointer to
259 -- match their new location (see a-finali.adb).
261 -- It is not possible to use a similar technique for arrays that have
262 -- Has_Controlled_Component set. In this case, deep procedures are
263 -- generated that call initialize/adjust/finalize + attachment or
264 -- detachment on the finalization list for all component.
266 -- Initialize calls: they are generated for declarations or dynamic
267 -- allocations of Controlled objects with no initial value. They are
268 -- always followed by an attachment to the current Finalization
269 -- Chain. For the dynamic allocation case this the chain attached to
270 -- the scope of the access type definition otherwise, this is the chain
271 -- of the current scope.
273 -- Adjust Calls: They are generated on 2 occasions: (1) for
274 -- declarations or dynamic allocations of Controlled objects with an
275 -- initial value. (2) after an assignment. In the first case they are
276 -- followed by an attachment to the final chain, in the second case
277 -- they are not.
279 -- Finalization Calls: They are generated on (1) scope exit, (2)
280 -- assignments, (3) unchecked deallocations. In case (3) they have to
281 -- be detached from the final chain, in case (2) they must not and in
282 -- case (1) this is not important since we are exiting the scope
283 -- anyway.
285 -- Other details:
286 -- - Type extensions will have a new record controller at each derivation
287 -- level containing controlled components.
288 -- - For types that are both Is_Controlled and Has_Controlled_Components,
289 -- the record controller and the object itself are handled separately.
290 -- It could seem simpler to attach the object at the end of its record
291 -- controller but this would not tackle view conversions properly.
292 -- - A classwide type can always potentially have controlled components
293 -- but the record controller of the corresponding actual type may not
294 -- be known at compile time so the dispatch table contains a special
295 -- field that allows to compute the offset of the record controller
296 -- dynamically. See s-finimp.Deep_Tag_Attach and a-tags.RC_Offset
298 -- Here is a simple example of the expansion of a controlled block :
300 -- declare
301 -- X : Controlled ;
302 -- Y : Controlled := Init;
304 -- type R is record
305 -- C : Controlled;
306 -- end record;
307 -- W : R;
308 -- Z : R := (C => X);
309 -- begin
310 -- X := Y;
311 -- W := Z;
312 -- end;
314 -- is expanded into
316 -- declare
317 -- _L : System.FI.Finalizable_Ptr;
319 -- procedure _Clean is
320 -- begin
321 -- Abort_Defer;
322 -- System.FI.Finalize_List (_L);
323 -- Abort_Undefer;
324 -- end _Clean;
326 -- X : Controlled;
327 -- begin
328 -- Abort_Defer;
329 -- Initialize (X);
330 -- Attach_To_Final_List (_L, Finalizable (X), 1);
331 -- at end: Abort_Undefer;
332 -- Y : Controlled := Init;
333 -- Adjust (Y);
334 -- Attach_To_Final_List (_L, Finalizable (Y), 1);
336 -- type R is record
337 -- _C : Record_Controller;
338 -- C : Controlled;
339 -- end record;
340 -- W : R;
341 -- begin
342 -- Abort_Defer;
343 -- Deep_Initialize (W, _L, 1);
344 -- at end: Abort_Under;
345 -- Z : R := (C => X);
346 -- Deep_Adjust (Z, _L, 1);
348 -- begin
349 -- _Assign (X, Y);
350 -- Deep_Finalize (W, False);
351 -- <save W's final pointers>
352 -- W := Z;
353 -- <restore W's final pointers>
354 -- Deep_Adjust (W, _L, 0);
355 -- at end
356 -- _Clean;
357 -- end;
359 function Global_Flist_Ref (Flist_Ref : Node_Id) return Boolean;
360 -- Return True if Flist_Ref refers to a global final list, either
361 -- the object GLobal_Final_List which is used to attach standalone
362 -- objects, or any of the list controllers associated with library
363 -- level access to controlled objects
365 procedure Clean_Simple_Protected_Objects (N : Node_Id);
366 -- Protected objects without entries are not controlled types, and the
367 -- locks have to be released explicitly when such an object goes out
368 -- of scope. Traverse declarations in scope to determine whether such
369 -- objects are present.
371 ----------------------------
372 -- Build_Array_Deep_Procs --
373 ----------------------------
375 procedure Build_Array_Deep_Procs (Typ : Entity_Id) is
376 begin
377 Set_TSS (Typ,
378 Make_Deep_Proc (
379 Prim => Initialize_Case,
380 Typ => Typ,
381 Stmts => Make_Deep_Array_Body (Initialize_Case, Typ)));
383 if not Is_Return_By_Reference_Type (Typ) then
384 Set_TSS (Typ,
385 Make_Deep_Proc (
386 Prim => Adjust_Case,
387 Typ => Typ,
388 Stmts => Make_Deep_Array_Body (Adjust_Case, Typ)));
389 end if;
391 Set_TSS (Typ,
392 Make_Deep_Proc (
393 Prim => Finalize_Case,
394 Typ => Typ,
395 Stmts => Make_Deep_Array_Body (Finalize_Case, Typ)));
396 end Build_Array_Deep_Procs;
398 -----------------------------
399 -- Build_Controlling_Procs --
400 -----------------------------
402 procedure Build_Controlling_Procs (Typ : Entity_Id) is
403 begin
404 if Is_Array_Type (Typ) then
405 Build_Array_Deep_Procs (Typ);
407 else pragma Assert (Is_Record_Type (Typ));
408 Build_Record_Deep_Procs (Typ);
409 end if;
410 end Build_Controlling_Procs;
412 ----------------------
413 -- Build_Final_List --
414 ----------------------
416 procedure Build_Final_List (N : Node_Id; Typ : Entity_Id) is
417 Loc : constant Source_Ptr := Sloc (N);
418 Decl : Node_Id;
420 begin
421 Set_Associated_Final_Chain (Typ,
422 Make_Defining_Identifier (Loc,
423 New_External_Name (Chars (Typ), 'L')));
425 Decl :=
426 Make_Object_Declaration (Loc,
427 Defining_Identifier =>
428 Associated_Final_Chain (Typ),
429 Object_Definition =>
430 New_Reference_To
431 (RTE (RE_List_Controller), Loc));
433 -- The type may have been frozen already, and this is a late freezing
434 -- action, in which case the declaration must be elaborated at once.
435 -- If the call is for an allocator, the chain must also be created now,
436 -- because the freezing of the type does not build one. Otherwise, the
437 -- declaration is one of the freezing actions for a user-defined type.
439 if Is_Frozen (Typ)
440 or else (Nkind (N) = N_Allocator
441 and then Ekind (Etype (N)) = E_Anonymous_Access_Type)
442 then
443 Insert_Action (N, Decl);
444 else
445 Append_Freeze_Action (Typ, Decl);
446 end if;
447 end Build_Final_List;
449 ---------------------
450 -- Build_Late_Proc --
451 ---------------------
453 procedure Build_Late_Proc (Typ : Entity_Id; Nam : Name_Id) is
454 begin
455 for Final_Prim in Name_Of'Range loop
456 if Name_Of (Final_Prim) = Nam then
457 Set_TSS (Typ,
458 Make_Deep_Proc (
459 Prim => Final_Prim,
460 Typ => Typ,
461 Stmts => Make_Deep_Record_Body (Final_Prim, Typ)));
462 end if;
463 end loop;
464 end Build_Late_Proc;
466 -----------------------------
467 -- Build_Record_Deep_Procs --
468 -----------------------------
470 procedure Build_Record_Deep_Procs (Typ : Entity_Id) is
471 begin
472 Set_TSS (Typ,
473 Make_Deep_Proc (
474 Prim => Initialize_Case,
475 Typ => Typ,
476 Stmts => Make_Deep_Record_Body (Initialize_Case, Typ)));
478 if not Is_Return_By_Reference_Type (Typ) then
479 Set_TSS (Typ,
480 Make_Deep_Proc (
481 Prim => Adjust_Case,
482 Typ => Typ,
483 Stmts => Make_Deep_Record_Body (Adjust_Case, Typ)));
484 end if;
486 Set_TSS (Typ,
487 Make_Deep_Proc (
488 Prim => Finalize_Case,
489 Typ => Typ,
490 Stmts => Make_Deep_Record_Body (Finalize_Case, Typ)));
491 end Build_Record_Deep_Procs;
493 -------------------
494 -- Cleanup_Array --
495 -------------------
497 function Cleanup_Array
498 (N : Node_Id;
499 Obj : Node_Id;
500 Typ : Entity_Id) return List_Id
502 Loc : constant Source_Ptr := Sloc (N);
503 Index_List : constant List_Id := New_List;
505 function Free_Component return List_Id;
506 -- Generate the code to finalize the task or protected subcomponents
507 -- of a single component of the array.
509 function Free_One_Dimension (Dim : Int) return List_Id;
510 -- Generate a loop over one dimension of the array
512 --------------------
513 -- Free_Component --
514 --------------------
516 function Free_Component return List_Id is
517 Stmts : List_Id := New_List;
518 Tsk : Node_Id;
519 C_Typ : constant Entity_Id := Component_Type (Typ);
521 begin
522 -- Component type is known to contain tasks or protected objects
524 Tsk :=
525 Make_Indexed_Component (Loc,
526 Prefix => Duplicate_Subexpr_No_Checks (Obj),
527 Expressions => Index_List);
529 Set_Etype (Tsk, C_Typ);
531 if Is_Task_Type (C_Typ) then
532 Append_To (Stmts, Cleanup_Task (N, Tsk));
534 elsif Is_Simple_Protected_Type (C_Typ) then
535 Append_To (Stmts, Cleanup_Protected_Object (N, Tsk));
537 elsif Is_Record_Type (C_Typ) then
538 Stmts := Cleanup_Record (N, Tsk, C_Typ);
540 elsif Is_Array_Type (C_Typ) then
541 Stmts := Cleanup_Array (N, Tsk, C_Typ);
542 end if;
544 return Stmts;
545 end Free_Component;
547 ------------------------
548 -- Free_One_Dimension --
549 ------------------------
551 function Free_One_Dimension (Dim : Int) return List_Id is
552 Index : Entity_Id;
554 begin
555 if Dim > Number_Dimensions (Typ) then
556 return Free_Component;
558 -- Here we generate the required loop
560 else
561 Index :=
562 Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
564 Append (New_Reference_To (Index, Loc), Index_List);
566 return New_List (
567 Make_Implicit_Loop_Statement (N,
568 Identifier => Empty,
569 Iteration_Scheme =>
570 Make_Iteration_Scheme (Loc,
571 Loop_Parameter_Specification =>
572 Make_Loop_Parameter_Specification (Loc,
573 Defining_Identifier => Index,
574 Discrete_Subtype_Definition =>
575 Make_Attribute_Reference (Loc,
576 Prefix => Duplicate_Subexpr (Obj),
577 Attribute_Name => Name_Range,
578 Expressions => New_List (
579 Make_Integer_Literal (Loc, Dim))))),
580 Statements => Free_One_Dimension (Dim + 1)));
581 end if;
582 end Free_One_Dimension;
584 -- Start of processing for Cleanup_Array
586 begin
587 return Free_One_Dimension (1);
588 end Cleanup_Array;
590 --------------------
591 -- Cleanup_Record --
592 --------------------
594 function Cleanup_Record
595 (N : Node_Id;
596 Obj : Node_Id;
597 Typ : Entity_Id) return List_Id
599 Loc : constant Source_Ptr := Sloc (N);
600 Tsk : Node_Id;
601 Comp : Entity_Id;
602 Stmts : constant List_Id := New_List;
603 U_Typ : constant Entity_Id := Underlying_Type (Typ);
605 begin
606 if Has_Discriminants (U_Typ)
607 and then Nkind (Parent (U_Typ)) = N_Full_Type_Declaration
608 and then
609 Nkind (Type_Definition (Parent (U_Typ))) = N_Record_Definition
610 and then
611 Present
612 (Variant_Part
613 (Component_List (Type_Definition (Parent (U_Typ)))))
614 then
615 -- For now, do not attempt to free a component that may appear in
616 -- a variant, and instead issue a warning. Doing this "properly"
617 -- would require building a case statement and would be quite a
618 -- mess. Note that the RM only requires that free "work" for the
619 -- case of a task access value, so already we go way beyond this
620 -- in that we deal with the array case and non-discriminated
621 -- record cases.
623 Error_Msg_N
624 ("task/protected object in variant record will not be freed?", N);
625 return New_List (Make_Null_Statement (Loc));
626 end if;
628 Comp := First_Component (Typ);
630 while Present (Comp) loop
631 if Has_Task (Etype (Comp))
632 or else Has_Simple_Protected_Object (Etype (Comp))
633 then
634 Tsk :=
635 Make_Selected_Component (Loc,
636 Prefix => Duplicate_Subexpr_No_Checks (Obj),
637 Selector_Name => New_Occurrence_Of (Comp, Loc));
638 Set_Etype (Tsk, Etype (Comp));
640 if Is_Task_Type (Etype (Comp)) then
641 Append_To (Stmts, Cleanup_Task (N, Tsk));
643 elsif Is_Simple_Protected_Type (Etype (Comp)) then
644 Append_To (Stmts, Cleanup_Protected_Object (N, Tsk));
646 elsif Is_Record_Type (Etype (Comp)) then
648 -- Recurse, by generating the prefix of the argument to
649 -- the eventual cleanup call.
651 Append_List_To
652 (Stmts, Cleanup_Record (N, Tsk, Etype (Comp)));
654 elsif Is_Array_Type (Etype (Comp)) then
655 Append_List_To
656 (Stmts, Cleanup_Array (N, Tsk, Etype (Comp)));
657 end if;
658 end if;
660 Next_Component (Comp);
661 end loop;
663 return Stmts;
664 end Cleanup_Record;
666 ------------------------------
667 -- Cleanup_Protected_Object --
668 ------------------------------
670 function Cleanup_Protected_Object
671 (N : Node_Id;
672 Ref : Node_Id) return Node_Id
674 Loc : constant Source_Ptr := Sloc (N);
676 begin
677 return
678 Make_Procedure_Call_Statement (Loc,
679 Name => New_Reference_To (RTE (RE_Finalize_Protection), Loc),
680 Parameter_Associations => New_List (
681 Concurrent_Ref (Ref)));
682 end Cleanup_Protected_Object;
684 ------------------------------------
685 -- Clean_Simple_Protected_Objects --
686 ------------------------------------
688 procedure Clean_Simple_Protected_Objects (N : Node_Id) is
689 Stmts : constant List_Id := Statements (Handled_Statement_Sequence (N));
690 Stmt : Node_Id := Last (Stmts);
691 E : Entity_Id;
693 begin
694 E := First_Entity (Current_Scope);
695 while Present (E) loop
696 if (Ekind (E) = E_Variable
697 or else Ekind (E) = E_Constant)
698 and then Has_Simple_Protected_Object (Etype (E))
699 and then not Has_Task (Etype (E))
700 and then Nkind (Parent (E)) /= N_Object_Renaming_Declaration
701 then
702 declare
703 Typ : constant Entity_Id := Etype (E);
704 Ref : constant Node_Id := New_Occurrence_Of (E, Sloc (Stmt));
706 begin
707 if Is_Simple_Protected_Type (Typ) then
708 Append_To (Stmts, Cleanup_Protected_Object (N, Ref));
710 elsif Has_Simple_Protected_Object (Typ) then
711 if Is_Record_Type (Typ) then
712 Append_List_To (Stmts, Cleanup_Record (N, Ref, Typ));
714 elsif Is_Array_Type (Typ) then
715 Append_List_To (Stmts, Cleanup_Array (N, Ref, Typ));
716 end if;
717 end if;
718 end;
719 end if;
721 Next_Entity (E);
722 end loop;
724 -- Analyze inserted cleanup statements
726 if Present (Stmt) then
727 Stmt := Next (Stmt);
729 while Present (Stmt) loop
730 Analyze (Stmt);
731 Next (Stmt);
732 end loop;
733 end if;
734 end Clean_Simple_Protected_Objects;
736 ------------------
737 -- Cleanup_Task --
738 ------------------
740 function Cleanup_Task
741 (N : Node_Id;
742 Ref : Node_Id) return Node_Id
744 Loc : constant Source_Ptr := Sloc (N);
745 begin
746 return
747 Make_Procedure_Call_Statement (Loc,
748 Name => New_Reference_To (RTE (RE_Free_Task), Loc),
749 Parameter_Associations =>
750 New_List (Concurrent_Ref (Ref)));
751 end Cleanup_Task;
753 ---------------------------------
754 -- Has_Simple_Protected_Object --
755 ---------------------------------
757 function Has_Simple_Protected_Object (T : Entity_Id) return Boolean is
758 Comp : Entity_Id;
760 begin
761 if Is_Simple_Protected_Type (T) then
762 return True;
764 elsif Is_Array_Type (T) then
765 return Has_Simple_Protected_Object (Component_Type (T));
767 elsif Is_Record_Type (T) then
768 Comp := First_Component (T);
770 while Present (Comp) loop
771 if Has_Simple_Protected_Object (Etype (Comp)) then
772 return True;
773 end if;
775 Next_Component (Comp);
776 end loop;
778 return False;
780 else
781 return False;
782 end if;
783 end Has_Simple_Protected_Object;
785 ------------------------------
786 -- Is_Simple_Protected_Type --
787 ------------------------------
789 function Is_Simple_Protected_Type (T : Entity_Id) return Boolean is
790 begin
791 return Is_Protected_Type (T) and then not Has_Entries (T);
792 end Is_Simple_Protected_Type;
794 ------------------------------
795 -- Check_Visibly_Controlled --
796 ------------------------------
798 procedure Check_Visibly_Controlled
799 (Prim : Final_Primitives;
800 Typ : Entity_Id;
801 E : in out Entity_Id;
802 Cref : in out Node_Id)
804 Parent_Type : Entity_Id;
805 Op : Entity_Id;
807 begin
808 if Is_Derived_Type (Typ)
809 and then Comes_From_Source (E)
810 and then not Is_Overriding_Operation (E)
811 then
812 -- We know that the explicit operation on the type does not override
813 -- the inherited operation of the parent, and that the derivation
814 -- is from a private type that is not visibly controlled.
816 Parent_Type := Etype (Typ);
817 Op := Find_Prim_Op (Parent_Type, Name_Of (Prim));
819 if Present (Op) then
820 E := Op;
822 -- Wrap the object to be initialized into the proper
823 -- unchecked conversion, to be compatible with the operation
824 -- to be called.
826 if Nkind (Cref) = N_Unchecked_Type_Conversion then
827 Cref := Unchecked_Convert_To (Parent_Type, Expression (Cref));
828 else
829 Cref := Unchecked_Convert_To (Parent_Type, Cref);
830 end if;
831 end if;
832 end if;
833 end Check_Visibly_Controlled;
835 ---------------------
836 -- Controlled_Type --
837 ---------------------
839 function Controlled_Type (T : Entity_Id) return Boolean is
841 function Has_Some_Controlled_Component (Rec : Entity_Id) return Boolean;
842 -- If type is not frozen yet, check explicitly among its components,
843 -- because flag is not necessarily set.
845 -----------------------------------
846 -- Has_Some_Controlled_Component --
847 -----------------------------------
849 function Has_Some_Controlled_Component
850 (Rec : Entity_Id) return Boolean
852 Comp : Entity_Id;
854 begin
855 if Has_Controlled_Component (Rec) then
856 return True;
858 elsif not Is_Frozen (Rec) then
859 if Is_Record_Type (Rec) then
860 Comp := First_Entity (Rec);
862 while Present (Comp) loop
863 if not Is_Type (Comp)
864 and then Controlled_Type (Etype (Comp))
865 then
866 return True;
867 end if;
869 Next_Entity (Comp);
870 end loop;
872 return False;
874 elsif Is_Array_Type (Rec) then
875 return Is_Controlled (Component_Type (Rec));
877 else
878 return Has_Controlled_Component (Rec);
879 end if;
880 else
881 return False;
882 end if;
883 end Has_Some_Controlled_Component;
885 -- Start of processing for Controlled_Type
887 begin
888 -- Class-wide types must be treated as controlled because they may
889 -- contain an extension that has controlled components
891 -- We can skip this if finalization is not available
893 return (Is_Class_Wide_Type (T)
894 and then not In_Finalization_Root (T)
895 and then not Restriction_Active (No_Finalization))
896 or else Is_Controlled (T)
897 or else Has_Some_Controlled_Component (T)
898 or else (Is_Concurrent_Type (T)
899 and then Present (Corresponding_Record_Type (T))
900 and then Controlled_Type (Corresponding_Record_Type (T)));
901 end Controlled_Type;
903 --------------------------
904 -- Controller_Component --
905 --------------------------
907 function Controller_Component (Typ : Entity_Id) return Entity_Id is
908 T : Entity_Id := Base_Type (Typ);
909 Comp : Entity_Id;
910 Comp_Scop : Entity_Id;
911 Res : Entity_Id := Empty;
912 Res_Scop : Entity_Id := Empty;
914 begin
915 if Is_Class_Wide_Type (T) then
916 T := Root_Type (T);
917 end if;
919 if Is_Private_Type (T) then
920 T := Underlying_Type (T);
921 end if;
923 -- Fetch the outermost controller
925 Comp := First_Entity (T);
926 while Present (Comp) loop
927 if Chars (Comp) = Name_uController then
928 Comp_Scop := Scope (Original_Record_Component (Comp));
930 -- If this controller is at the outermost level, no need to
931 -- look for another one
933 if Comp_Scop = T then
934 return Comp;
936 -- Otherwise record the outermost one and continue looking
938 elsif Res = Empty or else Is_Ancestor (Res_Scop, Comp_Scop) then
939 Res := Comp;
940 Res_Scop := Comp_Scop;
941 end if;
942 end if;
944 Next_Entity (Comp);
945 end loop;
947 -- If we fall through the loop, there is no controller component
949 return Res;
950 end Controller_Component;
952 ------------------
953 -- Convert_View --
954 ------------------
956 function Convert_View
957 (Proc : Entity_Id;
958 Arg : Node_Id;
959 Ind : Pos := 1) return Node_Id
961 Fent : Entity_Id := First_Entity (Proc);
962 Ftyp : Entity_Id;
963 Atyp : Entity_Id;
965 begin
966 for J in 2 .. Ind loop
967 Next_Entity (Fent);
968 end loop;
970 Ftyp := Etype (Fent);
972 if Nkind (Arg) = N_Type_Conversion
973 or else Nkind (Arg) = N_Unchecked_Type_Conversion
974 then
975 Atyp := Entity (Subtype_Mark (Arg));
976 else
977 Atyp := Etype (Arg);
978 end if;
980 if Is_Abstract (Proc) and then Is_Tagged_Type (Ftyp) then
981 return Unchecked_Convert_To (Class_Wide_Type (Ftyp), Arg);
983 elsif Ftyp /= Atyp
984 and then Present (Atyp)
985 and then
986 (Is_Private_Type (Ftyp) or else Is_Private_Type (Atyp))
987 and then
988 Base_Type (Underlying_Type (Atyp)) =
989 Base_Type (Underlying_Type (Ftyp))
990 then
991 return Unchecked_Convert_To (Ftyp, Arg);
993 -- If the argument is already a conversion, as generated by
994 -- Make_Init_Call, set the target type to the type of the formal
995 -- directly, to avoid spurious typing problems.
997 elsif (Nkind (Arg) = N_Unchecked_Type_Conversion
998 or else Nkind (Arg) = N_Type_Conversion)
999 and then not Is_Class_Wide_Type (Atyp)
1000 then
1001 Set_Subtype_Mark (Arg, New_Occurrence_Of (Ftyp, Sloc (Arg)));
1002 Set_Etype (Arg, Ftyp);
1003 return Arg;
1005 else
1006 return Arg;
1007 end if;
1008 end Convert_View;
1010 -------------------------------
1011 -- Establish_Transient_Scope --
1012 -------------------------------
1014 -- This procedure is called each time a transient block has to be inserted
1015 -- that is to say for each call to a function with unconstrained ot tagged
1016 -- result. It creates a new scope on the stack scope in order to enclose
1017 -- all transient variables generated
1019 procedure Establish_Transient_Scope (N : Node_Id; Sec_Stack : Boolean) is
1020 Loc : constant Source_Ptr := Sloc (N);
1021 Wrap_Node : Node_Id;
1023 Sec_Stk : constant Boolean :=
1024 Sec_Stack and not Functions_Return_By_DSP_On_Target;
1025 -- We never need a secondary stack if functions return by DSP
1027 begin
1028 -- Do not create a transient scope if we are already inside one
1030 for S in reverse Scope_Stack.First .. Scope_Stack.Last loop
1032 if Scope_Stack.Table (S).Is_Transient then
1033 if Sec_Stk then
1034 Set_Uses_Sec_Stack (Scope_Stack.Table (S).Entity);
1035 end if;
1037 return;
1039 -- If we have encountered Standard there are no enclosing
1040 -- transient scopes.
1042 elsif Scope_Stack.Table (S).Entity = Standard_Standard then
1043 exit;
1045 end if;
1046 end loop;
1048 Wrap_Node := Find_Node_To_Be_Wrapped (N);
1050 -- Case of no wrap node, false alert, no transient scope needed
1052 if No (Wrap_Node) then
1053 null;
1055 -- If the node to wrap is an iteration_scheme, the expression is
1056 -- one of the bounds, and the expansion will make an explicit
1057 -- declaration for it (see Analyze_Iteration_Scheme, sem_ch5.adb),
1058 -- so do not apply any transformations here.
1060 elsif Nkind (Wrap_Node) = N_Iteration_Scheme then
1061 null;
1063 else
1064 New_Scope (New_Internal_Entity (E_Block, Current_Scope, Loc, 'B'));
1065 Set_Scope_Is_Transient;
1067 if Sec_Stk then
1068 Set_Uses_Sec_Stack (Current_Scope);
1069 Check_Restriction (No_Secondary_Stack, N);
1070 end if;
1072 Set_Etype (Current_Scope, Standard_Void_Type);
1073 Set_Node_To_Be_Wrapped (Wrap_Node);
1075 if Debug_Flag_W then
1076 Write_Str (" <Transient>");
1077 Write_Eol;
1078 end if;
1079 end if;
1080 end Establish_Transient_Scope;
1082 ----------------------------
1083 -- Expand_Cleanup_Actions --
1084 ----------------------------
1086 procedure Expand_Cleanup_Actions (N : Node_Id) is
1087 Loc : Source_Ptr;
1088 S : constant Entity_Id :=
1089 Current_Scope;
1090 Flist : constant Entity_Id :=
1091 Finalization_Chain_Entity (S);
1092 Is_Task : constant Boolean :=
1093 (Nkind (Original_Node (N)) = N_Task_Body);
1094 Is_Master : constant Boolean :=
1095 Nkind (N) /= N_Entry_Body
1096 and then Is_Task_Master (N);
1097 Is_Protected : constant Boolean :=
1098 Nkind (N) = N_Subprogram_Body
1099 and then Is_Protected_Subprogram_Body (N);
1100 Is_Task_Allocation : constant Boolean :=
1101 Nkind (N) = N_Block_Statement
1102 and then Is_Task_Allocation_Block (N);
1103 Is_Asynchronous_Call : constant Boolean :=
1104 Nkind (N) = N_Block_Statement
1105 and then Is_Asynchronous_Call_Block (N);
1107 Clean : Entity_Id;
1108 Mark : Entity_Id := Empty;
1109 New_Decls : constant List_Id := New_List;
1110 Blok : Node_Id;
1111 End_Lab : Node_Id;
1112 Wrapped : Boolean;
1113 Chain : Entity_Id := Empty;
1114 Decl : Node_Id;
1115 Old_Poll : Boolean;
1117 begin
1119 -- Compute a location that is not directly in the user code in
1120 -- order to avoid to generate confusing debug info. A good
1121 -- approximation is the name of the outer user-defined scope
1123 declare
1124 S1 : Entity_Id := S;
1126 begin
1127 while not Comes_From_Source (S1) and then S1 /= Standard_Standard loop
1128 S1 := Scope (S1);
1129 end loop;
1131 Loc := Sloc (S1);
1132 end;
1134 -- There are cleanup actions only if the secondary stack needs
1135 -- releasing or some finalizations are needed or in the context
1136 -- of tasking
1138 if Uses_Sec_Stack (Current_Scope)
1139 and then not Sec_Stack_Needed_For_Return (Current_Scope)
1140 then
1141 null;
1142 elsif No (Flist)
1143 and then not Is_Master
1144 and then not Is_Task
1145 and then not Is_Protected
1146 and then not Is_Task_Allocation
1147 and then not Is_Asynchronous_Call
1148 then
1149 Clean_Simple_Protected_Objects (N);
1150 return;
1151 end if;
1153 -- If the current scope is the subprogram body that is the rewriting
1154 -- of a task body, and the descriptors have not been delayed (due to
1155 -- some nested instantiations) do not generate redundant cleanup
1156 -- actions: the cleanup procedure already exists for this body.
1158 if Nkind (N) = N_Subprogram_Body
1159 and then Nkind (Original_Node (N)) = N_Task_Body
1160 and then not Delay_Subprogram_Descriptors (Corresponding_Spec (N))
1161 then
1162 return;
1163 end if;
1165 -- Set polling off, since we don't need to poll during cleanup
1166 -- actions, and indeed for the cleanup routine, which is executed
1167 -- with aborts deferred, we don't want polling.
1169 Old_Poll := Polling_Required;
1170 Polling_Required := False;
1172 -- Make sure we have a declaration list, since we will add to it
1174 if No (Declarations (N)) then
1175 Set_Declarations (N, New_List);
1176 end if;
1178 -- The task activation call has already been built for task
1179 -- allocation blocks.
1181 if not Is_Task_Allocation then
1182 Build_Task_Activation_Call (N);
1183 end if;
1185 if Is_Master then
1186 Establish_Task_Master (N);
1187 end if;
1189 -- If secondary stack is in use, expand:
1190 -- _Mxx : constant Mark_Id := SS_Mark;
1192 -- Suppress calls to SS_Mark and SS_Release if Java_VM,
1193 -- since we never use the secondary stack on the JVM.
1195 if Uses_Sec_Stack (Current_Scope)
1196 and then not Sec_Stack_Needed_For_Return (Current_Scope)
1197 and then not Java_VM
1198 then
1199 Mark := Make_Defining_Identifier (Loc, New_Internal_Name ('M'));
1200 Append_To (New_Decls,
1201 Make_Object_Declaration (Loc,
1202 Defining_Identifier => Mark,
1203 Object_Definition => New_Reference_To (RTE (RE_Mark_Id), Loc),
1204 Expression =>
1205 Make_Function_Call (Loc,
1206 Name => New_Reference_To (RTE (RE_SS_Mark), Loc))));
1208 Set_Uses_Sec_Stack (Current_Scope, False);
1209 end if;
1211 -- If finalization list is present then expand:
1212 -- Local_Final_List : System.FI.Finalizable_Ptr;
1214 if Present (Flist) then
1215 Append_To (New_Decls,
1216 Make_Object_Declaration (Loc,
1217 Defining_Identifier => Flist,
1218 Object_Definition =>
1219 New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
1220 end if;
1222 -- Clean-up procedure definition
1224 Clean := Make_Defining_Identifier (Loc, Name_uClean);
1225 Set_Suppress_Elaboration_Warnings (Clean);
1226 Append_To (New_Decls,
1227 Make_Clean (N, Clean, Mark, Flist,
1228 Is_Task,
1229 Is_Master,
1230 Is_Protected,
1231 Is_Task_Allocation,
1232 Is_Asynchronous_Call));
1234 -- If exception handlers are present, wrap the Sequence of
1235 -- statements in a block because it is not possible to get
1236 -- exception handlers and an AT END call in the same scope.
1238 if Present (Exception_Handlers (Handled_Statement_Sequence (N))) then
1240 -- Preserve end label to provide proper cross-reference information
1242 End_Lab := End_Label (Handled_Statement_Sequence (N));
1243 Blok :=
1244 Make_Block_Statement (Loc,
1245 Handled_Statement_Sequence => Handled_Statement_Sequence (N));
1246 Set_Handled_Statement_Sequence (N,
1247 Make_Handled_Sequence_Of_Statements (Loc, New_List (Blok)));
1248 Set_End_Label (Handled_Statement_Sequence (N), End_Lab);
1249 Wrapped := True;
1251 -- Comment needed here, see RH for 1.306 ???
1253 if Nkind (N) = N_Subprogram_Body then
1254 Set_Has_Nested_Block_With_Handler (Current_Scope);
1255 end if;
1257 -- Otherwise we do not wrap
1259 else
1260 Wrapped := False;
1261 Blok := Empty;
1262 end if;
1264 -- Don't move the _chain Activation_Chain declaration in task
1265 -- allocation blocks. Task allocation blocks use this object
1266 -- in their cleanup handlers, and gigi complains if it is declared
1267 -- in the sequence of statements of the scope that declares the
1268 -- handler.
1270 if Is_Task_Allocation then
1271 Chain := Activation_Chain_Entity (N);
1272 Decl := First (Declarations (N));
1274 while Nkind (Decl) /= N_Object_Declaration
1275 or else Defining_Identifier (Decl) /= Chain
1276 loop
1277 Next (Decl);
1278 pragma Assert (Present (Decl));
1279 end loop;
1281 Remove (Decl);
1282 Prepend_To (New_Decls, Decl);
1283 end if;
1285 -- Now we move the declarations into the Sequence of statements
1286 -- in order to get them protected by the AT END call. It may seem
1287 -- weird to put declarations in the sequence of statement but in
1288 -- fact nothing forbids that at the tree level. We also set the
1289 -- First_Real_Statement field so that we remember where the real
1290 -- statements (i.e. original statements) begin. Note that if we
1291 -- wrapped the statements, the first real statement is inside the
1292 -- inner block. If the First_Real_Statement is already set (as is
1293 -- the case for subprogram bodies that are expansions of task bodies)
1294 -- then do not reset it, because its declarative part would migrate
1295 -- to the statement part.
1297 if not Wrapped then
1298 if No (First_Real_Statement (Handled_Statement_Sequence (N))) then
1299 Set_First_Real_Statement (Handled_Statement_Sequence (N),
1300 First (Statements (Handled_Statement_Sequence (N))));
1301 end if;
1303 else
1304 Set_First_Real_Statement (Handled_Statement_Sequence (N), Blok);
1305 end if;
1307 Append_List_To (Declarations (N),
1308 Statements (Handled_Statement_Sequence (N)));
1309 Set_Statements (Handled_Statement_Sequence (N), Declarations (N));
1311 -- We need to reset the Sloc of the handled statement sequence to
1312 -- properly reflect the new initial "statement" in the sequence.
1314 Set_Sloc
1315 (Handled_Statement_Sequence (N), Sloc (First (Declarations (N))));
1317 -- The declarations of the _Clean procedure and finalization chain
1318 -- replace the old declarations that have been moved inward
1320 Set_Declarations (N, New_Decls);
1321 Analyze_Declarations (New_Decls);
1323 -- The At_End call is attached to the sequence of statements
1325 declare
1326 HSS : Node_Id;
1328 begin
1329 -- If the construct is a protected subprogram, then the call to
1330 -- the corresponding unprotected program appears in a block which
1331 -- is the last statement in the body, and it is this block that
1332 -- must be covered by the At_End handler.
1334 if Is_Protected then
1335 HSS := Handled_Statement_Sequence
1336 (Last (Statements (Handled_Statement_Sequence (N))));
1337 else
1338 HSS := Handled_Statement_Sequence (N);
1339 end if;
1341 Set_At_End_Proc (HSS, New_Occurrence_Of (Clean, Loc));
1342 Expand_At_End_Handler (HSS, Empty);
1343 end;
1345 -- Restore saved polling mode
1347 Polling_Required := Old_Poll;
1348 end Expand_Cleanup_Actions;
1350 -------------------------------
1351 -- Expand_Ctrl_Function_Call --
1352 -------------------------------
1354 procedure Expand_Ctrl_Function_Call (N : Node_Id) is
1355 Loc : constant Source_Ptr := Sloc (N);
1356 Rtype : constant Entity_Id := Etype (N);
1357 Utype : constant Entity_Id := Underlying_Type (Rtype);
1358 Ref : Node_Id;
1359 Action : Node_Id;
1360 Action2 : Node_Id := Empty;
1362 Attach_Level : Uint := Uint_1;
1363 Len_Ref : Node_Id := Empty;
1365 function Last_Array_Component
1366 (Ref : Node_Id;
1367 Typ : Entity_Id) return Node_Id;
1368 -- Creates a reference to the last component of the array object
1369 -- designated by Ref whose type is Typ.
1371 --------------------------
1372 -- Last_Array_Component --
1373 --------------------------
1375 function Last_Array_Component
1376 (Ref : Node_Id;
1377 Typ : Entity_Id) return Node_Id
1379 Index_List : constant List_Id := New_List;
1381 begin
1382 for N in 1 .. Number_Dimensions (Typ) loop
1383 Append_To (Index_List,
1384 Make_Attribute_Reference (Loc,
1385 Prefix => Duplicate_Subexpr_No_Checks (Ref),
1386 Attribute_Name => Name_Last,
1387 Expressions => New_List (
1388 Make_Integer_Literal (Loc, N))));
1389 end loop;
1391 return
1392 Make_Indexed_Component (Loc,
1393 Prefix => Duplicate_Subexpr (Ref),
1394 Expressions => Index_List);
1395 end Last_Array_Component;
1397 -- Start of processing for Expand_Ctrl_Function_Call
1399 begin
1400 -- Optimization, if the returned value (which is on the sec-stack)
1401 -- is returned again, no need to copy/readjust/finalize, we can just
1402 -- pass the value thru (see Expand_N_Return_Statement), and thus no
1403 -- attachment is needed
1405 if Nkind (Parent (N)) = N_Return_Statement then
1406 return;
1407 end if;
1409 -- Resolution is now finished, make sure we don't start analysis again
1410 -- because of the duplication
1412 Set_Analyzed (N);
1413 Ref := Duplicate_Subexpr_No_Checks (N);
1415 -- Now we can generate the Attach Call, note that this value is
1416 -- always in the (secondary) stack and thus is attached to a singly
1417 -- linked final list:
1419 -- Resx := F (X)'reference;
1420 -- Attach_To_Final_List (_Lx, Resx.all, 1);
1422 -- or when there are controlled components
1424 -- Attach_To_Final_List (_Lx, Resx._controller, 1);
1426 -- or when it is both is_controlled and has_controlled_components
1428 -- Attach_To_Final_List (_Lx, Resx._controller, 1);
1429 -- Attach_To_Final_List (_Lx, Resx, 1);
1431 -- or if it is an array with is_controlled (and has_controlled)
1433 -- Attach_To_Final_List (_Lx, Resx (Resx'last), 3);
1434 -- An attach level of 3 means that a whole array is to be
1435 -- attached to the finalization list (including the controlled
1436 -- components)
1438 -- or if it is an array with has_controlled components but not
1439 -- is_controlled
1441 -- Attach_To_Final_List (_Lx, Resx (Resx'last)._controller, 3);
1443 if Has_Controlled_Component (Rtype) then
1444 declare
1445 T1 : Entity_Id := Rtype;
1446 T2 : Entity_Id := Utype;
1448 begin
1449 if Is_Array_Type (T2) then
1450 Len_Ref :=
1451 Make_Attribute_Reference (Loc,
1452 Prefix =>
1453 Duplicate_Subexpr_Move_Checks
1454 (Unchecked_Convert_To (T2, Ref)),
1455 Attribute_Name => Name_Length);
1456 end if;
1458 while Is_Array_Type (T2) loop
1459 if T1 /= T2 then
1460 Ref := Unchecked_Convert_To (T2, Ref);
1461 end if;
1463 Ref := Last_Array_Component (Ref, T2);
1464 Attach_Level := Uint_3;
1465 T1 := Component_Type (T2);
1466 T2 := Underlying_Type (T1);
1467 end loop;
1469 -- If the type has controlled components, go to the controller
1470 -- except in the case of arrays of controlled objects since in
1471 -- this case objects and their components are already chained
1472 -- and the head of the chain is the last array element.
1474 if Is_Array_Type (Rtype) and then Is_Controlled (T2) then
1475 null;
1477 elsif Has_Controlled_Component (T2) then
1478 if T1 /= T2 then
1479 Ref := Unchecked_Convert_To (T2, Ref);
1480 end if;
1482 Ref :=
1483 Make_Selected_Component (Loc,
1484 Prefix => Ref,
1485 Selector_Name => Make_Identifier (Loc, Name_uController));
1486 end if;
1487 end;
1489 -- Here we know that 'Ref' has a controller so we may as well
1490 -- attach it directly
1492 Action :=
1493 Make_Attach_Call (
1494 Obj_Ref => Ref,
1495 Flist_Ref => Find_Final_List (Current_Scope),
1496 With_Attach => Make_Integer_Literal (Loc, Attach_Level));
1498 -- If it is also Is_Controlled we need to attach the global object
1500 if Is_Controlled (Rtype) then
1501 Action2 :=
1502 Make_Attach_Call (
1503 Obj_Ref => Duplicate_Subexpr_No_Checks (N),
1504 Flist_Ref => Find_Final_List (Current_Scope),
1505 With_Attach => Make_Integer_Literal (Loc, Attach_Level));
1506 end if;
1508 else
1509 -- Here, we have a controlled type that does not seem to have
1510 -- controlled components but it could be a class wide type whose
1511 -- further derivations have controlled components. So we don't know
1512 -- if the object itself needs to be attached or if it
1513 -- has a record controller. We need to call a runtime function
1514 -- (Deep_Tag_Attach) which knows what to do thanks to the
1515 -- RC_Offset in the dispatch table.
1517 Action :=
1518 Make_Procedure_Call_Statement (Loc,
1519 Name => New_Reference_To (RTE (RE_Deep_Tag_Attach), Loc),
1520 Parameter_Associations => New_List (
1521 Find_Final_List (Current_Scope),
1523 Make_Attribute_Reference (Loc,
1524 Prefix => Ref,
1525 Attribute_Name => Name_Address),
1527 Make_Integer_Literal (Loc, Attach_Level)));
1528 end if;
1530 if Present (Len_Ref) then
1531 Action :=
1532 Make_Implicit_If_Statement (N,
1533 Condition => Make_Op_Gt (Loc,
1534 Left_Opnd => Len_Ref,
1535 Right_Opnd => Make_Integer_Literal (Loc, 0)),
1536 Then_Statements => New_List (Action));
1537 end if;
1539 Insert_Action (N, Action);
1540 if Present (Action2) then
1541 Insert_Action (N, Action2);
1542 end if;
1543 end Expand_Ctrl_Function_Call;
1545 ---------------------------
1546 -- Expand_N_Package_Body --
1547 ---------------------------
1549 -- Add call to Activate_Tasks if body is an activator (actual
1550 -- processing is in chapter 9).
1552 -- Generate subprogram descriptor for elaboration routine
1554 -- ENcode entity names in package body
1556 procedure Expand_N_Package_Body (N : Node_Id) is
1557 Ent : constant Entity_Id := Corresponding_Spec (N);
1559 begin
1560 -- This is done only for non-generic packages
1562 if Ekind (Ent) = E_Package then
1563 New_Scope (Corresponding_Spec (N));
1564 Build_Task_Activation_Call (N);
1565 Pop_Scope;
1566 end if;
1568 Set_Elaboration_Flag (N, Corresponding_Spec (N));
1569 Set_In_Package_Body (Ent, False);
1571 -- Set to encode entity names in package body before gigi is called
1573 Qualify_Entity_Names (N);
1574 end Expand_N_Package_Body;
1576 ----------------------------------
1577 -- Expand_N_Package_Declaration --
1578 ----------------------------------
1580 -- Add call to Activate_Tasks if there are tasks declared and the
1581 -- package has no body. Note that in Ada83, this may result in
1582 -- premature activation of some tasks, given that we cannot tell
1583 -- whether a body will eventually appear.
1585 procedure Expand_N_Package_Declaration (N : Node_Id) is
1586 begin
1587 if Nkind (Parent (N)) = N_Compilation_Unit
1588 and then not Body_Required (Parent (N))
1589 and then not Unit_Requires_Body (Defining_Entity (N))
1590 and then Present (Activation_Chain_Entity (N))
1591 then
1592 New_Scope (Defining_Entity (N));
1593 Build_Task_Activation_Call (N);
1594 Pop_Scope;
1595 end if;
1597 -- Note: it is not necessary to worry about generating a subprogram
1598 -- descriptor, since the only way to get exception handlers into a
1599 -- package spec is to include instantiations, and that would cause
1600 -- generation of subprogram descriptors to be delayed in any case.
1602 -- Set to encode entity names in package spec before gigi is called
1604 Qualify_Entity_Names (N);
1605 end Expand_N_Package_Declaration;
1607 ---------------------
1608 -- Find_Final_List --
1609 ---------------------
1611 function Find_Final_List
1612 (E : Entity_Id;
1613 Ref : Node_Id := Empty) return Node_Id
1615 Loc : constant Source_Ptr := Sloc (Ref);
1616 S : Entity_Id;
1617 Id : Entity_Id;
1618 R : Node_Id;
1620 begin
1621 -- Case of an internal component. The Final list is the record
1622 -- controller of the enclosing record
1624 if Present (Ref) then
1625 R := Ref;
1626 loop
1627 case Nkind (R) is
1628 when N_Unchecked_Type_Conversion | N_Type_Conversion =>
1629 R := Expression (R);
1631 when N_Indexed_Component | N_Explicit_Dereference =>
1632 R := Prefix (R);
1634 when N_Selected_Component =>
1635 R := Prefix (R);
1636 exit;
1638 when N_Identifier =>
1639 exit;
1641 when others =>
1642 raise Program_Error;
1643 end case;
1644 end loop;
1646 return
1647 Make_Selected_Component (Loc,
1648 Prefix =>
1649 Make_Selected_Component (Loc,
1650 Prefix => R,
1651 Selector_Name => Make_Identifier (Loc, Name_uController)),
1652 Selector_Name => Make_Identifier (Loc, Name_F));
1654 -- Case of a dynamically allocated object. The final list is the
1655 -- corresponding list controller (The next entity in the scope of
1656 -- the access type with the right type). If the type comes from a
1657 -- With_Type clause, no controller was created, and we use the
1658 -- global chain instead.
1660 elsif Is_Access_Type (E) then
1661 if not From_With_Type (E) then
1662 return
1663 Make_Selected_Component (Loc,
1664 Prefix =>
1665 New_Reference_To
1666 (Associated_Final_Chain (Base_Type (E)), Loc),
1667 Selector_Name => Make_Identifier (Loc, Name_F));
1668 else
1669 return New_Reference_To (RTE (RE_Global_Final_List), Sloc (E));
1670 end if;
1672 else
1673 if Is_Dynamic_Scope (E) then
1674 S := E;
1675 else
1676 S := Enclosing_Dynamic_Scope (E);
1677 end if;
1679 -- When the finalization chain entity is 'Error', it means that
1680 -- there should not be any chain at that level and that the
1681 -- enclosing one should be used
1683 -- This is a nasty kludge, see ??? note in exp_ch11
1685 while Finalization_Chain_Entity (S) = Error loop
1686 S := Enclosing_Dynamic_Scope (S);
1687 end loop;
1689 if S = Standard_Standard then
1690 return New_Reference_To (RTE (RE_Global_Final_List), Sloc (E));
1691 else
1692 if No (Finalization_Chain_Entity (S)) then
1694 Id := Make_Defining_Identifier (Sloc (S),
1695 New_Internal_Name ('F'));
1696 Set_Finalization_Chain_Entity (S, Id);
1698 -- Set momentarily some semantics attributes to allow normal
1699 -- analysis of expansions containing references to this chain.
1700 -- Will be fully decorated during the expansion of the scope
1701 -- itself
1703 Set_Ekind (Id, E_Variable);
1704 Set_Etype (Id, RTE (RE_Finalizable_Ptr));
1705 end if;
1707 return New_Reference_To (Finalization_Chain_Entity (S), Sloc (E));
1708 end if;
1709 end if;
1710 end Find_Final_List;
1712 -----------------------------
1713 -- Find_Node_To_Be_Wrapped --
1714 -----------------------------
1716 function Find_Node_To_Be_Wrapped (N : Node_Id) return Node_Id is
1717 P : Node_Id;
1718 The_Parent : Node_Id;
1720 begin
1721 The_Parent := N;
1722 loop
1723 P := The_Parent;
1724 pragma Assert (P /= Empty);
1725 The_Parent := Parent (P);
1727 case Nkind (The_Parent) is
1729 -- Simple statement can be wrapped
1731 when N_Pragma =>
1732 return The_Parent;
1734 -- Usually assignments are good candidate for wrapping
1735 -- except when they have been generated as part of a
1736 -- controlled aggregate where the wrapping should take
1737 -- place more globally.
1739 when N_Assignment_Statement =>
1740 if No_Ctrl_Actions (The_Parent) then
1741 null;
1742 else
1743 return The_Parent;
1744 end if;
1746 -- An entry call statement is a special case if it occurs in
1747 -- the context of a Timed_Entry_Call. In this case we wrap
1748 -- the entire timed entry call.
1750 when N_Entry_Call_Statement |
1751 N_Procedure_Call_Statement =>
1752 if Nkind (Parent (The_Parent)) = N_Entry_Call_Alternative
1753 and then
1754 (Nkind (Parent (Parent (The_Parent)))
1755 = N_Timed_Entry_Call
1756 or else
1757 Nkind (Parent (Parent (The_Parent)))
1758 = N_Conditional_Entry_Call)
1759 then
1760 return Parent (Parent (The_Parent));
1761 else
1762 return The_Parent;
1763 end if;
1765 -- Object declarations are also a boundary for the transient scope
1766 -- even if they are not really wrapped
1767 -- (see Wrap_Transient_Declaration)
1769 when N_Object_Declaration |
1770 N_Object_Renaming_Declaration |
1771 N_Subtype_Declaration =>
1772 return The_Parent;
1774 -- The expression itself is to be wrapped if its parent is a
1775 -- compound statement or any other statement where the expression
1776 -- is known to be scalar
1778 when N_Accept_Alternative |
1779 N_Attribute_Definition_Clause |
1780 N_Case_Statement |
1781 N_Code_Statement |
1782 N_Delay_Alternative |
1783 N_Delay_Until_Statement |
1784 N_Delay_Relative_Statement |
1785 N_Discriminant_Association |
1786 N_Elsif_Part |
1787 N_Entry_Body_Formal_Part |
1788 N_Exit_Statement |
1789 N_If_Statement |
1790 N_Iteration_Scheme |
1791 N_Terminate_Alternative =>
1792 return P;
1794 when N_Attribute_Reference =>
1796 if Is_Procedure_Attribute_Name
1797 (Attribute_Name (The_Parent))
1798 then
1799 return The_Parent;
1800 end if;
1802 -- A raise statement can be wrapped. This will arise when the
1803 -- expression in a raise_with_expression uses the secondary
1804 -- stack, for example.
1806 when N_Raise_Statement =>
1807 return The_Parent;
1809 -- If the expression is within the iteration scheme of a loop,
1810 -- we must create a declaration for it, followed by an assignment
1811 -- in order to have a usable statement to wrap.
1813 when N_Loop_Parameter_Specification =>
1814 return Parent (The_Parent);
1816 -- The following nodes contains "dummy calls" which don't
1817 -- need to be wrapped.
1819 when N_Parameter_Specification |
1820 N_Discriminant_Specification |
1821 N_Component_Declaration =>
1822 return Empty;
1824 -- The return statement is not to be wrapped when the function
1825 -- itself needs wrapping at the outer-level
1827 when N_Return_Statement =>
1828 if Requires_Transient_Scope (Return_Type (The_Parent)) then
1829 return Empty;
1830 else
1831 return The_Parent;
1832 end if;
1834 -- If we leave a scope without having been able to find a node to
1835 -- wrap, something is going wrong but this can happen in error
1836 -- situation that are not detected yet (such as a dynamic string
1837 -- in a pragma export)
1839 when N_Subprogram_Body |
1840 N_Package_Declaration |
1841 N_Package_Body |
1842 N_Block_Statement =>
1843 return Empty;
1845 -- otherwise continue the search
1847 when others =>
1848 null;
1849 end case;
1850 end loop;
1851 end Find_Node_To_Be_Wrapped;
1853 ----------------------
1854 -- Global_Flist_Ref --
1855 ----------------------
1857 function Global_Flist_Ref (Flist_Ref : Node_Id) return Boolean is
1858 Flist : Entity_Id;
1860 begin
1861 -- Look for the Global_Final_List
1863 if Is_Entity_Name (Flist_Ref) then
1864 Flist := Entity (Flist_Ref);
1866 -- Look for the final list associated with an access to controlled
1868 elsif Nkind (Flist_Ref) = N_Selected_Component
1869 and then Is_Entity_Name (Prefix (Flist_Ref))
1870 then
1871 Flist := Entity (Prefix (Flist_Ref));
1872 else
1873 return False;
1874 end if;
1876 return Present (Flist)
1877 and then Present (Scope (Flist))
1878 and then Enclosing_Dynamic_Scope (Flist) = Standard_Standard;
1879 end Global_Flist_Ref;
1881 ----------------------------------
1882 -- Has_New_Controlled_Component --
1883 ----------------------------------
1885 function Has_New_Controlled_Component (E : Entity_Id) return Boolean is
1886 Comp : Entity_Id;
1888 begin
1889 if not Is_Tagged_Type (E) then
1890 return Has_Controlled_Component (E);
1891 elsif not Is_Derived_Type (E) then
1892 return Has_Controlled_Component (E);
1893 end if;
1895 Comp := First_Component (E);
1896 while Present (Comp) loop
1898 if Chars (Comp) = Name_uParent then
1899 null;
1901 elsif Scope (Original_Record_Component (Comp)) = E
1902 and then Controlled_Type (Etype (Comp))
1903 then
1904 return True;
1905 end if;
1907 Next_Component (Comp);
1908 end loop;
1910 return False;
1911 end Has_New_Controlled_Component;
1913 --------------------------
1914 -- In_Finalization_Root --
1915 --------------------------
1917 -- It would seem simpler to test Scope (RTE (RE_Root_Controlled)) but
1918 -- the purpose of this function is to avoid a circular call to Rtsfind
1919 -- which would been caused by such a test.
1921 function In_Finalization_Root (E : Entity_Id) return Boolean is
1922 S : constant Entity_Id := Scope (E);
1924 begin
1925 return Chars (Scope (S)) = Name_System
1926 and then Chars (S) = Name_Finalization_Root
1927 and then Scope (Scope (S)) = Standard_Standard;
1928 end In_Finalization_Root;
1930 ------------------------------------
1931 -- Insert_Actions_In_Scope_Around --
1932 ------------------------------------
1934 procedure Insert_Actions_In_Scope_Around (N : Node_Id) is
1935 SE : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
1936 Target : Node_Id;
1938 begin
1939 -- If the node to be wrapped is the triggering alternative of an
1940 -- asynchronous select, it is not part of a statement list. The
1941 -- actions must be inserted before the Select itself, which is
1942 -- part of some list of statements.
1944 if Nkind (Parent (Node_To_Be_Wrapped)) = N_Triggering_Alternative then
1945 Target := Parent (Parent (Node_To_Be_Wrapped));
1946 else
1947 Target := N;
1948 end if;
1950 if Present (SE.Actions_To_Be_Wrapped_Before) then
1951 Insert_List_Before (Target, SE.Actions_To_Be_Wrapped_Before);
1952 SE.Actions_To_Be_Wrapped_Before := No_List;
1953 end if;
1955 if Present (SE.Actions_To_Be_Wrapped_After) then
1956 Insert_List_After (Target, SE.Actions_To_Be_Wrapped_After);
1957 SE.Actions_To_Be_Wrapped_After := No_List;
1958 end if;
1959 end Insert_Actions_In_Scope_Around;
1961 -----------------------
1962 -- Make_Adjust_Call --
1963 -----------------------
1965 function Make_Adjust_Call
1966 (Ref : Node_Id;
1967 Typ : Entity_Id;
1968 Flist_Ref : Node_Id;
1969 With_Attach : Node_Id;
1970 Allocator : Boolean := False) return List_Id
1972 Loc : constant Source_Ptr := Sloc (Ref);
1973 Res : constant List_Id := New_List;
1974 Utyp : Entity_Id;
1975 Proc : Entity_Id;
1976 Cref : Node_Id := Ref;
1977 Cref2 : Node_Id;
1978 Attach : Node_Id := With_Attach;
1980 begin
1981 if Is_Class_Wide_Type (Typ) then
1982 Utyp := Underlying_Type (Base_Type (Root_Type (Typ)));
1983 else
1984 Utyp := Underlying_Type (Base_Type (Typ));
1985 end if;
1987 Set_Assignment_OK (Cref);
1989 -- Deal with non-tagged derivation of private views
1991 if Is_Untagged_Derivation (Typ) then
1992 Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
1993 Cref := Unchecked_Convert_To (Utyp, Cref);
1994 Set_Assignment_OK (Cref);
1995 -- To prevent problems with UC see 1.156 RH ???
1996 end if;
1998 -- If the underlying_type is a subtype, we are dealing with
1999 -- the completion of a private type. We need to access
2000 -- the base type and generate a conversion to it.
2002 if Utyp /= Base_Type (Utyp) then
2003 pragma Assert (Is_Private_Type (Typ));
2004 Utyp := Base_Type (Utyp);
2005 Cref := Unchecked_Convert_To (Utyp, Cref);
2006 end if;
2008 -- If the object is unanalyzed, set its expected type for use
2009 -- in Convert_View in case an additional conversion is needed.
2011 if No (Etype (Cref))
2012 and then Nkind (Cref) /= N_Unchecked_Type_Conversion
2013 then
2014 Set_Etype (Cref, Typ);
2015 end if;
2017 -- We do not need to attach to one of the Global Final Lists
2018 -- the objects whose type is Finalize_Storage_Only
2020 if Finalize_Storage_Only (Typ)
2021 and then (Global_Flist_Ref (Flist_Ref)
2022 or else Entity (Constant_Value (RTE (RE_Garbage_Collected)))
2023 = Standard_True)
2024 then
2025 Attach := Make_Integer_Literal (Loc, 0);
2026 end if;
2028 -- Special case for allocators: need initialization of the chain
2029 -- pointers. For the 0 case, reset them to null.
2031 if Allocator then
2032 pragma Assert (Nkind (Attach) = N_Integer_Literal);
2034 if Intval (Attach) = 0 then
2035 Set_Intval (Attach, Uint_4);
2036 end if;
2037 end if;
2039 -- Generate:
2040 -- Deep_Adjust (Flist_Ref, Ref, Attach);
2042 if Has_Controlled_Component (Utyp)
2043 or else Is_Class_Wide_Type (Typ)
2044 then
2045 if Is_Tagged_Type (Utyp) then
2046 Proc := Find_Prim_Op (Utyp, TSS_Deep_Adjust);
2048 else
2049 Proc := TSS (Utyp, TSS_Deep_Adjust);
2050 end if;
2052 Cref := Convert_View (Proc, Cref, 2);
2054 Append_To (Res,
2055 Make_Procedure_Call_Statement (Loc,
2056 Name => New_Reference_To (Proc, Loc),
2057 Parameter_Associations =>
2058 New_List (Flist_Ref, Cref, Attach)));
2060 -- Generate:
2061 -- if With_Attach then
2062 -- Attach_To_Final_List (Ref, Flist_Ref);
2063 -- end if;
2064 -- Adjust (Ref);
2066 else -- Is_Controlled (Utyp)
2068 Proc := Find_Prim_Op (Utyp, Name_Of (Adjust_Case));
2069 Cref := Convert_View (Proc, Cref);
2070 Cref2 := New_Copy_Tree (Cref);
2072 Append_To (Res,
2073 Make_Procedure_Call_Statement (Loc,
2074 Name => New_Reference_To (Proc, Loc),
2075 Parameter_Associations => New_List (Cref2)));
2077 Append_To (Res, Make_Attach_Call (Cref, Flist_Ref, Attach));
2078 end if;
2080 return Res;
2081 end Make_Adjust_Call;
2083 ----------------------
2084 -- Make_Attach_Call --
2085 ----------------------
2087 -- Generate:
2088 -- System.FI.Attach_To_Final_List (Flist, Ref, Nb_Link)
2090 function Make_Attach_Call
2091 (Obj_Ref : Node_Id;
2092 Flist_Ref : Node_Id;
2093 With_Attach : Node_Id) return Node_Id
2095 Loc : constant Source_Ptr := Sloc (Obj_Ref);
2097 begin
2098 -- Optimization: If the number of links is statically '0', don't
2099 -- call the attach_proc.
2101 if Nkind (With_Attach) = N_Integer_Literal
2102 and then Intval (With_Attach) = Uint_0
2103 then
2104 return Make_Null_Statement (Loc);
2105 end if;
2107 return
2108 Make_Procedure_Call_Statement (Loc,
2109 Name => New_Reference_To (RTE (RE_Attach_To_Final_List), Loc),
2110 Parameter_Associations => New_List (
2111 Flist_Ref,
2112 OK_Convert_To (RTE (RE_Finalizable), Obj_Ref),
2113 With_Attach));
2114 end Make_Attach_Call;
2116 ----------------
2117 -- Make_Clean --
2118 ----------------
2120 function Make_Clean
2121 (N : Node_Id;
2122 Clean : Entity_Id;
2123 Mark : Entity_Id;
2124 Flist : Entity_Id;
2125 Is_Task : Boolean;
2126 Is_Master : Boolean;
2127 Is_Protected_Subprogram : Boolean;
2128 Is_Task_Allocation_Block : Boolean;
2129 Is_Asynchronous_Call_Block : Boolean) return Node_Id
2131 Loc : constant Source_Ptr := Sloc (Clean);
2132 Stmt : constant List_Id := New_List;
2134 Sbody : Node_Id;
2135 Spec : Node_Id;
2136 Name : Node_Id;
2137 Param : Node_Id;
2138 Param_Type : Entity_Id;
2139 Pid : Entity_Id := Empty;
2140 Cancel_Param : Entity_Id;
2142 begin
2143 if Is_Task then
2144 if Restricted_Profile then
2145 Append_To
2146 (Stmt, Build_Runtime_Call (Loc, RE_Complete_Restricted_Task));
2147 else
2148 Append_To (Stmt, Build_Runtime_Call (Loc, RE_Complete_Task));
2149 end if;
2151 elsif Is_Master then
2152 if Restriction_Active (No_Task_Hierarchy) = False then
2153 Append_To (Stmt, Build_Runtime_Call (Loc, RE_Complete_Master));
2154 end if;
2156 elsif Is_Protected_Subprogram then
2158 -- Add statements to the cleanup handler of the (ordinary)
2159 -- subprogram expanded to implement a protected subprogram,
2160 -- unlocking the protected object parameter and undeferring abort.
2161 -- If this is a protected procedure, and the object contains
2162 -- entries, this also calls the entry service routine.
2164 -- NOTE: This cleanup handler references _object, a parameter
2165 -- to the procedure.
2167 -- Find the _object parameter representing the protected object
2169 Spec := Parent (Corresponding_Spec (N));
2171 Param := First (Parameter_Specifications (Spec));
2172 loop
2173 Param_Type := Etype (Parameter_Type (Param));
2175 if Ekind (Param_Type) = E_Record_Type then
2176 Pid := Corresponding_Concurrent_Type (Param_Type);
2177 end if;
2179 exit when No (Param) or else Present (Pid);
2180 Next (Param);
2181 end loop;
2183 pragma Assert (Present (Param));
2185 -- If the associated protected object declares entries,
2186 -- a protected procedure has to service entry queues.
2187 -- In this case, add
2189 -- Service_Entries (_object._object'Access);
2191 -- _object is the record used to implement the protected object.
2192 -- It is a parameter to the protected subprogram.
2194 if Nkind (Specification (N)) = N_Procedure_Specification
2195 and then Has_Entries (Pid)
2196 then
2197 if Abort_Allowed
2198 or else Restriction_Active (No_Entry_Queue) = False
2199 or else Number_Entries (Pid) > 1
2200 then
2201 Name := New_Reference_To (RTE (RE_Service_Entries), Loc);
2202 else
2203 Name := New_Reference_To (RTE (RE_Service_Entry), Loc);
2204 end if;
2206 Append_To (Stmt,
2207 Make_Procedure_Call_Statement (Loc,
2208 Name => Name,
2209 Parameter_Associations => New_List (
2210 Make_Attribute_Reference (Loc,
2211 Prefix =>
2212 Make_Selected_Component (Loc,
2213 Prefix => New_Reference_To (
2214 Defining_Identifier (Param), Loc),
2215 Selector_Name =>
2216 Make_Identifier (Loc, Name_uObject)),
2217 Attribute_Name => Name_Unchecked_Access))));
2219 else
2220 -- Unlock (_object._object'Access);
2222 -- object is the record used to implement the protected object.
2223 -- It is a parameter to the protected subprogram.
2225 -- If the protected object is controlled (i.e it has entries or
2226 -- needs finalization for interrupt handling), call
2227 -- Unlock_Entries, except if the protected object follows the
2228 -- ravenscar profile, in which case call Unlock_Entry, otherwise
2229 -- call the simplified version, Unlock.
2231 if Has_Entries (Pid)
2232 or else Has_Interrupt_Handler (Pid)
2233 or else (Has_Attach_Handler (Pid)
2234 and then not Restricted_Profile)
2235 or else (Ada_Version >= Ada_05
2236 and then Present (Interface_List (Parent (Pid))))
2237 then
2238 if Abort_Allowed
2239 or else Restriction_Active (No_Entry_Queue) = False
2240 or else Number_Entries (Pid) > 1
2241 then
2242 Name := New_Reference_To (RTE (RE_Unlock_Entries), Loc);
2243 else
2244 Name := New_Reference_To (RTE (RE_Unlock_Entry), Loc);
2245 end if;
2247 else
2248 Name := New_Reference_To (RTE (RE_Unlock), 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 =>
2259 New_Reference_To (Defining_Identifier (Param), Loc),
2260 Selector_Name =>
2261 Make_Identifier (Loc, Name_uObject)),
2262 Attribute_Name => Name_Unchecked_Access))));
2263 end if;
2265 if Abort_Allowed then
2267 -- Abort_Undefer;
2269 Append_To (Stmt,
2270 Make_Procedure_Call_Statement (Loc,
2271 Name =>
2272 New_Reference_To (
2273 RTE (RE_Abort_Undefer), Loc),
2274 Parameter_Associations => Empty_List));
2275 end if;
2277 elsif Is_Task_Allocation_Block then
2279 -- Add a call to Expunge_Unactivated_Tasks to the cleanup
2280 -- handler of a block created for the dynamic allocation of
2281 -- tasks:
2283 -- Expunge_Unactivated_Tasks (_chain);
2285 -- where _chain is the list of tasks created by the allocator
2286 -- but not yet activated. This list will be empty unless
2287 -- the block completes abnormally.
2289 -- This only applies to dynamically allocated tasks;
2290 -- other unactivated tasks are completed by Complete_Task or
2291 -- Complete_Master.
2293 -- NOTE: This cleanup handler references _chain, a local
2294 -- object.
2296 Append_To (Stmt,
2297 Make_Procedure_Call_Statement (Loc,
2298 Name =>
2299 New_Reference_To (
2300 RTE (RE_Expunge_Unactivated_Tasks), Loc),
2301 Parameter_Associations => New_List (
2302 New_Reference_To (Activation_Chain_Entity (N), Loc))));
2304 elsif Is_Asynchronous_Call_Block then
2306 -- Add a call to attempt to cancel the asynchronous entry call
2307 -- whenever the block containing the abortable part is exited.
2309 -- NOTE: This cleanup handler references C, a local object
2311 -- Get the argument to the Cancel procedure
2312 Cancel_Param := Entry_Cancel_Parameter (Entity (Identifier (N)));
2314 -- If it is of type Communication_Block, this must be a
2315 -- protected entry call.
2317 if Is_RTE (Etype (Cancel_Param), RE_Communication_Block) then
2319 Append_To (Stmt,
2321 -- if Enqueued (Cancel_Parameter) then
2323 Make_Implicit_If_Statement (Clean,
2324 Condition => Make_Function_Call (Loc,
2325 Name => New_Reference_To (
2326 RTE (RE_Enqueued), Loc),
2327 Parameter_Associations => New_List (
2328 New_Reference_To (Cancel_Param, Loc))),
2329 Then_Statements => New_List (
2331 -- Cancel_Protected_Entry_Call (Cancel_Param);
2333 Make_Procedure_Call_Statement (Loc,
2334 Name => New_Reference_To (
2335 RTE (RE_Cancel_Protected_Entry_Call), Loc),
2336 Parameter_Associations => New_List (
2337 New_Reference_To (Cancel_Param, Loc))))));
2339 -- Asynchronous delay
2341 elsif Is_RTE (Etype (Cancel_Param), RE_Delay_Block) then
2342 Append_To (Stmt,
2343 Make_Procedure_Call_Statement (Loc,
2344 Name => New_Reference_To (RTE (RE_Cancel_Async_Delay), Loc),
2345 Parameter_Associations => New_List (
2346 Make_Attribute_Reference (Loc,
2347 Prefix => New_Reference_To (Cancel_Param, Loc),
2348 Attribute_Name => Name_Unchecked_Access))));
2350 -- Task entry call
2352 else
2353 -- Append call to Cancel_Task_Entry_Call (C);
2355 Append_To (Stmt,
2356 Make_Procedure_Call_Statement (Loc,
2357 Name => New_Reference_To (
2358 RTE (RE_Cancel_Task_Entry_Call),
2359 Loc),
2360 Parameter_Associations => New_List (
2361 New_Reference_To (Cancel_Param, Loc))));
2363 end if;
2364 end if;
2366 if Present (Flist) then
2367 Append_To (Stmt,
2368 Make_Procedure_Call_Statement (Loc,
2369 Name => New_Reference_To (RTE (RE_Finalize_List), Loc),
2370 Parameter_Associations => New_List (
2371 New_Reference_To (Flist, Loc))));
2372 end if;
2374 if Present (Mark) then
2375 Append_To (Stmt,
2376 Make_Procedure_Call_Statement (Loc,
2377 Name => New_Reference_To (RTE (RE_SS_Release), Loc),
2378 Parameter_Associations => New_List (
2379 New_Reference_To (Mark, Loc))));
2380 end if;
2382 Sbody :=
2383 Make_Subprogram_Body (Loc,
2384 Specification =>
2385 Make_Procedure_Specification (Loc,
2386 Defining_Unit_Name => Clean),
2388 Declarations => New_List,
2390 Handled_Statement_Sequence =>
2391 Make_Handled_Sequence_Of_Statements (Loc,
2392 Statements => Stmt));
2394 if Present (Flist) or else Is_Task or else Is_Master then
2395 Wrap_Cleanup_Procedure (Sbody);
2396 end if;
2398 -- We do not want debug information for _Clean routines,
2399 -- since it just confuses the debugging operation unless
2400 -- we are debugging generated code.
2402 if not Debug_Generated_Code then
2403 Set_Debug_Info_Off (Clean, True);
2404 end if;
2406 return Sbody;
2407 end Make_Clean;
2409 --------------------------
2410 -- Make_Deep_Array_Body --
2411 --------------------------
2413 -- Array components are initialized and adjusted in the normal order
2414 -- and finalized in the reverse order. Exceptions are handled and
2415 -- Program_Error is re-raise in the Adjust and Finalize case
2416 -- (RM 7.6.1(12)). Generate the following code :
2418 -- procedure Deep_<P> -- with <P> being Initialize or Adjust or Finalize
2419 -- (L : in out Finalizable_Ptr;
2420 -- V : in out Typ)
2421 -- is
2422 -- begin
2423 -- for J1 in Typ'First (1) .. Typ'Last (1) loop
2424 -- ^ reverse ^ -- in the finalization case
2425 -- ...
2426 -- for J2 in Typ'First (n) .. Typ'Last (n) loop
2427 -- Make_<P>_Call (Typ, V (J1, .. , Jn), L, V);
2428 -- end loop;
2429 -- ...
2430 -- end loop;
2431 -- exception -- not in the
2432 -- when others => raise Program_Error; -- Initialize case
2433 -- end Deep_<P>;
2435 function Make_Deep_Array_Body
2436 (Prim : Final_Primitives;
2437 Typ : Entity_Id) return List_Id
2439 Loc : constant Source_Ptr := Sloc (Typ);
2441 Index_List : constant List_Id := New_List;
2442 -- Stores the list of references to the indexes (one per dimension)
2444 function One_Component return List_Id;
2445 -- Create one statement to initialize/adjust/finalize one array
2446 -- component, designated by a full set of indices.
2448 function One_Dimension (N : Int) return List_Id;
2449 -- Create loop to deal with one dimension of the array. The single
2450 -- statement in the body of the loop initializes the inner dimensions if
2451 -- any, or else a single component.
2453 -------------------
2454 -- One_Component --
2455 -------------------
2457 function One_Component return List_Id is
2458 Comp_Typ : constant Entity_Id := Component_Type (Typ);
2459 Comp_Ref : constant Node_Id :=
2460 Make_Indexed_Component (Loc,
2461 Prefix => Make_Identifier (Loc, Name_V),
2462 Expressions => Index_List);
2464 begin
2465 -- Set the etype of the component Reference, which is used to
2466 -- determine whether a conversion to a parent type is needed.
2468 Set_Etype (Comp_Ref, Comp_Typ);
2470 case Prim is
2471 when Initialize_Case =>
2472 return Make_Init_Call (Comp_Ref, Comp_Typ,
2473 Make_Identifier (Loc, Name_L),
2474 Make_Identifier (Loc, Name_B));
2476 when Adjust_Case =>
2477 return Make_Adjust_Call (Comp_Ref, Comp_Typ,
2478 Make_Identifier (Loc, Name_L),
2479 Make_Identifier (Loc, Name_B));
2481 when Finalize_Case =>
2482 return Make_Final_Call (Comp_Ref, Comp_Typ,
2483 Make_Identifier (Loc, Name_B));
2484 end case;
2485 end One_Component;
2487 -------------------
2488 -- One_Dimension --
2489 -------------------
2491 function One_Dimension (N : Int) return List_Id is
2492 Index : Entity_Id;
2494 begin
2495 if N > Number_Dimensions (Typ) then
2496 return One_Component;
2498 else
2499 Index :=
2500 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
2502 Append_To (Index_List, New_Reference_To (Index, Loc));
2504 return New_List (
2505 Make_Implicit_Loop_Statement (Typ,
2506 Identifier => Empty,
2507 Iteration_Scheme =>
2508 Make_Iteration_Scheme (Loc,
2509 Loop_Parameter_Specification =>
2510 Make_Loop_Parameter_Specification (Loc,
2511 Defining_Identifier => Index,
2512 Discrete_Subtype_Definition =>
2513 Make_Attribute_Reference (Loc,
2514 Prefix => Make_Identifier (Loc, Name_V),
2515 Attribute_Name => Name_Range,
2516 Expressions => New_List (
2517 Make_Integer_Literal (Loc, N))),
2518 Reverse_Present => Prim = Finalize_Case)),
2519 Statements => One_Dimension (N + 1)));
2520 end if;
2521 end One_Dimension;
2523 -- Start of processing for Make_Deep_Array_Body
2525 begin
2526 return One_Dimension (1);
2527 end Make_Deep_Array_Body;
2529 --------------------
2530 -- Make_Deep_Proc --
2531 --------------------
2533 -- Generate:
2534 -- procedure DEEP_<prim>
2535 -- (L : IN OUT Finalizable_Ptr; -- not for Finalize
2536 -- V : IN OUT <typ>;
2537 -- B : IN Short_Short_Integer) is
2538 -- begin
2539 -- <stmts>;
2540 -- exception -- Finalize and Adjust Cases only
2541 -- raise Program_Error; -- idem
2542 -- end DEEP_<prim>;
2544 function Make_Deep_Proc
2545 (Prim : Final_Primitives;
2546 Typ : Entity_Id;
2547 Stmts : List_Id) return Entity_Id
2549 Loc : constant Source_Ptr := Sloc (Typ);
2550 Formals : List_Id;
2551 Proc_Name : Entity_Id;
2552 Handler : List_Id := No_List;
2553 Type_B : Entity_Id;
2555 begin
2556 if Prim = Finalize_Case then
2557 Formals := New_List;
2558 Type_B := Standard_Boolean;
2560 else
2561 Formals := New_List (
2562 Make_Parameter_Specification (Loc,
2563 Defining_Identifier => Make_Defining_Identifier (Loc, Name_L),
2564 In_Present => True,
2565 Out_Present => True,
2566 Parameter_Type =>
2567 New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
2568 Type_B := Standard_Short_Short_Integer;
2569 end if;
2571 Append_To (Formals,
2572 Make_Parameter_Specification (Loc,
2573 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
2574 In_Present => True,
2575 Out_Present => True,
2576 Parameter_Type => New_Reference_To (Typ, Loc)));
2578 Append_To (Formals,
2579 Make_Parameter_Specification (Loc,
2580 Defining_Identifier => Make_Defining_Identifier (Loc, Name_B),
2581 Parameter_Type => New_Reference_To (Type_B, Loc)));
2583 if Prim = Finalize_Case or else Prim = Adjust_Case then
2584 Handler := New_List (
2585 Make_Exception_Handler (Loc,
2586 Exception_Choices => New_List (Make_Others_Choice (Loc)),
2587 Statements => New_List (
2588 Make_Raise_Program_Error (Loc,
2589 Reason => PE_Finalize_Raised_Exception))));
2590 end if;
2592 Proc_Name :=
2593 Make_Defining_Identifier (Loc,
2594 Chars => Make_TSS_Name (Typ, Deep_Name_Of (Prim)));
2596 Discard_Node (
2597 Make_Subprogram_Body (Loc,
2598 Specification =>
2599 Make_Procedure_Specification (Loc,
2600 Defining_Unit_Name => Proc_Name,
2601 Parameter_Specifications => Formals),
2603 Declarations => Empty_List,
2604 Handled_Statement_Sequence =>
2605 Make_Handled_Sequence_Of_Statements (Loc,
2606 Statements => Stmts,
2607 Exception_Handlers => Handler)));
2609 return Proc_Name;
2610 end Make_Deep_Proc;
2612 ---------------------------
2613 -- Make_Deep_Record_Body --
2614 ---------------------------
2616 -- The Deep procedures call the appropriate Controlling proc on the
2617 -- the controller component. In the init case, it also attach the
2618 -- controller to the current finalization list.
2620 function Make_Deep_Record_Body
2621 (Prim : Final_Primitives;
2622 Typ : Entity_Id) return List_Id
2624 Loc : constant Source_Ptr := Sloc (Typ);
2625 Controller_Typ : Entity_Id;
2626 Obj_Ref : constant Node_Id := Make_Identifier (Loc, Name_V);
2627 Controller_Ref : constant Node_Id :=
2628 Make_Selected_Component (Loc,
2629 Prefix => Obj_Ref,
2630 Selector_Name =>
2631 Make_Identifier (Loc, Name_uController));
2632 Res : constant List_Id := New_List;
2634 begin
2635 if Is_Return_By_Reference_Type (Typ) then
2636 Controller_Typ := RTE (RE_Limited_Record_Controller);
2637 else
2638 Controller_Typ := RTE (RE_Record_Controller);
2639 end if;
2641 case Prim is
2642 when Initialize_Case =>
2643 Append_List_To (Res,
2644 Make_Init_Call (
2645 Ref => Controller_Ref,
2646 Typ => Controller_Typ,
2647 Flist_Ref => Make_Identifier (Loc, Name_L),
2648 With_Attach => Make_Identifier (Loc, Name_B)));
2650 -- When the type is also a controlled type by itself,
2651 -- Initialize it and attach it to the finalization chain
2653 if Is_Controlled (Typ) then
2654 Append_To (Res,
2655 Make_Procedure_Call_Statement (Loc,
2656 Name => New_Reference_To (
2657 Find_Prim_Op (Typ, Name_Of (Prim)), Loc),
2658 Parameter_Associations =>
2659 New_List (New_Copy_Tree (Obj_Ref))));
2661 Append_To (Res, Make_Attach_Call (
2662 Obj_Ref => New_Copy_Tree (Obj_Ref),
2663 Flist_Ref => Make_Identifier (Loc, Name_L),
2664 With_Attach => Make_Identifier (Loc, Name_B)));
2665 end if;
2667 when Adjust_Case =>
2668 Append_List_To (Res,
2669 Make_Adjust_Call (Controller_Ref, Controller_Typ,
2670 Make_Identifier (Loc, Name_L),
2671 Make_Identifier (Loc, Name_B)));
2673 -- When the type is also a controlled type by itself,
2674 -- Adjust it it and attach it to the finalization chain
2676 if Is_Controlled (Typ) then
2677 Append_To (Res,
2678 Make_Procedure_Call_Statement (Loc,
2679 Name => New_Reference_To (
2680 Find_Prim_Op (Typ, Name_Of (Prim)), Loc),
2681 Parameter_Associations =>
2682 New_List (New_Copy_Tree (Obj_Ref))));
2684 Append_To (Res, Make_Attach_Call (
2685 Obj_Ref => New_Copy_Tree (Obj_Ref),
2686 Flist_Ref => Make_Identifier (Loc, Name_L),
2687 With_Attach => Make_Identifier (Loc, Name_B)));
2688 end if;
2690 when Finalize_Case =>
2691 if Is_Controlled (Typ) then
2692 Append_To (Res,
2693 Make_Implicit_If_Statement (Obj_Ref,
2694 Condition => Make_Identifier (Loc, Name_B),
2695 Then_Statements => New_List (
2696 Make_Procedure_Call_Statement (Loc,
2697 Name => New_Reference_To (RTE (RE_Finalize_One), Loc),
2698 Parameter_Associations => New_List (
2699 OK_Convert_To (RTE (RE_Finalizable),
2700 New_Copy_Tree (Obj_Ref))))),
2702 Else_Statements => New_List (
2703 Make_Procedure_Call_Statement (Loc,
2704 Name => New_Reference_To (
2705 Find_Prim_Op (Typ, Name_Of (Prim)), Loc),
2706 Parameter_Associations =>
2707 New_List (New_Copy_Tree (Obj_Ref))))));
2708 end if;
2710 Append_List_To (Res,
2711 Make_Final_Call (Controller_Ref, Controller_Typ,
2712 Make_Identifier (Loc, Name_B)));
2713 end case;
2714 return Res;
2715 end Make_Deep_Record_Body;
2717 ----------------------
2718 -- Make_Final_Call --
2719 ----------------------
2721 function Make_Final_Call
2722 (Ref : Node_Id;
2723 Typ : Entity_Id;
2724 With_Detach : Node_Id) return List_Id
2726 Loc : constant Source_Ptr := Sloc (Ref);
2727 Res : constant List_Id := New_List;
2728 Cref : Node_Id;
2729 Cref2 : Node_Id;
2730 Proc : Entity_Id;
2731 Utyp : Entity_Id;
2733 begin
2734 if Is_Class_Wide_Type (Typ) then
2735 Utyp := Root_Type (Typ);
2736 Cref := Ref;
2738 elsif Is_Concurrent_Type (Typ) then
2739 Utyp := Corresponding_Record_Type (Typ);
2740 Cref := Convert_Concurrent (Ref, Typ);
2742 elsif Is_Private_Type (Typ)
2743 and then Present (Full_View (Typ))
2744 and then Is_Concurrent_Type (Full_View (Typ))
2745 then
2746 Utyp := Corresponding_Record_Type (Full_View (Typ));
2747 Cref := Convert_Concurrent (Ref, Full_View (Typ));
2748 else
2749 Utyp := Typ;
2750 Cref := Ref;
2751 end if;
2753 Utyp := Underlying_Type (Base_Type (Utyp));
2754 Set_Assignment_OK (Cref);
2756 -- Deal with non-tagged derivation of private views. If the parent is
2757 -- now known to be protected, the finalization routine is the one
2758 -- defined on the corresponding record of the ancestor (corresponding
2759 -- records do not automatically inherit operations, but maybe they
2760 -- should???)
2762 if Is_Untagged_Derivation (Typ) then
2763 if Is_Protected_Type (Typ) then
2764 Utyp := Corresponding_Record_Type (Root_Type (Base_Type (Typ)));
2765 else
2766 Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
2767 end if;
2769 Cref := Unchecked_Convert_To (Utyp, Cref);
2771 -- We need to set Assignment_OK to prevent problems with unchecked
2772 -- conversions, where we do not want them to be converted back in the
2773 -- case of untagged record derivation (see code in Make_*_Call
2774 -- procedures for similar situations).
2776 Set_Assignment_OK (Cref);
2777 end if;
2779 -- If the underlying_type is a subtype, we are dealing with
2780 -- the completion of a private type. We need to access
2781 -- the base type and generate a conversion to it.
2783 if Utyp /= Base_Type (Utyp) then
2784 pragma Assert (Is_Private_Type (Typ));
2785 Utyp := Base_Type (Utyp);
2786 Cref := Unchecked_Convert_To (Utyp, Cref);
2787 end if;
2789 -- Generate:
2790 -- Deep_Finalize (Ref, With_Detach);
2792 if Has_Controlled_Component (Utyp)
2793 or else Is_Class_Wide_Type (Typ)
2794 then
2795 if Is_Tagged_Type (Utyp) then
2796 Proc := Find_Prim_Op (Utyp, TSS_Deep_Finalize);
2797 else
2798 Proc := TSS (Utyp, TSS_Deep_Finalize);
2799 end if;
2801 Cref := Convert_View (Proc, Cref);
2803 Append_To (Res,
2804 Make_Procedure_Call_Statement (Loc,
2805 Name => New_Reference_To (Proc, Loc),
2806 Parameter_Associations =>
2807 New_List (Cref, With_Detach)));
2809 -- Generate:
2810 -- if With_Detach then
2811 -- Finalize_One (Ref);
2812 -- else
2813 -- Finalize (Ref);
2814 -- end if;
2816 else
2817 Proc := Find_Prim_Op (Utyp, Name_Of (Finalize_Case));
2819 if Chars (With_Detach) = Chars (Standard_True) then
2820 Append_To (Res,
2821 Make_Procedure_Call_Statement (Loc,
2822 Name => New_Reference_To (RTE (RE_Finalize_One), Loc),
2823 Parameter_Associations => New_List (
2824 OK_Convert_To (RTE (RE_Finalizable), Cref))));
2826 elsif Chars (With_Detach) = Chars (Standard_False) then
2827 Append_To (Res,
2828 Make_Procedure_Call_Statement (Loc,
2829 Name => New_Reference_To (Proc, Loc),
2830 Parameter_Associations =>
2831 New_List (Convert_View (Proc, Cref))));
2833 else
2834 Cref2 := New_Copy_Tree (Cref);
2835 Append_To (Res,
2836 Make_Implicit_If_Statement (Ref,
2837 Condition => With_Detach,
2838 Then_Statements => New_List (
2839 Make_Procedure_Call_Statement (Loc,
2840 Name => New_Reference_To (RTE (RE_Finalize_One), Loc),
2841 Parameter_Associations => New_List (
2842 OK_Convert_To (RTE (RE_Finalizable), Cref)))),
2844 Else_Statements => New_List (
2845 Make_Procedure_Call_Statement (Loc,
2846 Name => New_Reference_To (Proc, Loc),
2847 Parameter_Associations =>
2848 New_List (Convert_View (Proc, Cref2))))));
2849 end if;
2850 end if;
2852 return Res;
2853 end Make_Final_Call;
2855 --------------------
2856 -- Make_Init_Call --
2857 --------------------
2859 function Make_Init_Call
2860 (Ref : Node_Id;
2861 Typ : Entity_Id;
2862 Flist_Ref : Node_Id;
2863 With_Attach : Node_Id) return List_Id
2865 Loc : constant Source_Ptr := Sloc (Ref);
2866 Is_Conc : Boolean;
2867 Res : constant List_Id := New_List;
2868 Proc : Entity_Id;
2869 Utyp : Entity_Id;
2870 Cref : Node_Id;
2871 Cref2 : Node_Id;
2872 Attach : Node_Id := With_Attach;
2874 begin
2875 if Is_Concurrent_Type (Typ) then
2876 Is_Conc := True;
2877 Utyp := Corresponding_Record_Type (Typ);
2878 Cref := Convert_Concurrent (Ref, Typ);
2880 elsif Is_Private_Type (Typ)
2881 and then Present (Full_View (Typ))
2882 and then Is_Concurrent_Type (Underlying_Type (Typ))
2883 then
2884 Is_Conc := True;
2885 Utyp := Corresponding_Record_Type (Underlying_Type (Typ));
2886 Cref := Convert_Concurrent (Ref, Underlying_Type (Typ));
2888 else
2889 Is_Conc := False;
2890 Utyp := Typ;
2891 Cref := Ref;
2892 end if;
2894 Utyp := Underlying_Type (Base_Type (Utyp));
2896 Set_Assignment_OK (Cref);
2898 -- Deal with non-tagged derivation of private views
2900 if Is_Untagged_Derivation (Typ)
2901 and then not Is_Conc
2902 then
2903 Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
2904 Cref := Unchecked_Convert_To (Utyp, Cref);
2905 Set_Assignment_OK (Cref);
2906 -- To prevent problems with UC see 1.156 RH ???
2907 end if;
2909 -- If the underlying_type is a subtype, we are dealing with
2910 -- the completion of a private type. We need to access
2911 -- the base type and generate a conversion to it.
2913 if Utyp /= Base_Type (Utyp) then
2914 pragma Assert (Is_Private_Type (Typ));
2915 Utyp := Base_Type (Utyp);
2916 Cref := Unchecked_Convert_To (Utyp, Cref);
2917 end if;
2919 -- We do not need to attach to one of the Global Final Lists
2920 -- the objects whose type is Finalize_Storage_Only
2922 if Finalize_Storage_Only (Typ)
2923 and then (Global_Flist_Ref (Flist_Ref)
2924 or else Entity (Constant_Value (RTE (RE_Garbage_Collected)))
2925 = Standard_True)
2926 then
2927 Attach := Make_Integer_Literal (Loc, 0);
2928 end if;
2930 -- Generate:
2931 -- Deep_Initialize (Ref, Flist_Ref);
2933 if Has_Controlled_Component (Utyp) then
2934 Proc := TSS (Utyp, Deep_Name_Of (Initialize_Case));
2936 Cref := Convert_View (Proc, Cref, 2);
2938 Append_To (Res,
2939 Make_Procedure_Call_Statement (Loc,
2940 Name => New_Reference_To (Proc, Loc),
2941 Parameter_Associations => New_List (
2942 Node1 => Flist_Ref,
2943 Node2 => Cref,
2944 Node3 => Attach)));
2946 -- Generate:
2947 -- Attach_To_Final_List (Ref, Flist_Ref);
2948 -- Initialize (Ref);
2950 else -- Is_Controlled (Utyp)
2951 Proc := Find_Prim_Op (Utyp, Name_Of (Initialize_Case));
2952 Check_Visibly_Controlled (Initialize_Case, Typ, Proc, Cref);
2954 Cref := Convert_View (Proc, Cref);
2955 Cref2 := New_Copy_Tree (Cref);
2957 Append_To (Res,
2958 Make_Procedure_Call_Statement (Loc,
2959 Name => New_Reference_To (Proc, Loc),
2960 Parameter_Associations => New_List (Cref2)));
2962 Append_To (Res,
2963 Make_Attach_Call (Cref, Flist_Ref, Attach));
2964 end if;
2966 return Res;
2967 end Make_Init_Call;
2969 --------------------------
2970 -- Make_Transient_Block --
2971 --------------------------
2973 -- If finalization is involved, this function just wraps the instruction
2974 -- into a block whose name is the transient block entity, and then
2975 -- Expand_Cleanup_Actions (called on the expansion of the handled
2976 -- sequence of statements will do the necessary expansions for
2977 -- cleanups).
2979 function Make_Transient_Block
2980 (Loc : Source_Ptr;
2981 Action : Node_Id) return Node_Id
2983 Flist : constant Entity_Id := Finalization_Chain_Entity (Current_Scope);
2984 Decls : constant List_Id := New_List;
2985 Par : constant Node_Id := Parent (Action);
2986 Instrs : constant List_Id := New_List (Action);
2987 Blk : Node_Id;
2989 begin
2990 -- Case where only secondary stack use is involved
2992 if Uses_Sec_Stack (Current_Scope)
2993 and then No (Flist)
2994 and then Nkind (Action) /= N_Return_Statement
2995 and then Nkind (Par) /= N_Exception_Handler
2996 then
2998 declare
2999 S : Entity_Id;
3000 K : Entity_Kind;
3001 begin
3002 S := Scope (Current_Scope);
3003 loop
3004 K := Ekind (S);
3006 -- At the outer level, no need to release the sec stack
3008 if S = Standard_Standard then
3009 Set_Uses_Sec_Stack (Current_Scope, False);
3010 exit;
3012 -- In a function, only release the sec stack if the
3013 -- function does not return on the sec stack otherwise
3014 -- the result may be lost. The caller is responsible for
3015 -- releasing.
3017 elsif K = E_Function then
3018 Set_Uses_Sec_Stack (Current_Scope, False);
3020 if not Requires_Transient_Scope (Etype (S)) then
3021 if not Functions_Return_By_DSP_On_Target then
3022 Set_Uses_Sec_Stack (S, True);
3023 Check_Restriction (No_Secondary_Stack, Action);
3024 end if;
3025 end if;
3027 exit;
3029 -- In a loop or entry we should install a block encompassing
3030 -- all the construct. For now just release right away.
3032 elsif K = E_Loop or else K = E_Entry then
3033 exit;
3035 -- In a procedure or a block, we release on exit of the
3036 -- procedure or block. ??? memory leak can be created by
3037 -- recursive calls.
3039 elsif K = E_Procedure
3040 or else K = E_Block
3041 then
3042 if not Functions_Return_By_DSP_On_Target then
3043 Set_Uses_Sec_Stack (S, True);
3044 Check_Restriction (No_Secondary_Stack, Action);
3045 end if;
3047 Set_Uses_Sec_Stack (Current_Scope, False);
3048 exit;
3050 else
3051 S := Scope (S);
3052 end if;
3053 end loop;
3054 end;
3055 end if;
3057 -- Insert actions stuck in the transient scopes as well as all
3058 -- freezing nodes needed by those actions
3060 Insert_Actions_In_Scope_Around (Action);
3062 declare
3063 Last_Inserted : Node_Id := Prev (Action);
3065 begin
3066 if Present (Last_Inserted) then
3067 Freeze_All (First_Entity (Current_Scope), Last_Inserted);
3068 end if;
3069 end;
3071 Blk :=
3072 Make_Block_Statement (Loc,
3073 Identifier => New_Reference_To (Current_Scope, Loc),
3074 Declarations => Decls,
3075 Handled_Statement_Sequence =>
3076 Make_Handled_Sequence_Of_Statements (Loc, Statements => Instrs),
3077 Has_Created_Identifier => True);
3079 -- When the transient scope was established, we pushed the entry for
3080 -- the transient scope onto the scope stack, so that the scope was
3081 -- active for the installation of finalizable entities etc. Now we
3082 -- must remove this entry, since we have constructed a proper block.
3084 Pop_Scope;
3086 return Blk;
3087 end Make_Transient_Block;
3089 ------------------------
3090 -- Node_To_Be_Wrapped --
3091 ------------------------
3093 function Node_To_Be_Wrapped return Node_Id is
3094 begin
3095 return Scope_Stack.Table (Scope_Stack.Last).Node_To_Be_Wrapped;
3096 end Node_To_Be_Wrapped;
3098 ----------------------------
3099 -- Set_Node_To_Be_Wrapped --
3100 ----------------------------
3102 procedure Set_Node_To_Be_Wrapped (N : Node_Id) is
3103 begin
3104 Scope_Stack.Table (Scope_Stack.Last).Node_To_Be_Wrapped := N;
3105 end Set_Node_To_Be_Wrapped;
3107 ----------------------------------
3108 -- Store_After_Actions_In_Scope --
3109 ----------------------------------
3111 procedure Store_After_Actions_In_Scope (L : List_Id) is
3112 SE : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
3114 begin
3115 if Present (SE.Actions_To_Be_Wrapped_After) then
3116 Insert_List_Before_And_Analyze (
3117 First (SE.Actions_To_Be_Wrapped_After), L);
3119 else
3120 SE.Actions_To_Be_Wrapped_After := L;
3122 if Is_List_Member (SE.Node_To_Be_Wrapped) then
3123 Set_Parent (L, Parent (SE.Node_To_Be_Wrapped));
3124 else
3125 Set_Parent (L, SE.Node_To_Be_Wrapped);
3126 end if;
3128 Analyze_List (L);
3129 end if;
3130 end Store_After_Actions_In_Scope;
3132 -----------------------------------
3133 -- Store_Before_Actions_In_Scope --
3134 -----------------------------------
3136 procedure Store_Before_Actions_In_Scope (L : List_Id) is
3137 SE : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
3139 begin
3140 if Present (SE.Actions_To_Be_Wrapped_Before) then
3141 Insert_List_After_And_Analyze (
3142 Last (SE.Actions_To_Be_Wrapped_Before), L);
3144 else
3145 SE.Actions_To_Be_Wrapped_Before := L;
3147 if Is_List_Member (SE.Node_To_Be_Wrapped) then
3148 Set_Parent (L, Parent (SE.Node_To_Be_Wrapped));
3149 else
3150 Set_Parent (L, SE.Node_To_Be_Wrapped);
3151 end if;
3153 Analyze_List (L);
3154 end if;
3155 end Store_Before_Actions_In_Scope;
3157 --------------------------------
3158 -- Wrap_Transient_Declaration --
3159 --------------------------------
3161 -- If a transient scope has been established during the processing of the
3162 -- Expression of an Object_Declaration, it is not possible to wrap the
3163 -- declaration into a transient block as usual case, otherwise the object
3164 -- would be itself declared in the wrong scope. Therefore, all entities (if
3165 -- any) defined in the transient block are moved to the proper enclosing
3166 -- scope, furthermore, if they are controlled variables they are finalized
3167 -- right after the declaration. The finalization list of the transient
3168 -- scope is defined as a renaming of the enclosing one so during their
3169 -- initialization they will be attached to the proper finalization
3170 -- list. For instance, the following declaration :
3172 -- X : Typ := F (G (A), G (B));
3174 -- (where G(A) and G(B) return controlled values, expanded as _v1 and _v2)
3175 -- is expanded into :
3177 -- _local_final_list_1 : Finalizable_Ptr;
3178 -- X : Typ := [ complex Expression-Action ];
3179 -- Finalize_One(_v1);
3180 -- Finalize_One (_v2);
3182 procedure Wrap_Transient_Declaration (N : Node_Id) is
3183 S : Entity_Id;
3184 LC : Entity_Id := Empty;
3185 Nodes : List_Id;
3186 Loc : constant Source_Ptr := Sloc (N);
3187 Enclosing_S : Entity_Id;
3188 Uses_SS : Boolean;
3189 Next_N : constant Node_Id := Next (N);
3191 begin
3192 S := Current_Scope;
3193 Enclosing_S := Scope (S);
3195 -- Insert Actions kept in the Scope stack
3197 Insert_Actions_In_Scope_Around (N);
3199 -- If the declaration is consuming some secondary stack, mark the
3200 -- Enclosing scope appropriately.
3202 Uses_SS := Uses_Sec_Stack (S);
3203 Pop_Scope;
3205 -- Create a List controller and rename the final list to be its
3206 -- internal final pointer:
3207 -- Lxxx : Simple_List_Controller;
3208 -- Fxxx : Finalizable_Ptr renames Lxxx.F;
3210 if Present (Finalization_Chain_Entity (S)) then
3211 LC := Make_Defining_Identifier (Loc, New_Internal_Name ('L'));
3213 Nodes := New_List (
3214 Make_Object_Declaration (Loc,
3215 Defining_Identifier => LC,
3216 Object_Definition =>
3217 New_Reference_To (RTE (RE_Simple_List_Controller), Loc)),
3219 Make_Object_Renaming_Declaration (Loc,
3220 Defining_Identifier => Finalization_Chain_Entity (S),
3221 Subtype_Mark => New_Reference_To (RTE (RE_Finalizable_Ptr), Loc),
3222 Name =>
3223 Make_Selected_Component (Loc,
3224 Prefix => New_Reference_To (LC, Loc),
3225 Selector_Name => Make_Identifier (Loc, Name_F))));
3227 -- Put the declaration at the beginning of the declaration part
3228 -- to make sure it will be before all other actions that have been
3229 -- inserted before N.
3231 Insert_List_Before_And_Analyze (First (List_Containing (N)), Nodes);
3233 -- Generate the Finalization calls by finalizing the list
3234 -- controller right away. It will be re-finalized on scope
3235 -- exit but it doesn't matter. It cannot be done when the
3236 -- call initializes a renaming object though because in this
3237 -- case, the object becomes a pointer to the temporary and thus
3238 -- increases its life span.
3240 if Nkind (N) = N_Object_Renaming_Declaration
3241 and then Controlled_Type (Etype (Defining_Identifier (N)))
3242 then
3243 null;
3245 else
3246 Nodes :=
3247 Make_Final_Call (
3248 Ref => New_Reference_To (LC, Loc),
3249 Typ => Etype (LC),
3250 With_Detach => New_Reference_To (Standard_False, Loc));
3251 if Present (Next_N) then
3252 Insert_List_Before_And_Analyze (Next_N, Nodes);
3253 else
3254 Append_List_To (List_Containing (N), Nodes);
3255 end if;
3256 end if;
3257 end if;
3259 -- Put the local entities back in the enclosing scope, and set the
3260 -- Is_Public flag appropriately.
3262 Transfer_Entities (S, Enclosing_S);
3264 -- Mark the enclosing dynamic scope so that the sec stack will be
3265 -- released upon its exit unless this is a function that returns on
3266 -- the sec stack in which case this will be done by the caller.
3268 if Uses_SS then
3269 S := Enclosing_Dynamic_Scope (S);
3271 if Ekind (S) = E_Function
3272 and then Requires_Transient_Scope (Etype (S))
3273 then
3274 null;
3275 else
3276 Set_Uses_Sec_Stack (S);
3277 Check_Restriction (No_Secondary_Stack, N);
3278 end if;
3279 end if;
3280 end Wrap_Transient_Declaration;
3282 -------------------------------
3283 -- Wrap_Transient_Expression --
3284 -------------------------------
3286 -- Insert actions before <Expression>:
3288 -- (lines marked with <CTRL> are expanded only in presence of Controlled
3289 -- objects needing finalization)
3291 -- _E : Etyp;
3292 -- declare
3293 -- _M : constant Mark_Id := SS_Mark;
3294 -- Local_Final_List : System.FI.Finalizable_Ptr; <CTRL>
3296 -- procedure _Clean is
3297 -- begin
3298 -- Abort_Defer;
3299 -- System.FI.Finalize_List (Local_Final_List); <CTRL>
3300 -- SS_Release (M);
3301 -- Abort_Undefer;
3302 -- end _Clean;
3304 -- begin
3305 -- _E := <Expression>;
3306 -- at end
3307 -- _Clean;
3308 -- end;
3310 -- then expression is replaced by _E
3312 procedure Wrap_Transient_Expression (N : Node_Id) is
3313 Loc : constant Source_Ptr := Sloc (N);
3314 E : constant Entity_Id :=
3315 Make_Defining_Identifier (Loc, New_Internal_Name ('E'));
3316 Etyp : constant Entity_Id := Etype (N);
3318 begin
3319 Insert_Actions (N, New_List (
3320 Make_Object_Declaration (Loc,
3321 Defining_Identifier => E,
3322 Object_Definition => New_Reference_To (Etyp, Loc)),
3324 Make_Transient_Block (Loc,
3325 Action =>
3326 Make_Assignment_Statement (Loc,
3327 Name => New_Reference_To (E, Loc),
3328 Expression => Relocate_Node (N)))));
3330 Rewrite (N, New_Reference_To (E, Loc));
3331 Analyze_And_Resolve (N, Etyp);
3332 end Wrap_Transient_Expression;
3334 ------------------------------
3335 -- Wrap_Transient_Statement --
3336 ------------------------------
3338 -- Transform <Instruction> into
3340 -- (lines marked with <CTRL> are expanded only in presence of Controlled
3341 -- objects needing finalization)
3343 -- declare
3344 -- _M : Mark_Id := SS_Mark;
3345 -- Local_Final_List : System.FI.Finalizable_Ptr ; <CTRL>
3347 -- procedure _Clean is
3348 -- begin
3349 -- Abort_Defer;
3350 -- System.FI.Finalize_List (Local_Final_List); <CTRL>
3351 -- SS_Release (_M);
3352 -- Abort_Undefer;
3353 -- end _Clean;
3355 -- begin
3356 -- <Instr uction>;
3357 -- at end
3358 -- _Clean;
3359 -- end;
3361 procedure Wrap_Transient_Statement (N : Node_Id) is
3362 Loc : constant Source_Ptr := Sloc (N);
3363 New_Statement : constant Node_Id := Relocate_Node (N);
3365 begin
3366 Rewrite (N, Make_Transient_Block (Loc, New_Statement));
3368 -- With the scope stack back to normal, we can call analyze on the
3369 -- resulting block. At this point, the transient scope is being
3370 -- treated like a perfectly normal scope, so there is nothing
3371 -- special about it.
3373 -- Note: Wrap_Transient_Statement is called with the node already
3374 -- analyzed (i.e. Analyzed (N) is True). This is important, since
3375 -- otherwise we would get a recursive processing of the node when
3376 -- we do this Analyze call.
3378 Analyze (N);
3379 end Wrap_Transient_Statement;
3381 end Exp_Ch7;