1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2008, 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_Type
; use Sem_Type
;
58 with Sem_Util
; use Sem_Util
;
59 with Snames
; use Snames
;
60 with Stand
; use Stand
;
61 with Targparm
; use Targparm
;
62 with Tbuild
; use Tbuild
;
63 with Uintp
; use Uintp
;
65 package body Exp_Ch7
is
67 --------------------------------
68 -- Transient Scope Management --
69 --------------------------------
71 -- A transient scope is created when temporary objects are created by the
72 -- compiler. These temporary objects are allocated on the secondary stack
73 -- and the transient scope is responsible for finalizing the object when
74 -- appropriate and reclaiming the memory at the right time. The temporary
75 -- objects are generally the objects allocated to store the result of a
76 -- function returning an unconstrained or a tagged value. Expressions
77 -- needing to be wrapped in a transient scope (functions calls returning
78 -- unconstrained or tagged values) may appear in 3 different contexts which
79 -- lead to 3 different kinds of transient scope expansion:
81 -- 1. In a simple statement (procedure call, assignment, ...). In
82 -- this case the instruction is wrapped into a transient block.
83 -- (See Wrap_Transient_Statement for details)
85 -- 2. In an expression of a control structure (test in a IF statement,
86 -- expression in a CASE statement, ...).
87 -- (See Wrap_Transient_Expression for details)
89 -- 3. In a expression of an object_declaration. No wrapping is possible
90 -- here, so the finalization actions, if any, are done right after the
91 -- declaration and the secondary stack deallocation is done in the
92 -- proper enclosing scope (see Wrap_Transient_Declaration for details)
94 -- Note about functions returning tagged types: it has been decided to
95 -- always allocate their result in the secondary stack, even though is not
96 -- absolutely mandatory when the tagged type is constrained because the
97 -- caller knows the size of the returned object and thus could allocate the
98 -- result in the primary stack. An exception to this is when the function
99 -- builds its result in place, as is done for functions with inherently
100 -- limited result types for Ada 2005. In that case, certain callers may
101 -- pass the address of a constrained object as the target object for the
104 -- By allocating tagged results in the secondary stack a number of
105 -- implementation difficulties are avoided:
107 -- - If it is a dispatching function call, the computation of the size of
108 -- the result is possible but complex from the outside.
110 -- - If the returned type is controlled, the assignment of the returned
111 -- value to the anonymous object involves an Adjust, and we have no
112 -- easy way to access the anonymous object created by the back end.
114 -- - If the returned type is class-wide, this is an unconstrained type
117 -- Furthermore, the small loss in efficiency which is the result of this
118 -- decision is not such a big deal because functions returning tagged types
119 -- are not as common in practice compared to functions returning access to
122 --------------------------------------------------
123 -- Transient Blocks and Finalization Management --
124 --------------------------------------------------
126 function Find_Node_To_Be_Wrapped
(N
: Node_Id
) return Node_Id
;
127 -- N is a node which may generate a transient scope. Loop over the parent
128 -- pointers of N until it find the appropriate node to wrap. If it returns
129 -- Empty, it means that no transient scope is needed in this context.
138 Is_Protected_Subprogram
: Boolean;
139 Is_Task_Allocation_Block
: Boolean;
140 Is_Asynchronous_Call_Block
: Boolean;
141 Chained_Cleanup_Action
: Node_Id
) return Node_Id
;
142 -- Expand the clean-up procedure for a controlled and/or transient block,
143 -- and/or task master or task body, or a block used to implement task
144 -- allocation or asynchronous entry calls, or a procedure used to implement
145 -- protected procedures. Clean is the entity for such a procedure. Mark
146 -- is the entity for the secondary stack mark, if empty only controlled
147 -- block clean-up will be performed. Flist is the entity for the local
148 -- final list, if empty only transient scope clean-up will be performed.
149 -- The flags Is_Task and Is_Master control the calls to the corresponding
150 -- finalization actions for a task body or for an entity that is a task
151 -- master. Finally if Chained_Cleanup_Action is present, it is a reference
152 -- to a previous cleanup procedure, a call to which is appended at the
153 -- end of the generated one.
155 procedure Set_Node_To_Be_Wrapped
(N
: Node_Id
);
156 -- Set the field Node_To_Be_Wrapped of the current scope
158 procedure Insert_Actions_In_Scope_Around
(N
: Node_Id
);
159 -- Insert the before-actions kept in the scope stack before N, and the
160 -- after-actions after N, which must be a member of a list.
162 function Make_Transient_Block
164 Action
: Node_Id
) return Node_Id
;
165 -- Create a transient block whose name is Scope, which is also a controlled
166 -- block if Flist is not empty and whose only code is Action (either a
167 -- single statement or single declaration).
169 type Final_Primitives
is (Initialize_Case
, Adjust_Case
, Finalize_Case
);
170 -- This enumeration type is defined in order to ease sharing code for
171 -- building finalization procedures for composite types.
173 Name_Of
: constant array (Final_Primitives
) of Name_Id
:=
174 (Initialize_Case
=> Name_Initialize
,
175 Adjust_Case
=> Name_Adjust
,
176 Finalize_Case
=> Name_Finalize
);
178 Deep_Name_Of
: constant array (Final_Primitives
) of TSS_Name_Type
:=
179 (Initialize_Case
=> TSS_Deep_Initialize
,
180 Adjust_Case
=> TSS_Deep_Adjust
,
181 Finalize_Case
=> TSS_Deep_Finalize
);
183 procedure Build_Record_Deep_Procs
(Typ
: Entity_Id
);
184 -- Build the deep Initialize/Adjust/Finalize for a record Typ with
185 -- Has_Component_Component set and store them using the TSS mechanism.
187 procedure Build_Array_Deep_Procs
(Typ
: Entity_Id
);
188 -- Build the deep Initialize/Adjust/Finalize for a record Typ with
189 -- Has_Controlled_Component set and store them using the TSS mechanism.
191 function Make_Deep_Proc
192 (Prim
: Final_Primitives
;
194 Stmts
: List_Id
) return Node_Id
;
195 -- This function generates the tree for Deep_Initialize, Deep_Adjust or
196 -- Deep_Finalize procedures according to the first parameter, these
197 -- procedures operate on the type Typ. The Stmts parameter gives the body
200 function Make_Deep_Array_Body
201 (Prim
: Final_Primitives
;
202 Typ
: Entity_Id
) return List_Id
;
203 -- This function generates the list of statements for implementing
204 -- Deep_Initialize, Deep_Adjust or Deep_Finalize procedures according to
205 -- the first parameter, these procedures operate on the array type Typ.
207 function Make_Deep_Record_Body
208 (Prim
: Final_Primitives
;
209 Typ
: Entity_Id
) return List_Id
;
210 -- This function generates the list of statements for implementing
211 -- Deep_Initialize, Deep_Adjust or Deep_Finalize procedures according to
212 -- the first parameter, these procedures operate on the record type Typ.
214 procedure Check_Visibly_Controlled
215 (Prim
: Final_Primitives
;
217 E
: in out Entity_Id
;
218 Cref
: in out Node_Id
);
219 -- The controlled operation declared for a derived type may not be
220 -- overriding, if the controlled operations of the parent type are
221 -- hidden, for example when the parent is a private type whose full
222 -- view is controlled. For other primitive operations we modify the
223 -- name of the operation to indicate that it is not overriding, but
224 -- this is not possible for Initialize, etc. because they have to be
225 -- retrievable by name. Before generating the proper call to one of
226 -- these operations we check whether Typ is known to be controlled at
227 -- the point of definition. If it is not then we must retrieve the
228 -- hidden operation of the parent and use it instead. This is one
229 -- case that might be solved more cleanly once Overriding pragmas or
230 -- declarations are in place.
232 function Convert_View
235 Ind
: Pos
:= 1) return Node_Id
;
236 -- Proc is one of the Initialize/Adjust/Finalize operations, and
237 -- Arg is the argument being passed to it. Ind indicates which
238 -- formal of procedure Proc we are trying to match. This function
239 -- will, if necessary, generate an conversion between the partial
240 -- and full view of Arg to match the type of the formal of Proc,
241 -- or force a conversion to the class-wide type in the case where
242 -- the operation is abstract.
244 -----------------------------
245 -- Finalization Management --
246 -----------------------------
248 -- This part describe how Initialization/Adjustment/Finalization procedures
249 -- are generated and called. Two cases must be considered, types that are
250 -- Controlled (Is_Controlled flag set) and composite types that contain
251 -- controlled components (Has_Controlled_Component flag set). In the first
252 -- case the procedures to call are the user-defined primitive operations
253 -- Initialize/Adjust/Finalize. In the second case, GNAT generates
254 -- Deep_Initialize, Deep_Adjust and Deep_Finalize that are in charge
255 -- of calling the former procedures on the controlled components.
257 -- For records with Has_Controlled_Component set, a hidden "controller"
258 -- component is inserted. This controller component contains its own
259 -- finalization list on which all controlled components are attached
260 -- creating an indirection on the upper-level Finalization list. This
261 -- technique facilitates the management of objects whose number of
262 -- controlled components changes during execution. This controller
263 -- component is itself controlled and is attached to the upper-level
264 -- finalization chain. Its adjust primitive is in charge of calling adjust
265 -- on the components and adjusting the finalization pointer to match their
266 -- new location (see a-finali.adb).
268 -- It is not possible to use a similar technique for arrays that have
269 -- Has_Controlled_Component set. In this case, deep procedures are
270 -- generated that call initialize/adjust/finalize + attachment or
271 -- detachment on the finalization list for all component.
273 -- Initialize calls: they are generated for declarations or dynamic
274 -- allocations of Controlled objects with no initial value. They are always
275 -- followed by an attachment to the current Finalization Chain. For the
276 -- dynamic allocation case this the chain attached to the scope of the
277 -- access type definition otherwise, this is the chain of the current
280 -- Adjust Calls: They are generated on 2 occasions: (1) for
281 -- declarations or dynamic allocations of Controlled objects with an
282 -- initial value. (2) after an assignment. In the first case they are
283 -- followed by an attachment to the final chain, in the second case
286 -- Finalization Calls: They are generated on (1) scope exit, (2)
287 -- assignments, (3) unchecked deallocations. In case (3) they have to
288 -- be detached from the final chain, in case (2) they must not and in
289 -- case (1) this is not important since we are exiting the scope anyway.
293 -- Type extensions will have a new record controller at each derivation
294 -- level containing controlled components. The record controller for
295 -- the parent/ancestor is attached to the finalization list of the
296 -- extension's record controller (i.e. the parent is like a component
297 -- of the extension).
299 -- For types that are both Is_Controlled and Has_Controlled_Components,
300 -- the record controller and the object itself are handled separately.
301 -- It could seem simpler to attach the object at the end of its record
302 -- controller but this would not tackle view conversions properly.
304 -- A classwide type can always potentially have controlled components
305 -- but the record controller of the corresponding actual type may not
306 -- be known at compile time so the dispatch table contains a special
307 -- field that allows to compute the offset of the record controller
308 -- dynamically. See s-finimp.Deep_Tag_Attach and a-tags.RC_Offset.
310 -- Here is a simple example of the expansion of a controlled block :
314 -- Y : Controlled := Init;
320 -- Z : R := (C => X);
329 -- _L : System.FI.Finalizable_Ptr;
331 -- procedure _Clean is
334 -- System.FI.Finalize_List (_L);
342 -- Attach_To_Final_List (_L, Finalizable (X), 1);
343 -- at end: Abort_Undefer;
344 -- Y : Controlled := Init;
346 -- Attach_To_Final_List (_L, Finalizable (Y), 1);
349 -- _C : Record_Controller;
355 -- Deep_Initialize (W, _L, 1);
356 -- at end: Abort_Under;
357 -- Z : R := (C => X);
358 -- Deep_Adjust (Z, _L, 1);
362 -- Deep_Finalize (W, False);
363 -- <save W's final pointers>
365 -- <restore W's final pointers>
366 -- Deep_Adjust (W, _L, 0);
371 function Global_Flist_Ref
(Flist_Ref
: Node_Id
) return Boolean;
372 -- Return True if Flist_Ref refers to a global final list, either the
373 -- object Global_Final_List which is used to attach standalone objects,
374 -- or any of the list controllers associated with library-level access
375 -- to controlled objects.
377 procedure Clean_Simple_Protected_Objects
(N
: Node_Id
);
378 -- Protected objects without entries are not controlled types, and the
379 -- locks have to be released explicitly when such an object goes out
380 -- of scope. Traverse declarations in scope to determine whether such
381 -- objects are present.
383 ----------------------------
384 -- Build_Array_Deep_Procs --
385 ----------------------------
387 procedure Build_Array_Deep_Procs
(Typ
: Entity_Id
) is
391 Prim
=> Initialize_Case
,
393 Stmts
=> Make_Deep_Array_Body
(Initialize_Case
, Typ
)));
395 if not Is_Inherently_Limited_Type
(Typ
) then
400 Stmts
=> Make_Deep_Array_Body
(Adjust_Case
, Typ
)));
405 Prim
=> Finalize_Case
,
407 Stmts
=> Make_Deep_Array_Body
(Finalize_Case
, Typ
)));
408 end Build_Array_Deep_Procs
;
410 -----------------------------
411 -- Build_Controlling_Procs --
412 -----------------------------
414 procedure Build_Controlling_Procs
(Typ
: Entity_Id
) is
416 if Is_Array_Type
(Typ
) then
417 Build_Array_Deep_Procs
(Typ
);
419 else pragma Assert
(Is_Record_Type
(Typ
));
420 Build_Record_Deep_Procs
(Typ
);
422 end Build_Controlling_Procs
;
424 ----------------------
425 -- Build_Final_List --
426 ----------------------
428 procedure Build_Final_List
(N
: Node_Id
; Typ
: Entity_Id
) is
429 Loc
: constant Source_Ptr
:= Sloc
(N
);
433 Set_Associated_Final_Chain
(Typ
,
434 Make_Defining_Identifier
(Loc
,
435 New_External_Name
(Chars
(Typ
), 'L')));
438 Make_Object_Declaration
(Loc
,
439 Defining_Identifier
=>
440 Associated_Final_Chain
(Typ
),
443 (RTE
(RE_List_Controller
), Loc
));
445 -- The type may have been frozen already, and this is a late freezing
446 -- action, in which case the declaration must be elaborated at once.
447 -- If the call is for an allocator, the chain must also be created now,
448 -- because the freezing of the type does not build one. Otherwise, the
449 -- declaration is one of the freezing actions for a user-defined type.
452 or else (Nkind
(N
) = N_Allocator
453 and then Ekind
(Etype
(N
)) = E_Anonymous_Access_Type
)
455 Insert_Action
(N
, Decl
);
457 Append_Freeze_Action
(Typ
, Decl
);
459 end Build_Final_List
;
461 ---------------------
462 -- Build_Late_Proc --
463 ---------------------
465 procedure Build_Late_Proc
(Typ
: Entity_Id
; Nam
: Name_Id
) is
467 for Final_Prim
in Name_Of
'Range loop
468 if Name_Of
(Final_Prim
) = Nam
then
473 Stmts
=> Make_Deep_Record_Body
(Final_Prim
, Typ
)));
478 -----------------------------
479 -- Build_Record_Deep_Procs --
480 -----------------------------
482 procedure Build_Record_Deep_Procs
(Typ
: Entity_Id
) is
486 Prim
=> Initialize_Case
,
488 Stmts
=> Make_Deep_Record_Body
(Initialize_Case
, Typ
)));
490 if not Is_Inherently_Limited_Type
(Typ
) then
495 Stmts
=> Make_Deep_Record_Body
(Adjust_Case
, Typ
)));
500 Prim
=> Finalize_Case
,
502 Stmts
=> Make_Deep_Record_Body
(Finalize_Case
, Typ
)));
503 end Build_Record_Deep_Procs
;
509 function Cleanup_Array
512 Typ
: Entity_Id
) return List_Id
514 Loc
: constant Source_Ptr
:= Sloc
(N
);
515 Index_List
: constant List_Id
:= New_List
;
517 function Free_Component
return List_Id
;
518 -- Generate the code to finalize the task or protected subcomponents
519 -- of a single component of the array.
521 function Free_One_Dimension
(Dim
: Int
) return List_Id
;
522 -- Generate a loop over one dimension of the array
528 function Free_Component
return List_Id
is
529 Stmts
: List_Id
:= New_List
;
531 C_Typ
: constant Entity_Id
:= Component_Type
(Typ
);
534 -- Component type is known to contain tasks or protected objects
537 Make_Indexed_Component
(Loc
,
538 Prefix
=> Duplicate_Subexpr_No_Checks
(Obj
),
539 Expressions
=> Index_List
);
541 Set_Etype
(Tsk
, C_Typ
);
543 if Is_Task_Type
(C_Typ
) then
544 Append_To
(Stmts
, Cleanup_Task
(N
, Tsk
));
546 elsif Is_Simple_Protected_Type
(C_Typ
) then
547 Append_To
(Stmts
, Cleanup_Protected_Object
(N
, Tsk
));
549 elsif Is_Record_Type
(C_Typ
) then
550 Stmts
:= Cleanup_Record
(N
, Tsk
, C_Typ
);
552 elsif Is_Array_Type
(C_Typ
) then
553 Stmts
:= Cleanup_Array
(N
, Tsk
, C_Typ
);
559 ------------------------
560 -- Free_One_Dimension --
561 ------------------------
563 function Free_One_Dimension
(Dim
: Int
) return List_Id
is
567 if Dim
> Number_Dimensions
(Typ
) then
568 return Free_Component
;
570 -- Here we generate the required loop
574 Make_Defining_Identifier
(Loc
, New_Internal_Name
('J'));
576 Append
(New_Reference_To
(Index
, Loc
), Index_List
);
579 Make_Implicit_Loop_Statement
(N
,
582 Make_Iteration_Scheme
(Loc
,
583 Loop_Parameter_Specification
=>
584 Make_Loop_Parameter_Specification
(Loc
,
585 Defining_Identifier
=> Index
,
586 Discrete_Subtype_Definition
=>
587 Make_Attribute_Reference
(Loc
,
588 Prefix
=> Duplicate_Subexpr
(Obj
),
589 Attribute_Name
=> Name_Range
,
590 Expressions
=> New_List
(
591 Make_Integer_Literal
(Loc
, Dim
))))),
592 Statements
=> Free_One_Dimension
(Dim
+ 1)));
594 end Free_One_Dimension
;
596 -- Start of processing for Cleanup_Array
599 return Free_One_Dimension
(1);
606 function Cleanup_Record
609 Typ
: Entity_Id
) return List_Id
611 Loc
: constant Source_Ptr
:= Sloc
(N
);
614 Stmts
: constant List_Id
:= New_List
;
615 U_Typ
: constant Entity_Id
:= Underlying_Type
(Typ
);
618 if Has_Discriminants
(U_Typ
)
619 and then Nkind
(Parent
(U_Typ
)) = N_Full_Type_Declaration
621 Nkind
(Type_Definition
(Parent
(U_Typ
))) = N_Record_Definition
625 (Component_List
(Type_Definition
(Parent
(U_Typ
)))))
627 -- For now, do not attempt to free a component that may appear in
628 -- a variant, and instead issue a warning. Doing this "properly"
629 -- would require building a case statement and would be quite a
630 -- mess. Note that the RM only requires that free "work" for the
631 -- case of a task access value, so already we go way beyond this
632 -- in that we deal with the array case and non-discriminated
636 ("task/protected object in variant record will not be freed?", N
);
637 return New_List
(Make_Null_Statement
(Loc
));
640 Comp
:= First_Component
(Typ
);
642 while Present
(Comp
) loop
643 if Has_Task
(Etype
(Comp
))
644 or else Has_Simple_Protected_Object
(Etype
(Comp
))
647 Make_Selected_Component
(Loc
,
648 Prefix
=> Duplicate_Subexpr_No_Checks
(Obj
),
649 Selector_Name
=> New_Occurrence_Of
(Comp
, Loc
));
650 Set_Etype
(Tsk
, Etype
(Comp
));
652 if Is_Task_Type
(Etype
(Comp
)) then
653 Append_To
(Stmts
, Cleanup_Task
(N
, Tsk
));
655 elsif Is_Simple_Protected_Type
(Etype
(Comp
)) then
656 Append_To
(Stmts
, Cleanup_Protected_Object
(N
, Tsk
));
658 elsif Is_Record_Type
(Etype
(Comp
)) then
660 -- Recurse, by generating the prefix of the argument to
661 -- the eventual cleanup call.
664 (Stmts
, Cleanup_Record
(N
, Tsk
, Etype
(Comp
)));
666 elsif Is_Array_Type
(Etype
(Comp
)) then
668 (Stmts
, Cleanup_Array
(N
, Tsk
, Etype
(Comp
)));
672 Next_Component
(Comp
);
678 ------------------------------
679 -- Cleanup_Protected_Object --
680 ------------------------------
682 function Cleanup_Protected_Object
684 Ref
: Node_Id
) return Node_Id
686 Loc
: constant Source_Ptr
:= Sloc
(N
);
690 Make_Procedure_Call_Statement
(Loc
,
691 Name
=> New_Reference_To
(RTE
(RE_Finalize_Protection
), Loc
),
692 Parameter_Associations
=> New_List
(
693 Concurrent_Ref
(Ref
)));
694 end Cleanup_Protected_Object
;
696 ------------------------------------
697 -- Clean_Simple_Protected_Objects --
698 ------------------------------------
700 procedure Clean_Simple_Protected_Objects
(N
: Node_Id
) is
701 Stmts
: constant List_Id
:= Statements
(Handled_Statement_Sequence
(N
));
702 Stmt
: Node_Id
:= Last
(Stmts
);
706 E
:= First_Entity
(Current_Scope
);
707 while Present
(E
) loop
708 if (Ekind
(E
) = E_Variable
709 or else Ekind
(E
) = E_Constant
)
710 and then Has_Simple_Protected_Object
(Etype
(E
))
711 and then not Has_Task
(Etype
(E
))
712 and then Nkind
(Parent
(E
)) /= N_Object_Renaming_Declaration
715 Typ
: constant Entity_Id
:= Etype
(E
);
716 Ref
: constant Node_Id
:= New_Occurrence_Of
(E
, Sloc
(Stmt
));
719 if Is_Simple_Protected_Type
(Typ
) then
720 Append_To
(Stmts
, Cleanup_Protected_Object
(N
, Ref
));
722 elsif Has_Simple_Protected_Object
(Typ
) then
723 if Is_Record_Type
(Typ
) then
724 Append_List_To
(Stmts
, Cleanup_Record
(N
, Ref
, Typ
));
726 elsif Is_Array_Type
(Typ
) then
727 Append_List_To
(Stmts
, Cleanup_Array
(N
, Ref
, Typ
));
736 -- Analyze inserted cleanup statements
738 if Present
(Stmt
) then
741 while Present
(Stmt
) loop
746 end Clean_Simple_Protected_Objects
;
752 function Cleanup_Task
754 Ref
: Node_Id
) return Node_Id
756 Loc
: constant Source_Ptr
:= Sloc
(N
);
759 Make_Procedure_Call_Statement
(Loc
,
760 Name
=> New_Reference_To
(RTE
(RE_Free_Task
), Loc
),
761 Parameter_Associations
=>
762 New_List
(Concurrent_Ref
(Ref
)));
765 ---------------------------------
766 -- Has_Simple_Protected_Object --
767 ---------------------------------
769 function Has_Simple_Protected_Object
(T
: Entity_Id
) return Boolean is
773 if Is_Simple_Protected_Type
(T
) then
776 elsif Is_Array_Type
(T
) then
777 return Has_Simple_Protected_Object
(Component_Type
(T
));
779 elsif Is_Record_Type
(T
) then
780 Comp
:= First_Component
(T
);
782 while Present
(Comp
) loop
783 if Has_Simple_Protected_Object
(Etype
(Comp
)) then
787 Next_Component
(Comp
);
795 end Has_Simple_Protected_Object
;
797 ------------------------------
798 -- Is_Simple_Protected_Type --
799 ------------------------------
801 function Is_Simple_Protected_Type
(T
: Entity_Id
) return Boolean is
803 return Is_Protected_Type
(T
) and then not Has_Entries
(T
);
804 end Is_Simple_Protected_Type
;
806 ------------------------------
807 -- Check_Visibly_Controlled --
808 ------------------------------
810 procedure Check_Visibly_Controlled
811 (Prim
: Final_Primitives
;
813 E
: in out Entity_Id
;
814 Cref
: in out Node_Id
)
816 Parent_Type
: Entity_Id
;
820 if Is_Derived_Type
(Typ
)
821 and then Comes_From_Source
(E
)
822 and then not Is_Overriding_Operation
(E
)
824 -- We know that the explicit operation on the type does not override
825 -- the inherited operation of the parent, and that the derivation
826 -- is from a private type that is not visibly controlled.
828 Parent_Type
:= Etype
(Typ
);
829 Op
:= Find_Prim_Op
(Parent_Type
, Name_Of
(Prim
));
834 -- Wrap the object to be initialized into the proper
835 -- unchecked conversion, to be compatible with the operation
838 if Nkind
(Cref
) = N_Unchecked_Type_Conversion
then
839 Cref
:= Unchecked_Convert_To
(Parent_Type
, Expression
(Cref
));
841 Cref
:= Unchecked_Convert_To
(Parent_Type
, Cref
);
845 end Check_Visibly_Controlled
;
847 -------------------------------
848 -- CW_Or_Has_Controlled_Part --
849 -------------------------------
851 function CW_Or_Has_Controlled_Part
(T
: Entity_Id
) return Boolean is
853 return Is_Class_Wide_Type
(T
) or else Needs_Finalization
(T
);
854 end CW_Or_Has_Controlled_Part
;
856 --------------------------
857 -- Controller_Component --
858 --------------------------
860 function Controller_Component
(Typ
: Entity_Id
) return Entity_Id
is
861 T
: Entity_Id
:= Base_Type
(Typ
);
863 Comp_Scop
: Entity_Id
;
864 Res
: Entity_Id
:= Empty
;
865 Res_Scop
: Entity_Id
:= Empty
;
868 if Is_Class_Wide_Type
(T
) then
872 if Is_Private_Type
(T
) then
873 T
:= Underlying_Type
(T
);
876 -- Fetch the outermost controller
878 Comp
:= First_Entity
(T
);
879 while Present
(Comp
) loop
880 if Chars
(Comp
) = Name_uController
then
881 Comp_Scop
:= Scope
(Original_Record_Component
(Comp
));
883 -- If this controller is at the outermost level, no need to
884 -- look for another one
886 if Comp_Scop
= T
then
889 -- Otherwise record the outermost one and continue looking
891 elsif Res
= Empty
or else Is_Ancestor
(Res_Scop
, Comp_Scop
) then
893 Res_Scop
:= Comp_Scop
;
900 -- If we fall through the loop, there is no controller component
903 end Controller_Component
;
909 function Convert_View
912 Ind
: Pos
:= 1) return Node_Id
914 Fent
: Entity_Id
:= First_Entity
(Proc
);
919 for J
in 2 .. Ind
loop
923 Ftyp
:= Etype
(Fent
);
925 if Nkind_In
(Arg
, N_Type_Conversion
, N_Unchecked_Type_Conversion
) then
926 Atyp
:= Entity
(Subtype_Mark
(Arg
));
931 if Is_Abstract_Subprogram
(Proc
) and then Is_Tagged_Type
(Ftyp
) then
932 return Unchecked_Convert_To
(Class_Wide_Type
(Ftyp
), Arg
);
935 and then Present
(Atyp
)
937 (Is_Private_Type
(Ftyp
) or else Is_Private_Type
(Atyp
))
939 Base_Type
(Underlying_Type
(Atyp
)) =
940 Base_Type
(Underlying_Type
(Ftyp
))
942 return Unchecked_Convert_To
(Ftyp
, Arg
);
944 -- If the argument is already a conversion, as generated by
945 -- Make_Init_Call, set the target type to the type of the formal
946 -- directly, to avoid spurious typing problems.
948 elsif Nkind_In
(Arg
, N_Unchecked_Type_Conversion
, N_Type_Conversion
)
949 and then not Is_Class_Wide_Type
(Atyp
)
951 Set_Subtype_Mark
(Arg
, New_Occurrence_Of
(Ftyp
, Sloc
(Arg
)));
952 Set_Etype
(Arg
, Ftyp
);
960 -------------------------------
961 -- Establish_Transient_Scope --
962 -------------------------------
964 -- This procedure is called each time a transient block has to be inserted
965 -- that is to say for each call to a function with unconstrained or tagged
966 -- result. It creates a new scope on the stack scope in order to enclose
967 -- all transient variables generated
969 procedure Establish_Transient_Scope
(N
: Node_Id
; Sec_Stack
: Boolean) is
970 Loc
: constant Source_Ptr
:= Sloc
(N
);
974 -- Nothing to do for virtual machines where memory is GCed
976 if VM_Target
/= No_VM
then
980 -- Do not create a transient scope if we are already inside one
982 for S
in reverse Scope_Stack
.First
.. Scope_Stack
.Last
loop
983 if Scope_Stack
.Table
(S
).Is_Transient
then
985 Set_Uses_Sec_Stack
(Scope_Stack
.Table
(S
).Entity
);
990 -- If we have encountered Standard there are no enclosing
993 elsif Scope_Stack
.Table
(S
).Entity
= Standard_Standard
then
999 Wrap_Node
:= Find_Node_To_Be_Wrapped
(N
);
1001 -- Case of no wrap node, false alert, no transient scope needed
1003 if No
(Wrap_Node
) then
1006 -- If the node to wrap is an iteration_scheme, the expression is
1007 -- one of the bounds, and the expansion will make an explicit
1008 -- declaration for it (see Analyze_Iteration_Scheme, sem_ch5.adb),
1009 -- so do not apply any transformations here.
1011 elsif Nkind
(Wrap_Node
) = N_Iteration_Scheme
then
1015 Push_Scope
(New_Internal_Entity
(E_Block
, Current_Scope
, Loc
, 'B'));
1016 Set_Scope_Is_Transient
;
1019 Set_Uses_Sec_Stack
(Current_Scope
);
1020 Check_Restriction
(No_Secondary_Stack
, N
);
1023 Set_Etype
(Current_Scope
, Standard_Void_Type
);
1024 Set_Node_To_Be_Wrapped
(Wrap_Node
);
1026 if Debug_Flag_W
then
1027 Write_Str
(" <Transient>");
1031 end Establish_Transient_Scope
;
1033 ----------------------------
1034 -- Expand_Cleanup_Actions --
1035 ----------------------------
1037 procedure Expand_Cleanup_Actions
(N
: Node_Id
) is
1038 S
: constant Entity_Id
:= Current_Scope
;
1039 Flist
: constant Entity_Id
:= Finalization_Chain_Entity
(S
);
1040 Is_Task
: constant Boolean := Nkind
(Original_Node
(N
)) = N_Task_Body
;
1042 Is_Master
: constant Boolean :=
1043 Nkind
(N
) /= N_Entry_Body
1044 and then Is_Task_Master
(N
);
1045 Is_Protected
: constant Boolean :=
1046 Nkind
(N
) = N_Subprogram_Body
1047 and then Is_Protected_Subprogram_Body
(N
);
1048 Is_Task_Allocation
: constant Boolean :=
1049 Nkind
(N
) = N_Block_Statement
1050 and then Is_Task_Allocation_Block
(N
);
1051 Is_Asynchronous_Call
: constant Boolean :=
1052 Nkind
(N
) = N_Block_Statement
1053 and then Is_Asynchronous_Call_Block
(N
);
1055 Previous_At_End_Proc
: constant Node_Id
:=
1056 At_End_Proc
(Handled_Statement_Sequence
(N
));
1060 Mark
: Entity_Id
:= Empty
;
1061 New_Decls
: constant List_Id
:= New_List
;
1065 Chain
: Entity_Id
:= Empty
;
1070 -- If we are generating expanded code for debugging purposes, use
1071 -- the Sloc of the point of insertion for the cleanup code. The Sloc
1072 -- will be updated subsequently to reference the proper line in the
1073 -- .dg file. If we are not debugging generated code, use instead
1074 -- No_Location, so that no debug information is generated for the
1075 -- cleanup code. This makes the behavior of the NEXT command in GDB
1076 -- monotonic, and makes the placement of breakpoints more accurate.
1078 if Debug_Generated_Code
then
1084 -- There are cleanup actions only if the secondary stack needs
1085 -- releasing or some finalizations are needed or in the context
1088 if Uses_Sec_Stack
(Current_Scope
)
1089 and then not Sec_Stack_Needed_For_Return
(Current_Scope
)
1093 and then not Is_Master
1094 and then not Is_Task
1095 and then not Is_Protected
1096 and then not Is_Task_Allocation
1097 and then not Is_Asynchronous_Call
1099 Clean_Simple_Protected_Objects
(N
);
1103 -- If the current scope is the subprogram body that is the rewriting
1104 -- of a task body, and the descriptors have not been delayed (due to
1105 -- some nested instantiations) do not generate redundant cleanup
1106 -- actions: the cleanup procedure already exists for this body.
1108 if Nkind
(N
) = N_Subprogram_Body
1109 and then Nkind
(Original_Node
(N
)) = N_Task_Body
1110 and then not Delay_Subprogram_Descriptors
(Corresponding_Spec
(N
))
1115 -- Set polling off, since we don't need to poll during cleanup
1116 -- actions, and indeed for the cleanup routine, which is executed
1117 -- with aborts deferred, we don't want polling.
1119 Old_Poll
:= Polling_Required
;
1120 Polling_Required
:= False;
1122 -- Make sure we have a declaration list, since we will add to it
1124 if No
(Declarations
(N
)) then
1125 Set_Declarations
(N
, New_List
);
1128 -- The task activation call has already been built for task
1129 -- allocation blocks.
1131 if not Is_Task_Allocation
then
1132 Build_Task_Activation_Call
(N
);
1136 Establish_Task_Master
(N
);
1139 -- If secondary stack is in use, expand:
1140 -- _Mxx : constant Mark_Id := SS_Mark;
1142 -- Suppress calls to SS_Mark and SS_Release if VM_Target,
1143 -- since we never use the secondary stack on the VM.
1145 if Uses_Sec_Stack
(Current_Scope
)
1146 and then not Sec_Stack_Needed_For_Return
(Current_Scope
)
1147 and then VM_Target
= No_VM
1149 Mark
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('M'));
1150 Append_To
(New_Decls
,
1151 Make_Object_Declaration
(Loc
,
1152 Defining_Identifier
=> Mark
,
1153 Object_Definition
=> New_Reference_To
(RTE
(RE_Mark_Id
), Loc
),
1155 Make_Function_Call
(Loc
,
1156 Name
=> New_Reference_To
(RTE
(RE_SS_Mark
), Loc
))));
1158 Set_Uses_Sec_Stack
(Current_Scope
, False);
1161 -- If finalization list is present then expand:
1162 -- Local_Final_List : System.FI.Finalizable_Ptr;
1164 if Present
(Flist
) then
1165 Append_To
(New_Decls
,
1166 Make_Object_Declaration
(Loc
,
1167 Defining_Identifier
=> Flist
,
1168 Object_Definition
=>
1169 New_Reference_To
(RTE
(RE_Finalizable_Ptr
), Loc
)));
1172 -- Clean-up procedure definition
1174 Clean
:= Make_Defining_Identifier
(Loc
, Name_uClean
);
1175 Set_Suppress_Elaboration_Warnings
(Clean
);
1176 Append_To
(New_Decls
,
1177 Make_Clean
(N
, Clean
, Mark
, Flist
,
1182 Is_Asynchronous_Call
,
1183 Previous_At_End_Proc
));
1185 -- The previous AT END procedure, if any, has been captured in Clean:
1186 -- reset it to Empty now because we check further on that we never
1187 -- overwrite an existing AT END call.
1189 Set_At_End_Proc
(Handled_Statement_Sequence
(N
), Empty
);
1191 -- If exception handlers are present, wrap the Sequence of statements in
1192 -- a block because it is not possible to get exception handlers and an
1193 -- AT END call in the same scope.
1195 if Present
(Exception_Handlers
(Handled_Statement_Sequence
(N
))) then
1197 -- Preserve end label to provide proper cross-reference information
1199 End_Lab
:= End_Label
(Handled_Statement_Sequence
(N
));
1201 Make_Block_Statement
(Loc
,
1202 Handled_Statement_Sequence
=> Handled_Statement_Sequence
(N
));
1203 Set_Handled_Statement_Sequence
(N
,
1204 Make_Handled_Sequence_Of_Statements
(Loc
, New_List
(Blok
)));
1205 Set_End_Label
(Handled_Statement_Sequence
(N
), End_Lab
);
1208 -- Comment needed here, see RH for 1.306 ???
1210 if Nkind
(N
) = N_Subprogram_Body
then
1211 Set_Has_Nested_Block_With_Handler
(Current_Scope
);
1214 -- Otherwise we do not wrap
1221 -- Don't move the _chain Activation_Chain declaration in task
1222 -- allocation blocks. Task allocation blocks use this object
1223 -- in their cleanup handlers, and gigi complains if it is declared
1224 -- in the sequence of statements of the scope that declares the
1227 if Is_Task_Allocation
then
1228 Chain
:= Activation_Chain_Entity
(N
);
1230 Decl
:= First
(Declarations
(N
));
1231 while Nkind
(Decl
) /= N_Object_Declaration
1232 or else Defining_Identifier
(Decl
) /= Chain
1235 pragma Assert
(Present
(Decl
));
1239 Prepend_To
(New_Decls
, Decl
);
1242 -- Now we move the declarations into the Sequence of statements
1243 -- in order to get them protected by the AT END call. It may seem
1244 -- weird to put declarations in the sequence of statement but in
1245 -- fact nothing forbids that at the tree level. We also set the
1246 -- First_Real_Statement field so that we remember where the real
1247 -- statements (i.e. original statements) begin. Note that if we
1248 -- wrapped the statements, the first real statement is inside the
1249 -- inner block. If the First_Real_Statement is already set (as is
1250 -- the case for subprogram bodies that are expansions of task bodies)
1251 -- then do not reset it, because its declarative part would migrate
1252 -- to the statement part.
1255 if No
(First_Real_Statement
(Handled_Statement_Sequence
(N
))) then
1256 Set_First_Real_Statement
(Handled_Statement_Sequence
(N
),
1257 First
(Statements
(Handled_Statement_Sequence
(N
))));
1261 Set_First_Real_Statement
(Handled_Statement_Sequence
(N
), Blok
);
1264 Append_List_To
(Declarations
(N
),
1265 Statements
(Handled_Statement_Sequence
(N
)));
1266 Set_Statements
(Handled_Statement_Sequence
(N
), Declarations
(N
));
1268 -- We need to reset the Sloc of the handled statement sequence to
1269 -- properly reflect the new initial "statement" in the sequence.
1272 (Handled_Statement_Sequence
(N
), Sloc
(First
(Declarations
(N
))));
1274 -- The declarations of the _Clean procedure and finalization chain
1275 -- replace the old declarations that have been moved inward.
1277 Set_Declarations
(N
, New_Decls
);
1278 Analyze_Declarations
(New_Decls
);
1280 -- The At_End call is attached to the sequence of statements
1286 -- If the construct is a protected subprogram, then the call to
1287 -- the corresponding unprotected subprogram appears in a block which
1288 -- is the last statement in the body, and it is this block that must
1289 -- be covered by the At_End handler.
1291 if Is_Protected
then
1292 HSS
:= Handled_Statement_Sequence
1293 (Last
(Statements
(Handled_Statement_Sequence
(N
))));
1295 HSS
:= Handled_Statement_Sequence
(N
);
1298 -- Never overwrite an existing AT END call
1300 pragma Assert
(No
(At_End_Proc
(HSS
)));
1302 Set_At_End_Proc
(HSS
, New_Occurrence_Of
(Clean
, Loc
));
1303 Expand_At_End_Handler
(HSS
, Empty
);
1306 -- Restore saved polling mode
1308 Polling_Required
:= Old_Poll
;
1309 end Expand_Cleanup_Actions
;
1311 -------------------------------
1312 -- Expand_Ctrl_Function_Call --
1313 -------------------------------
1315 procedure Expand_Ctrl_Function_Call
(N
: Node_Id
) is
1316 Loc
: constant Source_Ptr
:= Sloc
(N
);
1317 Rtype
: constant Entity_Id
:= Etype
(N
);
1318 Utype
: constant Entity_Id
:= Underlying_Type
(Rtype
);
1321 Action2
: Node_Id
:= Empty
;
1323 Attach_Level
: Uint
:= Uint_1
;
1324 Len_Ref
: Node_Id
:= Empty
;
1326 function Last_Array_Component
1328 Typ
: Entity_Id
) return Node_Id
;
1329 -- Creates a reference to the last component of the array object
1330 -- designated by Ref whose type is Typ.
1332 --------------------------
1333 -- Last_Array_Component --
1334 --------------------------
1336 function Last_Array_Component
1338 Typ
: Entity_Id
) return Node_Id
1340 Index_List
: constant List_Id
:= New_List
;
1343 for N
in 1 .. Number_Dimensions
(Typ
) loop
1344 Append_To
(Index_List
,
1345 Make_Attribute_Reference
(Loc
,
1346 Prefix
=> Duplicate_Subexpr_No_Checks
(Ref
),
1347 Attribute_Name
=> Name_Last
,
1348 Expressions
=> New_List
(
1349 Make_Integer_Literal
(Loc
, N
))));
1353 Make_Indexed_Component
(Loc
,
1354 Prefix
=> Duplicate_Subexpr
(Ref
),
1355 Expressions
=> Index_List
);
1356 end Last_Array_Component
;
1358 -- Start of processing for Expand_Ctrl_Function_Call
1361 -- Optimization, if the returned value (which is on the sec-stack) is
1362 -- returned again, no need to copy/readjust/finalize, we can just pass
1363 -- the value thru (see Expand_N_Simple_Return_Statement), and thus no
1364 -- attachment is needed
1366 if Nkind
(Parent
(N
)) = N_Simple_Return_Statement
then
1370 -- Resolution is now finished, make sure we don't start analysis again
1371 -- because of the duplication.
1374 Ref
:= Duplicate_Subexpr_No_Checks
(N
);
1376 -- Now we can generate the Attach Call. Note that this value is always
1377 -- on the (secondary) stack and thus is attached to a singly linked
1380 -- Resx := F (X)'reference;
1381 -- Attach_To_Final_List (_Lx, Resx.all, 1);
1383 -- or when there are controlled components:
1385 -- Attach_To_Final_List (_Lx, Resx._controller, 1);
1387 -- or when it is both Is_Controlled and Has_Controlled_Components:
1389 -- Attach_To_Final_List (_Lx, Resx._controller, 1);
1390 -- Attach_To_Final_List (_Lx, Resx, 1);
1392 -- or if it is an array with Is_Controlled (and Has_Controlled)
1394 -- Attach_To_Final_List (_Lx, Resx (Resx'last), 3);
1396 -- An attach level of 3 means that a whole array is to be attached to
1397 -- the finalization list (including the controlled components).
1399 -- or if it is an array with Has_Controlled_Components but not
1402 -- Attach_To_Final_List (_Lx, Resx (Resx'last)._controller, 3);
1404 -- Case where type has controlled components
1406 if Has_Controlled_Component
(Rtype
) then
1408 T1
: Entity_Id
:= Rtype
;
1409 T2
: Entity_Id
:= Utype
;
1412 if Is_Array_Type
(T2
) then
1414 Make_Attribute_Reference
(Loc
,
1416 Duplicate_Subexpr_Move_Checks
1417 (Unchecked_Convert_To
(T2
, Ref
)),
1418 Attribute_Name
=> Name_Length
);
1421 while Is_Array_Type
(T2
) loop
1423 Ref
:= Unchecked_Convert_To
(T2
, Ref
);
1426 Ref
:= Last_Array_Component
(Ref
, T2
);
1427 Attach_Level
:= Uint_3
;
1428 T1
:= Component_Type
(T2
);
1429 T2
:= Underlying_Type
(T1
);
1432 -- If the type has controlled components, go to the controller
1433 -- except in the case of arrays of controlled objects since in
1434 -- this case objects and their components are already chained
1435 -- and the head of the chain is the last array element.
1437 if Is_Array_Type
(Rtype
) and then Is_Controlled
(T2
) then
1440 elsif Has_Controlled_Component
(T2
) then
1442 Ref
:= Unchecked_Convert_To
(T2
, Ref
);
1446 Make_Selected_Component
(Loc
,
1448 Selector_Name
=> Make_Identifier
(Loc
, Name_uController
));
1452 -- Here we know that 'Ref' has a controller so we may as well attach
1458 Flist_Ref
=> Find_Final_List
(Current_Scope
),
1459 With_Attach
=> Make_Integer_Literal
(Loc
, Attach_Level
));
1461 -- If it is also Is_Controlled we need to attach the global object
1463 if Is_Controlled
(Rtype
) then
1466 Obj_Ref
=> Duplicate_Subexpr_No_Checks
(N
),
1467 Flist_Ref
=> Find_Final_List
(Current_Scope
),
1468 With_Attach
=> Make_Integer_Literal
(Loc
, Attach_Level
));
1471 -- Here, we have a controlled type that does not seem to have controlled
1472 -- components but it could be a class wide type whose further
1473 -- derivations have controlled components. So we don't know if the
1474 -- object itself needs to be attached or if it has a record controller.
1475 -- We need to call a runtime function (Deep_Tag_Attach) which knows what
1476 -- to do thanks to the RC_Offset in the dispatch table.
1480 Make_Procedure_Call_Statement
(Loc
,
1481 Name
=> New_Reference_To
(RTE
(RE_Deep_Tag_Attach
), Loc
),
1482 Parameter_Associations
=> New_List
(
1483 Find_Final_List
(Current_Scope
),
1485 Make_Attribute_Reference
(Loc
,
1487 Attribute_Name
=> Name_Address
),
1489 Make_Integer_Literal
(Loc
, Attach_Level
)));
1492 if Present
(Len_Ref
) then
1494 Make_Implicit_If_Statement
(N
,
1495 Condition
=> Make_Op_Gt
(Loc
,
1496 Left_Opnd
=> Len_Ref
,
1497 Right_Opnd
=> Make_Integer_Literal
(Loc
, 0)),
1498 Then_Statements
=> New_List
(Action
));
1501 Insert_Action
(N
, Action
);
1502 if Present
(Action2
) then
1503 Insert_Action
(N
, Action2
);
1505 end Expand_Ctrl_Function_Call
;
1507 ---------------------------
1508 -- Expand_N_Package_Body --
1509 ---------------------------
1511 -- Add call to Activate_Tasks if body is an activator (actual processing
1512 -- is in chapter 9).
1514 -- Generate subprogram descriptor for elaboration routine
1516 -- Encode entity names in package body
1518 procedure Expand_N_Package_Body
(N
: Node_Id
) is
1519 Ent
: constant Entity_Id
:= Corresponding_Spec
(N
);
1522 -- This is done only for non-generic packages
1524 if Ekind
(Ent
) = E_Package
then
1525 Push_Scope
(Corresponding_Spec
(N
));
1527 -- Build dispatch tables of library level tagged types
1529 if Is_Library_Level_Entity
(Ent
) then
1530 Build_Static_Dispatch_Tables
(N
);
1533 Build_Task_Activation_Call
(N
);
1537 Set_Elaboration_Flag
(N
, Corresponding_Spec
(N
));
1538 Set_In_Package_Body
(Ent
, False);
1540 -- Set to encode entity names in package body before gigi is called
1542 Qualify_Entity_Names
(N
);
1543 end Expand_N_Package_Body
;
1545 ----------------------------------
1546 -- Expand_N_Package_Declaration --
1547 ----------------------------------
1549 -- Add call to Activate_Tasks if there are tasks declared and the package
1550 -- has no body. Note that in Ada83, this may result in premature activation
1551 -- of some tasks, given that we cannot tell whether a body will eventually
1554 procedure Expand_N_Package_Declaration
(N
: Node_Id
) is
1555 Spec
: constant Node_Id
:= Specification
(N
);
1556 Id
: constant Entity_Id
:= Defining_Entity
(N
);
1558 No_Body
: Boolean := False;
1559 -- True in the case of a package declaration that is a compilation unit
1560 -- and for which no associated body will be compiled in
1561 -- this compilation.
1564 -- Case of a package declaration other than a compilation unit
1566 if Nkind
(Parent
(N
)) /= N_Compilation_Unit
then
1569 -- Case of a compilation unit that does not require a body
1571 elsif not Body_Required
(Parent
(N
))
1572 and then not Unit_Requires_Body
(Id
)
1576 -- Special case of generating calling stubs for a remote call interface
1577 -- package: even though the package declaration requires one, the
1578 -- body won't be processed in this compilation (so any stubs for RACWs
1579 -- declared in the package must be generated here, along with the
1582 elsif Parent
(N
) = Cunit
(Main_Unit
)
1583 and then Is_Remote_Call_Interface
(Id
)
1584 and then Distribution_Stub_Mode
= Generate_Caller_Stub_Body
1589 -- For a package declaration that implies no associated body, generate
1590 -- task activation call and RACW supporting bodies now (since we won't
1591 -- have a specific separate compilation unit for that).
1596 if Has_RACW
(Id
) then
1598 -- Generate RACW subprogram bodies
1600 Decls
:= Private_Declarations
(Spec
);
1603 Decls
:= Visible_Declarations
(Spec
);
1608 Set_Visible_Declarations
(Spec
, Decls
);
1611 Append_RACW_Bodies
(Decls
, Id
);
1612 Analyze_List
(Decls
);
1615 if Present
(Activation_Chain_Entity
(N
)) then
1617 -- Generate task activation call as last step of elaboration
1619 Build_Task_Activation_Call
(N
);
1625 -- Build dispatch tables of library level tagged types
1627 if Is_Compilation_Unit
(Id
)
1628 or else (Is_Generic_Instance
(Id
)
1629 and then Is_Library_Level_Entity
(Id
))
1631 Build_Static_Dispatch_Tables
(N
);
1634 -- Note: it is not necessary to worry about generating a subprogram
1635 -- descriptor, since the only way to get exception handlers into a
1636 -- package spec is to include instantiations, and that would cause
1637 -- generation of subprogram descriptors to be delayed in any case.
1639 -- Set to encode entity names in package spec before gigi is called
1641 Qualify_Entity_Names
(N
);
1642 end Expand_N_Package_Declaration
;
1644 ---------------------
1645 -- Find_Final_List --
1646 ---------------------
1648 function Find_Final_List
1650 Ref
: Node_Id
:= Empty
) return Node_Id
1652 Loc
: constant Source_Ptr
:= Sloc
(Ref
);
1658 -- If the restriction No_Finalization applies, then there's not any
1659 -- finalization list available to return, so return Empty.
1661 if Restriction_Active
(No_Finalization
) then
1664 -- Case of an internal component. The Final list is the record
1665 -- controller of the enclosing record.
1667 elsif Present
(Ref
) then
1671 when N_Unchecked_Type_Conversion | N_Type_Conversion
=>
1672 R
:= Expression
(R
);
1674 when N_Indexed_Component | N_Explicit_Dereference
=>
1677 when N_Selected_Component
=>
1681 when N_Identifier
=>
1685 raise Program_Error
;
1690 Make_Selected_Component
(Loc
,
1692 Make_Selected_Component
(Loc
,
1694 Selector_Name
=> Make_Identifier
(Loc
, Name_uController
)),
1695 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
1697 -- Case of a dynamically allocated object whose access type has an
1698 -- Associated_Final_Chain. The final list is the corresponding list
1699 -- controller (the next entity in the scope of the access type with
1700 -- the right type). If the type comes from a With_Type clause, no
1701 -- controller was created, we use the global chain instead. (The code
1702 -- related to with_type clauses should presumably be removed at some
1703 -- point since that feature is obsolete???)
1705 -- An anonymous access type either has a list created for it when the
1706 -- allocator is a for an access parameter or an access discriminant,
1707 -- or else it uses the list of the enclosing dynamic scope, when the
1708 -- context is a declaration or an assignment.
1710 elsif Is_Access_Type
(E
)
1711 and then (Present
(Associated_Final_Chain
(E
))
1712 or else From_With_Type
(E
))
1714 if From_With_Type
(E
) then
1715 return New_Reference_To
(RTE
(RE_Global_Final_List
), Sloc
(E
));
1717 -- Use the access type's associated finalization chain
1721 Make_Selected_Component
(Loc
,
1724 (Associated_Final_Chain
(Base_Type
(E
)), Loc
),
1725 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
1729 if Is_Dynamic_Scope
(E
) then
1732 S
:= Enclosing_Dynamic_Scope
(E
);
1735 -- When the finalization chain entity is 'Error', it means that there
1736 -- should not be any chain at that level and that the enclosing one
1739 -- This is a nasty kludge, see ??? note in exp_ch11
1741 while Finalization_Chain_Entity
(S
) = Error
loop
1742 S
:= Enclosing_Dynamic_Scope
(S
);
1745 if S
= Standard_Standard
then
1746 return New_Reference_To
(RTE
(RE_Global_Final_List
), Sloc
(E
));
1748 if No
(Finalization_Chain_Entity
(S
)) then
1750 -- In the case where the scope is a subprogram, retrieve the
1751 -- Sloc of subprogram's body for association with the chain,
1752 -- since using the Sloc of the spec would be confusing during
1753 -- source-line stepping within the debugger.
1756 Flist_Loc
: Source_Ptr
:= Sloc
(S
);
1757 Subp_Body
: Node_Id
;
1760 if Ekind
(S
) in Subprogram_Kind
then
1761 Subp_Body
:= Unit_Declaration_Node
(S
);
1763 if Nkind
(Subp_Body
) /= N_Subprogram_Body
then
1764 Subp_Body
:= Corresponding_Body
(Subp_Body
);
1767 if Present
(Subp_Body
) then
1768 Flist_Loc
:= Sloc
(Subp_Body
);
1773 Make_Defining_Identifier
(Flist_Loc
,
1774 Chars
=> New_Internal_Name
('F'));
1777 Set_Finalization_Chain_Entity
(S
, Id
);
1779 -- Set momentarily some semantics attributes to allow normal
1780 -- analysis of expansions containing references to this chain.
1781 -- Will be fully decorated during the expansion of the scope
1784 Set_Ekind
(Id
, E_Variable
);
1785 Set_Etype
(Id
, RTE
(RE_Finalizable_Ptr
));
1788 return New_Reference_To
(Finalization_Chain_Entity
(S
), Sloc
(E
));
1791 end Find_Final_List
;
1793 -----------------------------
1794 -- Find_Node_To_Be_Wrapped --
1795 -----------------------------
1797 function Find_Node_To_Be_Wrapped
(N
: Node_Id
) return Node_Id
is
1799 The_Parent
: Node_Id
;
1805 pragma Assert
(P
/= Empty
);
1806 The_Parent
:= Parent
(P
);
1808 case Nkind
(The_Parent
) is
1810 -- Simple statement can be wrapped
1815 -- Usually assignments are good candidate for wrapping
1816 -- except when they have been generated as part of a
1817 -- controlled aggregate where the wrapping should take
1818 -- place more globally.
1820 when N_Assignment_Statement
=>
1821 if No_Ctrl_Actions
(The_Parent
) then
1827 -- An entry call statement is a special case if it occurs in
1828 -- the context of a Timed_Entry_Call. In this case we wrap
1829 -- the entire timed entry call.
1831 when N_Entry_Call_Statement |
1832 N_Procedure_Call_Statement
=>
1833 if Nkind
(Parent
(The_Parent
)) = N_Entry_Call_Alternative
1834 and then Nkind_In
(Parent
(Parent
(The_Parent
)),
1836 N_Conditional_Entry_Call
)
1838 return Parent
(Parent
(The_Parent
));
1843 -- Object declarations are also a boundary for the transient scope
1844 -- even if they are not really wrapped
1845 -- (see Wrap_Transient_Declaration)
1847 when N_Object_Declaration |
1848 N_Object_Renaming_Declaration |
1849 N_Subtype_Declaration
=>
1852 -- The expression itself is to be wrapped if its parent is a
1853 -- compound statement or any other statement where the expression
1854 -- is known to be scalar
1856 when N_Accept_Alternative |
1857 N_Attribute_Definition_Clause |
1860 N_Delay_Alternative |
1861 N_Delay_Until_Statement |
1862 N_Delay_Relative_Statement |
1863 N_Discriminant_Association |
1865 N_Entry_Body_Formal_Part |
1868 N_Iteration_Scheme |
1869 N_Terminate_Alternative
=>
1872 when N_Attribute_Reference
=>
1874 if Is_Procedure_Attribute_Name
1875 (Attribute_Name
(The_Parent
))
1880 -- A raise statement can be wrapped. This will arise when the
1881 -- expression in a raise_with_expression uses the secondary
1882 -- stack, for example.
1884 when N_Raise_Statement
=>
1887 -- If the expression is within the iteration scheme of a loop,
1888 -- we must create a declaration for it, followed by an assignment
1889 -- in order to have a usable statement to wrap.
1891 when N_Loop_Parameter_Specification
=>
1892 return Parent
(The_Parent
);
1894 -- The following nodes contains "dummy calls" which don't
1895 -- need to be wrapped.
1897 when N_Parameter_Specification |
1898 N_Discriminant_Specification |
1899 N_Component_Declaration
=>
1902 -- The return statement is not to be wrapped when the function
1903 -- itself needs wrapping at the outer-level
1905 when N_Simple_Return_Statement
=>
1907 Applies_To
: constant Entity_Id
:=
1909 (Return_Statement_Entity
(The_Parent
));
1910 Return_Type
: constant Entity_Id
:= Etype
(Applies_To
);
1912 if Requires_Transient_Scope
(Return_Type
) then
1919 -- If we leave a scope without having been able to find a node to
1920 -- wrap, something is going wrong but this can happen in error
1921 -- situation that are not detected yet (such as a dynamic string
1922 -- in a pragma export)
1924 when N_Subprogram_Body |
1925 N_Package_Declaration |
1927 N_Block_Statement
=>
1930 -- otherwise continue the search
1936 end Find_Node_To_Be_Wrapped
;
1938 ----------------------
1939 -- Global_Flist_Ref --
1940 ----------------------
1942 function Global_Flist_Ref
(Flist_Ref
: Node_Id
) return Boolean is
1946 -- Look for the Global_Final_List
1948 if Is_Entity_Name
(Flist_Ref
) then
1949 Flist
:= Entity
(Flist_Ref
);
1951 -- Look for the final list associated with an access to controlled
1953 elsif Nkind
(Flist_Ref
) = N_Selected_Component
1954 and then Is_Entity_Name
(Prefix
(Flist_Ref
))
1956 Flist
:= Entity
(Prefix
(Flist_Ref
));
1961 return Present
(Flist
)
1962 and then Present
(Scope
(Flist
))
1963 and then Enclosing_Dynamic_Scope
(Flist
) = Standard_Standard
;
1964 end Global_Flist_Ref
;
1966 ----------------------------------
1967 -- Has_New_Controlled_Component --
1968 ----------------------------------
1970 function Has_New_Controlled_Component
(E
: Entity_Id
) return Boolean is
1974 if not Is_Tagged_Type
(E
) then
1975 return Has_Controlled_Component
(E
);
1976 elsif not Is_Derived_Type
(E
) then
1977 return Has_Controlled_Component
(E
);
1980 Comp
:= First_Component
(E
);
1981 while Present
(Comp
) loop
1983 if Chars
(Comp
) = Name_uParent
then
1986 elsif Scope
(Original_Record_Component
(Comp
)) = E
1987 and then Needs_Finalization
(Etype
(Comp
))
1992 Next_Component
(Comp
);
1996 end Has_New_Controlled_Component
;
1998 --------------------------
1999 -- In_Finalization_Root --
2000 --------------------------
2002 -- It would seem simpler to test Scope (RTE (RE_Root_Controlled)) but
2003 -- the purpose of this function is to avoid a circular call to Rtsfind
2004 -- which would been caused by such a test.
2006 function In_Finalization_Root
(E
: Entity_Id
) return Boolean is
2007 S
: constant Entity_Id
:= Scope
(E
);
2010 return Chars
(Scope
(S
)) = Name_System
2011 and then Chars
(S
) = Name_Finalization_Root
2012 and then Scope
(Scope
(S
)) = Standard_Standard
;
2013 end In_Finalization_Root
;
2015 ------------------------------------
2016 -- Insert_Actions_In_Scope_Around --
2017 ------------------------------------
2019 procedure Insert_Actions_In_Scope_Around
(N
: Node_Id
) is
2020 SE
: Scope_Stack_Entry
renames Scope_Stack
.Table
(Scope_Stack
.Last
);
2024 -- If the node to be wrapped is the triggering statement of an
2025 -- asynchronous select, it is not part of a statement list. The
2026 -- actions must be inserted before the Select itself, which is
2027 -- part of some list of statements. Note that the triggering
2028 -- alternative includes the triggering statement and an optional
2029 -- statement list. If the node to be wrapped is part of that list,
2030 -- the normal insertion applies.
2032 if Nkind
(Parent
(Node_To_Be_Wrapped
)) = N_Triggering_Alternative
2033 and then not Is_List_Member
(Node_To_Be_Wrapped
)
2035 Target
:= Parent
(Parent
(Node_To_Be_Wrapped
));
2040 if Present
(SE
.Actions_To_Be_Wrapped_Before
) then
2041 Insert_List_Before
(Target
, SE
.Actions_To_Be_Wrapped_Before
);
2042 SE
.Actions_To_Be_Wrapped_Before
:= No_List
;
2045 if Present
(SE
.Actions_To_Be_Wrapped_After
) then
2046 Insert_List_After
(Target
, SE
.Actions_To_Be_Wrapped_After
);
2047 SE
.Actions_To_Be_Wrapped_After
:= No_List
;
2049 end Insert_Actions_In_Scope_Around
;
2051 -----------------------
2052 -- Make_Adjust_Call --
2053 -----------------------
2055 function Make_Adjust_Call
2058 Flist_Ref
: Node_Id
;
2059 With_Attach
: Node_Id
;
2060 Allocator
: Boolean := False) return List_Id
2062 Loc
: constant Source_Ptr
:= Sloc
(Ref
);
2063 Res
: constant List_Id
:= New_List
;
2066 Cref
: Node_Id
:= Ref
;
2068 Attach
: Node_Id
:= With_Attach
;
2071 if Is_Class_Wide_Type
(Typ
) then
2072 Utyp
:= Underlying_Type
(Base_Type
(Root_Type
(Typ
)));
2074 Utyp
:= Underlying_Type
(Base_Type
(Typ
));
2077 Set_Assignment_OK
(Cref
);
2079 -- Deal with non-tagged derivation of private views
2081 if Is_Untagged_Derivation
(Typ
) then
2082 Utyp
:= Underlying_Type
(Root_Type
(Base_Type
(Typ
)));
2083 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
2084 Set_Assignment_OK
(Cref
);
2085 -- To prevent problems with UC see 1.156 RH ???
2088 -- If the underlying_type is a subtype, we are dealing with
2089 -- the completion of a private type. We need to access
2090 -- the base type and generate a conversion to it.
2092 if Utyp
/= Base_Type
(Utyp
) then
2093 pragma Assert
(Is_Private_Type
(Typ
));
2094 Utyp
:= Base_Type
(Utyp
);
2095 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
2098 -- If the object is unanalyzed, set its expected type for use
2099 -- in Convert_View in case an additional conversion is needed.
2101 if No
(Etype
(Cref
))
2102 and then Nkind
(Cref
) /= N_Unchecked_Type_Conversion
2104 Set_Etype
(Cref
, Typ
);
2107 -- We do not need to attach to one of the Global Final Lists
2108 -- the objects whose type is Finalize_Storage_Only
2110 if Finalize_Storage_Only
(Typ
)
2111 and then (Global_Flist_Ref
(Flist_Ref
)
2112 or else Entity
(Constant_Value
(RTE
(RE_Garbage_Collected
)))
2115 Attach
:= Make_Integer_Literal
(Loc
, 0);
2118 -- Special case for allocators: need initialization of the chain
2119 -- pointers. For the 0 case, reset them to null.
2122 pragma Assert
(Nkind
(Attach
) = N_Integer_Literal
);
2124 if Intval
(Attach
) = 0 then
2125 Set_Intval
(Attach
, Uint_4
);
2130 -- Deep_Adjust (Flist_Ref, Ref, Attach);
2132 if Has_Controlled_Component
(Utyp
)
2133 or else Is_Class_Wide_Type
(Typ
)
2135 if Is_Tagged_Type
(Utyp
) then
2136 Proc
:= Find_Prim_Op
(Utyp
, TSS_Deep_Adjust
);
2139 Proc
:= TSS
(Utyp
, TSS_Deep_Adjust
);
2142 Cref
:= Convert_View
(Proc
, Cref
, 2);
2145 Make_Procedure_Call_Statement
(Loc
,
2146 Name
=> New_Reference_To
(Proc
, Loc
),
2147 Parameter_Associations
=>
2148 New_List
(Flist_Ref
, Cref
, Attach
)));
2151 -- if With_Attach then
2152 -- Attach_To_Final_List (Ref, Flist_Ref);
2156 else -- Is_Controlled (Utyp)
2158 Proc
:= Find_Prim_Op
(Utyp
, Name_Of
(Adjust_Case
));
2159 Cref
:= Convert_View
(Proc
, Cref
);
2160 Cref2
:= New_Copy_Tree
(Cref
);
2163 Make_Procedure_Call_Statement
(Loc
,
2164 Name
=> New_Reference_To
(Proc
, Loc
),
2165 Parameter_Associations
=> New_List
(Cref2
)));
2167 Append_To
(Res
, Make_Attach_Call
(Cref
, Flist_Ref
, Attach
));
2171 end Make_Adjust_Call
;
2173 ----------------------
2174 -- Make_Attach_Call --
2175 ----------------------
2178 -- System.FI.Attach_To_Final_List (Flist, Ref, Nb_Link)
2180 function Make_Attach_Call
2182 Flist_Ref
: Node_Id
;
2183 With_Attach
: Node_Id
) return Node_Id
2185 Loc
: constant Source_Ptr
:= Sloc
(Obj_Ref
);
2188 -- Optimization: If the number of links is statically '0', don't
2189 -- call the attach_proc.
2191 if Nkind
(With_Attach
) = N_Integer_Literal
2192 and then Intval
(With_Attach
) = Uint_0
2194 return Make_Null_Statement
(Loc
);
2198 Make_Procedure_Call_Statement
(Loc
,
2199 Name
=> New_Reference_To
(RTE
(RE_Attach_To_Final_List
), Loc
),
2200 Parameter_Associations
=> New_List
(
2202 OK_Convert_To
(RTE
(RE_Finalizable
), Obj_Ref
),
2204 end Make_Attach_Call
;
2216 Is_Master
: Boolean;
2217 Is_Protected_Subprogram
: Boolean;
2218 Is_Task_Allocation_Block
: Boolean;
2219 Is_Asynchronous_Call_Block
: Boolean;
2220 Chained_Cleanup_Action
: Node_Id
) return Node_Id
2222 Loc
: constant Source_Ptr
:= Sloc
(Clean
);
2223 Stmt
: constant List_Id
:= New_List
;
2229 Param_Type
: Entity_Id
;
2230 Pid
: Entity_Id
:= Empty
;
2231 Cancel_Param
: Entity_Id
;
2235 if Restricted_Profile
then
2237 (Stmt
, Build_Runtime_Call
(Loc
, RE_Complete_Restricted_Task
));
2239 Append_To
(Stmt
, Build_Runtime_Call
(Loc
, RE_Complete_Task
));
2242 elsif Is_Master
then
2243 if Restriction_Active
(No_Task_Hierarchy
) = False then
2244 Append_To
(Stmt
, Build_Runtime_Call
(Loc
, RE_Complete_Master
));
2247 elsif Is_Protected_Subprogram
then
2249 -- Add statements to the cleanup handler of the (ordinary)
2250 -- subprogram expanded to implement a protected subprogram,
2251 -- unlocking the protected object parameter and undeferring abort.
2252 -- If this is a protected procedure, and the object contains
2253 -- entries, this also calls the entry service routine.
2255 -- NOTE: This cleanup handler references _object, a parameter
2256 -- to the procedure.
2258 -- Find the _object parameter representing the protected object
2260 Spec
:= Parent
(Corresponding_Spec
(N
));
2262 Param
:= First
(Parameter_Specifications
(Spec
));
2264 Param_Type
:= Etype
(Parameter_Type
(Param
));
2266 if Ekind
(Param_Type
) = E_Record_Type
then
2267 Pid
:= Corresponding_Concurrent_Type
(Param_Type
);
2270 exit when No
(Param
) or else Present
(Pid
);
2274 pragma Assert
(Present
(Param
));
2276 -- If the associated protected object declares entries,
2277 -- a protected procedure has to service entry queues.
2278 -- In this case, add
2280 -- Service_Entries (_object._object'Access);
2282 -- _object is the record used to implement the protected object.
2283 -- It is a parameter to the protected subprogram.
2285 if Nkind
(Specification
(N
)) = N_Procedure_Specification
2286 and then Has_Entries
(Pid
)
2288 case Corresponding_Runtime_Package
(Pid
) is
2289 when System_Tasking_Protected_Objects_Entries
=>
2290 Name
:= New_Reference_To
(RTE
(RE_Service_Entries
), Loc
);
2292 when System_Tasking_Protected_Objects_Single_Entry
=>
2293 Name
:= New_Reference_To
(RTE
(RE_Service_Entry
), Loc
);
2296 raise Program_Error
;
2300 Make_Procedure_Call_Statement
(Loc
,
2302 Parameter_Associations
=> New_List
(
2303 Make_Attribute_Reference
(Loc
,
2305 Make_Selected_Component
(Loc
,
2306 Prefix
=> New_Reference_To
(
2307 Defining_Identifier
(Param
), Loc
),
2309 Make_Identifier
(Loc
, Name_uObject
)),
2310 Attribute_Name
=> Name_Unchecked_Access
))));
2313 -- Unlock (_object._object'Access);
2315 -- object is the record used to implement the protected object.
2316 -- It is a parameter to the protected subprogram.
2318 case Corresponding_Runtime_Package
(Pid
) is
2319 when System_Tasking_Protected_Objects_Entries
=>
2320 Name
:= New_Reference_To
(RTE
(RE_Unlock_Entries
), Loc
);
2322 when System_Tasking_Protected_Objects_Single_Entry
=>
2323 Name
:= New_Reference_To
(RTE
(RE_Unlock_Entry
), Loc
);
2325 when System_Tasking_Protected_Objects
=>
2326 Name
:= New_Reference_To
(RTE
(RE_Unlock
), Loc
);
2329 raise Program_Error
;
2333 Make_Procedure_Call_Statement
(Loc
,
2335 Parameter_Associations
=> New_List
(
2336 Make_Attribute_Reference
(Loc
,
2338 Make_Selected_Component
(Loc
,
2340 New_Reference_To
(Defining_Identifier
(Param
), Loc
),
2342 Make_Identifier
(Loc
, Name_uObject
)),
2343 Attribute_Name
=> Name_Unchecked_Access
))));
2346 if Abort_Allowed
then
2351 Make_Procedure_Call_Statement
(Loc
,
2354 RTE
(RE_Abort_Undefer
), Loc
),
2355 Parameter_Associations
=> Empty_List
));
2358 elsif Is_Task_Allocation_Block
then
2360 -- Add a call to Expunge_Unactivated_Tasks to the cleanup
2361 -- handler of a block created for the dynamic allocation of
2364 -- Expunge_Unactivated_Tasks (_chain);
2366 -- where _chain is the list of tasks created by the allocator
2367 -- but not yet activated. This list will be empty unless
2368 -- the block completes abnormally.
2370 -- This only applies to dynamically allocated tasks;
2371 -- other unactivated tasks are completed by Complete_Task or
2374 -- NOTE: This cleanup handler references _chain, a local
2378 Make_Procedure_Call_Statement
(Loc
,
2381 RTE
(RE_Expunge_Unactivated_Tasks
), Loc
),
2382 Parameter_Associations
=> New_List
(
2383 New_Reference_To
(Activation_Chain_Entity
(N
), Loc
))));
2385 elsif Is_Asynchronous_Call_Block
then
2387 -- Add a call to attempt to cancel the asynchronous entry call
2388 -- whenever the block containing the abortable part is exited.
2390 -- NOTE: This cleanup handler references C, a local object
2392 -- Get the argument to the Cancel procedure
2393 Cancel_Param
:= Entry_Cancel_Parameter
(Entity
(Identifier
(N
)));
2395 -- If it is of type Communication_Block, this must be a
2396 -- protected entry call.
2398 if Is_RTE
(Etype
(Cancel_Param
), RE_Communication_Block
) then
2402 -- if Enqueued (Cancel_Parameter) then
2404 Make_Implicit_If_Statement
(Clean
,
2405 Condition
=> Make_Function_Call
(Loc
,
2406 Name
=> New_Reference_To
(
2407 RTE
(RE_Enqueued
), Loc
),
2408 Parameter_Associations
=> New_List
(
2409 New_Reference_To
(Cancel_Param
, Loc
))),
2410 Then_Statements
=> New_List
(
2412 -- Cancel_Protected_Entry_Call (Cancel_Param);
2414 Make_Procedure_Call_Statement
(Loc
,
2415 Name
=> New_Reference_To
(
2416 RTE
(RE_Cancel_Protected_Entry_Call
), Loc
),
2417 Parameter_Associations
=> New_List
(
2418 New_Reference_To
(Cancel_Param
, Loc
))))));
2420 -- Asynchronous delay
2422 elsif Is_RTE
(Etype
(Cancel_Param
), RE_Delay_Block
) then
2424 Make_Procedure_Call_Statement
(Loc
,
2425 Name
=> New_Reference_To
(RTE
(RE_Cancel_Async_Delay
), Loc
),
2426 Parameter_Associations
=> New_List
(
2427 Make_Attribute_Reference
(Loc
,
2428 Prefix
=> New_Reference_To
(Cancel_Param
, Loc
),
2429 Attribute_Name
=> Name_Unchecked_Access
))));
2434 -- Append call to Cancel_Task_Entry_Call (C);
2437 Make_Procedure_Call_Statement
(Loc
,
2438 Name
=> New_Reference_To
(
2439 RTE
(RE_Cancel_Task_Entry_Call
),
2441 Parameter_Associations
=> New_List
(
2442 New_Reference_To
(Cancel_Param
, Loc
))));
2447 if Present
(Flist
) then
2449 Make_Procedure_Call_Statement
(Loc
,
2450 Name
=> New_Reference_To
(RTE
(RE_Finalize_List
), Loc
),
2451 Parameter_Associations
=> New_List
(
2452 New_Reference_To
(Flist
, Loc
))));
2455 if Present
(Mark
) then
2457 Make_Procedure_Call_Statement
(Loc
,
2458 Name
=> New_Reference_To
(RTE
(RE_SS_Release
), Loc
),
2459 Parameter_Associations
=> New_List
(
2460 New_Reference_To
(Mark
, Loc
))));
2463 if Present
(Chained_Cleanup_Action
) then
2465 Make_Procedure_Call_Statement
(Loc
,
2466 Name
=> Chained_Cleanup_Action
));
2470 Make_Subprogram_Body
(Loc
,
2472 Make_Procedure_Specification
(Loc
,
2473 Defining_Unit_Name
=> Clean
),
2475 Declarations
=> New_List
,
2477 Handled_Statement_Sequence
=>
2478 Make_Handled_Sequence_Of_Statements
(Loc
,
2479 Statements
=> Stmt
));
2481 if Present
(Flist
) or else Is_Task
or else Is_Master
then
2482 Wrap_Cleanup_Procedure
(Sbody
);
2485 -- We do not want debug information for _Clean routines,
2486 -- since it just confuses the debugging operation unless
2487 -- we are debugging generated code.
2489 if not Debug_Generated_Code
then
2490 Set_Debug_Info_Off
(Clean
, True);
2496 --------------------------
2497 -- Make_Deep_Array_Body --
2498 --------------------------
2500 -- Array components are initialized and adjusted in the normal order
2501 -- and finalized in the reverse order. Exceptions are handled and
2502 -- Program_Error is re-raise in the Adjust and Finalize case
2503 -- (RM 7.6.1(12)). Generate the following code :
2505 -- procedure Deep_<P> -- with <P> being Initialize or Adjust or Finalize
2506 -- (L : in out Finalizable_Ptr;
2510 -- for J1 in Typ'First (1) .. Typ'Last (1) loop
2511 -- ^ reverse ^ -- in the finalization case
2513 -- for J2 in Typ'First (n) .. Typ'Last (n) loop
2514 -- Make_<P>_Call (Typ, V (J1, .. , Jn), L, V);
2518 -- exception -- not in the
2519 -- when others => raise Program_Error; -- Initialize case
2522 function Make_Deep_Array_Body
2523 (Prim
: Final_Primitives
;
2524 Typ
: Entity_Id
) return List_Id
2526 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
2528 Index_List
: constant List_Id
:= New_List
;
2529 -- Stores the list of references to the indexes (one per dimension)
2531 function One_Component
return List_Id
;
2532 -- Create one statement to initialize/adjust/finalize one array
2533 -- component, designated by a full set of indices.
2535 function One_Dimension
(N
: Int
) return List_Id
;
2536 -- Create loop to deal with one dimension of the array. The single
2537 -- statement in the body of the loop initializes the inner dimensions if
2538 -- any, or else a single component.
2544 function One_Component
return List_Id
is
2545 Comp_Typ
: constant Entity_Id
:= Component_Type
(Typ
);
2546 Comp_Ref
: constant Node_Id
:=
2547 Make_Indexed_Component
(Loc
,
2548 Prefix
=> Make_Identifier
(Loc
, Name_V
),
2549 Expressions
=> Index_List
);
2552 -- Set the etype of the component Reference, which is used to
2553 -- determine whether a conversion to a parent type is needed.
2555 Set_Etype
(Comp_Ref
, Comp_Typ
);
2558 when Initialize_Case
=>
2559 return Make_Init_Call
(Comp_Ref
, Comp_Typ
,
2560 Make_Identifier
(Loc
, Name_L
),
2561 Make_Identifier
(Loc
, Name_B
));
2564 return Make_Adjust_Call
(Comp_Ref
, Comp_Typ
,
2565 Make_Identifier
(Loc
, Name_L
),
2566 Make_Identifier
(Loc
, Name_B
));
2568 when Finalize_Case
=>
2569 return Make_Final_Call
(Comp_Ref
, Comp_Typ
,
2570 Make_Identifier
(Loc
, Name_B
));
2578 function One_Dimension
(N
: Int
) return List_Id
is
2582 if N
> Number_Dimensions
(Typ
) then
2583 return One_Component
;
2587 Make_Defining_Identifier
(Loc
, New_External_Name
('J', N
));
2589 Append_To
(Index_List
, New_Reference_To
(Index
, Loc
));
2592 Make_Implicit_Loop_Statement
(Typ
,
2593 Identifier
=> Empty
,
2595 Make_Iteration_Scheme
(Loc
,
2596 Loop_Parameter_Specification
=>
2597 Make_Loop_Parameter_Specification
(Loc
,
2598 Defining_Identifier
=> Index
,
2599 Discrete_Subtype_Definition
=>
2600 Make_Attribute_Reference
(Loc
,
2601 Prefix
=> Make_Identifier
(Loc
, Name_V
),
2602 Attribute_Name
=> Name_Range
,
2603 Expressions
=> New_List
(
2604 Make_Integer_Literal
(Loc
, N
))),
2605 Reverse_Present
=> Prim
= Finalize_Case
)),
2606 Statements
=> One_Dimension
(N
+ 1)));
2610 -- Start of processing for Make_Deep_Array_Body
2613 return One_Dimension
(1);
2614 end Make_Deep_Array_Body
;
2616 --------------------
2617 -- Make_Deep_Proc --
2618 --------------------
2621 -- procedure DEEP_<prim>
2622 -- (L : IN OUT Finalizable_Ptr; -- not for Finalize
2623 -- V : IN OUT <typ>;
2624 -- B : IN Short_Short_Integer) is
2627 -- exception -- Finalize and Adjust Cases only
2628 -- raise Program_Error; -- idem
2631 function Make_Deep_Proc
2632 (Prim
: Final_Primitives
;
2634 Stmts
: List_Id
) return Entity_Id
2636 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
2638 Proc_Name
: Entity_Id
;
2639 Handler
: List_Id
:= No_List
;
2643 if Prim
= Finalize_Case
then
2644 Formals
:= New_List
;
2645 Type_B
:= Standard_Boolean
;
2648 Formals
:= New_List
(
2649 Make_Parameter_Specification
(Loc
,
2650 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_L
),
2652 Out_Present
=> True,
2654 New_Reference_To
(RTE
(RE_Finalizable_Ptr
), Loc
)));
2655 Type_B
:= Standard_Short_Short_Integer
;
2659 Make_Parameter_Specification
(Loc
,
2660 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_V
),
2662 Out_Present
=> True,
2663 Parameter_Type
=> New_Reference_To
(Typ
, Loc
)));
2666 Make_Parameter_Specification
(Loc
,
2667 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_B
),
2668 Parameter_Type
=> New_Reference_To
(Type_B
, Loc
)));
2670 if Prim
= Finalize_Case
or else Prim
= Adjust_Case
then
2671 Handler
:= New_List
(Make_Handler_For_Ctrl_Operation
(Loc
));
2675 Make_Defining_Identifier
(Loc
,
2676 Chars
=> Make_TSS_Name
(Typ
, Deep_Name_Of
(Prim
)));
2679 Make_Subprogram_Body
(Loc
,
2681 Make_Procedure_Specification
(Loc
,
2682 Defining_Unit_Name
=> Proc_Name
,
2683 Parameter_Specifications
=> Formals
),
2685 Declarations
=> Empty_List
,
2686 Handled_Statement_Sequence
=>
2687 Make_Handled_Sequence_Of_Statements
(Loc
,
2688 Statements
=> Stmts
,
2689 Exception_Handlers
=> Handler
)));
2694 ---------------------------
2695 -- Make_Deep_Record_Body --
2696 ---------------------------
2698 -- The Deep procedures call the appropriate Controlling proc on the
2699 -- the controller component. In the init case, it also attach the
2700 -- controller to the current finalization list.
2702 function Make_Deep_Record_Body
2703 (Prim
: Final_Primitives
;
2704 Typ
: Entity_Id
) return List_Id
2706 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
2707 Controller_Typ
: Entity_Id
;
2708 Obj_Ref
: constant Node_Id
:= Make_Identifier
(Loc
, Name_V
);
2709 Controller_Ref
: constant Node_Id
:=
2710 Make_Selected_Component
(Loc
,
2713 Make_Identifier
(Loc
, Name_uController
));
2714 Res
: constant List_Id
:= New_List
;
2717 if Is_Inherently_Limited_Type
(Typ
) then
2718 Controller_Typ
:= RTE
(RE_Limited_Record_Controller
);
2720 Controller_Typ
:= RTE
(RE_Record_Controller
);
2724 when Initialize_Case
=>
2725 Append_List_To
(Res
,
2727 Ref
=> Controller_Ref
,
2728 Typ
=> Controller_Typ
,
2729 Flist_Ref
=> Make_Identifier
(Loc
, Name_L
),
2730 With_Attach
=> Make_Identifier
(Loc
, Name_B
)));
2732 -- When the type is also a controlled type by itself,
2733 -- initialize it and attach it to the finalization chain.
2735 if Is_Controlled
(Typ
) then
2737 Make_Procedure_Call_Statement
(Loc
,
2738 Name
=> New_Reference_To
(
2739 Find_Prim_Op
(Typ
, Name_Of
(Prim
)), Loc
),
2740 Parameter_Associations
=>
2741 New_List
(New_Copy_Tree
(Obj_Ref
))));
2743 Append_To
(Res
, Make_Attach_Call
(
2744 Obj_Ref
=> New_Copy_Tree
(Obj_Ref
),
2745 Flist_Ref
=> Make_Identifier
(Loc
, Name_L
),
2746 With_Attach
=> Make_Identifier
(Loc
, Name_B
)));
2750 Append_List_To
(Res
,
2751 Make_Adjust_Call
(Controller_Ref
, Controller_Typ
,
2752 Make_Identifier
(Loc
, Name_L
),
2753 Make_Identifier
(Loc
, Name_B
)));
2755 -- When the type is also a controlled type by itself,
2756 -- adjust it and attach it to the finalization chain.
2758 if Is_Controlled
(Typ
) then
2760 Make_Procedure_Call_Statement
(Loc
,
2761 Name
=> New_Reference_To
(
2762 Find_Prim_Op
(Typ
, Name_Of
(Prim
)), Loc
),
2763 Parameter_Associations
=>
2764 New_List
(New_Copy_Tree
(Obj_Ref
))));
2766 Append_To
(Res
, Make_Attach_Call
(
2767 Obj_Ref
=> New_Copy_Tree
(Obj_Ref
),
2768 Flist_Ref
=> Make_Identifier
(Loc
, Name_L
),
2769 With_Attach
=> Make_Identifier
(Loc
, Name_B
)));
2772 when Finalize_Case
=>
2773 if Is_Controlled
(Typ
) then
2775 Make_Implicit_If_Statement
(Obj_Ref
,
2776 Condition
=> Make_Identifier
(Loc
, Name_B
),
2777 Then_Statements
=> New_List
(
2778 Make_Procedure_Call_Statement
(Loc
,
2779 Name
=> New_Reference_To
(RTE
(RE_Finalize_One
), Loc
),
2780 Parameter_Associations
=> New_List
(
2781 OK_Convert_To
(RTE
(RE_Finalizable
),
2782 New_Copy_Tree
(Obj_Ref
))))),
2784 Else_Statements
=> New_List
(
2785 Make_Procedure_Call_Statement
(Loc
,
2786 Name
=> New_Reference_To
(
2787 Find_Prim_Op
(Typ
, Name_Of
(Prim
)), Loc
),
2788 Parameter_Associations
=>
2789 New_List
(New_Copy_Tree
(Obj_Ref
))))));
2792 Append_List_To
(Res
,
2793 Make_Final_Call
(Controller_Ref
, Controller_Typ
,
2794 Make_Identifier
(Loc
, Name_B
)));
2797 end Make_Deep_Record_Body
;
2799 ----------------------
2800 -- Make_Final_Call --
2801 ----------------------
2803 function Make_Final_Call
2806 With_Detach
: Node_Id
) return List_Id
2808 Loc
: constant Source_Ptr
:= Sloc
(Ref
);
2809 Res
: constant List_Id
:= New_List
;
2816 if Is_Class_Wide_Type
(Typ
) then
2817 Utyp
:= Root_Type
(Typ
);
2820 elsif Is_Concurrent_Type
(Typ
) then
2821 Utyp
:= Corresponding_Record_Type
(Typ
);
2822 Cref
:= Convert_Concurrent
(Ref
, Typ
);
2824 elsif Is_Private_Type
(Typ
)
2825 and then Present
(Full_View
(Typ
))
2826 and then Is_Concurrent_Type
(Full_View
(Typ
))
2828 Utyp
:= Corresponding_Record_Type
(Full_View
(Typ
));
2829 Cref
:= Convert_Concurrent
(Ref
, Full_View
(Typ
));
2835 Utyp
:= Underlying_Type
(Base_Type
(Utyp
));
2836 Set_Assignment_OK
(Cref
);
2838 -- Deal with non-tagged derivation of private views. If the parent is
2839 -- now known to be protected, the finalization routine is the one
2840 -- defined on the corresponding record of the ancestor (corresponding
2841 -- records do not automatically inherit operations, but maybe they
2844 if Is_Untagged_Derivation
(Typ
) then
2845 if Is_Protected_Type
(Typ
) then
2846 Utyp
:= Corresponding_Record_Type
(Root_Type
(Base_Type
(Typ
)));
2848 Utyp
:= Underlying_Type
(Root_Type
(Base_Type
(Typ
)));
2851 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
2853 -- We need to set Assignment_OK to prevent problems with unchecked
2854 -- conversions, where we do not want them to be converted back in the
2855 -- case of untagged record derivation (see code in Make_*_Call
2856 -- procedures for similar situations).
2858 Set_Assignment_OK
(Cref
);
2861 -- If the underlying_type is a subtype, we are dealing with
2862 -- the completion of a private type. We need to access
2863 -- the base type and generate a conversion to it.
2865 if Utyp
/= Base_Type
(Utyp
) then
2866 pragma Assert
(Is_Private_Type
(Typ
));
2867 Utyp
:= Base_Type
(Utyp
);
2868 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
2872 -- Deep_Finalize (Ref, With_Detach);
2874 if Has_Controlled_Component
(Utyp
)
2875 or else Is_Class_Wide_Type
(Typ
)
2877 if Is_Tagged_Type
(Utyp
) then
2878 Proc
:= Find_Prim_Op
(Utyp
, TSS_Deep_Finalize
);
2880 Proc
:= TSS
(Utyp
, TSS_Deep_Finalize
);
2883 Cref
:= Convert_View
(Proc
, Cref
);
2886 Make_Procedure_Call_Statement
(Loc
,
2887 Name
=> New_Reference_To
(Proc
, Loc
),
2888 Parameter_Associations
=>
2889 New_List
(Cref
, With_Detach
)));
2892 -- if With_Detach then
2893 -- Finalize_One (Ref);
2899 Proc
:= Find_Prim_Op
(Utyp
, Name_Of
(Finalize_Case
));
2901 if Chars
(With_Detach
) = Chars
(Standard_True
) then
2903 Make_Procedure_Call_Statement
(Loc
,
2904 Name
=> New_Reference_To
(RTE
(RE_Finalize_One
), Loc
),
2905 Parameter_Associations
=> New_List
(
2906 OK_Convert_To
(RTE
(RE_Finalizable
), Cref
))));
2908 elsif Chars
(With_Detach
) = Chars
(Standard_False
) then
2910 Make_Procedure_Call_Statement
(Loc
,
2911 Name
=> New_Reference_To
(Proc
, Loc
),
2912 Parameter_Associations
=>
2913 New_List
(Convert_View
(Proc
, Cref
))));
2916 Cref2
:= New_Copy_Tree
(Cref
);
2918 Make_Implicit_If_Statement
(Ref
,
2919 Condition
=> With_Detach
,
2920 Then_Statements
=> New_List
(
2921 Make_Procedure_Call_Statement
(Loc
,
2922 Name
=> New_Reference_To
(RTE
(RE_Finalize_One
), Loc
),
2923 Parameter_Associations
=> New_List
(
2924 OK_Convert_To
(RTE
(RE_Finalizable
), Cref
)))),
2926 Else_Statements
=> New_List
(
2927 Make_Procedure_Call_Statement
(Loc
,
2928 Name
=> New_Reference_To
(Proc
, Loc
),
2929 Parameter_Associations
=>
2930 New_List
(Convert_View
(Proc
, Cref2
))))));
2935 end Make_Final_Call
;
2937 -------------------------------------
2938 -- Make_Handler_For_Ctrl_Operation --
2939 -------------------------------------
2943 -- when E : others =>
2944 -- Raise_From_Controlled_Operation (X => E);
2949 -- raise Program_Error [finalize raised exception];
2951 -- depending on whether Raise_From_Controlled_Operation is available
2953 function Make_Handler_For_Ctrl_Operation
2954 (Loc
: Source_Ptr
) return Node_Id
2957 -- Choice parameter (for the first case above)
2959 Raise_Node
: Node_Id
;
2960 -- Procedure call or raise statement
2963 if RTE_Available
(RE_Raise_From_Controlled_Operation
) then
2965 -- Standard runtime: add choice parameter E, and pass it to
2966 -- Raise_From_Controlled_Operation so that the original exception
2967 -- name and message can be recorded in the exception message for
2970 E_Occ
:= Make_Defining_Identifier
(Loc
, Name_E
);
2971 Raise_Node
:= Make_Procedure_Call_Statement
(Loc
,
2974 RTE
(RE_Raise_From_Controlled_Operation
), Loc
),
2975 Parameter_Associations
=> New_List
(
2976 New_Occurrence_Of
(E_Occ
, Loc
)));
2979 -- Restricted runtime: exception messages are not supported
2982 Raise_Node
:= Make_Raise_Program_Error
(Loc
,
2983 Reason
=> PE_Finalize_Raised_Exception
);
2986 return Make_Implicit_Exception_Handler
(Loc
,
2987 Exception_Choices
=> New_List
(Make_Others_Choice
(Loc
)),
2988 Choice_Parameter
=> E_Occ
,
2989 Statements
=> New_List
(Raise_Node
));
2990 end Make_Handler_For_Ctrl_Operation
;
2992 --------------------
2993 -- Make_Init_Call --
2994 --------------------
2996 function Make_Init_Call
2999 Flist_Ref
: Node_Id
;
3000 With_Attach
: Node_Id
) return List_Id
3002 Loc
: constant Source_Ptr
:= Sloc
(Ref
);
3004 Res
: constant List_Id
:= New_List
;
3009 Attach
: Node_Id
:= With_Attach
;
3012 if Is_Concurrent_Type
(Typ
) then
3014 Utyp
:= Corresponding_Record_Type
(Typ
);
3015 Cref
:= Convert_Concurrent
(Ref
, Typ
);
3017 elsif Is_Private_Type
(Typ
)
3018 and then Present
(Full_View
(Typ
))
3019 and then Is_Concurrent_Type
(Underlying_Type
(Typ
))
3022 Utyp
:= Corresponding_Record_Type
(Underlying_Type
(Typ
));
3023 Cref
:= Convert_Concurrent
(Ref
, Underlying_Type
(Typ
));
3031 Utyp
:= Underlying_Type
(Base_Type
(Utyp
));
3033 Set_Assignment_OK
(Cref
);
3035 -- Deal with non-tagged derivation of private views
3037 if Is_Untagged_Derivation
(Typ
)
3038 and then not Is_Conc
3040 Utyp
:= Underlying_Type
(Root_Type
(Base_Type
(Typ
)));
3041 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
3042 Set_Assignment_OK
(Cref
);
3043 -- To prevent problems with UC see 1.156 RH ???
3046 -- If the underlying_type is a subtype, we are dealing with
3047 -- the completion of a private type. We need to access
3048 -- the base type and generate a conversion to it.
3050 if Utyp
/= Base_Type
(Utyp
) then
3051 pragma Assert
(Is_Private_Type
(Typ
));
3052 Utyp
:= Base_Type
(Utyp
);
3053 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
3056 -- We do not need to attach to one of the Global Final Lists
3057 -- the objects whose type is Finalize_Storage_Only
3059 if Finalize_Storage_Only
(Typ
)
3060 and then (Global_Flist_Ref
(Flist_Ref
)
3061 or else Entity
(Constant_Value
(RTE
(RE_Garbage_Collected
)))
3064 Attach
:= Make_Integer_Literal
(Loc
, 0);
3068 -- Deep_Initialize (Ref, Flist_Ref);
3070 if Has_Controlled_Component
(Utyp
) then
3071 Proc
:= TSS
(Utyp
, Deep_Name_Of
(Initialize_Case
));
3073 Cref
:= Convert_View
(Proc
, Cref
, 2);
3076 Make_Procedure_Call_Statement
(Loc
,
3077 Name
=> New_Reference_To
(Proc
, Loc
),
3078 Parameter_Associations
=> New_List
(
3084 -- Attach_To_Final_List (Ref, Flist_Ref);
3085 -- Initialize (Ref);
3087 else -- Is_Controlled (Utyp)
3088 Proc
:= Find_Prim_Op
(Utyp
, Name_Of
(Initialize_Case
));
3089 Check_Visibly_Controlled
(Initialize_Case
, Typ
, Proc
, Cref
);
3091 Cref
:= Convert_View
(Proc
, Cref
);
3092 Cref2
:= New_Copy_Tree
(Cref
);
3095 Make_Procedure_Call_Statement
(Loc
,
3096 Name
=> New_Reference_To
(Proc
, Loc
),
3097 Parameter_Associations
=> New_List
(Cref2
)));
3100 Make_Attach_Call
(Cref
, Flist_Ref
, Attach
));
3106 --------------------------
3107 -- Make_Transient_Block --
3108 --------------------------
3110 -- If finalization is involved, this function just wraps the instruction
3111 -- into a block whose name is the transient block entity, and then
3112 -- Expand_Cleanup_Actions (called on the expansion of the handled
3113 -- sequence of statements will do the necessary expansions for
3116 function Make_Transient_Block
3118 Action
: Node_Id
) return Node_Id
3120 Flist
: constant Entity_Id
:= Finalization_Chain_Entity
(Current_Scope
);
3121 Decls
: constant List_Id
:= New_List
;
3122 Par
: constant Node_Id
:= Parent
(Action
);
3123 Instrs
: constant List_Id
:= New_List
(Action
);
3127 -- Case where only secondary stack use is involved
3129 if VM_Target
= No_VM
3130 and then Uses_Sec_Stack
(Current_Scope
)
3132 and then Nkind
(Action
) /= N_Simple_Return_Statement
3133 and then Nkind
(Par
) /= N_Exception_Handler
3140 S
:= Scope
(Current_Scope
);
3144 -- At the outer level, no need to release the sec stack
3146 if S
= Standard_Standard
then
3147 Set_Uses_Sec_Stack
(Current_Scope
, False);
3150 -- In a function, only release the sec stack if the
3151 -- function does not return on the sec stack otherwise
3152 -- the result may be lost. The caller is responsible for
3155 elsif K
= E_Function
then
3156 Set_Uses_Sec_Stack
(Current_Scope
, False);
3158 if not Requires_Transient_Scope
(Etype
(S
)) then
3159 Set_Uses_Sec_Stack
(S
, True);
3160 Check_Restriction
(No_Secondary_Stack
, Action
);
3165 -- In a loop or entry we should install a block encompassing
3166 -- all the construct. For now just release right away.
3168 elsif K
= E_Loop
or else K
= E_Entry
then
3171 -- In a procedure or a block, we release on exit of the
3172 -- procedure or block. ??? memory leak can be created by
3175 elsif K
= E_Procedure
3178 Set_Uses_Sec_Stack
(S
, True);
3179 Check_Restriction
(No_Secondary_Stack
, Action
);
3180 Set_Uses_Sec_Stack
(Current_Scope
, False);
3190 -- Insert actions stuck in the transient scopes as well as all
3191 -- freezing nodes needed by those actions
3193 Insert_Actions_In_Scope_Around
(Action
);
3196 Last_Inserted
: Node_Id
:= Prev
(Action
);
3198 if Present
(Last_Inserted
) then
3199 Freeze_All
(First_Entity
(Current_Scope
), Last_Inserted
);
3204 Make_Block_Statement
(Loc
,
3205 Identifier
=> New_Reference_To
(Current_Scope
, Loc
),
3206 Declarations
=> Decls
,
3207 Handled_Statement_Sequence
=>
3208 Make_Handled_Sequence_Of_Statements
(Loc
, Statements
=> Instrs
),
3209 Has_Created_Identifier
=> True);
3211 -- When the transient scope was established, we pushed the entry for
3212 -- the transient scope onto the scope stack, so that the scope was
3213 -- active for the installation of finalizable entities etc. Now we
3214 -- must remove this entry, since we have constructed a proper block.
3219 end Make_Transient_Block
;
3221 ------------------------
3222 -- Needs_Finalization --
3223 ------------------------
3225 function Needs_Finalization
(T
: Entity_Id
) return Boolean is
3227 function Has_Some_Controlled_Component
(Rec
: Entity_Id
) return Boolean;
3228 -- If type is not frozen yet, check explicitly among its components,
3229 -- because the Has_Controlled_Component flag is not necessarily set.
3231 -----------------------------------
3232 -- Has_Some_Controlled_Component --
3233 -----------------------------------
3235 function Has_Some_Controlled_Component
3236 (Rec
: Entity_Id
) return Boolean
3241 if Has_Controlled_Component
(Rec
) then
3244 elsif not Is_Frozen
(Rec
) then
3245 if Is_Record_Type
(Rec
) then
3246 Comp
:= First_Entity
(Rec
);
3248 while Present
(Comp
) loop
3249 if not Is_Type
(Comp
)
3250 and then Needs_Finalization
(Etype
(Comp
))
3260 elsif Is_Array_Type
(Rec
) then
3261 return Needs_Finalization
(Component_Type
(Rec
));
3264 return Has_Controlled_Component
(Rec
);
3269 end Has_Some_Controlled_Component
;
3271 -- Start of processing for Needs_Finalization
3274 -- Class-wide types must be treated as controlled because they may
3275 -- contain an extension that has controlled components
3277 -- We can skip this if finalization is not available
3279 return (Is_Class_Wide_Type
(T
)
3280 and then not In_Finalization_Root
(T
)
3281 and then not Restriction_Active
(No_Finalization
))
3282 or else Is_Controlled
(T
)
3283 or else Has_Some_Controlled_Component
(T
)
3284 or else (Is_Concurrent_Type
(T
)
3285 and then Present
(Corresponding_Record_Type
(T
))
3286 and then Needs_Finalization
(Corresponding_Record_Type
(T
)));
3287 end Needs_Finalization
;
3289 ------------------------
3290 -- Node_To_Be_Wrapped --
3291 ------------------------
3293 function Node_To_Be_Wrapped
return Node_Id
is
3295 return Scope_Stack
.Table
(Scope_Stack
.Last
).Node_To_Be_Wrapped
;
3296 end Node_To_Be_Wrapped
;
3298 ----------------------------
3299 -- Set_Node_To_Be_Wrapped --
3300 ----------------------------
3302 procedure Set_Node_To_Be_Wrapped
(N
: Node_Id
) is
3304 Scope_Stack
.Table
(Scope_Stack
.Last
).Node_To_Be_Wrapped
:= N
;
3305 end Set_Node_To_Be_Wrapped
;
3307 ----------------------------------
3308 -- Store_After_Actions_In_Scope --
3309 ----------------------------------
3311 procedure Store_After_Actions_In_Scope
(L
: List_Id
) is
3312 SE
: Scope_Stack_Entry
renames Scope_Stack
.Table
(Scope_Stack
.Last
);
3315 if Present
(SE
.Actions_To_Be_Wrapped_After
) then
3316 Insert_List_Before_And_Analyze
(
3317 First
(SE
.Actions_To_Be_Wrapped_After
), L
);
3320 SE
.Actions_To_Be_Wrapped_After
:= L
;
3322 if Is_List_Member
(SE
.Node_To_Be_Wrapped
) then
3323 Set_Parent
(L
, Parent
(SE
.Node_To_Be_Wrapped
));
3325 Set_Parent
(L
, SE
.Node_To_Be_Wrapped
);
3330 end Store_After_Actions_In_Scope
;
3332 -----------------------------------
3333 -- Store_Before_Actions_In_Scope --
3334 -----------------------------------
3336 procedure Store_Before_Actions_In_Scope
(L
: List_Id
) is
3337 SE
: Scope_Stack_Entry
renames Scope_Stack
.Table
(Scope_Stack
.Last
);
3340 if Present
(SE
.Actions_To_Be_Wrapped_Before
) then
3341 Insert_List_After_And_Analyze
(
3342 Last
(SE
.Actions_To_Be_Wrapped_Before
), L
);
3345 SE
.Actions_To_Be_Wrapped_Before
:= L
;
3347 if Is_List_Member
(SE
.Node_To_Be_Wrapped
) then
3348 Set_Parent
(L
, Parent
(SE
.Node_To_Be_Wrapped
));
3350 Set_Parent
(L
, SE
.Node_To_Be_Wrapped
);
3355 end Store_Before_Actions_In_Scope
;
3357 --------------------------------
3358 -- Wrap_Transient_Declaration --
3359 --------------------------------
3361 -- If a transient scope has been established during the processing of the
3362 -- Expression of an Object_Declaration, it is not possible to wrap the
3363 -- declaration into a transient block as usual case, otherwise the object
3364 -- would be itself declared in the wrong scope. Therefore, all entities (if
3365 -- any) defined in the transient block are moved to the proper enclosing
3366 -- scope, furthermore, if they are controlled variables they are finalized
3367 -- right after the declaration. The finalization list of the transient
3368 -- scope is defined as a renaming of the enclosing one so during their
3369 -- initialization they will be attached to the proper finalization
3370 -- list. For instance, the following declaration :
3372 -- X : Typ := F (G (A), G (B));
3374 -- (where G(A) and G(B) return controlled values, expanded as _v1 and _v2)
3375 -- is expanded into :
3377 -- _local_final_list_1 : Finalizable_Ptr;
3378 -- X : Typ := [ complex Expression-Action ];
3379 -- Finalize_One(_v1);
3380 -- Finalize_One (_v2);
3382 procedure Wrap_Transient_Declaration
(N
: Node_Id
) is
3384 LC
: Entity_Id
:= Empty
;
3386 Loc
: constant Source_Ptr
:= Sloc
(N
);
3387 First_Decl_Loc
: Source_Ptr
;
3388 Enclosing_S
: Entity_Id
;
3390 Next_N
: constant Node_Id
:= Next
(N
);
3394 Enclosing_S
:= Scope
(S
);
3396 -- Insert Actions kept in the Scope stack
3398 Insert_Actions_In_Scope_Around
(N
);
3400 -- If the declaration is consuming some secondary stack, mark the
3401 -- Enclosing scope appropriately.
3403 Uses_SS
:= Uses_Sec_Stack
(S
);
3406 -- Create a List controller and rename the final list to be its
3407 -- internal final pointer:
3408 -- Lxxx : Simple_List_Controller;
3409 -- Fxxx : Finalizable_Ptr renames Lxxx.F;
3411 if Present
(Finalization_Chain_Entity
(S
)) then
3412 LC
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('L'));
3414 -- Use the Sloc of the first declaration of N's containing list, to
3415 -- maintain monotonicity of source-line stepping during debugging.
3417 First_Decl_Loc
:= Sloc
(First
(List_Containing
(N
)));
3420 Make_Object_Declaration
(First_Decl_Loc
,
3421 Defining_Identifier
=> LC
,
3422 Object_Definition
=>
3424 (RTE
(RE_Simple_List_Controller
), First_Decl_Loc
)),
3426 Make_Object_Renaming_Declaration
(First_Decl_Loc
,
3427 Defining_Identifier
=> Finalization_Chain_Entity
(S
),
3429 New_Reference_To
(RTE
(RE_Finalizable_Ptr
), First_Decl_Loc
),
3431 Make_Selected_Component
(Loc
,
3432 Prefix
=> New_Reference_To
(LC
, First_Decl_Loc
),
3433 Selector_Name
=> Make_Identifier
(First_Decl_Loc
, Name_F
))));
3435 -- Put the declaration at the beginning of the declaration part
3436 -- to make sure it will be before all other actions that have been
3437 -- inserted before N.
3439 Insert_List_Before_And_Analyze
(First
(List_Containing
(N
)), Nodes
);
3441 -- Generate the Finalization calls by finalizing the list controller
3442 -- right away. It will be re-finalized on scope exit but it doesn't
3443 -- matter. It cannot be done when the call initializes a renaming
3444 -- object though because in this case, the object becomes a pointer
3445 -- to the temporary and thus increases its life span. Ditto if this
3446 -- is a renaming of a component of an expression (such as a function
3449 -- Note that there is a problem if an actual in the call needs
3450 -- finalization, because in that case the call itself is the master,
3451 -- and the actual should be finalized on return from the call ???
3453 if Nkind
(N
) = N_Object_Renaming_Declaration
3454 and then Needs_Finalization
(Etype
(Defining_Identifier
(N
)))
3458 elsif Nkind
(N
) = N_Object_Renaming_Declaration
3460 Nkind_In
(Renamed_Object
(Defining_Identifier
(N
)),
3461 N_Selected_Component
,
3462 N_Indexed_Component
)
3465 (Etype
(Prefix
(Renamed_Object
(Defining_Identifier
(N
)))))
3472 (Ref
=> New_Reference_To
(LC
, Loc
),
3474 With_Detach
=> New_Reference_To
(Standard_False
, Loc
));
3476 if Present
(Next_N
) then
3477 Insert_List_Before_And_Analyze
(Next_N
, Nodes
);
3479 Append_List_To
(List_Containing
(N
), Nodes
);
3484 -- Put the local entities back in the enclosing scope, and set the
3485 -- Is_Public flag appropriately.
3487 Transfer_Entities
(S
, Enclosing_S
);
3489 -- Mark the enclosing dynamic scope so that the sec stack will be
3490 -- released upon its exit unless this is a function that returns on
3491 -- the sec stack in which case this will be done by the caller.
3493 if VM_Target
= No_VM
and then Uses_SS
then
3494 S
:= Enclosing_Dynamic_Scope
(S
);
3496 if Ekind
(S
) = E_Function
3497 and then Requires_Transient_Scope
(Etype
(S
))
3501 Set_Uses_Sec_Stack
(S
);
3502 Check_Restriction
(No_Secondary_Stack
, N
);
3505 end Wrap_Transient_Declaration
;
3507 -------------------------------
3508 -- Wrap_Transient_Expression --
3509 -------------------------------
3511 -- Insert actions before <Expression>:
3513 -- (lines marked with <CTRL> are expanded only in presence of Controlled
3514 -- objects needing finalization)
3518 -- _M : constant Mark_Id := SS_Mark;
3519 -- Local_Final_List : System.FI.Finalizable_Ptr; <CTRL>
3521 -- procedure _Clean is
3524 -- System.FI.Finalize_List (Local_Final_List); <CTRL>
3530 -- _E := <Expression>;
3535 -- then expression is replaced by _E
3537 procedure Wrap_Transient_Expression
(N
: Node_Id
) is
3538 Loc
: constant Source_Ptr
:= Sloc
(N
);
3539 E
: constant Entity_Id
:=
3540 Make_Defining_Identifier
(Loc
, New_Internal_Name
('E'));
3541 Etyp
: constant Entity_Id
:= Etype
(N
);
3544 Insert_Actions
(N
, New_List
(
3545 Make_Object_Declaration
(Loc
,
3546 Defining_Identifier
=> E
,
3547 Object_Definition
=> New_Reference_To
(Etyp
, Loc
)),
3549 Make_Transient_Block
(Loc
,
3551 Make_Assignment_Statement
(Loc
,
3552 Name
=> New_Reference_To
(E
, Loc
),
3553 Expression
=> Relocate_Node
(N
)))));
3555 Rewrite
(N
, New_Reference_To
(E
, Loc
));
3556 Analyze_And_Resolve
(N
, Etyp
);
3557 end Wrap_Transient_Expression
;
3559 ------------------------------
3560 -- Wrap_Transient_Statement --
3561 ------------------------------
3563 -- Transform <Instruction> into
3565 -- (lines marked with <CTRL> are expanded only in presence of Controlled
3566 -- objects needing finalization)
3569 -- _M : Mark_Id := SS_Mark;
3570 -- Local_Final_List : System.FI.Finalizable_Ptr ; <CTRL>
3572 -- procedure _Clean is
3575 -- System.FI.Finalize_List (Local_Final_List); <CTRL>
3586 procedure Wrap_Transient_Statement
(N
: Node_Id
) is
3587 Loc
: constant Source_Ptr
:= Sloc
(N
);
3588 New_Statement
: constant Node_Id
:= Relocate_Node
(N
);
3591 Rewrite
(N
, Make_Transient_Block
(Loc
, New_Statement
));
3593 -- With the scope stack back to normal, we can call analyze on the
3594 -- resulting block. At this point, the transient scope is being
3595 -- treated like a perfectly normal scope, so there is nothing
3596 -- special about it.
3598 -- Note: Wrap_Transient_Statement is called with the node already
3599 -- analyzed (i.e. Analyzed (N) is True). This is important, since
3600 -- otherwise we would get a recursive processing of the node when
3601 -- we do this Analyze call.
3604 end Wrap_Transient_Statement
;