1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2009, Free Software Foundation, Inc. --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 ------------------------------------------------------------------------------
26 -- This package contains virtually all expansion mechanisms related to
30 with Atree
; use Atree
;
31 with Debug
; use Debug
;
32 with Einfo
; use Einfo
;
33 with Errout
; use Errout
;
34 with Exp_Ch9
; use Exp_Ch9
;
35 with Exp_Ch11
; use Exp_Ch11
;
36 with Exp_Dbug
; use Exp_Dbug
;
37 with Exp_Dist
; use Exp_Dist
;
38 with Exp_Disp
; use Exp_Disp
;
39 with Exp_Tss
; use Exp_Tss
;
40 with Exp_Util
; use Exp_Util
;
41 with Freeze
; use Freeze
;
43 with Nlists
; use Nlists
;
44 with Nmake
; use Nmake
;
46 with Output
; use Output
;
47 with Restrict
; use Restrict
;
48 with Rident
; use Rident
;
49 with Rtsfind
; use Rtsfind
;
50 with Sinfo
; use Sinfo
;
52 with Sem_Aux
; use Sem_Aux
;
53 with Sem_Ch3
; use Sem_Ch3
;
54 with Sem_Ch7
; use Sem_Ch7
;
55 with Sem_Ch8
; use Sem_Ch8
;
56 with Sem_Res
; use Sem_Res
;
57 with Sem_SCIL
; use Sem_SCIL
;
58 with Sem_Type
; use Sem_Type
;
59 with Sem_Util
; use Sem_Util
;
60 with Snames
; use Snames
;
61 with Stand
; use Stand
;
62 with Targparm
; use Targparm
;
63 with Tbuild
; use Tbuild
;
64 with Uintp
; use Uintp
;
66 package body Exp_Ch7
is
68 --------------------------------
69 -- Transient Scope Management --
70 --------------------------------
72 -- A transient scope is created when temporary objects are created by the
73 -- compiler. These temporary objects are allocated on the secondary stack
74 -- and the transient scope is responsible for finalizing the object when
75 -- appropriate and reclaiming the memory at the right time. The temporary
76 -- objects are generally the objects allocated to store the result of a
77 -- function returning an unconstrained or a tagged value. Expressions
78 -- needing to be wrapped in a transient scope (functions calls returning
79 -- unconstrained or tagged values) may appear in 3 different contexts which
80 -- lead to 3 different kinds of transient scope expansion:
82 -- 1. In a simple statement (procedure call, assignment, ...). In
83 -- this case the instruction is wrapped into a transient block.
84 -- (See Wrap_Transient_Statement for details)
86 -- 2. In an expression of a control structure (test in a IF statement,
87 -- expression in a CASE statement, ...).
88 -- (See Wrap_Transient_Expression for details)
90 -- 3. In a expression of an object_declaration. No wrapping is possible
91 -- here, so the finalization actions, if any, are done right after the
92 -- declaration and the secondary stack deallocation is done in the
93 -- proper enclosing scope (see Wrap_Transient_Declaration for details)
95 -- Note about functions returning tagged types: it has been decided to
96 -- always allocate their result in the secondary stack, even though is not
97 -- absolutely mandatory when the tagged type is constrained because the
98 -- caller knows the size of the returned object and thus could allocate the
99 -- result in the primary stack. An exception to this is when the function
100 -- builds its result in place, as is done for functions with inherently
101 -- limited result types for Ada 2005. In that case, certain callers may
102 -- pass the address of a constrained object as the target object for the
105 -- By allocating tagged results in the secondary stack a number of
106 -- implementation difficulties are avoided:
108 -- - If it is a dispatching function call, the computation of the size of
109 -- the result is possible but complex from the outside.
111 -- - If the returned type is controlled, the assignment of the returned
112 -- value to the anonymous object involves an Adjust, and we have no
113 -- easy way to access the anonymous object created by the back end.
115 -- - If the returned type is class-wide, this is an unconstrained type
118 -- Furthermore, the small loss in efficiency which is the result of this
119 -- decision is not such a big deal because functions returning tagged types
120 -- are not as common in practice compared to functions returning access to
123 --------------------------------------------------
124 -- Transient Blocks and Finalization Management --
125 --------------------------------------------------
127 function Find_Node_To_Be_Wrapped
(N
: Node_Id
) return Node_Id
;
128 -- N is a node which may generate a transient scope. Loop over the parent
129 -- pointers of N until it find the appropriate node to wrap. If it returns
130 -- Empty, it means that no transient scope is needed in this context.
139 Is_Protected_Subprogram
: Boolean;
140 Is_Task_Allocation_Block
: Boolean;
141 Is_Asynchronous_Call_Block
: Boolean;
142 Chained_Cleanup_Action
: Node_Id
) return Node_Id
;
143 -- Expand the clean-up procedure for a controlled and/or transient block,
144 -- and/or task master or task body, or a block used to implement task
145 -- allocation or asynchronous entry calls, or a procedure used to implement
146 -- protected procedures. Clean is the entity for such a procedure. Mark
147 -- is the entity for the secondary stack mark, if empty only controlled
148 -- block clean-up will be performed. Flist is the entity for the local
149 -- final list, if empty only transient scope clean-up will be performed.
150 -- The flags Is_Task and Is_Master control the calls to the corresponding
151 -- finalization actions for a task body or for an entity that is a task
152 -- master. Finally if Chained_Cleanup_Action is present, it is a reference
153 -- to a previous cleanup procedure, a call to which is appended at the
154 -- end of the generated one.
156 procedure Set_Node_To_Be_Wrapped
(N
: Node_Id
);
157 -- Set the field Node_To_Be_Wrapped of the current scope
159 procedure Insert_Actions_In_Scope_Around
(N
: Node_Id
);
160 -- Insert the before-actions kept in the scope stack before N, and the
161 -- after-actions after N, which must be a member of a list.
163 function Make_Transient_Block
165 Action
: Node_Id
) return Node_Id
;
166 -- Create a transient block whose name is Scope, which is also a controlled
167 -- block if Flist is not empty and whose only code is Action (either a
168 -- single statement or single declaration).
170 type Final_Primitives
is (Initialize_Case
, Adjust_Case
, Finalize_Case
);
171 -- This enumeration type is defined in order to ease sharing code for
172 -- building finalization procedures for composite types.
174 Name_Of
: constant array (Final_Primitives
) of Name_Id
:=
175 (Initialize_Case
=> Name_Initialize
,
176 Adjust_Case
=> Name_Adjust
,
177 Finalize_Case
=> Name_Finalize
);
179 Deep_Name_Of
: constant array (Final_Primitives
) of TSS_Name_Type
:=
180 (Initialize_Case
=> TSS_Deep_Initialize
,
181 Adjust_Case
=> TSS_Deep_Adjust
,
182 Finalize_Case
=> TSS_Deep_Finalize
);
184 procedure Build_Record_Deep_Procs
(Typ
: Entity_Id
);
185 -- Build the deep Initialize/Adjust/Finalize for a record Typ with
186 -- Has_Component_Component set and store them using the TSS mechanism.
188 procedure Build_Array_Deep_Procs
(Typ
: Entity_Id
);
189 -- Build the deep Initialize/Adjust/Finalize for a record Typ with
190 -- Has_Controlled_Component set and store them using the TSS mechanism.
192 function Make_Deep_Proc
193 (Prim
: Final_Primitives
;
195 Stmts
: List_Id
) return Node_Id
;
196 -- This function generates the tree for Deep_Initialize, Deep_Adjust or
197 -- Deep_Finalize procedures according to the first parameter, these
198 -- procedures operate on the type Typ. The Stmts parameter gives the body
201 function Make_Deep_Array_Body
202 (Prim
: Final_Primitives
;
203 Typ
: Entity_Id
) return List_Id
;
204 -- This function generates the list of statements for implementing
205 -- Deep_Initialize, Deep_Adjust or Deep_Finalize procedures according to
206 -- the first parameter, these procedures operate on the array type Typ.
208 function Make_Deep_Record_Body
209 (Prim
: Final_Primitives
;
210 Typ
: Entity_Id
) return List_Id
;
211 -- This function generates the list of statements for implementing
212 -- Deep_Initialize, Deep_Adjust or Deep_Finalize procedures according to
213 -- the first parameter, these procedures operate on the record type Typ.
215 procedure Check_Visibly_Controlled
216 (Prim
: Final_Primitives
;
218 E
: in out Entity_Id
;
219 Cref
: in out Node_Id
);
220 -- The controlled operation declared for a derived type may not be
221 -- overriding, if the controlled operations of the parent type are
222 -- hidden, for example when the parent is a private type whose full
223 -- view is controlled. For other primitive operations we modify the
224 -- name of the operation to indicate that it is not overriding, but
225 -- this is not possible for Initialize, etc. because they have to be
226 -- retrievable by name. Before generating the proper call to one of
227 -- these operations we check whether Typ is known to be controlled at
228 -- the point of definition. If it is not then we must retrieve the
229 -- hidden operation of the parent and use it instead. This is one
230 -- case that might be solved more cleanly once Overriding pragmas or
231 -- declarations are in place.
233 function Convert_View
236 Ind
: Pos
:= 1) return Node_Id
;
237 -- Proc is one of the Initialize/Adjust/Finalize operations, and
238 -- Arg is the argument being passed to it. Ind indicates which
239 -- formal of procedure Proc we are trying to match. This function
240 -- will, if necessary, generate an conversion between the partial
241 -- and full view of Arg to match the type of the formal of Proc,
242 -- or force a conversion to the class-wide type in the case where
243 -- the operation is abstract.
245 -----------------------------
246 -- Finalization Management --
247 -----------------------------
249 -- This part describe how Initialization/Adjustment/Finalization procedures
250 -- are generated and called. Two cases must be considered, types that are
251 -- Controlled (Is_Controlled flag set) and composite types that contain
252 -- controlled components (Has_Controlled_Component flag set). In the first
253 -- case the procedures to call are the user-defined primitive operations
254 -- Initialize/Adjust/Finalize. In the second case, GNAT generates
255 -- Deep_Initialize, Deep_Adjust and Deep_Finalize that are in charge
256 -- of calling the former procedures on the controlled components.
258 -- For records with Has_Controlled_Component set, a hidden "controller"
259 -- component is inserted. This controller component contains its own
260 -- finalization list on which all controlled components are attached
261 -- creating an indirection on the upper-level Finalization list. This
262 -- technique facilitates the management of objects whose number of
263 -- controlled components changes during execution. This controller
264 -- component is itself controlled and is attached to the upper-level
265 -- finalization chain. Its adjust primitive is in charge of calling adjust
266 -- on the components and adjusting the finalization pointer to match their
267 -- new location (see a-finali.adb).
269 -- It is not possible to use a similar technique for arrays that have
270 -- Has_Controlled_Component set. In this case, deep procedures are
271 -- generated that call initialize/adjust/finalize + attachment or
272 -- detachment on the finalization list for all component.
274 -- Initialize calls: they are generated for declarations or dynamic
275 -- allocations of Controlled objects with no initial value. They are always
276 -- followed by an attachment to the current Finalization Chain. For the
277 -- dynamic allocation case this the chain attached to the scope of the
278 -- access type definition otherwise, this is the chain of the current
281 -- Adjust Calls: They are generated on 2 occasions: (1) for
282 -- declarations or dynamic allocations of Controlled objects with an
283 -- initial value. (2) after an assignment. In the first case they are
284 -- followed by an attachment to the final chain, in the second case
287 -- Finalization Calls: They are generated on (1) scope exit, (2)
288 -- assignments, (3) unchecked deallocations. In case (3) they have to
289 -- be detached from the final chain, in case (2) they must not and in
290 -- case (1) this is not important since we are exiting the scope anyway.
294 -- Type extensions will have a new record controller at each derivation
295 -- level containing controlled components. The record controller for
296 -- the parent/ancestor is attached to the finalization list of the
297 -- extension's record controller (i.e. the parent is like a component
298 -- of the extension).
300 -- For types that are both Is_Controlled and Has_Controlled_Components,
301 -- the record controller and the object itself are handled separately.
302 -- It could seem simpler to attach the object at the end of its record
303 -- controller but this would not tackle view conversions properly.
305 -- A classwide type can always potentially have controlled components
306 -- but the record controller of the corresponding actual type may not
307 -- be known at compile time so the dispatch table contains a special
308 -- field that allows to compute the offset of the record controller
309 -- dynamically. See s-finimp.Deep_Tag_Attach and a-tags.RC_Offset.
311 -- Here is a simple example of the expansion of a controlled block :
315 -- Y : Controlled := Init;
321 -- Z : R := (C => X);
330 -- _L : System.FI.Finalizable_Ptr;
332 -- procedure _Clean is
335 -- System.FI.Finalize_List (_L);
343 -- Attach_To_Final_List (_L, Finalizable (X), 1);
344 -- at end: Abort_Undefer;
345 -- Y : Controlled := Init;
347 -- Attach_To_Final_List (_L, Finalizable (Y), 1);
350 -- _C : Record_Controller;
356 -- Deep_Initialize (W, _L, 1);
357 -- at end: Abort_Under;
358 -- Z : R := (C => X);
359 -- Deep_Adjust (Z, _L, 1);
363 -- Deep_Finalize (W, False);
364 -- <save W's final pointers>
366 -- <restore W's final pointers>
367 -- Deep_Adjust (W, _L, 0);
372 function Global_Flist_Ref
(Flist_Ref
: Node_Id
) return Boolean;
373 -- Return True if Flist_Ref refers to a global final list, either the
374 -- object Global_Final_List which is used to attach standalone objects,
375 -- or any of the list controllers associated with library-level access
376 -- to controlled objects.
378 procedure Clean_Simple_Protected_Objects
(N
: Node_Id
);
379 -- Protected objects without entries are not controlled types, and the
380 -- locks have to be released explicitly when such an object goes out
381 -- of scope. Traverse declarations in scope to determine whether such
382 -- objects are present.
384 ----------------------------
385 -- Build_Array_Deep_Procs --
386 ----------------------------
388 procedure Build_Array_Deep_Procs
(Typ
: Entity_Id
) is
392 Prim
=> Initialize_Case
,
394 Stmts
=> Make_Deep_Array_Body
(Initialize_Case
, Typ
)));
396 if not Is_Inherently_Limited_Type
(Typ
) then
401 Stmts
=> Make_Deep_Array_Body
(Adjust_Case
, Typ
)));
406 Prim
=> Finalize_Case
,
408 Stmts
=> Make_Deep_Array_Body
(Finalize_Case
, Typ
)));
409 end Build_Array_Deep_Procs
;
411 -----------------------------
412 -- Build_Controlling_Procs --
413 -----------------------------
415 procedure Build_Controlling_Procs
(Typ
: Entity_Id
) is
417 if Is_Array_Type
(Typ
) then
418 Build_Array_Deep_Procs
(Typ
);
420 else pragma Assert
(Is_Record_Type
(Typ
));
421 Build_Record_Deep_Procs
(Typ
);
423 end Build_Controlling_Procs
;
425 ----------------------
426 -- Build_Final_List --
427 ----------------------
429 procedure Build_Final_List
(N
: Node_Id
; Typ
: Entity_Id
) is
430 Loc
: constant Source_Ptr
:= Sloc
(N
);
434 Set_Associated_Final_Chain
(Typ
,
435 Make_Defining_Identifier
(Loc
,
436 New_External_Name
(Chars
(Typ
), 'L')));
439 Make_Object_Declaration
(Loc
,
440 Defining_Identifier
=>
441 Associated_Final_Chain
(Typ
),
444 (RTE
(RE_List_Controller
), Loc
));
446 -- If the type is declared in a package declaration and designates a
447 -- Taft amendment type that requires finalization, place declaration
448 -- of finalization list in the body, because no client of the package
449 -- can create objects of the type and thus make use of this list. This
450 -- ensures the tree for the spec is identical whenever it is compiled.
452 if Has_Completion_In_Body
(Directly_Designated_Type
(Typ
))
453 and then In_Package_Body
(Current_Scope
)
454 and then Nkind
(Unit
(Cunit
(Current_Sem_Unit
))) = N_Package_Body
456 Nkind
(Parent
(Declaration_Node
(Typ
))) = N_Package_Specification
458 Insert_Action
(Parent
(Designated_Type
(Typ
)), Decl
);
460 -- The type may have been frozen already, and this is a late freezing
461 -- action, in which case the declaration must be elaborated at once.
462 -- If the call is for an allocator, the chain must also be created now,
463 -- because the freezing of the type does not build one. Otherwise, the
464 -- declaration is one of the freezing actions for a user-defined type.
466 elsif Is_Frozen
(Typ
)
467 or else (Nkind
(N
) = N_Allocator
468 and then Ekind
(Etype
(N
)) = E_Anonymous_Access_Type
)
470 Insert_Action
(N
, Decl
);
473 Append_Freeze_Action
(Typ
, Decl
);
475 end Build_Final_List
;
477 ---------------------
478 -- Build_Late_Proc --
479 ---------------------
481 procedure Build_Late_Proc
(Typ
: Entity_Id
; Nam
: Name_Id
) is
483 for Final_Prim
in Name_Of
'Range loop
484 if Name_Of
(Final_Prim
) = Nam
then
489 Stmts
=> Make_Deep_Record_Body
(Final_Prim
, Typ
)));
494 -----------------------------
495 -- Build_Record_Deep_Procs --
496 -----------------------------
498 procedure Build_Record_Deep_Procs
(Typ
: Entity_Id
) is
502 Prim
=> Initialize_Case
,
504 Stmts
=> Make_Deep_Record_Body
(Initialize_Case
, Typ
)));
506 if not Is_Inherently_Limited_Type
(Typ
) then
511 Stmts
=> Make_Deep_Record_Body
(Adjust_Case
, Typ
)));
516 Prim
=> Finalize_Case
,
518 Stmts
=> Make_Deep_Record_Body
(Finalize_Case
, Typ
)));
519 end Build_Record_Deep_Procs
;
525 function Cleanup_Array
528 Typ
: Entity_Id
) return List_Id
530 Loc
: constant Source_Ptr
:= Sloc
(N
);
531 Index_List
: constant List_Id
:= New_List
;
533 function Free_Component
return List_Id
;
534 -- Generate the code to finalize the task or protected subcomponents
535 -- of a single component of the array.
537 function Free_One_Dimension
(Dim
: Int
) return List_Id
;
538 -- Generate a loop over one dimension of the array
544 function Free_Component
return List_Id
is
545 Stmts
: List_Id
:= New_List
;
547 C_Typ
: constant Entity_Id
:= Component_Type
(Typ
);
550 -- Component type is known to contain tasks or protected objects
553 Make_Indexed_Component
(Loc
,
554 Prefix
=> Duplicate_Subexpr_No_Checks
(Obj
),
555 Expressions
=> Index_List
);
557 Set_Etype
(Tsk
, C_Typ
);
559 if Is_Task_Type
(C_Typ
) then
560 Append_To
(Stmts
, Cleanup_Task
(N
, Tsk
));
562 elsif Is_Simple_Protected_Type
(C_Typ
) then
563 Append_To
(Stmts
, Cleanup_Protected_Object
(N
, Tsk
));
565 elsif Is_Record_Type
(C_Typ
) then
566 Stmts
:= Cleanup_Record
(N
, Tsk
, C_Typ
);
568 elsif Is_Array_Type
(C_Typ
) then
569 Stmts
:= Cleanup_Array
(N
, Tsk
, C_Typ
);
575 ------------------------
576 -- Free_One_Dimension --
577 ------------------------
579 function Free_One_Dimension
(Dim
: Int
) return List_Id
is
583 if Dim
> Number_Dimensions
(Typ
) then
584 return Free_Component
;
586 -- Here we generate the required loop
590 Make_Defining_Identifier
(Loc
, New_Internal_Name
('J'));
592 Append
(New_Reference_To
(Index
, Loc
), Index_List
);
595 Make_Implicit_Loop_Statement
(N
,
598 Make_Iteration_Scheme
(Loc
,
599 Loop_Parameter_Specification
=>
600 Make_Loop_Parameter_Specification
(Loc
,
601 Defining_Identifier
=> Index
,
602 Discrete_Subtype_Definition
=>
603 Make_Attribute_Reference
(Loc
,
604 Prefix
=> Duplicate_Subexpr
(Obj
),
605 Attribute_Name
=> Name_Range
,
606 Expressions
=> New_List
(
607 Make_Integer_Literal
(Loc
, Dim
))))),
608 Statements
=> Free_One_Dimension
(Dim
+ 1)));
610 end Free_One_Dimension
;
612 -- Start of processing for Cleanup_Array
615 return Free_One_Dimension
(1);
622 function Cleanup_Record
625 Typ
: Entity_Id
) return List_Id
627 Loc
: constant Source_Ptr
:= Sloc
(N
);
630 Stmts
: constant List_Id
:= New_List
;
631 U_Typ
: constant Entity_Id
:= Underlying_Type
(Typ
);
634 if Has_Discriminants
(U_Typ
)
635 and then Nkind
(Parent
(U_Typ
)) = N_Full_Type_Declaration
637 Nkind
(Type_Definition
(Parent
(U_Typ
))) = N_Record_Definition
641 (Component_List
(Type_Definition
(Parent
(U_Typ
)))))
643 -- For now, do not attempt to free a component that may appear in
644 -- a variant, and instead issue a warning. Doing this "properly"
645 -- would require building a case statement and would be quite a
646 -- mess. Note that the RM only requires that free "work" for the
647 -- case of a task access value, so already we go way beyond this
648 -- in that we deal with the array case and non-discriminated
652 ("task/protected object in variant record will not be freed?", N
);
653 return New_List
(Make_Null_Statement
(Loc
));
656 Comp
:= First_Component
(Typ
);
658 while Present
(Comp
) loop
659 if Has_Task
(Etype
(Comp
))
660 or else Has_Simple_Protected_Object
(Etype
(Comp
))
663 Make_Selected_Component
(Loc
,
664 Prefix
=> Duplicate_Subexpr_No_Checks
(Obj
),
665 Selector_Name
=> New_Occurrence_Of
(Comp
, Loc
));
666 Set_Etype
(Tsk
, Etype
(Comp
));
668 if Is_Task_Type
(Etype
(Comp
)) then
669 Append_To
(Stmts
, Cleanup_Task
(N
, Tsk
));
671 elsif Is_Simple_Protected_Type
(Etype
(Comp
)) then
672 Append_To
(Stmts
, Cleanup_Protected_Object
(N
, Tsk
));
674 elsif Is_Record_Type
(Etype
(Comp
)) then
676 -- Recurse, by generating the prefix of the argument to
677 -- the eventual cleanup call.
680 (Stmts
, Cleanup_Record
(N
, Tsk
, Etype
(Comp
)));
682 elsif Is_Array_Type
(Etype
(Comp
)) then
684 (Stmts
, Cleanup_Array
(N
, Tsk
, Etype
(Comp
)));
688 Next_Component
(Comp
);
694 ------------------------------
695 -- Cleanup_Protected_Object --
696 ------------------------------
698 function Cleanup_Protected_Object
700 Ref
: Node_Id
) return Node_Id
702 Loc
: constant Source_Ptr
:= Sloc
(N
);
706 Make_Procedure_Call_Statement
(Loc
,
707 Name
=> New_Reference_To
(RTE
(RE_Finalize_Protection
), Loc
),
708 Parameter_Associations
=> New_List
(
709 Concurrent_Ref
(Ref
)));
710 end Cleanup_Protected_Object
;
712 ------------------------------------
713 -- Clean_Simple_Protected_Objects --
714 ------------------------------------
716 procedure Clean_Simple_Protected_Objects
(N
: Node_Id
) is
717 Stmts
: constant List_Id
:= Statements
(Handled_Statement_Sequence
(N
));
718 Stmt
: Node_Id
:= Last
(Stmts
);
722 E
:= First_Entity
(Current_Scope
);
723 while Present
(E
) loop
724 if (Ekind
(E
) = E_Variable
725 or else Ekind
(E
) = E_Constant
)
726 and then Has_Simple_Protected_Object
(Etype
(E
))
727 and then not Has_Task
(Etype
(E
))
728 and then Nkind
(Parent
(E
)) /= N_Object_Renaming_Declaration
731 Typ
: constant Entity_Id
:= Etype
(E
);
732 Ref
: constant Node_Id
:= New_Occurrence_Of
(E
, Sloc
(Stmt
));
735 if Is_Simple_Protected_Type
(Typ
) then
736 Append_To
(Stmts
, Cleanup_Protected_Object
(N
, Ref
));
738 elsif Has_Simple_Protected_Object
(Typ
) then
739 if Is_Record_Type
(Typ
) then
740 Append_List_To
(Stmts
, Cleanup_Record
(N
, Ref
, Typ
));
742 elsif Is_Array_Type
(Typ
) then
743 Append_List_To
(Stmts
, Cleanup_Array
(N
, Ref
, Typ
));
752 -- Analyze inserted cleanup statements
754 if Present
(Stmt
) then
757 while Present
(Stmt
) loop
762 end Clean_Simple_Protected_Objects
;
768 function Cleanup_Task
770 Ref
: Node_Id
) return Node_Id
772 Loc
: constant Source_Ptr
:= Sloc
(N
);
775 Make_Procedure_Call_Statement
(Loc
,
776 Name
=> New_Reference_To
(RTE
(RE_Free_Task
), Loc
),
777 Parameter_Associations
=>
778 New_List
(Concurrent_Ref
(Ref
)));
781 ---------------------------------
782 -- Has_Simple_Protected_Object --
783 ---------------------------------
785 function Has_Simple_Protected_Object
(T
: Entity_Id
) return Boolean is
789 if Is_Simple_Protected_Type
(T
) then
792 elsif Is_Array_Type
(T
) then
793 return Has_Simple_Protected_Object
(Component_Type
(T
));
795 elsif Is_Record_Type
(T
) then
796 Comp
:= First_Component
(T
);
798 while Present
(Comp
) loop
799 if Has_Simple_Protected_Object
(Etype
(Comp
)) then
803 Next_Component
(Comp
);
811 end Has_Simple_Protected_Object
;
813 ------------------------------
814 -- Is_Simple_Protected_Type --
815 ------------------------------
817 function Is_Simple_Protected_Type
(T
: Entity_Id
) return Boolean is
819 return Is_Protected_Type
(T
) and then not Has_Entries
(T
);
820 end Is_Simple_Protected_Type
;
822 ------------------------------
823 -- Check_Visibly_Controlled --
824 ------------------------------
826 procedure Check_Visibly_Controlled
827 (Prim
: Final_Primitives
;
829 E
: in out Entity_Id
;
830 Cref
: in out Node_Id
)
832 Parent_Type
: Entity_Id
;
836 if Is_Derived_Type
(Typ
)
837 and then Comes_From_Source
(E
)
838 and then not Is_Overriding_Operation
(E
)
840 -- We know that the explicit operation on the type does not override
841 -- the inherited operation of the parent, and that the derivation
842 -- is from a private type that is not visibly controlled.
844 Parent_Type
:= Etype
(Typ
);
845 Op
:= Find_Prim_Op
(Parent_Type
, Name_Of
(Prim
));
850 -- Wrap the object to be initialized into the proper
851 -- unchecked conversion, to be compatible with the operation
854 if Nkind
(Cref
) = N_Unchecked_Type_Conversion
then
855 Cref
:= Unchecked_Convert_To
(Parent_Type
, Expression
(Cref
));
857 Cref
:= Unchecked_Convert_To
(Parent_Type
, Cref
);
861 end Check_Visibly_Controlled
;
863 -------------------------------
864 -- CW_Or_Has_Controlled_Part --
865 -------------------------------
867 function CW_Or_Has_Controlled_Part
(T
: Entity_Id
) return Boolean is
869 return Is_Class_Wide_Type
(T
) or else Needs_Finalization
(T
);
870 end CW_Or_Has_Controlled_Part
;
872 --------------------------
873 -- Controller_Component --
874 --------------------------
876 function Controller_Component
(Typ
: Entity_Id
) return Entity_Id
is
877 T
: Entity_Id
:= Base_Type
(Typ
);
879 Comp_Scop
: Entity_Id
;
880 Res
: Entity_Id
:= Empty
;
881 Res_Scop
: Entity_Id
:= Empty
;
884 if Is_Class_Wide_Type
(T
) then
888 if Is_Private_Type
(T
) then
889 T
:= Underlying_Type
(T
);
892 -- Fetch the outermost controller
894 Comp
:= First_Entity
(T
);
895 while Present
(Comp
) loop
896 if Chars
(Comp
) = Name_uController
then
897 Comp_Scop
:= Scope
(Original_Record_Component
(Comp
));
899 -- If this controller is at the outermost level, no need to
900 -- look for another one
902 if Comp_Scop
= T
then
905 -- Otherwise record the outermost one and continue looking
907 elsif Res
= Empty
or else Is_Ancestor
(Res_Scop
, Comp_Scop
) then
909 Res_Scop
:= Comp_Scop
;
916 -- If we fall through the loop, there is no controller component
919 end Controller_Component
;
925 function Convert_View
928 Ind
: Pos
:= 1) return Node_Id
930 Fent
: Entity_Id
:= First_Entity
(Proc
);
935 for J
in 2 .. Ind
loop
939 Ftyp
:= Etype
(Fent
);
941 if Nkind_In
(Arg
, N_Type_Conversion
, N_Unchecked_Type_Conversion
) then
942 Atyp
:= Entity
(Subtype_Mark
(Arg
));
947 if Is_Abstract_Subprogram
(Proc
) and then Is_Tagged_Type
(Ftyp
) then
948 return Unchecked_Convert_To
(Class_Wide_Type
(Ftyp
), Arg
);
951 and then Present
(Atyp
)
953 (Is_Private_Type
(Ftyp
) or else Is_Private_Type
(Atyp
))
955 Base_Type
(Underlying_Type
(Atyp
)) =
956 Base_Type
(Underlying_Type
(Ftyp
))
958 return Unchecked_Convert_To
(Ftyp
, Arg
);
960 -- If the argument is already a conversion, as generated by
961 -- Make_Init_Call, set the target type to the type of the formal
962 -- directly, to avoid spurious typing problems.
964 elsif Nkind_In
(Arg
, N_Unchecked_Type_Conversion
, N_Type_Conversion
)
965 and then not Is_Class_Wide_Type
(Atyp
)
967 Set_Subtype_Mark
(Arg
, New_Occurrence_Of
(Ftyp
, Sloc
(Arg
)));
968 Set_Etype
(Arg
, Ftyp
);
976 -------------------------------
977 -- Establish_Transient_Scope --
978 -------------------------------
980 -- This procedure is called each time a transient block has to be inserted
981 -- that is to say for each call to a function with unconstrained or tagged
982 -- result. It creates a new scope on the stack scope in order to enclose
983 -- all transient variables generated
985 procedure Establish_Transient_Scope
(N
: Node_Id
; Sec_Stack
: Boolean) is
986 Loc
: constant Source_Ptr
:= Sloc
(N
);
990 -- Nothing to do for virtual machines where memory is GCed
992 if VM_Target
/= No_VM
then
996 -- Do not create a transient scope if we are already inside one
998 for S
in reverse Scope_Stack
.First
.. Scope_Stack
.Last
loop
999 if Scope_Stack
.Table
(S
).Is_Transient
then
1001 Set_Uses_Sec_Stack
(Scope_Stack
.Table
(S
).Entity
);
1006 -- If we have encountered Standard there are no enclosing
1007 -- transient scopes.
1009 elsif Scope_Stack
.Table
(S
).Entity
= Standard_Standard
then
1015 Wrap_Node
:= Find_Node_To_Be_Wrapped
(N
);
1017 -- Case of no wrap node, false alert, no transient scope needed
1019 if No
(Wrap_Node
) then
1022 -- If the node to wrap is an iteration_scheme, the expression is
1023 -- one of the bounds, and the expansion will make an explicit
1024 -- declaration for it (see Analyze_Iteration_Scheme, sem_ch5.adb),
1025 -- so do not apply any transformations here.
1027 elsif Nkind
(Wrap_Node
) = N_Iteration_Scheme
then
1031 Push_Scope
(New_Internal_Entity
(E_Block
, Current_Scope
, Loc
, 'B'));
1032 Set_Scope_Is_Transient
;
1035 Set_Uses_Sec_Stack
(Current_Scope
);
1036 Check_Restriction
(No_Secondary_Stack
, N
);
1039 Set_Etype
(Current_Scope
, Standard_Void_Type
);
1040 Set_Node_To_Be_Wrapped
(Wrap_Node
);
1042 if Debug_Flag_W
then
1043 Write_Str
(" <Transient>");
1047 end Establish_Transient_Scope
;
1049 ----------------------------
1050 -- Expand_Cleanup_Actions --
1051 ----------------------------
1053 procedure Expand_Cleanup_Actions
(N
: Node_Id
) is
1054 S
: constant Entity_Id
:= Current_Scope
;
1055 Flist
: constant Entity_Id
:= Finalization_Chain_Entity
(S
);
1056 Is_Task
: constant Boolean := Nkind
(Original_Node
(N
)) = N_Task_Body
;
1058 Is_Master
: constant Boolean :=
1059 Nkind
(N
) /= N_Entry_Body
1060 and then Is_Task_Master
(N
);
1061 Is_Protected
: constant Boolean :=
1062 Nkind
(N
) = N_Subprogram_Body
1063 and then Is_Protected_Subprogram_Body
(N
);
1064 Is_Task_Allocation
: constant Boolean :=
1065 Nkind
(N
) = N_Block_Statement
1066 and then Is_Task_Allocation_Block
(N
);
1067 Is_Asynchronous_Call
: constant Boolean :=
1068 Nkind
(N
) = N_Block_Statement
1069 and then Is_Asynchronous_Call_Block
(N
);
1071 Previous_At_End_Proc
: constant Node_Id
:=
1072 At_End_Proc
(Handled_Statement_Sequence
(N
));
1076 Mark
: Entity_Id
:= Empty
;
1077 New_Decls
: constant List_Id
:= New_List
;
1081 Chain
: Entity_Id
:= Empty
;
1086 -- If we are generating expanded code for debugging purposes, use
1087 -- the Sloc of the point of insertion for the cleanup code. The Sloc
1088 -- will be updated subsequently to reference the proper line in the
1089 -- .dg file. If we are not debugging generated code, use instead
1090 -- No_Location, so that no debug information is generated for the
1091 -- cleanup code. This makes the behavior of the NEXT command in GDB
1092 -- monotonic, and makes the placement of breakpoints more accurate.
1094 if Debug_Generated_Code
then
1100 -- There are cleanup actions only if the secondary stack needs
1101 -- releasing or some finalizations are needed or in the context
1104 if Uses_Sec_Stack
(Current_Scope
)
1105 and then not Sec_Stack_Needed_For_Return
(Current_Scope
)
1109 and then not Is_Master
1110 and then not Is_Task
1111 and then not Is_Protected
1112 and then not Is_Task_Allocation
1113 and then not Is_Asynchronous_Call
1115 Clean_Simple_Protected_Objects
(N
);
1119 -- If the current scope is the subprogram body that is the rewriting
1120 -- of a task body, and the descriptors have not been delayed (due to
1121 -- some nested instantiations) do not generate redundant cleanup
1122 -- actions: the cleanup procedure already exists for this body.
1124 if Nkind
(N
) = N_Subprogram_Body
1125 and then Nkind
(Original_Node
(N
)) = N_Task_Body
1126 and then not Delay_Subprogram_Descriptors
(Corresponding_Spec
(N
))
1131 -- Set polling off, since we don't need to poll during cleanup
1132 -- actions, and indeed for the cleanup routine, which is executed
1133 -- with aborts deferred, we don't want polling.
1135 Old_Poll
:= Polling_Required
;
1136 Polling_Required
:= False;
1138 -- Make sure we have a declaration list, since we will add to it
1140 if No
(Declarations
(N
)) then
1141 Set_Declarations
(N
, New_List
);
1144 -- The task activation call has already been built for task
1145 -- allocation blocks.
1147 if not Is_Task_Allocation
then
1148 Build_Task_Activation_Call
(N
);
1152 Establish_Task_Master
(N
);
1155 -- If secondary stack is in use, expand:
1156 -- _Mxx : constant Mark_Id := SS_Mark;
1158 -- Suppress calls to SS_Mark and SS_Release if VM_Target,
1159 -- since we never use the secondary stack on the VM.
1161 if Uses_Sec_Stack
(Current_Scope
)
1162 and then not Sec_Stack_Needed_For_Return
(Current_Scope
)
1163 and then VM_Target
= No_VM
1165 Mark
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('M'));
1166 Append_To
(New_Decls
,
1167 Make_Object_Declaration
(Loc
,
1168 Defining_Identifier
=> Mark
,
1169 Object_Definition
=> New_Reference_To
(RTE
(RE_Mark_Id
), Loc
),
1171 Make_Function_Call
(Loc
,
1172 Name
=> New_Reference_To
(RTE
(RE_SS_Mark
), Loc
))));
1174 Set_Uses_Sec_Stack
(Current_Scope
, False);
1177 -- If finalization list is present then expand:
1178 -- Local_Final_List : System.FI.Finalizable_Ptr;
1180 if Present
(Flist
) then
1181 Append_To
(New_Decls
,
1182 Make_Object_Declaration
(Loc
,
1183 Defining_Identifier
=> Flist
,
1184 Object_Definition
=>
1185 New_Reference_To
(RTE
(RE_Finalizable_Ptr
), Loc
)));
1188 -- Clean-up procedure definition
1190 Clean
:= Make_Defining_Identifier
(Loc
, Name_uClean
);
1191 Set_Suppress_Elaboration_Warnings
(Clean
);
1192 Append_To
(New_Decls
,
1193 Make_Clean
(N
, Clean
, Mark
, Flist
,
1198 Is_Asynchronous_Call
,
1199 Previous_At_End_Proc
));
1201 -- The previous AT END procedure, if any, has been captured in Clean:
1202 -- reset it to Empty now because we check further on that we never
1203 -- overwrite an existing AT END call.
1205 Set_At_End_Proc
(Handled_Statement_Sequence
(N
), Empty
);
1207 -- If exception handlers are present, wrap the Sequence of statements in
1208 -- a block because it is not possible to get exception handlers and an
1209 -- AT END call in the same scope.
1211 if Present
(Exception_Handlers
(Handled_Statement_Sequence
(N
))) then
1213 -- Preserve end label to provide proper cross-reference information
1215 End_Lab
:= End_Label
(Handled_Statement_Sequence
(N
));
1217 Make_Block_Statement
(Loc
,
1218 Handled_Statement_Sequence
=> Handled_Statement_Sequence
(N
));
1219 Set_Handled_Statement_Sequence
(N
,
1220 Make_Handled_Sequence_Of_Statements
(Loc
, New_List
(Blok
)));
1221 Set_End_Label
(Handled_Statement_Sequence
(N
), End_Lab
);
1224 -- Comment needed here, see RH for 1.306 ???
1226 if Nkind
(N
) = N_Subprogram_Body
then
1227 Set_Has_Nested_Block_With_Handler
(Current_Scope
);
1230 -- Otherwise we do not wrap
1237 -- Don't move the _chain Activation_Chain declaration in task
1238 -- allocation blocks. Task allocation blocks use this object
1239 -- in their cleanup handlers, and gigi complains if it is declared
1240 -- in the sequence of statements of the scope that declares the
1243 if Is_Task_Allocation
then
1244 Chain
:= Activation_Chain_Entity
(N
);
1246 Decl
:= First
(Declarations
(N
));
1247 while Nkind
(Decl
) /= N_Object_Declaration
1248 or else Defining_Identifier
(Decl
) /= Chain
1251 pragma Assert
(Present
(Decl
));
1255 Prepend_To
(New_Decls
, Decl
);
1258 -- Now we move the declarations into the Sequence of statements
1259 -- in order to get them protected by the AT END call. It may seem
1260 -- weird to put declarations in the sequence of statement but in
1261 -- fact nothing forbids that at the tree level. We also set the
1262 -- First_Real_Statement field so that we remember where the real
1263 -- statements (i.e. original statements) begin. Note that if we
1264 -- wrapped the statements, the first real statement is inside the
1265 -- inner block. If the First_Real_Statement is already set (as is
1266 -- the case for subprogram bodies that are expansions of task bodies)
1267 -- then do not reset it, because its declarative part would migrate
1268 -- to the statement part.
1271 if No
(First_Real_Statement
(Handled_Statement_Sequence
(N
))) then
1272 Set_First_Real_Statement
(Handled_Statement_Sequence
(N
),
1273 First
(Statements
(Handled_Statement_Sequence
(N
))));
1277 Set_First_Real_Statement
(Handled_Statement_Sequence
(N
), Blok
);
1280 Append_List_To
(Declarations
(N
),
1281 Statements
(Handled_Statement_Sequence
(N
)));
1282 Set_Statements
(Handled_Statement_Sequence
(N
), Declarations
(N
));
1284 -- We need to reset the Sloc of the handled statement sequence to
1285 -- properly reflect the new initial "statement" in the sequence.
1288 (Handled_Statement_Sequence
(N
), Sloc
(First
(Declarations
(N
))));
1290 -- The declarations of the _Clean procedure and finalization chain
1291 -- replace the old declarations that have been moved inward.
1293 Set_Declarations
(N
, New_Decls
);
1294 Analyze_Declarations
(New_Decls
);
1296 -- The At_End call is attached to the sequence of statements
1302 -- If the construct is a protected subprogram, then the call to
1303 -- the corresponding unprotected subprogram appears in a block which
1304 -- is the last statement in the body, and it is this block that must
1305 -- be covered by the At_End handler.
1307 if Is_Protected
then
1308 HSS
:= Handled_Statement_Sequence
1309 (Last
(Statements
(Handled_Statement_Sequence
(N
))));
1311 HSS
:= Handled_Statement_Sequence
(N
);
1314 -- Never overwrite an existing AT END call
1316 pragma Assert
(No
(At_End_Proc
(HSS
)));
1318 Set_At_End_Proc
(HSS
, New_Occurrence_Of
(Clean
, Loc
));
1319 Expand_At_End_Handler
(HSS
, Empty
);
1322 -- Restore saved polling mode
1324 Polling_Required
:= Old_Poll
;
1325 end Expand_Cleanup_Actions
;
1327 -------------------------------
1328 -- Expand_Ctrl_Function_Call --
1329 -------------------------------
1331 procedure Expand_Ctrl_Function_Call
(N
: Node_Id
) is
1332 Loc
: constant Source_Ptr
:= Sloc
(N
);
1333 Rtype
: constant Entity_Id
:= Etype
(N
);
1334 Utype
: constant Entity_Id
:= Underlying_Type
(Rtype
);
1337 Action2
: Node_Id
:= Empty
;
1339 Attach_Level
: Uint
:= Uint_1
;
1340 Len_Ref
: Node_Id
:= Empty
;
1342 function Last_Array_Component
1344 Typ
: Entity_Id
) return Node_Id
;
1345 -- Creates a reference to the last component of the array object
1346 -- designated by Ref whose type is Typ.
1348 --------------------------
1349 -- Last_Array_Component --
1350 --------------------------
1352 function Last_Array_Component
1354 Typ
: Entity_Id
) return Node_Id
1356 Index_List
: constant List_Id
:= New_List
;
1359 for N
in 1 .. Number_Dimensions
(Typ
) loop
1360 Append_To
(Index_List
,
1361 Make_Attribute_Reference
(Loc
,
1362 Prefix
=> Duplicate_Subexpr_No_Checks
(Ref
),
1363 Attribute_Name
=> Name_Last
,
1364 Expressions
=> New_List
(
1365 Make_Integer_Literal
(Loc
, N
))));
1369 Make_Indexed_Component
(Loc
,
1370 Prefix
=> Duplicate_Subexpr
(Ref
),
1371 Expressions
=> Index_List
);
1372 end Last_Array_Component
;
1374 -- Start of processing for Expand_Ctrl_Function_Call
1377 -- Optimization, if the returned value (which is on the sec-stack) is
1378 -- returned again, no need to copy/readjust/finalize, we can just pass
1379 -- the value thru (see Expand_N_Simple_Return_Statement), and thus no
1380 -- attachment is needed
1382 if Nkind
(Parent
(N
)) = N_Simple_Return_Statement
then
1386 -- Resolution is now finished, make sure we don't start analysis again
1387 -- because of the duplication.
1390 Ref
:= Duplicate_Subexpr_No_Checks
(N
);
1392 -- Now we can generate the Attach Call. Note that this value is always
1393 -- on the (secondary) stack and thus is attached to a singly linked
1396 -- Resx := F (X)'reference;
1397 -- Attach_To_Final_List (_Lx, Resx.all, 1);
1399 -- or when there are controlled components:
1401 -- Attach_To_Final_List (_Lx, Resx._controller, 1);
1403 -- or when it is both Is_Controlled and Has_Controlled_Components:
1405 -- Attach_To_Final_List (_Lx, Resx._controller, 1);
1406 -- Attach_To_Final_List (_Lx, Resx, 1);
1408 -- or if it is an array with Is_Controlled (and Has_Controlled)
1410 -- Attach_To_Final_List (_Lx, Resx (Resx'last), 3);
1412 -- An attach level of 3 means that a whole array is to be attached to
1413 -- the finalization list (including the controlled components).
1415 -- or if it is an array with Has_Controlled_Components but not
1418 -- Attach_To_Final_List (_Lx, Resx (Resx'last)._controller, 3);
1420 -- Case where type has controlled components
1422 if Has_Controlled_Component
(Rtype
) then
1424 T1
: Entity_Id
:= Rtype
;
1425 T2
: Entity_Id
:= Utype
;
1428 if Is_Array_Type
(T2
) then
1430 Make_Attribute_Reference
(Loc
,
1432 Duplicate_Subexpr_Move_Checks
1433 (Unchecked_Convert_To
(T2
, Ref
)),
1434 Attribute_Name
=> Name_Length
);
1437 while Is_Array_Type
(T2
) loop
1439 Ref
:= Unchecked_Convert_To
(T2
, Ref
);
1442 Ref
:= Last_Array_Component
(Ref
, T2
);
1443 Attach_Level
:= Uint_3
;
1444 T1
:= Component_Type
(T2
);
1445 T2
:= Underlying_Type
(T1
);
1448 -- If the type has controlled components, go to the controller
1449 -- except in the case of arrays of controlled objects since in
1450 -- this case objects and their components are already chained
1451 -- and the head of the chain is the last array element.
1453 if Is_Array_Type
(Rtype
) and then Is_Controlled
(T2
) then
1456 elsif Has_Controlled_Component
(T2
) then
1458 Ref
:= Unchecked_Convert_To
(T2
, Ref
);
1462 Make_Selected_Component
(Loc
,
1464 Selector_Name
=> Make_Identifier
(Loc
, Name_uController
));
1468 -- Here we know that 'Ref' has a controller so we may as well attach
1474 Flist_Ref
=> Find_Final_List
(Current_Scope
),
1475 With_Attach
=> Make_Integer_Literal
(Loc
, Attach_Level
));
1477 -- If it is also Is_Controlled we need to attach the global object
1479 if Is_Controlled
(Rtype
) then
1482 Obj_Ref
=> Duplicate_Subexpr_No_Checks
(N
),
1483 Flist_Ref
=> Find_Final_List
(Current_Scope
),
1484 With_Attach
=> Make_Integer_Literal
(Loc
, Attach_Level
));
1487 -- Here, we have a controlled type that does not seem to have controlled
1488 -- components but it could be a class wide type whose further
1489 -- derivations have controlled components. So we don't know if the
1490 -- object itself needs to be attached or if it has a record controller.
1491 -- We need to call a runtime function (Deep_Tag_Attach) which knows what
1492 -- to do thanks to the RC_Offset in the dispatch table.
1496 Make_Procedure_Call_Statement
(Loc
,
1497 Name
=> New_Reference_To
(RTE
(RE_Deep_Tag_Attach
), Loc
),
1498 Parameter_Associations
=> New_List
(
1499 Find_Final_List
(Current_Scope
),
1501 Make_Attribute_Reference
(Loc
,
1503 Attribute_Name
=> Name_Address
),
1505 Make_Integer_Literal
(Loc
, Attach_Level
)));
1508 if Present
(Len_Ref
) then
1510 Make_Implicit_If_Statement
(N
,
1511 Condition
=> Make_Op_Gt
(Loc
,
1512 Left_Opnd
=> Len_Ref
,
1513 Right_Opnd
=> Make_Integer_Literal
(Loc
, 0)),
1514 Then_Statements
=> New_List
(Action
));
1517 Insert_Action
(N
, Action
);
1518 if Present
(Action2
) then
1519 Insert_Action
(N
, Action2
);
1521 end Expand_Ctrl_Function_Call
;
1523 ---------------------------
1524 -- Expand_N_Package_Body --
1525 ---------------------------
1527 -- Add call to Activate_Tasks if body is an activator (actual processing
1528 -- is in chapter 9).
1530 -- Generate subprogram descriptor for elaboration routine
1532 -- Encode entity names in package body
1534 procedure Expand_N_Package_Body
(N
: Node_Id
) is
1535 Ent
: constant Entity_Id
:= Corresponding_Spec
(N
);
1538 -- This is done only for non-generic packages
1540 if Ekind
(Ent
) = E_Package
then
1541 Push_Scope
(Corresponding_Spec
(N
));
1543 -- Build dispatch tables of library level tagged types
1545 if Is_Library_Level_Entity
(Ent
) then
1546 Build_Static_Dispatch_Tables
(N
);
1549 Build_Task_Activation_Call
(N
);
1553 Set_Elaboration_Flag
(N
, Corresponding_Spec
(N
));
1554 Set_In_Package_Body
(Ent
, False);
1556 -- Set to encode entity names in package body before gigi is called
1558 Qualify_Entity_Names
(N
);
1559 end Expand_N_Package_Body
;
1561 ----------------------------------
1562 -- Expand_N_Package_Declaration --
1563 ----------------------------------
1565 -- Add call to Activate_Tasks if there are tasks declared and the package
1566 -- has no body. Note that in Ada83, this may result in premature activation
1567 -- of some tasks, given that we cannot tell whether a body will eventually
1570 procedure Expand_N_Package_Declaration
(N
: Node_Id
) is
1571 Spec
: constant Node_Id
:= Specification
(N
);
1572 Id
: constant Entity_Id
:= Defining_Entity
(N
);
1574 No_Body
: Boolean := False;
1575 -- True in the case of a package declaration that is a compilation unit
1576 -- and for which no associated body will be compiled in
1577 -- this compilation.
1580 -- Case of a package declaration other than a compilation unit
1582 if Nkind
(Parent
(N
)) /= N_Compilation_Unit
then
1585 -- Case of a compilation unit that does not require a body
1587 elsif not Body_Required
(Parent
(N
))
1588 and then not Unit_Requires_Body
(Id
)
1592 -- Special case of generating calling stubs for a remote call interface
1593 -- package: even though the package declaration requires one, the
1594 -- body won't be processed in this compilation (so any stubs for RACWs
1595 -- declared in the package must be generated here, along with the
1598 elsif Parent
(N
) = Cunit
(Main_Unit
)
1599 and then Is_Remote_Call_Interface
(Id
)
1600 and then Distribution_Stub_Mode
= Generate_Caller_Stub_Body
1605 -- For a package declaration that implies no associated body, generate
1606 -- task activation call and RACW supporting bodies now (since we won't
1607 -- have a specific separate compilation unit for that).
1612 if Has_RACW
(Id
) then
1614 -- Generate RACW subprogram bodies
1616 Decls
:= Private_Declarations
(Spec
);
1619 Decls
:= Visible_Declarations
(Spec
);
1624 Set_Visible_Declarations
(Spec
, Decls
);
1627 Append_RACW_Bodies
(Decls
, Id
);
1628 Analyze_List
(Decls
);
1631 if Present
(Activation_Chain_Entity
(N
)) then
1633 -- Generate task activation call as last step of elaboration
1635 Build_Task_Activation_Call
(N
);
1641 -- Build dispatch tables of library level tagged types
1643 if Is_Compilation_Unit
(Id
)
1644 or else (Is_Generic_Instance
(Id
)
1645 and then Is_Library_Level_Entity
(Id
))
1647 Build_Static_Dispatch_Tables
(N
);
1650 -- Note: it is not necessary to worry about generating a subprogram
1651 -- descriptor, since the only way to get exception handlers into a
1652 -- package spec is to include instantiations, and that would cause
1653 -- generation of subprogram descriptors to be delayed in any case.
1655 -- Set to encode entity names in package spec before gigi is called
1657 Qualify_Entity_Names
(N
);
1658 end Expand_N_Package_Declaration
;
1660 ---------------------
1661 -- Find_Final_List --
1662 ---------------------
1664 function Find_Final_List
1666 Ref
: Node_Id
:= Empty
) return Node_Id
1668 Loc
: constant Source_Ptr
:= Sloc
(Ref
);
1674 -- If the restriction No_Finalization applies, then there's not any
1675 -- finalization list available to return, so return Empty.
1677 if Restriction_Active
(No_Finalization
) then
1680 -- Case of an internal component. The Final list is the record
1681 -- controller of the enclosing record.
1683 elsif Present
(Ref
) then
1687 when N_Unchecked_Type_Conversion | N_Type_Conversion
=>
1688 R
:= Expression
(R
);
1690 when N_Indexed_Component | N_Explicit_Dereference
=>
1693 when N_Selected_Component
=>
1697 when N_Identifier
=>
1701 raise Program_Error
;
1706 Make_Selected_Component
(Loc
,
1708 Make_Selected_Component
(Loc
,
1710 Selector_Name
=> Make_Identifier
(Loc
, Name_uController
)),
1711 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
1713 -- Case of a dynamically allocated object whose access type has an
1714 -- Associated_Final_Chain. The final list is the corresponding list
1715 -- controller (the next entity in the scope of the access type with
1716 -- the right type). If the type comes from a With_Type clause, no
1717 -- controller was created, we use the global chain instead. (The code
1718 -- related to with_type clauses should presumably be removed at some
1719 -- point since that feature is obsolete???)
1721 -- An anonymous access type either has a list created for it when the
1722 -- allocator is a for an access parameter or an access discriminant,
1723 -- or else it uses the list of the enclosing dynamic scope, when the
1724 -- context is a declaration or an assignment.
1726 elsif Is_Access_Type
(E
)
1727 and then (Present
(Associated_Final_Chain
(E
))
1728 or else From_With_Type
(E
))
1730 if From_With_Type
(E
) then
1731 return New_Reference_To
(RTE
(RE_Global_Final_List
), Sloc
(E
));
1733 -- Use the access type's associated finalization chain
1737 Make_Selected_Component
(Loc
,
1740 (Associated_Final_Chain
(Base_Type
(E
)), Loc
),
1741 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
1745 if Is_Dynamic_Scope
(E
) then
1748 S
:= Enclosing_Dynamic_Scope
(E
);
1751 -- When the finalization chain entity is 'Error', it means that there
1752 -- should not be any chain at that level and that the enclosing one
1755 -- This is a nasty kludge, see ??? note in exp_ch11
1757 while Finalization_Chain_Entity
(S
) = Error
loop
1758 S
:= Enclosing_Dynamic_Scope
(S
);
1761 if S
= Standard_Standard
then
1762 return New_Reference_To
(RTE
(RE_Global_Final_List
), Sloc
(E
));
1764 if No
(Finalization_Chain_Entity
(S
)) then
1766 -- In the case where the scope is a subprogram, retrieve the
1767 -- Sloc of subprogram's body for association with the chain,
1768 -- since using the Sloc of the spec would be confusing during
1769 -- source-line stepping within the debugger.
1772 Flist_Loc
: Source_Ptr
:= Sloc
(S
);
1773 Subp_Body
: Node_Id
;
1776 if Ekind
(S
) in Subprogram_Kind
then
1777 Subp_Body
:= Unit_Declaration_Node
(S
);
1779 if Nkind
(Subp_Body
) /= N_Subprogram_Body
then
1780 Subp_Body
:= Corresponding_Body
(Subp_Body
);
1783 if Present
(Subp_Body
) then
1784 Flist_Loc
:= Sloc
(Subp_Body
);
1789 Make_Defining_Identifier
(Flist_Loc
,
1790 Chars
=> New_Internal_Name
('F'));
1793 Set_Finalization_Chain_Entity
(S
, Id
);
1795 -- Set momentarily some semantics attributes to allow normal
1796 -- analysis of expansions containing references to this chain.
1797 -- Will be fully decorated during the expansion of the scope
1800 Set_Ekind
(Id
, E_Variable
);
1801 Set_Etype
(Id
, RTE
(RE_Finalizable_Ptr
));
1804 return New_Reference_To
(Finalization_Chain_Entity
(S
), Sloc
(E
));
1807 end Find_Final_List
;
1809 -----------------------------
1810 -- Find_Node_To_Be_Wrapped --
1811 -----------------------------
1813 function Find_Node_To_Be_Wrapped
(N
: Node_Id
) return Node_Id
is
1815 The_Parent
: Node_Id
;
1821 pragma Assert
(P
/= Empty
);
1822 The_Parent
:= Parent
(P
);
1824 case Nkind
(The_Parent
) is
1826 -- Simple statement can be wrapped
1831 -- Usually assignments are good candidate for wrapping
1832 -- except when they have been generated as part of a
1833 -- controlled aggregate where the wrapping should take
1834 -- place more globally.
1836 when N_Assignment_Statement
=>
1837 if No_Ctrl_Actions
(The_Parent
) then
1843 -- An entry call statement is a special case if it occurs in
1844 -- the context of a Timed_Entry_Call. In this case we wrap
1845 -- the entire timed entry call.
1847 when N_Entry_Call_Statement |
1848 N_Procedure_Call_Statement
=>
1849 if Nkind
(Parent
(The_Parent
)) = N_Entry_Call_Alternative
1850 and then Nkind_In
(Parent
(Parent
(The_Parent
)),
1852 N_Conditional_Entry_Call
)
1854 return Parent
(Parent
(The_Parent
));
1859 -- Object declarations are also a boundary for the transient scope
1860 -- even if they are not really wrapped
1861 -- (see Wrap_Transient_Declaration)
1863 when N_Object_Declaration |
1864 N_Object_Renaming_Declaration |
1865 N_Subtype_Declaration
=>
1868 -- The expression itself is to be wrapped if its parent is a
1869 -- compound statement or any other statement where the expression
1870 -- is known to be scalar
1872 when N_Accept_Alternative |
1873 N_Attribute_Definition_Clause |
1876 N_Delay_Alternative |
1877 N_Delay_Until_Statement |
1878 N_Delay_Relative_Statement |
1879 N_Discriminant_Association |
1881 N_Entry_Body_Formal_Part |
1884 N_Iteration_Scheme |
1885 N_Terminate_Alternative
=>
1888 when N_Attribute_Reference
=>
1890 if Is_Procedure_Attribute_Name
1891 (Attribute_Name
(The_Parent
))
1896 -- A raise statement can be wrapped. This will arise when the
1897 -- expression in a raise_with_expression uses the secondary
1898 -- stack, for example.
1900 when N_Raise_Statement
=>
1903 -- If the expression is within the iteration scheme of a loop,
1904 -- we must create a declaration for it, followed by an assignment
1905 -- in order to have a usable statement to wrap.
1907 when N_Loop_Parameter_Specification
=>
1908 return Parent
(The_Parent
);
1910 -- The following nodes contains "dummy calls" which don't
1911 -- need to be wrapped.
1913 when N_Parameter_Specification |
1914 N_Discriminant_Specification |
1915 N_Component_Declaration
=>
1918 -- The return statement is not to be wrapped when the function
1919 -- itself needs wrapping at the outer-level
1921 when N_Simple_Return_Statement
=>
1923 Applies_To
: constant Entity_Id
:=
1925 (Return_Statement_Entity
(The_Parent
));
1926 Return_Type
: constant Entity_Id
:= Etype
(Applies_To
);
1928 if Requires_Transient_Scope
(Return_Type
) then
1935 -- If we leave a scope without having been able to find a node to
1936 -- wrap, something is going wrong but this can happen in error
1937 -- situation that are not detected yet (such as a dynamic string
1938 -- in a pragma export)
1940 when N_Subprogram_Body |
1941 N_Package_Declaration |
1943 N_Block_Statement
=>
1946 -- otherwise continue the search
1952 end Find_Node_To_Be_Wrapped
;
1954 ----------------------
1955 -- Global_Flist_Ref --
1956 ----------------------
1958 function Global_Flist_Ref
(Flist_Ref
: Node_Id
) return Boolean is
1962 -- Look for the Global_Final_List
1964 if Is_Entity_Name
(Flist_Ref
) then
1965 Flist
:= Entity
(Flist_Ref
);
1967 -- Look for the final list associated with an access to controlled
1969 elsif Nkind
(Flist_Ref
) = N_Selected_Component
1970 and then Is_Entity_Name
(Prefix
(Flist_Ref
))
1972 Flist
:= Entity
(Prefix
(Flist_Ref
));
1977 return Present
(Flist
)
1978 and then Present
(Scope
(Flist
))
1979 and then Enclosing_Dynamic_Scope
(Flist
) = Standard_Standard
;
1980 end Global_Flist_Ref
;
1982 ----------------------------------
1983 -- Has_New_Controlled_Component --
1984 ----------------------------------
1986 function Has_New_Controlled_Component
(E
: Entity_Id
) return Boolean is
1990 if not Is_Tagged_Type
(E
) then
1991 return Has_Controlled_Component
(E
);
1992 elsif not Is_Derived_Type
(E
) then
1993 return Has_Controlled_Component
(E
);
1996 Comp
:= First_Component
(E
);
1997 while Present
(Comp
) loop
1999 if Chars
(Comp
) = Name_uParent
then
2002 elsif Scope
(Original_Record_Component
(Comp
)) = E
2003 and then Needs_Finalization
(Etype
(Comp
))
2008 Next_Component
(Comp
);
2012 end Has_New_Controlled_Component
;
2014 --------------------------
2015 -- In_Finalization_Root --
2016 --------------------------
2018 -- It would seem simpler to test Scope (RTE (RE_Root_Controlled)) but
2019 -- the purpose of this function is to avoid a circular call to Rtsfind
2020 -- which would been caused by such a test.
2022 function In_Finalization_Root
(E
: Entity_Id
) return Boolean is
2023 S
: constant Entity_Id
:= Scope
(E
);
2026 return Chars
(Scope
(S
)) = Name_System
2027 and then Chars
(S
) = Name_Finalization_Root
2028 and then Scope
(Scope
(S
)) = Standard_Standard
;
2029 end In_Finalization_Root
;
2031 ------------------------------------
2032 -- Insert_Actions_In_Scope_Around --
2033 ------------------------------------
2035 procedure Insert_Actions_In_Scope_Around
(N
: Node_Id
) is
2036 SE
: Scope_Stack_Entry
renames Scope_Stack
.Table
(Scope_Stack
.Last
);
2040 -- If the node to be wrapped is the triggering statement of an
2041 -- asynchronous select, it is not part of a statement list. The
2042 -- actions must be inserted before the Select itself, which is
2043 -- part of some list of statements. Note that the triggering
2044 -- alternative includes the triggering statement and an optional
2045 -- statement list. If the node to be wrapped is part of that list,
2046 -- the normal insertion applies.
2048 if Nkind
(Parent
(Node_To_Be_Wrapped
)) = N_Triggering_Alternative
2049 and then not Is_List_Member
(Node_To_Be_Wrapped
)
2051 Target
:= Parent
(Parent
(Node_To_Be_Wrapped
));
2056 if Present
(SE
.Actions_To_Be_Wrapped_Before
) then
2057 Insert_List_Before
(Target
, SE
.Actions_To_Be_Wrapped_Before
);
2058 SE
.Actions_To_Be_Wrapped_Before
:= No_List
;
2061 if Present
(SE
.Actions_To_Be_Wrapped_After
) then
2062 Insert_List_After
(Target
, SE
.Actions_To_Be_Wrapped_After
);
2063 SE
.Actions_To_Be_Wrapped_After
:= No_List
;
2065 end Insert_Actions_In_Scope_Around
;
2067 -----------------------
2068 -- Make_Adjust_Call --
2069 -----------------------
2071 function Make_Adjust_Call
2074 Flist_Ref
: Node_Id
;
2075 With_Attach
: Node_Id
;
2076 Allocator
: Boolean := False) return List_Id
2078 Loc
: constant Source_Ptr
:= Sloc
(Ref
);
2079 Res
: constant List_Id
:= New_List
;
2082 Cref
: Node_Id
:= Ref
;
2084 Attach
: Node_Id
:= With_Attach
;
2087 if Is_Class_Wide_Type
(Typ
) then
2088 Utyp
:= Underlying_Type
(Base_Type
(Root_Type
(Typ
)));
2090 Utyp
:= Underlying_Type
(Base_Type
(Typ
));
2093 Set_Assignment_OK
(Cref
);
2095 -- Deal with non-tagged derivation of private views
2097 if Is_Untagged_Derivation
(Typ
) then
2098 Utyp
:= Underlying_Type
(Root_Type
(Base_Type
(Typ
)));
2099 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
2100 Set_Assignment_OK
(Cref
);
2101 -- To prevent problems with UC see 1.156 RH ???
2104 -- If the underlying_type is a subtype, we are dealing with
2105 -- the completion of a private type. We need to access
2106 -- the base type and generate a conversion to it.
2108 if Utyp
/= Base_Type
(Utyp
) then
2109 pragma Assert
(Is_Private_Type
(Typ
));
2110 Utyp
:= Base_Type
(Utyp
);
2111 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
2114 -- If the object is unanalyzed, set its expected type for use
2115 -- in Convert_View in case an additional conversion is needed.
2117 if No
(Etype
(Cref
))
2118 and then Nkind
(Cref
) /= N_Unchecked_Type_Conversion
2120 Set_Etype
(Cref
, Typ
);
2123 -- We do not need to attach to one of the Global Final Lists
2124 -- the objects whose type is Finalize_Storage_Only
2126 if Finalize_Storage_Only
(Typ
)
2127 and then (Global_Flist_Ref
(Flist_Ref
)
2128 or else Entity
(Constant_Value
(RTE
(RE_Garbage_Collected
)))
2131 Attach
:= Make_Integer_Literal
(Loc
, 0);
2134 -- Special case for allocators: need initialization of the chain
2135 -- pointers. For the 0 case, reset them to null.
2138 pragma Assert
(Nkind
(Attach
) = N_Integer_Literal
);
2140 if Intval
(Attach
) = 0 then
2141 Set_Intval
(Attach
, Uint_4
);
2146 -- Deep_Adjust (Flist_Ref, Ref, Attach);
2148 if Has_Controlled_Component
(Utyp
)
2149 or else Is_Class_Wide_Type
(Typ
)
2151 if Is_Tagged_Type
(Utyp
) then
2152 Proc
:= Find_Prim_Op
(Utyp
, TSS_Deep_Adjust
);
2155 Proc
:= TSS
(Utyp
, TSS_Deep_Adjust
);
2158 Cref
:= Convert_View
(Proc
, Cref
, 2);
2161 Make_Procedure_Call_Statement
(Loc
,
2162 Name
=> New_Reference_To
(Proc
, Loc
),
2163 Parameter_Associations
=>
2164 New_List
(Flist_Ref
, Cref
, Attach
)));
2167 -- if With_Attach then
2168 -- Attach_To_Final_List (Ref, Flist_Ref);
2172 else -- Is_Controlled (Utyp)
2174 Proc
:= Find_Prim_Op
(Utyp
, Name_Of
(Adjust_Case
));
2175 Cref
:= Convert_View
(Proc
, Cref
);
2176 Cref2
:= New_Copy_Tree
(Cref
);
2179 Make_Procedure_Call_Statement
(Loc
,
2180 Name
=> New_Reference_To
(Proc
, Loc
),
2181 Parameter_Associations
=> New_List
(Cref2
)));
2183 Append_To
(Res
, Make_Attach_Call
(Cref
, Flist_Ref
, Attach
));
2187 end Make_Adjust_Call
;
2189 ----------------------
2190 -- Make_Attach_Call --
2191 ----------------------
2194 -- System.FI.Attach_To_Final_List (Flist, Ref, Nb_Link)
2196 function Make_Attach_Call
2198 Flist_Ref
: Node_Id
;
2199 With_Attach
: Node_Id
) return Node_Id
2201 Loc
: constant Source_Ptr
:= Sloc
(Obj_Ref
);
2204 -- Optimization: If the number of links is statically '0', don't
2205 -- call the attach_proc.
2207 if Nkind
(With_Attach
) = N_Integer_Literal
2208 and then Intval
(With_Attach
) = Uint_0
2210 return Make_Null_Statement
(Loc
);
2214 Make_Procedure_Call_Statement
(Loc
,
2215 Name
=> New_Reference_To
(RTE
(RE_Attach_To_Final_List
), Loc
),
2216 Parameter_Associations
=> New_List
(
2218 OK_Convert_To
(RTE
(RE_Finalizable
), Obj_Ref
),
2220 end Make_Attach_Call
;
2232 Is_Master
: Boolean;
2233 Is_Protected_Subprogram
: Boolean;
2234 Is_Task_Allocation_Block
: Boolean;
2235 Is_Asynchronous_Call_Block
: Boolean;
2236 Chained_Cleanup_Action
: Node_Id
) return Node_Id
2238 Loc
: constant Source_Ptr
:= Sloc
(Clean
);
2239 Stmt
: constant List_Id
:= New_List
;
2245 Param_Type
: Entity_Id
;
2246 Pid
: Entity_Id
:= Empty
;
2247 Cancel_Param
: Entity_Id
;
2251 if Restricted_Profile
then
2253 (Stmt
, Build_Runtime_Call
(Loc
, RE_Complete_Restricted_Task
));
2255 Append_To
(Stmt
, Build_Runtime_Call
(Loc
, RE_Complete_Task
));
2258 elsif Is_Master
then
2259 if Restriction_Active
(No_Task_Hierarchy
) = False then
2260 Append_To
(Stmt
, Build_Runtime_Call
(Loc
, RE_Complete_Master
));
2263 elsif Is_Protected_Subprogram
then
2265 -- Add statements to the cleanup handler of the (ordinary)
2266 -- subprogram expanded to implement a protected subprogram,
2267 -- unlocking the protected object parameter and undeferring abort.
2268 -- If this is a protected procedure, and the object contains
2269 -- entries, this also calls the entry service routine.
2271 -- NOTE: This cleanup handler references _object, a parameter
2272 -- to the procedure.
2274 -- Find the _object parameter representing the protected object
2276 Spec
:= Parent
(Corresponding_Spec
(N
));
2278 Param
:= First
(Parameter_Specifications
(Spec
));
2280 Param_Type
:= Etype
(Parameter_Type
(Param
));
2282 if Ekind
(Param_Type
) = E_Record_Type
then
2283 Pid
:= Corresponding_Concurrent_Type
(Param_Type
);
2286 exit when No
(Param
) or else Present
(Pid
);
2290 pragma Assert
(Present
(Param
));
2292 -- If the associated protected object declares entries,
2293 -- a protected procedure has to service entry queues.
2294 -- In this case, add
2296 -- Service_Entries (_object._object'Access);
2298 -- _object is the record used to implement the protected object.
2299 -- It is a parameter to the protected subprogram.
2301 if Nkind
(Specification
(N
)) = N_Procedure_Specification
2302 and then Has_Entries
(Pid
)
2304 case Corresponding_Runtime_Package
(Pid
) is
2305 when System_Tasking_Protected_Objects_Entries
=>
2306 Name
:= New_Reference_To
(RTE
(RE_Service_Entries
), Loc
);
2308 when System_Tasking_Protected_Objects_Single_Entry
=>
2309 Name
:= New_Reference_To
(RTE
(RE_Service_Entry
), Loc
);
2312 raise Program_Error
;
2316 Make_Procedure_Call_Statement
(Loc
,
2318 Parameter_Associations
=> New_List
(
2319 Make_Attribute_Reference
(Loc
,
2321 Make_Selected_Component
(Loc
,
2322 Prefix
=> New_Reference_To
(
2323 Defining_Identifier
(Param
), Loc
),
2325 Make_Identifier
(Loc
, Name_uObject
)),
2326 Attribute_Name
=> Name_Unchecked_Access
))));
2329 -- Unlock (_object._object'Access);
2331 -- object is the record used to implement the protected object.
2332 -- It is a parameter to the protected subprogram.
2334 case Corresponding_Runtime_Package
(Pid
) is
2335 when System_Tasking_Protected_Objects_Entries
=>
2336 Name
:= New_Reference_To
(RTE
(RE_Unlock_Entries
), Loc
);
2338 when System_Tasking_Protected_Objects_Single_Entry
=>
2339 Name
:= New_Reference_To
(RTE
(RE_Unlock_Entry
), Loc
);
2341 when System_Tasking_Protected_Objects
=>
2342 Name
:= New_Reference_To
(RTE
(RE_Unlock
), Loc
);
2345 raise Program_Error
;
2349 Make_Procedure_Call_Statement
(Loc
,
2351 Parameter_Associations
=> New_List
(
2352 Make_Attribute_Reference
(Loc
,
2354 Make_Selected_Component
(Loc
,
2356 New_Reference_To
(Defining_Identifier
(Param
), Loc
),
2358 Make_Identifier
(Loc
, Name_uObject
)),
2359 Attribute_Name
=> Name_Unchecked_Access
))));
2362 if Abort_Allowed
then
2367 Make_Procedure_Call_Statement
(Loc
,
2370 RTE
(RE_Abort_Undefer
), Loc
),
2371 Parameter_Associations
=> Empty_List
));
2374 elsif Is_Task_Allocation_Block
then
2376 -- Add a call to Expunge_Unactivated_Tasks to the cleanup
2377 -- handler of a block created for the dynamic allocation of
2380 -- Expunge_Unactivated_Tasks (_chain);
2382 -- where _chain is the list of tasks created by the allocator
2383 -- but not yet activated. This list will be empty unless
2384 -- the block completes abnormally.
2386 -- This only applies to dynamically allocated tasks;
2387 -- other unactivated tasks are completed by Complete_Task or
2390 -- NOTE: This cleanup handler references _chain, a local
2394 Make_Procedure_Call_Statement
(Loc
,
2397 RTE
(RE_Expunge_Unactivated_Tasks
), Loc
),
2398 Parameter_Associations
=> New_List
(
2399 New_Reference_To
(Activation_Chain_Entity
(N
), Loc
))));
2401 elsif Is_Asynchronous_Call_Block
then
2403 -- Add a call to attempt to cancel the asynchronous entry call
2404 -- whenever the block containing the abortable part is exited.
2406 -- NOTE: This cleanup handler references C, a local object
2408 -- Get the argument to the Cancel procedure
2409 Cancel_Param
:= Entry_Cancel_Parameter
(Entity
(Identifier
(N
)));
2411 -- If it is of type Communication_Block, this must be a
2412 -- protected entry call.
2414 if Is_RTE
(Etype
(Cancel_Param
), RE_Communication_Block
) then
2418 -- if Enqueued (Cancel_Parameter) then
2420 Make_Implicit_If_Statement
(Clean
,
2421 Condition
=> Make_Function_Call
(Loc
,
2422 Name
=> New_Reference_To
(
2423 RTE
(RE_Enqueued
), Loc
),
2424 Parameter_Associations
=> New_List
(
2425 New_Reference_To
(Cancel_Param
, Loc
))),
2426 Then_Statements
=> New_List
(
2428 -- Cancel_Protected_Entry_Call (Cancel_Param);
2430 Make_Procedure_Call_Statement
(Loc
,
2431 Name
=> New_Reference_To
(
2432 RTE
(RE_Cancel_Protected_Entry_Call
), Loc
),
2433 Parameter_Associations
=> New_List
(
2434 New_Reference_To
(Cancel_Param
, Loc
))))));
2436 -- Asynchronous delay
2438 elsif Is_RTE
(Etype
(Cancel_Param
), RE_Delay_Block
) then
2440 Make_Procedure_Call_Statement
(Loc
,
2441 Name
=> New_Reference_To
(RTE
(RE_Cancel_Async_Delay
), Loc
),
2442 Parameter_Associations
=> New_List
(
2443 Make_Attribute_Reference
(Loc
,
2444 Prefix
=> New_Reference_To
(Cancel_Param
, Loc
),
2445 Attribute_Name
=> Name_Unchecked_Access
))));
2450 -- Append call to Cancel_Task_Entry_Call (C);
2453 Make_Procedure_Call_Statement
(Loc
,
2454 Name
=> New_Reference_To
(
2455 RTE
(RE_Cancel_Task_Entry_Call
),
2457 Parameter_Associations
=> New_List
(
2458 New_Reference_To
(Cancel_Param
, Loc
))));
2463 if Present
(Flist
) then
2465 Make_Procedure_Call_Statement
(Loc
,
2466 Name
=> New_Reference_To
(RTE
(RE_Finalize_List
), Loc
),
2467 Parameter_Associations
=> New_List
(
2468 New_Reference_To
(Flist
, Loc
))));
2471 if Present
(Mark
) then
2473 Make_Procedure_Call_Statement
(Loc
,
2474 Name
=> New_Reference_To
(RTE
(RE_SS_Release
), Loc
),
2475 Parameter_Associations
=> New_List
(
2476 New_Reference_To
(Mark
, Loc
))));
2479 if Present
(Chained_Cleanup_Action
) then
2481 Make_Procedure_Call_Statement
(Loc
,
2482 Name
=> Chained_Cleanup_Action
));
2486 Make_Subprogram_Body
(Loc
,
2488 Make_Procedure_Specification
(Loc
,
2489 Defining_Unit_Name
=> Clean
),
2491 Declarations
=> New_List
,
2493 Handled_Statement_Sequence
=>
2494 Make_Handled_Sequence_Of_Statements
(Loc
,
2495 Statements
=> Stmt
));
2497 if Present
(Flist
) or else Is_Task
or else Is_Master
then
2498 Wrap_Cleanup_Procedure
(Sbody
);
2501 -- We do not want debug information for _Clean routines,
2502 -- since it just confuses the debugging operation unless
2503 -- we are debugging generated code.
2505 if not Debug_Generated_Code
then
2506 Set_Debug_Info_Off
(Clean
, True);
2512 --------------------------
2513 -- Make_Deep_Array_Body --
2514 --------------------------
2516 -- Array components are initialized and adjusted in the normal order
2517 -- and finalized in the reverse order. Exceptions are handled and
2518 -- Program_Error is re-raise in the Adjust and Finalize case
2519 -- (RM 7.6.1(12)). Generate the following code :
2521 -- procedure Deep_<P> -- with <P> being Initialize or Adjust or Finalize
2522 -- (L : in out Finalizable_Ptr;
2526 -- for J1 in Typ'First (1) .. Typ'Last (1) loop
2527 -- ^ reverse ^ -- in the finalization case
2529 -- for J2 in Typ'First (n) .. Typ'Last (n) loop
2530 -- Make_<P>_Call (Typ, V (J1, .. , Jn), L, V);
2534 -- exception -- not in the
2535 -- when others => raise Program_Error; -- Initialize case
2538 function Make_Deep_Array_Body
2539 (Prim
: Final_Primitives
;
2540 Typ
: Entity_Id
) return List_Id
2542 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
2544 Index_List
: constant List_Id
:= New_List
;
2545 -- Stores the list of references to the indexes (one per dimension)
2547 function One_Component
return List_Id
;
2548 -- Create one statement to initialize/adjust/finalize one array
2549 -- component, designated by a full set of indices.
2551 function One_Dimension
(N
: Int
) return List_Id
;
2552 -- Create loop to deal with one dimension of the array. The single
2553 -- statement in the body of the loop initializes the inner dimensions if
2554 -- any, or else a single component.
2560 function One_Component
return List_Id
is
2561 Comp_Typ
: constant Entity_Id
:= Component_Type
(Typ
);
2562 Comp_Ref
: constant Node_Id
:=
2563 Make_Indexed_Component
(Loc
,
2564 Prefix
=> Make_Identifier
(Loc
, Name_V
),
2565 Expressions
=> Index_List
);
2568 -- Set the etype of the component Reference, which is used to
2569 -- determine whether a conversion to a parent type is needed.
2571 Set_Etype
(Comp_Ref
, Comp_Typ
);
2574 when Initialize_Case
=>
2575 return Make_Init_Call
(Comp_Ref
, Comp_Typ
,
2576 Make_Identifier
(Loc
, Name_L
),
2577 Make_Identifier
(Loc
, Name_B
));
2580 return Make_Adjust_Call
(Comp_Ref
, Comp_Typ
,
2581 Make_Identifier
(Loc
, Name_L
),
2582 Make_Identifier
(Loc
, Name_B
));
2584 when Finalize_Case
=>
2585 return Make_Final_Call
(Comp_Ref
, Comp_Typ
,
2586 Make_Identifier
(Loc
, Name_B
));
2594 function One_Dimension
(N
: Int
) return List_Id
is
2598 if N
> Number_Dimensions
(Typ
) then
2599 return One_Component
;
2603 Make_Defining_Identifier
(Loc
, New_External_Name
('J', N
));
2605 Append_To
(Index_List
, New_Reference_To
(Index
, Loc
));
2608 Make_Implicit_Loop_Statement
(Typ
,
2609 Identifier
=> Empty
,
2611 Make_Iteration_Scheme
(Loc
,
2612 Loop_Parameter_Specification
=>
2613 Make_Loop_Parameter_Specification
(Loc
,
2614 Defining_Identifier
=> Index
,
2615 Discrete_Subtype_Definition
=>
2616 Make_Attribute_Reference
(Loc
,
2617 Prefix
=> Make_Identifier
(Loc
, Name_V
),
2618 Attribute_Name
=> Name_Range
,
2619 Expressions
=> New_List
(
2620 Make_Integer_Literal
(Loc
, N
))),
2621 Reverse_Present
=> Prim
= Finalize_Case
)),
2622 Statements
=> One_Dimension
(N
+ 1)));
2626 -- Start of processing for Make_Deep_Array_Body
2629 return One_Dimension
(1);
2630 end Make_Deep_Array_Body
;
2632 --------------------
2633 -- Make_Deep_Proc --
2634 --------------------
2637 -- procedure DEEP_<prim>
2638 -- (L : IN OUT Finalizable_Ptr; -- not for Finalize
2639 -- V : IN OUT <typ>;
2640 -- B : IN Short_Short_Integer) is
2643 -- exception -- Finalize and Adjust Cases only
2644 -- raise Program_Error; -- idem
2647 function Make_Deep_Proc
2648 (Prim
: Final_Primitives
;
2650 Stmts
: List_Id
) return Entity_Id
2652 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
2654 Proc_Name
: Entity_Id
;
2655 Handler
: List_Id
:= No_List
;
2659 if Prim
= Finalize_Case
then
2660 Formals
:= New_List
;
2661 Type_B
:= Standard_Boolean
;
2664 Formals
:= New_List
(
2665 Make_Parameter_Specification
(Loc
,
2666 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_L
),
2668 Out_Present
=> True,
2670 New_Reference_To
(RTE
(RE_Finalizable_Ptr
), Loc
)));
2671 Type_B
:= Standard_Short_Short_Integer
;
2675 Make_Parameter_Specification
(Loc
,
2676 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_V
),
2678 Out_Present
=> True,
2679 Parameter_Type
=> New_Reference_To
(Typ
, Loc
)));
2682 Make_Parameter_Specification
(Loc
,
2683 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_B
),
2684 Parameter_Type
=> New_Reference_To
(Type_B
, Loc
)));
2686 if Prim
= Finalize_Case
or else Prim
= Adjust_Case
then
2687 Handler
:= New_List
(Make_Handler_For_Ctrl_Operation
(Loc
));
2691 Make_Defining_Identifier
(Loc
,
2692 Chars
=> Make_TSS_Name
(Typ
, Deep_Name_Of
(Prim
)));
2695 Make_Subprogram_Body
(Loc
,
2697 Make_Procedure_Specification
(Loc
,
2698 Defining_Unit_Name
=> Proc_Name
,
2699 Parameter_Specifications
=> Formals
),
2701 Declarations
=> Empty_List
,
2702 Handled_Statement_Sequence
=>
2703 Make_Handled_Sequence_Of_Statements
(Loc
,
2704 Statements
=> Stmts
,
2705 Exception_Handlers
=> Handler
)));
2710 ---------------------------
2711 -- Make_Deep_Record_Body --
2712 ---------------------------
2714 -- The Deep procedures call the appropriate Controlling proc on the
2715 -- the controller component. In the init case, it also attach the
2716 -- controller to the current finalization list.
2718 function Make_Deep_Record_Body
2719 (Prim
: Final_Primitives
;
2720 Typ
: Entity_Id
) return List_Id
2722 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
2723 Controller_Typ
: Entity_Id
;
2724 Obj_Ref
: constant Node_Id
:= Make_Identifier
(Loc
, Name_V
);
2725 Controller_Ref
: constant Node_Id
:=
2726 Make_Selected_Component
(Loc
,
2729 Make_Identifier
(Loc
, Name_uController
));
2730 Res
: constant List_Id
:= New_List
;
2733 if Is_Inherently_Limited_Type
(Typ
) then
2734 Controller_Typ
:= RTE
(RE_Limited_Record_Controller
);
2736 Controller_Typ
:= RTE
(RE_Record_Controller
);
2740 when Initialize_Case
=>
2741 Append_List_To
(Res
,
2743 Ref
=> Controller_Ref
,
2744 Typ
=> Controller_Typ
,
2745 Flist_Ref
=> Make_Identifier
(Loc
, Name_L
),
2746 With_Attach
=> Make_Identifier
(Loc
, Name_B
)));
2748 -- When the type is also a controlled type by itself,
2749 -- initialize it and attach it to the finalization chain.
2751 if Is_Controlled
(Typ
) then
2753 Make_Procedure_Call_Statement
(Loc
,
2754 Name
=> New_Reference_To
(
2755 Find_Prim_Op
(Typ
, Name_Of
(Prim
)), Loc
),
2756 Parameter_Associations
=>
2757 New_List
(New_Copy_Tree
(Obj_Ref
))));
2759 Append_To
(Res
, Make_Attach_Call
(
2760 Obj_Ref
=> New_Copy_Tree
(Obj_Ref
),
2761 Flist_Ref
=> Make_Identifier
(Loc
, Name_L
),
2762 With_Attach
=> Make_Identifier
(Loc
, Name_B
)));
2766 Append_List_To
(Res
,
2767 Make_Adjust_Call
(Controller_Ref
, Controller_Typ
,
2768 Make_Identifier
(Loc
, Name_L
),
2769 Make_Identifier
(Loc
, Name_B
)));
2771 -- When the type is also a controlled type by itself,
2772 -- adjust it and attach it to the finalization chain.
2774 if Is_Controlled
(Typ
) then
2776 Make_Procedure_Call_Statement
(Loc
,
2777 Name
=> New_Reference_To
(
2778 Find_Prim_Op
(Typ
, Name_Of
(Prim
)), Loc
),
2779 Parameter_Associations
=>
2780 New_List
(New_Copy_Tree
(Obj_Ref
))));
2782 Append_To
(Res
, Make_Attach_Call
(
2783 Obj_Ref
=> New_Copy_Tree
(Obj_Ref
),
2784 Flist_Ref
=> Make_Identifier
(Loc
, Name_L
),
2785 With_Attach
=> Make_Identifier
(Loc
, Name_B
)));
2788 when Finalize_Case
=>
2789 if Is_Controlled
(Typ
) then
2791 Make_Implicit_If_Statement
(Obj_Ref
,
2792 Condition
=> Make_Identifier
(Loc
, Name_B
),
2793 Then_Statements
=> New_List
(
2794 Make_Procedure_Call_Statement
(Loc
,
2795 Name
=> New_Reference_To
(RTE
(RE_Finalize_One
), Loc
),
2796 Parameter_Associations
=> New_List
(
2797 OK_Convert_To
(RTE
(RE_Finalizable
),
2798 New_Copy_Tree
(Obj_Ref
))))),
2800 Else_Statements
=> New_List
(
2801 Make_Procedure_Call_Statement
(Loc
,
2802 Name
=> New_Reference_To
(
2803 Find_Prim_Op
(Typ
, Name_Of
(Prim
)), Loc
),
2804 Parameter_Associations
=>
2805 New_List
(New_Copy_Tree
(Obj_Ref
))))));
2808 Append_List_To
(Res
,
2809 Make_Final_Call
(Controller_Ref
, Controller_Typ
,
2810 Make_Identifier
(Loc
, Name_B
)));
2813 end Make_Deep_Record_Body
;
2815 ----------------------
2816 -- Make_Final_Call --
2817 ----------------------
2819 function Make_Final_Call
2822 With_Detach
: Node_Id
) return List_Id
2824 Loc
: constant Source_Ptr
:= Sloc
(Ref
);
2825 Res
: constant List_Id
:= New_List
;
2832 if Is_Class_Wide_Type
(Typ
) then
2833 Utyp
:= Root_Type
(Typ
);
2836 elsif Is_Concurrent_Type
(Typ
) then
2837 Utyp
:= Corresponding_Record_Type
(Typ
);
2838 Cref
:= Convert_Concurrent
(Ref
, Typ
);
2840 elsif Is_Private_Type
(Typ
)
2841 and then Present
(Full_View
(Typ
))
2842 and then Is_Concurrent_Type
(Full_View
(Typ
))
2844 Utyp
:= Corresponding_Record_Type
(Full_View
(Typ
));
2845 Cref
:= Convert_Concurrent
(Ref
, Full_View
(Typ
));
2851 Utyp
:= Underlying_Type
(Base_Type
(Utyp
));
2852 Set_Assignment_OK
(Cref
);
2854 -- Deal with non-tagged derivation of private views. If the parent is
2855 -- now known to be protected, the finalization routine is the one
2856 -- defined on the corresponding record of the ancestor (corresponding
2857 -- records do not automatically inherit operations, but maybe they
2860 if Is_Untagged_Derivation
(Typ
) then
2861 if Is_Protected_Type
(Typ
) then
2862 Utyp
:= Corresponding_Record_Type
(Root_Type
(Base_Type
(Typ
)));
2864 Utyp
:= Underlying_Type
(Root_Type
(Base_Type
(Typ
)));
2867 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
2869 -- We need to set Assignment_OK to prevent problems with unchecked
2870 -- conversions, where we do not want them to be converted back in the
2871 -- case of untagged record derivation (see code in Make_*_Call
2872 -- procedures for similar situations).
2874 Set_Assignment_OK
(Cref
);
2877 -- If the underlying_type is a subtype, we are dealing with
2878 -- the completion of a private type. We need to access
2879 -- the base type and generate a conversion to it.
2881 if Utyp
/= Base_Type
(Utyp
) then
2882 pragma Assert
(Is_Private_Type
(Typ
));
2883 Utyp
:= Base_Type
(Utyp
);
2884 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
2888 -- Deep_Finalize (Ref, With_Detach);
2890 if Has_Controlled_Component
(Utyp
)
2891 or else Is_Class_Wide_Type
(Typ
)
2893 if Is_Tagged_Type
(Utyp
) then
2894 Proc
:= Find_Prim_Op
(Utyp
, TSS_Deep_Finalize
);
2896 Proc
:= TSS
(Utyp
, TSS_Deep_Finalize
);
2899 Cref
:= Convert_View
(Proc
, Cref
);
2902 Make_Procedure_Call_Statement
(Loc
,
2903 Name
=> New_Reference_To
(Proc
, Loc
),
2904 Parameter_Associations
=>
2905 New_List
(Cref
, With_Detach
)));
2908 -- if With_Detach then
2909 -- Finalize_One (Ref);
2915 Proc
:= Find_Prim_Op
(Utyp
, Name_Of
(Finalize_Case
));
2917 if Chars
(With_Detach
) = Chars
(Standard_True
) then
2919 Make_Procedure_Call_Statement
(Loc
,
2920 Name
=> New_Reference_To
(RTE
(RE_Finalize_One
), Loc
),
2921 Parameter_Associations
=> New_List
(
2922 OK_Convert_To
(RTE
(RE_Finalizable
), Cref
))));
2924 elsif Chars
(With_Detach
) = Chars
(Standard_False
) then
2926 Make_Procedure_Call_Statement
(Loc
,
2927 Name
=> New_Reference_To
(Proc
, Loc
),
2928 Parameter_Associations
=>
2929 New_List
(Convert_View
(Proc
, Cref
))));
2932 Cref2
:= New_Copy_Tree
(Cref
);
2934 Make_Implicit_If_Statement
(Ref
,
2935 Condition
=> With_Detach
,
2936 Then_Statements
=> New_List
(
2937 Make_Procedure_Call_Statement
(Loc
,
2938 Name
=> New_Reference_To
(RTE
(RE_Finalize_One
), Loc
),
2939 Parameter_Associations
=> New_List
(
2940 OK_Convert_To
(RTE
(RE_Finalizable
), Cref
)))),
2942 Else_Statements
=> New_List
(
2943 Make_Procedure_Call_Statement
(Loc
,
2944 Name
=> New_Reference_To
(Proc
, Loc
),
2945 Parameter_Associations
=>
2946 New_List
(Convert_View
(Proc
, Cref2
))))));
2951 end Make_Final_Call
;
2953 -------------------------------------
2954 -- Make_Handler_For_Ctrl_Operation --
2955 -------------------------------------
2959 -- when E : others =>
2960 -- Raise_From_Controlled_Operation (X => E);
2965 -- raise Program_Error [finalize raised exception];
2967 -- depending on whether Raise_From_Controlled_Operation is available
2969 function Make_Handler_For_Ctrl_Operation
2970 (Loc
: Source_Ptr
) return Node_Id
2973 -- Choice parameter (for the first case above)
2975 Raise_Node
: Node_Id
;
2976 -- Procedure call or raise statement
2979 if RTE_Available
(RE_Raise_From_Controlled_Operation
) then
2981 -- Standard runtime: add choice parameter E, and pass it to
2982 -- Raise_From_Controlled_Operation so that the original exception
2983 -- name and message can be recorded in the exception message for
2986 E_Occ
:= Make_Defining_Identifier
(Loc
, Name_E
);
2987 Raise_Node
:= Make_Procedure_Call_Statement
(Loc
,
2990 RTE
(RE_Raise_From_Controlled_Operation
), Loc
),
2991 Parameter_Associations
=> New_List
(
2992 New_Occurrence_Of
(E_Occ
, Loc
)));
2995 -- Restricted runtime: exception messages are not supported
2998 Raise_Node
:= Make_Raise_Program_Error
(Loc
,
2999 Reason
=> PE_Finalize_Raised_Exception
);
3002 return Make_Implicit_Exception_Handler
(Loc
,
3003 Exception_Choices
=> New_List
(Make_Others_Choice
(Loc
)),
3004 Choice_Parameter
=> E_Occ
,
3005 Statements
=> New_List
(Raise_Node
));
3006 end Make_Handler_For_Ctrl_Operation
;
3008 --------------------
3009 -- Make_Init_Call --
3010 --------------------
3012 function Make_Init_Call
3015 Flist_Ref
: Node_Id
;
3016 With_Attach
: Node_Id
) return List_Id
3018 Loc
: constant Source_Ptr
:= Sloc
(Ref
);
3020 Res
: constant List_Id
:= New_List
;
3025 Attach
: Node_Id
:= With_Attach
;
3028 if Is_Concurrent_Type
(Typ
) then
3030 Utyp
:= Corresponding_Record_Type
(Typ
);
3031 Cref
:= Convert_Concurrent
(Ref
, Typ
);
3033 elsif Is_Private_Type
(Typ
)
3034 and then Present
(Full_View
(Typ
))
3035 and then Is_Concurrent_Type
(Underlying_Type
(Typ
))
3038 Utyp
:= Corresponding_Record_Type
(Underlying_Type
(Typ
));
3039 Cref
:= Convert_Concurrent
(Ref
, Underlying_Type
(Typ
));
3047 Utyp
:= Underlying_Type
(Base_Type
(Utyp
));
3049 Set_Assignment_OK
(Cref
);
3051 -- Deal with non-tagged derivation of private views
3053 if Is_Untagged_Derivation
(Typ
)
3054 and then not Is_Conc
3056 Utyp
:= Underlying_Type
(Root_Type
(Base_Type
(Typ
)));
3057 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
3058 Set_Assignment_OK
(Cref
);
3059 -- To prevent problems with UC see 1.156 RH ???
3062 -- If the underlying_type is a subtype, we are dealing with
3063 -- the completion of a private type. We need to access
3064 -- the base type and generate a conversion to it.
3066 if Utyp
/= Base_Type
(Utyp
) then
3067 pragma Assert
(Is_Private_Type
(Typ
));
3068 Utyp
:= Base_Type
(Utyp
);
3069 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
3072 -- We do not need to attach to one of the Global Final Lists
3073 -- the objects whose type is Finalize_Storage_Only
3075 if Finalize_Storage_Only
(Typ
)
3076 and then (Global_Flist_Ref
(Flist_Ref
)
3077 or else Entity
(Constant_Value
(RTE
(RE_Garbage_Collected
)))
3080 Attach
:= Make_Integer_Literal
(Loc
, 0);
3084 -- Deep_Initialize (Ref, Flist_Ref);
3086 if Has_Controlled_Component
(Utyp
) then
3087 Proc
:= TSS
(Utyp
, Deep_Name_Of
(Initialize_Case
));
3089 Cref
:= Convert_View
(Proc
, Cref
, 2);
3092 Make_Procedure_Call_Statement
(Loc
,
3093 Name
=> New_Reference_To
(Proc
, Loc
),
3094 Parameter_Associations
=> New_List
(
3100 -- Attach_To_Final_List (Ref, Flist_Ref);
3101 -- Initialize (Ref);
3103 else -- Is_Controlled (Utyp)
3104 Proc
:= Find_Prim_Op
(Utyp
, Name_Of
(Initialize_Case
));
3105 Check_Visibly_Controlled
(Initialize_Case
, Typ
, Proc
, Cref
);
3107 Cref
:= Convert_View
(Proc
, Cref
);
3108 Cref2
:= New_Copy_Tree
(Cref
);
3111 Make_Procedure_Call_Statement
(Loc
,
3112 Name
=> New_Reference_To
(Proc
, Loc
),
3113 Parameter_Associations
=> New_List
(Cref2
)));
3116 Make_Attach_Call
(Cref
, Flist_Ref
, Attach
));
3122 --------------------------
3123 -- Make_Transient_Block --
3124 --------------------------
3126 -- If finalization is involved, this function just wraps the instruction
3127 -- into a block whose name is the transient block entity, and then
3128 -- Expand_Cleanup_Actions (called on the expansion of the handled
3129 -- sequence of statements will do the necessary expansions for
3132 function Make_Transient_Block
3134 Action
: Node_Id
) return Node_Id
3136 Flist
: constant Entity_Id
:= Finalization_Chain_Entity
(Current_Scope
);
3137 Decls
: constant List_Id
:= New_List
;
3138 Par
: constant Node_Id
:= Parent
(Action
);
3139 Instrs
: constant List_Id
:= New_List
(Action
);
3143 -- Case where only secondary stack use is involved
3145 if VM_Target
= No_VM
3146 and then Uses_Sec_Stack
(Current_Scope
)
3148 and then Nkind
(Action
) /= N_Simple_Return_Statement
3149 and then Nkind
(Par
) /= N_Exception_Handler
3156 S
:= Scope
(Current_Scope
);
3160 -- At the outer level, no need to release the sec stack
3162 if S
= Standard_Standard
then
3163 Set_Uses_Sec_Stack
(Current_Scope
, False);
3166 -- In a function, only release the sec stack if the
3167 -- function does not return on the sec stack otherwise
3168 -- the result may be lost. The caller is responsible for
3171 elsif K
= E_Function
then
3172 Set_Uses_Sec_Stack
(Current_Scope
, False);
3174 if not Requires_Transient_Scope
(Etype
(S
)) then
3175 Set_Uses_Sec_Stack
(S
, True);
3176 Check_Restriction
(No_Secondary_Stack
, Action
);
3181 -- In a loop or entry we should install a block encompassing
3182 -- all the construct. For now just release right away.
3184 elsif K
= E_Loop
or else K
= E_Entry
then
3187 -- In a procedure or a block, we release on exit of the
3188 -- procedure or block. ??? memory leak can be created by
3191 elsif K
= E_Procedure
3194 Set_Uses_Sec_Stack
(S
, True);
3195 Check_Restriction
(No_Secondary_Stack
, Action
);
3196 Set_Uses_Sec_Stack
(Current_Scope
, False);
3206 -- Insert actions stuck in the transient scopes as well as all
3207 -- freezing nodes needed by those actions
3209 Insert_Actions_In_Scope_Around
(Action
);
3212 Last_Inserted
: Node_Id
:= Prev
(Action
);
3214 if Present
(Last_Inserted
) then
3215 Freeze_All
(First_Entity
(Current_Scope
), Last_Inserted
);
3220 Make_Block_Statement
(Loc
,
3221 Identifier
=> New_Reference_To
(Current_Scope
, Loc
),
3222 Declarations
=> Decls
,
3223 Handled_Statement_Sequence
=>
3224 Make_Handled_Sequence_Of_Statements
(Loc
, Statements
=> Instrs
),
3225 Has_Created_Identifier
=> True);
3227 -- When the transient scope was established, we pushed the entry for
3228 -- the transient scope onto the scope stack, so that the scope was
3229 -- active for the installation of finalizable entities etc. Now we
3230 -- must remove this entry, since we have constructed a proper block.
3235 end Make_Transient_Block
;
3237 ------------------------
3238 -- Needs_Finalization --
3239 ------------------------
3241 function Needs_Finalization
(T
: Entity_Id
) return Boolean is
3243 function Has_Some_Controlled_Component
(Rec
: Entity_Id
) return Boolean;
3244 -- If type is not frozen yet, check explicitly among its components,
3245 -- because the Has_Controlled_Component flag is not necessarily set.
3247 -----------------------------------
3248 -- Has_Some_Controlled_Component --
3249 -----------------------------------
3251 function Has_Some_Controlled_Component
3252 (Rec
: Entity_Id
) return Boolean
3257 if Has_Controlled_Component
(Rec
) then
3260 elsif not Is_Frozen
(Rec
) then
3261 if Is_Record_Type
(Rec
) then
3262 Comp
:= First_Entity
(Rec
);
3264 while Present
(Comp
) loop
3265 if not Is_Type
(Comp
)
3266 and then Needs_Finalization
(Etype
(Comp
))
3276 elsif Is_Array_Type
(Rec
) then
3277 return Needs_Finalization
(Component_Type
(Rec
));
3280 return Has_Controlled_Component
(Rec
);
3285 end Has_Some_Controlled_Component
;
3287 -- Start of processing for Needs_Finalization
3292 -- Class-wide types must be treated as controlled and therefore
3293 -- requiring finalization (because they may be extended with an
3294 -- extension that has controlled components.
3296 (Is_Class_Wide_Type
(T
)
3298 -- However, avoid treating class-wide types as controlled if
3299 -- finalization is not available and in particular CIL value
3300 -- types never have finalization).
3302 and then not In_Finalization_Root
(T
)
3303 and then not Restriction_Active
(No_Finalization
)
3304 and then not Is_Value_Type
(Etype
(T
)))
3306 -- Controlled types always need finalization
3308 or else Is_Controlled
(T
)
3309 or else Has_Some_Controlled_Component
(T
)
3311 -- For concurrent types, test the corresponding record type
3313 or else (Is_Concurrent_Type
(T
)
3314 and then Present
(Corresponding_Record_Type
(T
))
3315 and then Needs_Finalization
(Corresponding_Record_Type
(T
)));
3316 end Needs_Finalization
;
3318 ------------------------
3319 -- Node_To_Be_Wrapped --
3320 ------------------------
3322 function Node_To_Be_Wrapped
return Node_Id
is
3324 return Scope_Stack
.Table
(Scope_Stack
.Last
).Node_To_Be_Wrapped
;
3325 end Node_To_Be_Wrapped
;
3327 ----------------------------
3328 -- Set_Node_To_Be_Wrapped --
3329 ----------------------------
3331 procedure Set_Node_To_Be_Wrapped
(N
: Node_Id
) is
3333 Scope_Stack
.Table
(Scope_Stack
.Last
).Node_To_Be_Wrapped
:= N
;
3334 end Set_Node_To_Be_Wrapped
;
3336 ----------------------------------
3337 -- Store_After_Actions_In_Scope --
3338 ----------------------------------
3340 procedure Store_After_Actions_In_Scope
(L
: List_Id
) is
3341 SE
: Scope_Stack_Entry
renames Scope_Stack
.Table
(Scope_Stack
.Last
);
3344 if Present
(SE
.Actions_To_Be_Wrapped_After
) then
3345 Insert_List_Before_And_Analyze
(
3346 First
(SE
.Actions_To_Be_Wrapped_After
), L
);
3349 SE
.Actions_To_Be_Wrapped_After
:= L
;
3351 if Is_List_Member
(SE
.Node_To_Be_Wrapped
) then
3352 Set_Parent
(L
, Parent
(SE
.Node_To_Be_Wrapped
));
3354 Set_Parent
(L
, SE
.Node_To_Be_Wrapped
);
3359 end Store_After_Actions_In_Scope
;
3361 -----------------------------------
3362 -- Store_Before_Actions_In_Scope --
3363 -----------------------------------
3365 procedure Store_Before_Actions_In_Scope
(L
: List_Id
) is
3366 SE
: Scope_Stack_Entry
renames Scope_Stack
.Table
(Scope_Stack
.Last
);
3369 if Present
(SE
.Actions_To_Be_Wrapped_Before
) then
3370 Insert_List_After_And_Analyze
(
3371 Last
(SE
.Actions_To_Be_Wrapped_Before
), L
);
3374 SE
.Actions_To_Be_Wrapped_Before
:= L
;
3376 if Is_List_Member
(SE
.Node_To_Be_Wrapped
) then
3377 Set_Parent
(L
, Parent
(SE
.Node_To_Be_Wrapped
));
3379 Set_Parent
(L
, SE
.Node_To_Be_Wrapped
);
3384 end Store_Before_Actions_In_Scope
;
3386 --------------------------------
3387 -- Wrap_Transient_Declaration --
3388 --------------------------------
3390 -- If a transient scope has been established during the processing of the
3391 -- Expression of an Object_Declaration, it is not possible to wrap the
3392 -- declaration into a transient block as usual case, otherwise the object
3393 -- would be itself declared in the wrong scope. Therefore, all entities (if
3394 -- any) defined in the transient block are moved to the proper enclosing
3395 -- scope, furthermore, if they are controlled variables they are finalized
3396 -- right after the declaration. The finalization list of the transient
3397 -- scope is defined as a renaming of the enclosing one so during their
3398 -- initialization they will be attached to the proper finalization
3399 -- list. For instance, the following declaration :
3401 -- X : Typ := F (G (A), G (B));
3403 -- (where G(A) and G(B) return controlled values, expanded as _v1 and _v2)
3404 -- is expanded into :
3406 -- _local_final_list_1 : Finalizable_Ptr;
3407 -- X : Typ := [ complex Expression-Action ];
3408 -- Finalize_One(_v1);
3409 -- Finalize_One (_v2);
3411 procedure Wrap_Transient_Declaration
(N
: Node_Id
) is
3413 LC
: Entity_Id
:= Empty
;
3415 Loc
: constant Source_Ptr
:= Sloc
(N
);
3416 First_Decl_Loc
: Source_Ptr
;
3417 Enclosing_S
: Entity_Id
;
3419 Next_N
: constant Node_Id
:= Next
(N
);
3423 Enclosing_S
:= Scope
(S
);
3425 -- Insert Actions kept in the Scope stack
3427 Insert_Actions_In_Scope_Around
(N
);
3429 -- If the declaration is consuming some secondary stack, mark the
3430 -- Enclosing scope appropriately.
3432 Uses_SS
:= Uses_Sec_Stack
(S
);
3435 -- Create a List controller and rename the final list to be its
3436 -- internal final pointer:
3437 -- Lxxx : Simple_List_Controller;
3438 -- Fxxx : Finalizable_Ptr renames Lxxx.F;
3440 if Present
(Finalization_Chain_Entity
(S
)) then
3441 LC
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('L'));
3443 -- Use the Sloc of the first declaration of N's containing list, to
3444 -- maintain monotonicity of source-line stepping during debugging.
3446 First_Decl_Loc
:= Sloc
(First
(List_Containing
(N
)));
3449 Make_Object_Declaration
(First_Decl_Loc
,
3450 Defining_Identifier
=> LC
,
3451 Object_Definition
=>
3453 (RTE
(RE_Simple_List_Controller
), First_Decl_Loc
)),
3455 Make_Object_Renaming_Declaration
(First_Decl_Loc
,
3456 Defining_Identifier
=> Finalization_Chain_Entity
(S
),
3458 New_Reference_To
(RTE
(RE_Finalizable_Ptr
), First_Decl_Loc
),
3460 Make_Selected_Component
(Loc
,
3461 Prefix
=> New_Reference_To
(LC
, First_Decl_Loc
),
3462 Selector_Name
=> Make_Identifier
(First_Decl_Loc
, Name_F
))));
3464 -- Put the declaration at the beginning of the declaration part
3465 -- to make sure it will be before all other actions that have been
3466 -- inserted before N.
3468 Insert_List_Before_And_Analyze
(First
(List_Containing
(N
)), Nodes
);
3470 -- Generate the Finalization calls by finalizing the list controller
3471 -- right away. It will be re-finalized on scope exit but it doesn't
3472 -- matter. It cannot be done when the call initializes a renaming
3473 -- object though because in this case, the object becomes a pointer
3474 -- to the temporary and thus increases its life span. Ditto if this
3475 -- is a renaming of a component of an expression (such as a function
3478 -- Note that there is a problem if an actual in the call needs
3479 -- finalization, because in that case the call itself is the master,
3480 -- and the actual should be finalized on return from the call ???
3482 if Nkind
(N
) = N_Object_Renaming_Declaration
3483 and then Needs_Finalization
(Etype
(Defining_Identifier
(N
)))
3487 elsif Nkind
(N
) = N_Object_Renaming_Declaration
3489 Nkind_In
(Renamed_Object
(Defining_Identifier
(N
)),
3490 N_Selected_Component
,
3491 N_Indexed_Component
)
3494 (Etype
(Prefix
(Renamed_Object
(Defining_Identifier
(N
)))))
3501 (Ref
=> New_Reference_To
(LC
, Loc
),
3503 With_Detach
=> New_Reference_To
(Standard_False
, Loc
));
3505 if Present
(Next_N
) then
3506 Insert_List_Before_And_Analyze
(Next_N
, Nodes
);
3508 Append_List_To
(List_Containing
(N
), Nodes
);
3513 -- Put the local entities back in the enclosing scope, and set the
3514 -- Is_Public flag appropriately.
3516 Transfer_Entities
(S
, Enclosing_S
);
3518 -- Mark the enclosing dynamic scope so that the sec stack will be
3519 -- released upon its exit unless this is a function that returns on
3520 -- the sec stack in which case this will be done by the caller.
3522 if VM_Target
= No_VM
and then Uses_SS
then
3523 S
:= Enclosing_Dynamic_Scope
(S
);
3525 if Ekind
(S
) = E_Function
3526 and then Requires_Transient_Scope
(Etype
(S
))
3530 Set_Uses_Sec_Stack
(S
);
3531 Check_Restriction
(No_Secondary_Stack
, N
);
3534 end Wrap_Transient_Declaration
;
3536 -------------------------------
3537 -- Wrap_Transient_Expression --
3538 -------------------------------
3540 -- Insert actions before <Expression>:
3542 -- (lines marked with <CTRL> are expanded only in presence of Controlled
3543 -- objects needing finalization)
3547 -- _M : constant Mark_Id := SS_Mark;
3548 -- Local_Final_List : System.FI.Finalizable_Ptr; <CTRL>
3550 -- procedure _Clean is
3553 -- System.FI.Finalize_List (Local_Final_List); <CTRL>
3559 -- _E := <Expression>;
3564 -- then expression is replaced by _E
3566 procedure Wrap_Transient_Expression
(N
: Node_Id
) is
3567 Loc
: constant Source_Ptr
:= Sloc
(N
);
3568 E
: constant Entity_Id
:= Make_Temporary
(Loc
, 'E', N
);
3569 Etyp
: constant Entity_Id
:= Etype
(N
);
3570 Expr
: constant Node_Id
:= Relocate_Node
(N
);
3573 -- If the relocated node is a function call then check if some SCIL
3574 -- node references it and needs readjustment.
3577 and then Nkind
(N
) = N_Function_Call
3579 Adjust_SCIL_Node
(N
, Expr
);
3582 Insert_Actions
(N
, New_List
(
3583 Make_Object_Declaration
(Loc
,
3584 Defining_Identifier
=> E
,
3585 Object_Definition
=> New_Reference_To
(Etyp
, Loc
)),
3587 Make_Transient_Block
(Loc
,
3589 Make_Assignment_Statement
(Loc
,
3590 Name
=> New_Reference_To
(E
, Loc
),
3591 Expression
=> Expr
))));
3593 Rewrite
(N
, New_Reference_To
(E
, Loc
));
3594 Analyze_And_Resolve
(N
, Etyp
);
3595 end Wrap_Transient_Expression
;
3597 ------------------------------
3598 -- Wrap_Transient_Statement --
3599 ------------------------------
3601 -- Transform <Instruction> into
3603 -- (lines marked with <CTRL> are expanded only in presence of Controlled
3604 -- objects needing finalization)
3607 -- _M : Mark_Id := SS_Mark;
3608 -- Local_Final_List : System.FI.Finalizable_Ptr ; <CTRL>
3610 -- procedure _Clean is
3613 -- System.FI.Finalize_List (Local_Final_List); <CTRL>
3624 procedure Wrap_Transient_Statement
(N
: Node_Id
) is
3625 Loc
: constant Source_Ptr
:= Sloc
(N
);
3626 New_Statement
: constant Node_Id
:= Relocate_Node
(N
);
3629 -- If the relocated node is a procedure call then check if some SCIL
3630 -- node references it and needs readjustment.
3633 and then Nkind
(New_Statement
) = N_Procedure_Call_Statement
3635 Adjust_SCIL_Node
(N
, New_Statement
);
3638 Rewrite
(N
, Make_Transient_Block
(Loc
, New_Statement
));
3640 -- With the scope stack back to normal, we can call analyze on the
3641 -- resulting block. At this point, the transient scope is being
3642 -- treated like a perfectly normal scope, so there is nothing
3643 -- special about it.
3645 -- Note: Wrap_Transient_Statement is called with the node already
3646 -- analyzed (i.e. Analyzed (N) is True). This is important, since
3647 -- otherwise we would get a recursive processing of the node when
3648 -- we do this Analyze call.
3651 end Wrap_Transient_Statement
;