1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2006, 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 2, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING. If not, write --
19 -- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
20 -- Boston, MA 02110-1301, USA. --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
25 ------------------------------------------------------------------------------
27 -- This package contains virtually all expansion mechanisms related to
31 with Atree
; use Atree
;
32 with Debug
; use Debug
;
33 with Einfo
; use Einfo
;
34 with Errout
; use Errout
;
35 with Exp_Ch9
; use Exp_Ch9
;
36 with Exp_Ch11
; use Exp_Ch11
;
37 with Exp_Dbug
; use Exp_Dbug
;
38 with Exp_Tss
; use Exp_Tss
;
39 with Exp_Util
; use Exp_Util
;
40 with Freeze
; use Freeze
;
41 with Hostparm
; use Hostparm
;
42 with Nlists
; use Nlists
;
43 with Nmake
; use Nmake
;
45 with Output
; use Output
;
46 with Restrict
; use Restrict
;
47 with Rident
; use Rident
;
48 with Rtsfind
; use Rtsfind
;
49 with Targparm
; use Targparm
;
50 with Sinfo
; use Sinfo
;
52 with Sem_Ch3
; use Sem_Ch3
;
53 with Sem_Ch7
; use Sem_Ch7
;
54 with Sem_Ch8
; use Sem_Ch8
;
55 with Sem_Res
; use Sem_Res
;
56 with Sem_Type
; use Sem_Type
;
57 with Sem_Util
; use Sem_Util
;
58 with Snames
; use Snames
;
59 with Stand
; use Stand
;
60 with Tbuild
; use Tbuild
;
61 with Uintp
; use Uintp
;
63 package body Exp_Ch7
is
65 --------------------------------
66 -- Transient Scope Management --
67 --------------------------------
69 -- A transient scope is created when temporary objects are created by the
70 -- compiler. These temporary objects are allocated on the secondary stack
71 -- and the transient scope is responsible for finalizing the object when
72 -- appropriate and reclaiming the memory at the right time. The temporary
73 -- objects are generally the objects allocated to store the result of a
74 -- function returning an unconstrained or a tagged value. Expressions
75 -- needing to be wrapped in a transient scope (functions calls returning
76 -- unconstrained or tagged values) may appear in 3 different contexts which
77 -- lead to 3 different kinds of transient scope expansion:
79 -- 1. In a simple statement (procedure call, assignment, ...). In
80 -- this case the instruction is wrapped into a transient block.
81 -- (See Wrap_Transient_Statement for details)
83 -- 2. In an expression of a control structure (test in a IF statement,
84 -- expression in a CASE statement, ...).
85 -- (See Wrap_Transient_Expression for details)
87 -- 3. In a expression of an object_declaration. No wrapping is possible
88 -- here, so the finalization actions, if any are done right after the
89 -- declaration and the secondary stack deallocation is done in the
90 -- proper enclosing scope (see Wrap_Transient_Declaration for details)
92 -- Note about function returning tagged types: It has been decided to
93 -- always allocate their result in the secondary stack while it is not
94 -- absolutely mandatory when the tagged type is constrained because the
95 -- caller knows the size of the returned object and thus could allocate the
96 -- result in the primary stack. But, allocating them always in the
97 -- secondary stack simplifies many implementation hassles:
99 -- - If it is dispatching function call, the computation of the size of
100 -- the result is possible but complex from the outside.
102 -- - If the returned type is controlled, the assignment of the returned
103 -- value to the anonymous object involves an Adjust, and we have no
104 -- easy way to access the anonymous object created by the back-end
106 -- - If the returned type is class-wide, this is an unconstrained type
109 -- Furthermore, the little loss in efficiency which is the result of this
110 -- decision is not such a big deal because function returning tagged types
111 -- are not very much used in real life as opposed to functions returning
112 -- access to a tagged type
114 --------------------------------------------------
115 -- Transient Blocks and Finalization Management --
116 --------------------------------------------------
118 function Find_Node_To_Be_Wrapped
(N
: Node_Id
) return Node_Id
;
119 -- N is a node wich may generate a transient scope. Loop over the
120 -- parent pointers of N until it find the appropriate node to
121 -- wrap. It it returns Empty, it means that no transient scope is
122 -- needed in this context.
131 Is_Protected_Subprogram
: Boolean;
132 Is_Task_Allocation_Block
: Boolean;
133 Is_Asynchronous_Call_Block
: Boolean) return Node_Id
;
134 -- Expand a the clean-up procedure for controlled and/or transient
135 -- block, and/or task master or task body, or blocks used to
136 -- implement task allocation or asynchronous entry calls, or
137 -- procedures used to implement protected procedures. Clean is the
138 -- entity for such a procedure. Mark is the entity for the secondary
139 -- stack mark, if empty only controlled block clean-up will be
140 -- performed. Flist is the entity for the local final list, if empty
141 -- only transient scope clean-up will be performed. The flags
142 -- Is_Task and Is_Master control the calls to the corresponding
143 -- finalization actions for a task body or for an entity that is a
146 procedure Set_Node_To_Be_Wrapped
(N
: Node_Id
);
147 -- Set the field Node_To_Be_Wrapped of the current scope
149 procedure Insert_Actions_In_Scope_Around
(N
: Node_Id
);
150 -- Insert the before-actions kept in the scope stack before N, and the
151 -- after after-actions, after N which must be a member of a list.
153 function Make_Transient_Block
155 Action
: Node_Id
) return Node_Id
;
156 -- Create a transient block whose name is Scope, which is also a
157 -- controlled block if Flist is not empty and whose only code is
158 -- Action (either a single statement or single declaration).
160 type Final_Primitives
is (Initialize_Case
, Adjust_Case
, Finalize_Case
);
161 -- This enumeration type is defined in order to ease sharing code for
162 -- building finalization procedures for composite types.
164 Name_Of
: constant array (Final_Primitives
) of Name_Id
:=
165 (Initialize_Case
=> Name_Initialize
,
166 Adjust_Case
=> Name_Adjust
,
167 Finalize_Case
=> Name_Finalize
);
169 Deep_Name_Of
: constant array (Final_Primitives
) of TSS_Name_Type
:=
170 (Initialize_Case
=> TSS_Deep_Initialize
,
171 Adjust_Case
=> TSS_Deep_Adjust
,
172 Finalize_Case
=> TSS_Deep_Finalize
);
174 procedure Build_Record_Deep_Procs
(Typ
: Entity_Id
);
175 -- Build the deep Initialize/Adjust/Finalize for a record Typ with
176 -- Has_Component_Component set and store them using the TSS mechanism.
178 procedure Build_Array_Deep_Procs
(Typ
: Entity_Id
);
179 -- Build the deep Initialize/Adjust/Finalize for a record Typ with
180 -- Has_Controlled_Component set and store them using the TSS mechanism.
182 function Make_Deep_Proc
183 (Prim
: Final_Primitives
;
185 Stmts
: List_Id
) return Node_Id
;
186 -- This function generates the tree for Deep_Initialize, Deep_Adjust
187 -- or Deep_Finalize procedures according to the first parameter,
188 -- these procedures operate on the type Typ. The Stmts parameter
189 -- gives the body of the procedure.
191 function Make_Deep_Array_Body
192 (Prim
: Final_Primitives
;
193 Typ
: Entity_Id
) return List_Id
;
194 -- This function generates the list of statements for implementing
195 -- Deep_Initialize, Deep_Adjust or Deep_Finalize procedures
196 -- according to the first parameter, these procedures operate on the
199 function Make_Deep_Record_Body
200 (Prim
: Final_Primitives
;
201 Typ
: Entity_Id
) return List_Id
;
202 -- This function generates the list of statements for implementing
203 -- Deep_Initialize, Deep_Adjust or Deep_Finalize procedures
204 -- according to the first parameter, these procedures operate on the
207 procedure Check_Visibly_Controlled
208 (Prim
: Final_Primitives
;
210 E
: in out Entity_Id
;
211 Cref
: in out Node_Id
);
212 -- The controlled operation declared for a derived type may not be
213 -- overriding, if the controlled operations of the parent type are
214 -- hidden, for example when the parent is a private type whose full
215 -- view is controlled. For other primitive operations we modify the
216 -- name of the operation to indicate that it is not overriding, but
217 -- this is not possible for Initialize, etc. because they have to be
218 -- retrievable by name. Before generating the proper call to one of
219 -- these operations we check whether Typ is known to be controlled at
220 -- the point of definition. If it is not then we must retrieve the
221 -- hidden operation of the parent and use it instead. This is one
222 -- case that might be solved more cleanly once Overriding pragmas or
223 -- declarations are in place.
225 function Convert_View
228 Ind
: Pos
:= 1) return Node_Id
;
229 -- Proc is one of the Initialize/Adjust/Finalize operations, and
230 -- Arg is the argument being passed to it. Ind indicates which
231 -- formal of procedure Proc we are trying to match. This function
232 -- will, if necessary, generate an conversion between the partial
233 -- and full view of Arg to match the type of the formal of Proc,
234 -- or force a conversion to the class-wide type in the case where
235 -- the operation is abstract.
237 -----------------------------
238 -- Finalization Management --
239 -----------------------------
241 -- This part describe how Initialization/Adjusment/Finalization procedures
242 -- are generated and called. Two cases must be considered, types that are
243 -- Controlled (Is_Controlled flag set) and composite types that contain
244 -- controlled components (Has_Controlled_Component flag set). In the first
245 -- case the procedures to call are the user-defined primitive operations
246 -- Initialize/Adjust/Finalize. In the second case, GNAT generates
247 -- Deep_Initialize, Deep_Adjust and Deep_Finalize that are in charge of
248 -- calling the former procedures on the controlled components.
250 -- For records with Has_Controlled_Component set, a hidden "controller"
251 -- component is inserted. This controller component contains its own
252 -- finalization list on which all controlled components are attached
253 -- creating an indirection on the upper-level Finalization list. This
254 -- technique facilitates the management of objects whose number of
255 -- controlled components changes during execution. This controller
256 -- component is itself controlled and is attached to the upper-level
257 -- finalization chain. Its adjust primitive is in charge of calling
258 -- adjust on the components and adusting the finalization pointer to
259 -- match their new location (see a-finali.adb).
261 -- It is not possible to use a similar technique for arrays that have
262 -- Has_Controlled_Component set. In this case, deep procedures are
263 -- generated that call initialize/adjust/finalize + attachment or
264 -- detachment on the finalization list for all component.
266 -- Initialize calls: they are generated for declarations or dynamic
267 -- allocations of Controlled objects with no initial value. They are
268 -- always followed by an attachment to the current Finalization
269 -- Chain. For the dynamic allocation case this the chain attached to
270 -- the scope of the access type definition otherwise, this is the chain
271 -- of the current scope.
273 -- Adjust Calls: They are generated on 2 occasions: (1) for
274 -- declarations or dynamic allocations of Controlled objects with an
275 -- initial value. (2) after an assignment. In the first case they are
276 -- followed by an attachment to the final chain, in the second case
279 -- Finalization Calls: They are generated on (1) scope exit, (2)
280 -- assignments, (3) unchecked deallocations. In case (3) they have to
281 -- be detached from the final chain, in case (2) they must not and in
282 -- case (1) this is not important since we are exiting the scope
286 -- - Type extensions will have a new record controller at each derivation
287 -- level containing controlled components.
288 -- - For types that are both Is_Controlled and Has_Controlled_Components,
289 -- the record controller and the object itself are handled separately.
290 -- It could seem simpler to attach the object at the end of its record
291 -- controller but this would not tackle view conversions properly.
292 -- - A classwide type can always potentially have controlled components
293 -- but the record controller of the corresponding actual type may not
294 -- be known at compile time so the dispatch table contains a special
295 -- field that allows to compute the offset of the record controller
296 -- dynamically. See s-finimp.Deep_Tag_Attach and a-tags.RC_Offset
298 -- Here is a simple example of the expansion of a controlled block :
302 -- Y : Controlled := Init;
308 -- Z : R := (C => X);
317 -- _L : System.FI.Finalizable_Ptr;
319 -- procedure _Clean is
322 -- System.FI.Finalize_List (_L);
330 -- Attach_To_Final_List (_L, Finalizable (X), 1);
331 -- at end: Abort_Undefer;
332 -- Y : Controlled := Init;
334 -- Attach_To_Final_List (_L, Finalizable (Y), 1);
337 -- _C : Record_Controller;
343 -- Deep_Initialize (W, _L, 1);
344 -- at end: Abort_Under;
345 -- Z : R := (C => X);
346 -- Deep_Adjust (Z, _L, 1);
350 -- Deep_Finalize (W, False);
351 -- <save W's final pointers>
353 -- <restore W's final pointers>
354 -- Deep_Adjust (W, _L, 0);
359 function Global_Flist_Ref
(Flist_Ref
: Node_Id
) return Boolean;
360 -- Return True if Flist_Ref refers to a global final list, either
361 -- the object GLobal_Final_List which is used to attach standalone
362 -- objects, or any of the list controllers associated with library
363 -- level access to controlled objects
365 procedure Clean_Simple_Protected_Objects
(N
: Node_Id
);
366 -- Protected objects without entries are not controlled types, and the
367 -- locks have to be released explicitly when such an object goes out
368 -- of scope. Traverse declarations in scope to determine whether such
369 -- objects are present.
371 ----------------------------
372 -- Build_Array_Deep_Procs --
373 ----------------------------
375 procedure Build_Array_Deep_Procs
(Typ
: Entity_Id
) is
379 Prim
=> Initialize_Case
,
381 Stmts
=> Make_Deep_Array_Body
(Initialize_Case
, Typ
)));
383 if not Is_Inherently_Limited_Type
(Typ
) then
388 Stmts
=> Make_Deep_Array_Body
(Adjust_Case
, Typ
)));
393 Prim
=> Finalize_Case
,
395 Stmts
=> Make_Deep_Array_Body
(Finalize_Case
, Typ
)));
396 end Build_Array_Deep_Procs
;
398 -----------------------------
399 -- Build_Controlling_Procs --
400 -----------------------------
402 procedure Build_Controlling_Procs
(Typ
: Entity_Id
) is
404 if Is_Array_Type
(Typ
) then
405 Build_Array_Deep_Procs
(Typ
);
407 else pragma Assert
(Is_Record_Type
(Typ
));
408 Build_Record_Deep_Procs
(Typ
);
410 end Build_Controlling_Procs
;
412 ----------------------
413 -- Build_Final_List --
414 ----------------------
416 procedure Build_Final_List
(N
: Node_Id
; Typ
: Entity_Id
) is
417 Loc
: constant Source_Ptr
:= Sloc
(N
);
421 Set_Associated_Final_Chain
(Typ
,
422 Make_Defining_Identifier
(Loc
,
423 New_External_Name
(Chars
(Typ
), 'L')));
426 Make_Object_Declaration
(Loc
,
427 Defining_Identifier
=>
428 Associated_Final_Chain
(Typ
),
431 (RTE
(RE_List_Controller
), Loc
));
433 -- The type may have been frozen already, and this is a late freezing
434 -- action, in which case the declaration must be elaborated at once.
435 -- If the call is for an allocator, the chain must also be created now,
436 -- because the freezing of the type does not build one. Otherwise, the
437 -- declaration is one of the freezing actions for a user-defined type.
440 or else (Nkind
(N
) = N_Allocator
441 and then Ekind
(Etype
(N
)) = E_Anonymous_Access_Type
)
443 Insert_Action
(N
, Decl
);
445 Append_Freeze_Action
(Typ
, Decl
);
447 end Build_Final_List
;
449 ---------------------
450 -- Build_Late_Proc --
451 ---------------------
453 procedure Build_Late_Proc
(Typ
: Entity_Id
; Nam
: Name_Id
) is
455 for Final_Prim
in Name_Of
'Range loop
456 if Name_Of
(Final_Prim
) = Nam
then
461 Stmts
=> Make_Deep_Record_Body
(Final_Prim
, Typ
)));
466 -----------------------------
467 -- Build_Record_Deep_Procs --
468 -----------------------------
470 procedure Build_Record_Deep_Procs
(Typ
: Entity_Id
) is
474 Prim
=> Initialize_Case
,
476 Stmts
=> Make_Deep_Record_Body
(Initialize_Case
, Typ
)));
478 if not Is_Inherently_Limited_Type
(Typ
) then
483 Stmts
=> Make_Deep_Record_Body
(Adjust_Case
, Typ
)));
488 Prim
=> Finalize_Case
,
490 Stmts
=> Make_Deep_Record_Body
(Finalize_Case
, Typ
)));
491 end Build_Record_Deep_Procs
;
497 function Cleanup_Array
500 Typ
: Entity_Id
) return List_Id
502 Loc
: constant Source_Ptr
:= Sloc
(N
);
503 Index_List
: constant List_Id
:= New_List
;
505 function Free_Component
return List_Id
;
506 -- Generate the code to finalize the task or protected subcomponents
507 -- of a single component of the array.
509 function Free_One_Dimension
(Dim
: Int
) return List_Id
;
510 -- Generate a loop over one dimension of the array
516 function Free_Component
return List_Id
is
517 Stmts
: List_Id
:= New_List
;
519 C_Typ
: constant Entity_Id
:= Component_Type
(Typ
);
522 -- Component type is known to contain tasks or protected objects
525 Make_Indexed_Component
(Loc
,
526 Prefix
=> Duplicate_Subexpr_No_Checks
(Obj
),
527 Expressions
=> Index_List
);
529 Set_Etype
(Tsk
, C_Typ
);
531 if Is_Task_Type
(C_Typ
) then
532 Append_To
(Stmts
, Cleanup_Task
(N
, Tsk
));
534 elsif Is_Simple_Protected_Type
(C_Typ
) then
535 Append_To
(Stmts
, Cleanup_Protected_Object
(N
, Tsk
));
537 elsif Is_Record_Type
(C_Typ
) then
538 Stmts
:= Cleanup_Record
(N
, Tsk
, C_Typ
);
540 elsif Is_Array_Type
(C_Typ
) then
541 Stmts
:= Cleanup_Array
(N
, Tsk
, C_Typ
);
547 ------------------------
548 -- Free_One_Dimension --
549 ------------------------
551 function Free_One_Dimension
(Dim
: Int
) return List_Id
is
555 if Dim
> Number_Dimensions
(Typ
) then
556 return Free_Component
;
558 -- Here we generate the required loop
562 Make_Defining_Identifier
(Loc
, New_Internal_Name
('J'));
564 Append
(New_Reference_To
(Index
, Loc
), Index_List
);
567 Make_Implicit_Loop_Statement
(N
,
570 Make_Iteration_Scheme
(Loc
,
571 Loop_Parameter_Specification
=>
572 Make_Loop_Parameter_Specification
(Loc
,
573 Defining_Identifier
=> Index
,
574 Discrete_Subtype_Definition
=>
575 Make_Attribute_Reference
(Loc
,
576 Prefix
=> Duplicate_Subexpr
(Obj
),
577 Attribute_Name
=> Name_Range
,
578 Expressions
=> New_List
(
579 Make_Integer_Literal
(Loc
, Dim
))))),
580 Statements
=> Free_One_Dimension
(Dim
+ 1)));
582 end Free_One_Dimension
;
584 -- Start of processing for Cleanup_Array
587 return Free_One_Dimension
(1);
594 function Cleanup_Record
597 Typ
: Entity_Id
) return List_Id
599 Loc
: constant Source_Ptr
:= Sloc
(N
);
602 Stmts
: constant List_Id
:= New_List
;
603 U_Typ
: constant Entity_Id
:= Underlying_Type
(Typ
);
606 if Has_Discriminants
(U_Typ
)
607 and then Nkind
(Parent
(U_Typ
)) = N_Full_Type_Declaration
609 Nkind
(Type_Definition
(Parent
(U_Typ
))) = N_Record_Definition
613 (Component_List
(Type_Definition
(Parent
(U_Typ
)))))
615 -- For now, do not attempt to free a component that may appear in
616 -- a variant, and instead issue a warning. Doing this "properly"
617 -- would require building a case statement and would be quite a
618 -- mess. Note that the RM only requires that free "work" for the
619 -- case of a task access value, so already we go way beyond this
620 -- in that we deal with the array case and non-discriminated
624 ("task/protected object in variant record will not be freed?", N
);
625 return New_List
(Make_Null_Statement
(Loc
));
628 Comp
:= First_Component
(Typ
);
630 while Present
(Comp
) loop
631 if Has_Task
(Etype
(Comp
))
632 or else Has_Simple_Protected_Object
(Etype
(Comp
))
635 Make_Selected_Component
(Loc
,
636 Prefix
=> Duplicate_Subexpr_No_Checks
(Obj
),
637 Selector_Name
=> New_Occurrence_Of
(Comp
, Loc
));
638 Set_Etype
(Tsk
, Etype
(Comp
));
640 if Is_Task_Type
(Etype
(Comp
)) then
641 Append_To
(Stmts
, Cleanup_Task
(N
, Tsk
));
643 elsif Is_Simple_Protected_Type
(Etype
(Comp
)) then
644 Append_To
(Stmts
, Cleanup_Protected_Object
(N
, Tsk
));
646 elsif Is_Record_Type
(Etype
(Comp
)) then
648 -- Recurse, by generating the prefix of the argument to
649 -- the eventual cleanup call.
652 (Stmts
, Cleanup_Record
(N
, Tsk
, Etype
(Comp
)));
654 elsif Is_Array_Type
(Etype
(Comp
)) then
656 (Stmts
, Cleanup_Array
(N
, Tsk
, Etype
(Comp
)));
660 Next_Component
(Comp
);
666 ------------------------------
667 -- Cleanup_Protected_Object --
668 ------------------------------
670 function Cleanup_Protected_Object
672 Ref
: Node_Id
) return Node_Id
674 Loc
: constant Source_Ptr
:= Sloc
(N
);
678 Make_Procedure_Call_Statement
(Loc
,
679 Name
=> New_Reference_To
(RTE
(RE_Finalize_Protection
), Loc
),
680 Parameter_Associations
=> New_List
(
681 Concurrent_Ref
(Ref
)));
682 end Cleanup_Protected_Object
;
684 ------------------------------------
685 -- Clean_Simple_Protected_Objects --
686 ------------------------------------
688 procedure Clean_Simple_Protected_Objects
(N
: Node_Id
) is
689 Stmts
: constant List_Id
:= Statements
(Handled_Statement_Sequence
(N
));
690 Stmt
: Node_Id
:= Last
(Stmts
);
694 E
:= First_Entity
(Current_Scope
);
695 while Present
(E
) loop
696 if (Ekind
(E
) = E_Variable
697 or else Ekind
(E
) = E_Constant
)
698 and then Has_Simple_Protected_Object
(Etype
(E
))
699 and then not Has_Task
(Etype
(E
))
700 and then Nkind
(Parent
(E
)) /= N_Object_Renaming_Declaration
703 Typ
: constant Entity_Id
:= Etype
(E
);
704 Ref
: constant Node_Id
:= New_Occurrence_Of
(E
, Sloc
(Stmt
));
707 if Is_Simple_Protected_Type
(Typ
) then
708 Append_To
(Stmts
, Cleanup_Protected_Object
(N
, Ref
));
710 elsif Has_Simple_Protected_Object
(Typ
) then
711 if Is_Record_Type
(Typ
) then
712 Append_List_To
(Stmts
, Cleanup_Record
(N
, Ref
, Typ
));
714 elsif Is_Array_Type
(Typ
) then
715 Append_List_To
(Stmts
, Cleanup_Array
(N
, Ref
, Typ
));
724 -- Analyze inserted cleanup statements
726 if Present
(Stmt
) then
729 while Present
(Stmt
) loop
734 end Clean_Simple_Protected_Objects
;
740 function Cleanup_Task
742 Ref
: Node_Id
) return Node_Id
744 Loc
: constant Source_Ptr
:= Sloc
(N
);
747 Make_Procedure_Call_Statement
(Loc
,
748 Name
=> New_Reference_To
(RTE
(RE_Free_Task
), Loc
),
749 Parameter_Associations
=>
750 New_List
(Concurrent_Ref
(Ref
)));
753 ---------------------------------
754 -- Has_Simple_Protected_Object --
755 ---------------------------------
757 function Has_Simple_Protected_Object
(T
: Entity_Id
) return Boolean is
761 if Is_Simple_Protected_Type
(T
) then
764 elsif Is_Array_Type
(T
) then
765 return Has_Simple_Protected_Object
(Component_Type
(T
));
767 elsif Is_Record_Type
(T
) then
768 Comp
:= First_Component
(T
);
770 while Present
(Comp
) loop
771 if Has_Simple_Protected_Object
(Etype
(Comp
)) then
775 Next_Component
(Comp
);
783 end Has_Simple_Protected_Object
;
785 ------------------------------
786 -- Is_Simple_Protected_Type --
787 ------------------------------
789 function Is_Simple_Protected_Type
(T
: Entity_Id
) return Boolean is
791 return Is_Protected_Type
(T
) and then not Has_Entries
(T
);
792 end Is_Simple_Protected_Type
;
794 ------------------------------
795 -- Check_Visibly_Controlled --
796 ------------------------------
798 procedure Check_Visibly_Controlled
799 (Prim
: Final_Primitives
;
801 E
: in out Entity_Id
;
802 Cref
: in out Node_Id
)
804 Parent_Type
: Entity_Id
;
808 if Is_Derived_Type
(Typ
)
809 and then Comes_From_Source
(E
)
810 and then not Is_Overriding_Operation
(E
)
812 -- We know that the explicit operation on the type does not override
813 -- the inherited operation of the parent, and that the derivation
814 -- is from a private type that is not visibly controlled.
816 Parent_Type
:= Etype
(Typ
);
817 Op
:= Find_Prim_Op
(Parent_Type
, Name_Of
(Prim
));
822 -- Wrap the object to be initialized into the proper
823 -- unchecked conversion, to be compatible with the operation
826 if Nkind
(Cref
) = N_Unchecked_Type_Conversion
then
827 Cref
:= Unchecked_Convert_To
(Parent_Type
, Expression
(Cref
));
829 Cref
:= Unchecked_Convert_To
(Parent_Type
, Cref
);
833 end Check_Visibly_Controlled
;
835 ---------------------
836 -- Controlled_Type --
837 ---------------------
839 function Controlled_Type
(T
: Entity_Id
) return Boolean is
841 function Has_Some_Controlled_Component
(Rec
: Entity_Id
) return Boolean;
842 -- If type is not frozen yet, check explicitly among its components,
843 -- because flag is not necessarily set.
845 -----------------------------------
846 -- Has_Some_Controlled_Component --
847 -----------------------------------
849 function Has_Some_Controlled_Component
850 (Rec
: Entity_Id
) return Boolean
855 if Has_Controlled_Component
(Rec
) then
858 elsif not Is_Frozen
(Rec
) then
859 if Is_Record_Type
(Rec
) then
860 Comp
:= First_Entity
(Rec
);
862 while Present
(Comp
) loop
863 if not Is_Type
(Comp
)
864 and then Controlled_Type
(Etype
(Comp
))
874 elsif Is_Array_Type
(Rec
) then
875 return Is_Controlled
(Component_Type
(Rec
));
878 return Has_Controlled_Component
(Rec
);
883 end Has_Some_Controlled_Component
;
885 -- Start of processing for Controlled_Type
888 -- Class-wide types must be treated as controlled because they may
889 -- contain an extension that has controlled components
891 -- We can skip this if finalization is not available
893 return (Is_Class_Wide_Type
(T
)
894 and then not In_Finalization_Root
(T
)
895 and then not Restriction_Active
(No_Finalization
))
896 or else Is_Controlled
(T
)
897 or else Has_Some_Controlled_Component
(T
)
898 or else (Is_Concurrent_Type
(T
)
899 and then Present
(Corresponding_Record_Type
(T
))
900 and then Controlled_Type
(Corresponding_Record_Type
(T
)));
903 --------------------------
904 -- Controller_Component --
905 --------------------------
907 function Controller_Component
(Typ
: Entity_Id
) return Entity_Id
is
908 T
: Entity_Id
:= Base_Type
(Typ
);
910 Comp_Scop
: Entity_Id
;
911 Res
: Entity_Id
:= Empty
;
912 Res_Scop
: Entity_Id
:= Empty
;
915 if Is_Class_Wide_Type
(T
) then
919 if Is_Private_Type
(T
) then
920 T
:= Underlying_Type
(T
);
923 -- Fetch the outermost controller
925 Comp
:= First_Entity
(T
);
926 while Present
(Comp
) loop
927 if Chars
(Comp
) = Name_uController
then
928 Comp_Scop
:= Scope
(Original_Record_Component
(Comp
));
930 -- If this controller is at the outermost level, no need to
931 -- look for another one
933 if Comp_Scop
= T
then
936 -- Otherwise record the outermost one and continue looking
938 elsif Res
= Empty
or else Is_Ancestor
(Res_Scop
, Comp_Scop
) then
940 Res_Scop
:= Comp_Scop
;
947 -- If we fall through the loop, there is no controller component
950 end Controller_Component
;
956 function Convert_View
959 Ind
: Pos
:= 1) return Node_Id
961 Fent
: Entity_Id
:= First_Entity
(Proc
);
966 for J
in 2 .. Ind
loop
970 Ftyp
:= Etype
(Fent
);
972 if Nkind
(Arg
) = N_Type_Conversion
973 or else Nkind
(Arg
) = N_Unchecked_Type_Conversion
975 Atyp
:= Entity
(Subtype_Mark
(Arg
));
980 if Is_Abstract
(Proc
) and then Is_Tagged_Type
(Ftyp
) then
981 return Unchecked_Convert_To
(Class_Wide_Type
(Ftyp
), Arg
);
984 and then Present
(Atyp
)
986 (Is_Private_Type
(Ftyp
) or else Is_Private_Type
(Atyp
))
988 Base_Type
(Underlying_Type
(Atyp
)) =
989 Base_Type
(Underlying_Type
(Ftyp
))
991 return Unchecked_Convert_To
(Ftyp
, Arg
);
993 -- If the argument is already a conversion, as generated by
994 -- Make_Init_Call, set the target type to the type of the formal
995 -- directly, to avoid spurious typing problems.
997 elsif (Nkind
(Arg
) = N_Unchecked_Type_Conversion
998 or else Nkind
(Arg
) = N_Type_Conversion
)
999 and then not Is_Class_Wide_Type
(Atyp
)
1001 Set_Subtype_Mark
(Arg
, New_Occurrence_Of
(Ftyp
, Sloc
(Arg
)));
1002 Set_Etype
(Arg
, Ftyp
);
1010 -------------------------------
1011 -- Establish_Transient_Scope --
1012 -------------------------------
1014 -- This procedure is called each time a transient block has to be inserted
1015 -- that is to say for each call to a function with unconstrained ot tagged
1016 -- result. It creates a new scope on the stack scope in order to enclose
1017 -- all transient variables generated
1019 procedure Establish_Transient_Scope
(N
: Node_Id
; Sec_Stack
: Boolean) is
1020 Loc
: constant Source_Ptr
:= Sloc
(N
);
1021 Wrap_Node
: Node_Id
;
1023 Sec_Stk
: constant Boolean :=
1024 Sec_Stack
and not Functions_Return_By_DSP_On_Target
;
1025 -- We never need a secondary stack if functions return by DSP
1028 -- Do not create a transient scope if we are already inside one
1030 for S
in reverse Scope_Stack
.First
.. Scope_Stack
.Last
loop
1032 if Scope_Stack
.Table
(S
).Is_Transient
then
1034 Set_Uses_Sec_Stack
(Scope_Stack
.Table
(S
).Entity
);
1039 -- If we have encountered Standard there are no enclosing
1040 -- transient scopes.
1042 elsif Scope_Stack
.Table
(S
).Entity
= Standard_Standard
then
1048 Wrap_Node
:= Find_Node_To_Be_Wrapped
(N
);
1050 -- Case of no wrap node, false alert, no transient scope needed
1052 if No
(Wrap_Node
) then
1055 -- If the node to wrap is an iteration_scheme, the expression is
1056 -- one of the bounds, and the expansion will make an explicit
1057 -- declaration for it (see Analyze_Iteration_Scheme, sem_ch5.adb),
1058 -- so do not apply any transformations here.
1060 elsif Nkind
(Wrap_Node
) = N_Iteration_Scheme
then
1064 New_Scope
(New_Internal_Entity
(E_Block
, Current_Scope
, Loc
, 'B'));
1065 Set_Scope_Is_Transient
;
1068 Set_Uses_Sec_Stack
(Current_Scope
);
1069 Check_Restriction
(No_Secondary_Stack
, N
);
1072 Set_Etype
(Current_Scope
, Standard_Void_Type
);
1073 Set_Node_To_Be_Wrapped
(Wrap_Node
);
1075 if Debug_Flag_W
then
1076 Write_Str
(" <Transient>");
1080 end Establish_Transient_Scope
;
1082 ----------------------------
1083 -- Expand_Cleanup_Actions --
1084 ----------------------------
1086 procedure Expand_Cleanup_Actions
(N
: Node_Id
) is
1088 S
: constant Entity_Id
:=
1090 Flist
: constant Entity_Id
:=
1091 Finalization_Chain_Entity
(S
);
1092 Is_Task
: constant Boolean :=
1093 (Nkind
(Original_Node
(N
)) = N_Task_Body
);
1094 Is_Master
: constant Boolean :=
1095 Nkind
(N
) /= N_Entry_Body
1096 and then Is_Task_Master
(N
);
1097 Is_Protected
: constant Boolean :=
1098 Nkind
(N
) = N_Subprogram_Body
1099 and then Is_Protected_Subprogram_Body
(N
);
1100 Is_Task_Allocation
: constant Boolean :=
1101 Nkind
(N
) = N_Block_Statement
1102 and then Is_Task_Allocation_Block
(N
);
1103 Is_Asynchronous_Call
: constant Boolean :=
1104 Nkind
(N
) = N_Block_Statement
1105 and then Is_Asynchronous_Call_Block
(N
);
1108 Mark
: Entity_Id
:= Empty
;
1109 New_Decls
: constant List_Id
:= New_List
;
1113 Chain
: Entity_Id
:= Empty
;
1119 -- Compute a location that is not directly in the user code in
1120 -- order to avoid to generate confusing debug info. A good
1121 -- approximation is the name of the outer user-defined scope
1124 S1
: Entity_Id
:= S
;
1127 while not Comes_From_Source
(S1
) and then S1
/= Standard_Standard
loop
1134 -- There are cleanup actions only if the secondary stack needs
1135 -- releasing or some finalizations are needed or in the context
1138 if Uses_Sec_Stack
(Current_Scope
)
1139 and then not Sec_Stack_Needed_For_Return
(Current_Scope
)
1143 and then not Is_Master
1144 and then not Is_Task
1145 and then not Is_Protected
1146 and then not Is_Task_Allocation
1147 and then not Is_Asynchronous_Call
1149 Clean_Simple_Protected_Objects
(N
);
1153 -- If the current scope is the subprogram body that is the rewriting
1154 -- of a task body, and the descriptors have not been delayed (due to
1155 -- some nested instantiations) do not generate redundant cleanup
1156 -- actions: the cleanup procedure already exists for this body.
1158 if Nkind
(N
) = N_Subprogram_Body
1159 and then Nkind
(Original_Node
(N
)) = N_Task_Body
1160 and then not Delay_Subprogram_Descriptors
(Corresponding_Spec
(N
))
1165 -- Set polling off, since we don't need to poll during cleanup
1166 -- actions, and indeed for the cleanup routine, which is executed
1167 -- with aborts deferred, we don't want polling.
1169 Old_Poll
:= Polling_Required
;
1170 Polling_Required
:= False;
1172 -- Make sure we have a declaration list, since we will add to it
1174 if No
(Declarations
(N
)) then
1175 Set_Declarations
(N
, New_List
);
1178 -- The task activation call has already been built for task
1179 -- allocation blocks.
1181 if not Is_Task_Allocation
then
1182 Build_Task_Activation_Call
(N
);
1186 Establish_Task_Master
(N
);
1189 -- If secondary stack is in use, expand:
1190 -- _Mxx : constant Mark_Id := SS_Mark;
1192 -- Suppress calls to SS_Mark and SS_Release if Java_VM,
1193 -- since we never use the secondary stack on the JVM.
1195 if Uses_Sec_Stack
(Current_Scope
)
1196 and then not Sec_Stack_Needed_For_Return
(Current_Scope
)
1197 and then not Java_VM
1199 Mark
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('M'));
1200 Append_To
(New_Decls
,
1201 Make_Object_Declaration
(Loc
,
1202 Defining_Identifier
=> Mark
,
1203 Object_Definition
=> New_Reference_To
(RTE
(RE_Mark_Id
), Loc
),
1205 Make_Function_Call
(Loc
,
1206 Name
=> New_Reference_To
(RTE
(RE_SS_Mark
), Loc
))));
1208 Set_Uses_Sec_Stack
(Current_Scope
, False);
1211 -- If finalization list is present then expand:
1212 -- Local_Final_List : System.FI.Finalizable_Ptr;
1214 if Present
(Flist
) then
1215 Append_To
(New_Decls
,
1216 Make_Object_Declaration
(Loc
,
1217 Defining_Identifier
=> Flist
,
1218 Object_Definition
=>
1219 New_Reference_To
(RTE
(RE_Finalizable_Ptr
), Loc
)));
1222 -- Clean-up procedure definition
1224 Clean
:= Make_Defining_Identifier
(Loc
, Name_uClean
);
1225 Set_Suppress_Elaboration_Warnings
(Clean
);
1226 Append_To
(New_Decls
,
1227 Make_Clean
(N
, Clean
, Mark
, Flist
,
1232 Is_Asynchronous_Call
));
1234 -- If exception handlers are present, wrap the Sequence of
1235 -- statements in a block because it is not possible to get
1236 -- exception handlers and an AT END call in the same scope.
1238 if Present
(Exception_Handlers
(Handled_Statement_Sequence
(N
))) then
1240 -- Preserve end label to provide proper cross-reference information
1242 End_Lab
:= End_Label
(Handled_Statement_Sequence
(N
));
1244 Make_Block_Statement
(Loc
,
1245 Handled_Statement_Sequence
=> Handled_Statement_Sequence
(N
));
1246 Set_Handled_Statement_Sequence
(N
,
1247 Make_Handled_Sequence_Of_Statements
(Loc
, New_List
(Blok
)));
1248 Set_End_Label
(Handled_Statement_Sequence
(N
), End_Lab
);
1251 -- Comment needed here, see RH for 1.306 ???
1253 if Nkind
(N
) = N_Subprogram_Body
then
1254 Set_Has_Nested_Block_With_Handler
(Current_Scope
);
1257 -- Otherwise we do not wrap
1264 -- Don't move the _chain Activation_Chain declaration in task
1265 -- allocation blocks. Task allocation blocks use this object
1266 -- in their cleanup handlers, and gigi complains if it is declared
1267 -- in the sequence of statements of the scope that declares the
1270 if Is_Task_Allocation
then
1271 Chain
:= Activation_Chain_Entity
(N
);
1272 Decl
:= First
(Declarations
(N
));
1274 while Nkind
(Decl
) /= N_Object_Declaration
1275 or else Defining_Identifier
(Decl
) /= Chain
1278 pragma Assert
(Present
(Decl
));
1282 Prepend_To
(New_Decls
, Decl
);
1285 -- Now we move the declarations into the Sequence of statements
1286 -- in order to get them protected by the AT END call. It may seem
1287 -- weird to put declarations in the sequence of statement but in
1288 -- fact nothing forbids that at the tree level. We also set the
1289 -- First_Real_Statement field so that we remember where the real
1290 -- statements (i.e. original statements) begin. Note that if we
1291 -- wrapped the statements, the first real statement is inside the
1292 -- inner block. If the First_Real_Statement is already set (as is
1293 -- the case for subprogram bodies that are expansions of task bodies)
1294 -- then do not reset it, because its declarative part would migrate
1295 -- to the statement part.
1298 if No
(First_Real_Statement
(Handled_Statement_Sequence
(N
))) then
1299 Set_First_Real_Statement
(Handled_Statement_Sequence
(N
),
1300 First
(Statements
(Handled_Statement_Sequence
(N
))));
1304 Set_First_Real_Statement
(Handled_Statement_Sequence
(N
), Blok
);
1307 Append_List_To
(Declarations
(N
),
1308 Statements
(Handled_Statement_Sequence
(N
)));
1309 Set_Statements
(Handled_Statement_Sequence
(N
), Declarations
(N
));
1311 -- We need to reset the Sloc of the handled statement sequence to
1312 -- properly reflect the new initial "statement" in the sequence.
1315 (Handled_Statement_Sequence
(N
), Sloc
(First
(Declarations
(N
))));
1317 -- The declarations of the _Clean procedure and finalization chain
1318 -- replace the old declarations that have been moved inward
1320 Set_Declarations
(N
, New_Decls
);
1321 Analyze_Declarations
(New_Decls
);
1323 -- The At_End call is attached to the sequence of statements
1329 -- If the construct is a protected subprogram, then the call to
1330 -- the corresponding unprotected program appears in a block which
1331 -- is the last statement in the body, and it is this block that
1332 -- must be covered by the At_End handler.
1334 if Is_Protected
then
1335 HSS
:= Handled_Statement_Sequence
1336 (Last
(Statements
(Handled_Statement_Sequence
(N
))));
1338 HSS
:= Handled_Statement_Sequence
(N
);
1341 Set_At_End_Proc
(HSS
, New_Occurrence_Of
(Clean
, Loc
));
1342 Expand_At_End_Handler
(HSS
, Empty
);
1345 -- Restore saved polling mode
1347 Polling_Required
:= Old_Poll
;
1348 end Expand_Cleanup_Actions
;
1350 -------------------------------
1351 -- Expand_Ctrl_Function_Call --
1352 -------------------------------
1354 procedure Expand_Ctrl_Function_Call
(N
: Node_Id
) is
1355 Loc
: constant Source_Ptr
:= Sloc
(N
);
1356 Rtype
: constant Entity_Id
:= Etype
(N
);
1357 Utype
: constant Entity_Id
:= Underlying_Type
(Rtype
);
1360 Action2
: Node_Id
:= Empty
;
1362 Attach_Level
: Uint
:= Uint_1
;
1363 Len_Ref
: Node_Id
:= Empty
;
1365 function Last_Array_Component
1367 Typ
: Entity_Id
) return Node_Id
;
1368 -- Creates a reference to the last component of the array object
1369 -- designated by Ref whose type is Typ.
1371 --------------------------
1372 -- Last_Array_Component --
1373 --------------------------
1375 function Last_Array_Component
1377 Typ
: Entity_Id
) return Node_Id
1379 Index_List
: constant List_Id
:= New_List
;
1382 for N
in 1 .. Number_Dimensions
(Typ
) loop
1383 Append_To
(Index_List
,
1384 Make_Attribute_Reference
(Loc
,
1385 Prefix
=> Duplicate_Subexpr_No_Checks
(Ref
),
1386 Attribute_Name
=> Name_Last
,
1387 Expressions
=> New_List
(
1388 Make_Integer_Literal
(Loc
, N
))));
1392 Make_Indexed_Component
(Loc
,
1393 Prefix
=> Duplicate_Subexpr
(Ref
),
1394 Expressions
=> Index_List
);
1395 end Last_Array_Component
;
1397 -- Start of processing for Expand_Ctrl_Function_Call
1400 -- Optimization, if the returned value (which is on the sec-stack)
1401 -- is returned again, no need to copy/readjust/finalize, we can just
1402 -- pass the value thru (see Expand_N_Return_Statement), and thus no
1403 -- attachment is needed
1405 if Nkind
(Parent
(N
)) = N_Return_Statement
then
1409 -- Resolution is now finished, make sure we don't start analysis again
1410 -- because of the duplication
1413 Ref
:= Duplicate_Subexpr_No_Checks
(N
);
1415 -- Now we can generate the Attach Call, note that this value is
1416 -- always in the (secondary) stack and thus is attached to a singly
1417 -- linked final list:
1419 -- Resx := F (X)'reference;
1420 -- Attach_To_Final_List (_Lx, Resx.all, 1);
1422 -- or when there are controlled components
1424 -- Attach_To_Final_List (_Lx, Resx._controller, 1);
1426 -- or when it is both is_controlled and has_controlled_components
1428 -- Attach_To_Final_List (_Lx, Resx._controller, 1);
1429 -- Attach_To_Final_List (_Lx, Resx, 1);
1431 -- or if it is an array with is_controlled (and has_controlled)
1433 -- Attach_To_Final_List (_Lx, Resx (Resx'last), 3);
1434 -- An attach level of 3 means that a whole array is to be
1435 -- attached to the finalization list (including the controlled
1438 -- or if it is an array with has_controlled components but not
1441 -- Attach_To_Final_List (_Lx, Resx (Resx'last)._controller, 3);
1443 if Has_Controlled_Component
(Rtype
) then
1445 T1
: Entity_Id
:= Rtype
;
1446 T2
: Entity_Id
:= Utype
;
1449 if Is_Array_Type
(T2
) then
1451 Make_Attribute_Reference
(Loc
,
1453 Duplicate_Subexpr_Move_Checks
1454 (Unchecked_Convert_To
(T2
, Ref
)),
1455 Attribute_Name
=> Name_Length
);
1458 while Is_Array_Type
(T2
) loop
1460 Ref
:= Unchecked_Convert_To
(T2
, Ref
);
1463 Ref
:= Last_Array_Component
(Ref
, T2
);
1464 Attach_Level
:= Uint_3
;
1465 T1
:= Component_Type
(T2
);
1466 T2
:= Underlying_Type
(T1
);
1469 -- If the type has controlled components, go to the controller
1470 -- except in the case of arrays of controlled objects since in
1471 -- this case objects and their components are already chained
1472 -- and the head of the chain is the last array element.
1474 if Is_Array_Type
(Rtype
) and then Is_Controlled
(T2
) then
1477 elsif Has_Controlled_Component
(T2
) then
1479 Ref
:= Unchecked_Convert_To
(T2
, Ref
);
1483 Make_Selected_Component
(Loc
,
1485 Selector_Name
=> Make_Identifier
(Loc
, Name_uController
));
1489 -- Here we know that 'Ref' has a controller so we may as well
1490 -- attach it directly
1495 Flist_Ref
=> Find_Final_List
(Current_Scope
),
1496 With_Attach
=> Make_Integer_Literal
(Loc
, Attach_Level
));
1498 -- If it is also Is_Controlled we need to attach the global object
1500 if Is_Controlled
(Rtype
) then
1503 Obj_Ref
=> Duplicate_Subexpr_No_Checks
(N
),
1504 Flist_Ref
=> Find_Final_List
(Current_Scope
),
1505 With_Attach
=> Make_Integer_Literal
(Loc
, Attach_Level
));
1509 -- Here, we have a controlled type that does not seem to have
1510 -- controlled components but it could be a class wide type whose
1511 -- further derivations have controlled components. So we don't know
1512 -- if the object itself needs to be attached or if it
1513 -- has a record controller. We need to call a runtime function
1514 -- (Deep_Tag_Attach) which knows what to do thanks to the
1515 -- RC_Offset in the dispatch table.
1518 Make_Procedure_Call_Statement
(Loc
,
1519 Name
=> New_Reference_To
(RTE
(RE_Deep_Tag_Attach
), Loc
),
1520 Parameter_Associations
=> New_List
(
1521 Find_Final_List
(Current_Scope
),
1523 Make_Attribute_Reference
(Loc
,
1525 Attribute_Name
=> Name_Address
),
1527 Make_Integer_Literal
(Loc
, Attach_Level
)));
1530 if Present
(Len_Ref
) then
1532 Make_Implicit_If_Statement
(N
,
1533 Condition
=> Make_Op_Gt
(Loc
,
1534 Left_Opnd
=> Len_Ref
,
1535 Right_Opnd
=> Make_Integer_Literal
(Loc
, 0)),
1536 Then_Statements
=> New_List
(Action
));
1539 Insert_Action
(N
, Action
);
1540 if Present
(Action2
) then
1541 Insert_Action
(N
, Action2
);
1543 end Expand_Ctrl_Function_Call
;
1545 ---------------------------
1546 -- Expand_N_Package_Body --
1547 ---------------------------
1549 -- Add call to Activate_Tasks if body is an activator (actual
1550 -- processing is in chapter 9).
1552 -- Generate subprogram descriptor for elaboration routine
1554 -- ENcode entity names in package body
1556 procedure Expand_N_Package_Body
(N
: Node_Id
) is
1557 Ent
: constant Entity_Id
:= Corresponding_Spec
(N
);
1560 -- This is done only for non-generic packages
1562 if Ekind
(Ent
) = E_Package
then
1563 New_Scope
(Corresponding_Spec
(N
));
1564 Build_Task_Activation_Call
(N
);
1568 Set_Elaboration_Flag
(N
, Corresponding_Spec
(N
));
1569 Set_In_Package_Body
(Ent
, False);
1571 -- Set to encode entity names in package body before gigi is called
1573 Qualify_Entity_Names
(N
);
1574 end Expand_N_Package_Body
;
1576 ----------------------------------
1577 -- Expand_N_Package_Declaration --
1578 ----------------------------------
1580 -- Add call to Activate_Tasks if there are tasks declared and the
1581 -- package has no body. Note that in Ada83, this may result in
1582 -- premature activation of some tasks, given that we cannot tell
1583 -- whether a body will eventually appear.
1585 procedure Expand_N_Package_Declaration
(N
: Node_Id
) is
1587 if Nkind
(Parent
(N
)) = N_Compilation_Unit
1588 and then not Body_Required
(Parent
(N
))
1589 and then not Unit_Requires_Body
(Defining_Entity
(N
))
1590 and then Present
(Activation_Chain_Entity
(N
))
1592 New_Scope
(Defining_Entity
(N
));
1593 Build_Task_Activation_Call
(N
);
1597 -- Note: it is not necessary to worry about generating a subprogram
1598 -- descriptor, since the only way to get exception handlers into a
1599 -- package spec is to include instantiations, and that would cause
1600 -- generation of subprogram descriptors to be delayed in any case.
1602 -- Set to encode entity names in package spec before gigi is called
1604 Qualify_Entity_Names
(N
);
1605 end Expand_N_Package_Declaration
;
1607 ---------------------
1608 -- Find_Final_List --
1609 ---------------------
1611 function Find_Final_List
1613 Ref
: Node_Id
:= Empty
) return Node_Id
1615 Loc
: constant Source_Ptr
:= Sloc
(Ref
);
1621 -- Case of an internal component. The Final list is the record
1622 -- controller of the enclosing record
1624 if Present
(Ref
) then
1628 when N_Unchecked_Type_Conversion | N_Type_Conversion
=>
1629 R
:= Expression
(R
);
1631 when N_Indexed_Component | N_Explicit_Dereference
=>
1634 when N_Selected_Component
=>
1638 when N_Identifier
=>
1642 raise Program_Error
;
1647 Make_Selected_Component
(Loc
,
1649 Make_Selected_Component
(Loc
,
1651 Selector_Name
=> Make_Identifier
(Loc
, Name_uController
)),
1652 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
1654 -- Case of a dynamically allocated object. The final list is the
1655 -- corresponding list controller (The next entity in the scope of
1656 -- the access type with the right type). If the type comes from a
1657 -- With_Type clause, no controller was created, and we use the
1658 -- global chain instead.
1660 elsif Is_Access_Type
(E
) then
1661 if not From_With_Type
(E
) then
1663 Make_Selected_Component
(Loc
,
1666 (Associated_Final_Chain
(Base_Type
(E
)), Loc
),
1667 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
1669 return New_Reference_To
(RTE
(RE_Global_Final_List
), Sloc
(E
));
1673 if Is_Dynamic_Scope
(E
) then
1676 S
:= Enclosing_Dynamic_Scope
(E
);
1679 -- When the finalization chain entity is 'Error', it means that
1680 -- there should not be any chain at that level and that the
1681 -- enclosing one should be used
1683 -- This is a nasty kludge, see ??? note in exp_ch11
1685 while Finalization_Chain_Entity
(S
) = Error
loop
1686 S
:= Enclosing_Dynamic_Scope
(S
);
1689 if S
= Standard_Standard
then
1690 return New_Reference_To
(RTE
(RE_Global_Final_List
), Sloc
(E
));
1692 if No
(Finalization_Chain_Entity
(S
)) then
1694 Id
:= Make_Defining_Identifier
(Sloc
(S
),
1695 New_Internal_Name
('F'));
1696 Set_Finalization_Chain_Entity
(S
, Id
);
1698 -- Set momentarily some semantics attributes to allow normal
1699 -- analysis of expansions containing references to this chain.
1700 -- Will be fully decorated during the expansion of the scope
1703 Set_Ekind
(Id
, E_Variable
);
1704 Set_Etype
(Id
, RTE
(RE_Finalizable_Ptr
));
1707 return New_Reference_To
(Finalization_Chain_Entity
(S
), Sloc
(E
));
1710 end Find_Final_List
;
1712 -----------------------------
1713 -- Find_Node_To_Be_Wrapped --
1714 -----------------------------
1716 function Find_Node_To_Be_Wrapped
(N
: Node_Id
) return Node_Id
is
1718 The_Parent
: Node_Id
;
1724 pragma Assert
(P
/= Empty
);
1725 The_Parent
:= Parent
(P
);
1727 case Nkind
(The_Parent
) is
1729 -- Simple statement can be wrapped
1734 -- Usually assignments are good candidate for wrapping
1735 -- except when they have been generated as part of a
1736 -- controlled aggregate where the wrapping should take
1737 -- place more globally.
1739 when N_Assignment_Statement
=>
1740 if No_Ctrl_Actions
(The_Parent
) then
1746 -- An entry call statement is a special case if it occurs in
1747 -- the context of a Timed_Entry_Call. In this case we wrap
1748 -- the entire timed entry call.
1750 when N_Entry_Call_Statement |
1751 N_Procedure_Call_Statement
=>
1752 if Nkind
(Parent
(The_Parent
)) = N_Entry_Call_Alternative
1754 (Nkind
(Parent
(Parent
(The_Parent
)))
1755 = N_Timed_Entry_Call
1757 Nkind
(Parent
(Parent
(The_Parent
)))
1758 = N_Conditional_Entry_Call
)
1760 return Parent
(Parent
(The_Parent
));
1765 -- Object declarations are also a boundary for the transient scope
1766 -- even if they are not really wrapped
1767 -- (see Wrap_Transient_Declaration)
1769 when N_Object_Declaration |
1770 N_Object_Renaming_Declaration |
1771 N_Subtype_Declaration
=>
1774 -- The expression itself is to be wrapped if its parent is a
1775 -- compound statement or any other statement where the expression
1776 -- is known to be scalar
1778 when N_Accept_Alternative |
1779 N_Attribute_Definition_Clause |
1782 N_Delay_Alternative |
1783 N_Delay_Until_Statement |
1784 N_Delay_Relative_Statement |
1785 N_Discriminant_Association |
1787 N_Entry_Body_Formal_Part |
1790 N_Iteration_Scheme |
1791 N_Terminate_Alternative
=>
1794 when N_Attribute_Reference
=>
1796 if Is_Procedure_Attribute_Name
1797 (Attribute_Name
(The_Parent
))
1802 -- A raise statement can be wrapped. This will arise when the
1803 -- expression in a raise_with_expression uses the secondary
1804 -- stack, for example.
1806 when N_Raise_Statement
=>
1809 -- If the expression is within the iteration scheme of a loop,
1810 -- we must create a declaration for it, followed by an assignment
1811 -- in order to have a usable statement to wrap.
1813 when N_Loop_Parameter_Specification
=>
1814 return Parent
(The_Parent
);
1816 -- The following nodes contains "dummy calls" which don't
1817 -- need to be wrapped.
1819 when N_Parameter_Specification |
1820 N_Discriminant_Specification |
1821 N_Component_Declaration
=>
1824 -- The return statement is not to be wrapped when the function
1825 -- itself needs wrapping at the outer-level
1827 when N_Return_Statement
=>
1829 Applies_To
: constant Entity_Id
:=
1831 (Return_Statement_Entity
(The_Parent
));
1832 Return_Type
: constant Entity_Id
:= Etype
(Applies_To
);
1834 if Requires_Transient_Scope
(Return_Type
) then
1841 -- If we leave a scope without having been able to find a node to
1842 -- wrap, something is going wrong but this can happen in error
1843 -- situation that are not detected yet (such as a dynamic string
1844 -- in a pragma export)
1846 when N_Subprogram_Body |
1847 N_Package_Declaration |
1849 N_Block_Statement
=>
1852 -- otherwise continue the search
1858 end Find_Node_To_Be_Wrapped
;
1860 ----------------------
1861 -- Global_Flist_Ref --
1862 ----------------------
1864 function Global_Flist_Ref
(Flist_Ref
: Node_Id
) return Boolean is
1868 -- Look for the Global_Final_List
1870 if Is_Entity_Name
(Flist_Ref
) then
1871 Flist
:= Entity
(Flist_Ref
);
1873 -- Look for the final list associated with an access to controlled
1875 elsif Nkind
(Flist_Ref
) = N_Selected_Component
1876 and then Is_Entity_Name
(Prefix
(Flist_Ref
))
1878 Flist
:= Entity
(Prefix
(Flist_Ref
));
1883 return Present
(Flist
)
1884 and then Present
(Scope
(Flist
))
1885 and then Enclosing_Dynamic_Scope
(Flist
) = Standard_Standard
;
1886 end Global_Flist_Ref
;
1888 ----------------------------------
1889 -- Has_New_Controlled_Component --
1890 ----------------------------------
1892 function Has_New_Controlled_Component
(E
: Entity_Id
) return Boolean is
1896 if not Is_Tagged_Type
(E
) then
1897 return Has_Controlled_Component
(E
);
1898 elsif not Is_Derived_Type
(E
) then
1899 return Has_Controlled_Component
(E
);
1902 Comp
:= First_Component
(E
);
1903 while Present
(Comp
) loop
1905 if Chars
(Comp
) = Name_uParent
then
1908 elsif Scope
(Original_Record_Component
(Comp
)) = E
1909 and then Controlled_Type
(Etype
(Comp
))
1914 Next_Component
(Comp
);
1918 end Has_New_Controlled_Component
;
1920 --------------------------
1921 -- In_Finalization_Root --
1922 --------------------------
1924 -- It would seem simpler to test Scope (RTE (RE_Root_Controlled)) but
1925 -- the purpose of this function is to avoid a circular call to Rtsfind
1926 -- which would been caused by such a test.
1928 function In_Finalization_Root
(E
: Entity_Id
) return Boolean is
1929 S
: constant Entity_Id
:= Scope
(E
);
1932 return Chars
(Scope
(S
)) = Name_System
1933 and then Chars
(S
) = Name_Finalization_Root
1934 and then Scope
(Scope
(S
)) = Standard_Standard
;
1935 end In_Finalization_Root
;
1937 ------------------------------------
1938 -- Insert_Actions_In_Scope_Around --
1939 ------------------------------------
1941 procedure Insert_Actions_In_Scope_Around
(N
: Node_Id
) is
1942 SE
: Scope_Stack_Entry
renames Scope_Stack
.Table
(Scope_Stack
.Last
);
1946 -- If the node to be wrapped is the triggering alternative of an
1947 -- asynchronous select, it is not part of a statement list. The
1948 -- actions must be inserted before the Select itself, which is
1949 -- part of some list of statements.
1951 if Nkind
(Parent
(Node_To_Be_Wrapped
)) = N_Triggering_Alternative
then
1952 Target
:= Parent
(Parent
(Node_To_Be_Wrapped
));
1957 if Present
(SE
.Actions_To_Be_Wrapped_Before
) then
1958 Insert_List_Before
(Target
, SE
.Actions_To_Be_Wrapped_Before
);
1959 SE
.Actions_To_Be_Wrapped_Before
:= No_List
;
1962 if Present
(SE
.Actions_To_Be_Wrapped_After
) then
1963 Insert_List_After
(Target
, SE
.Actions_To_Be_Wrapped_After
);
1964 SE
.Actions_To_Be_Wrapped_After
:= No_List
;
1966 end Insert_Actions_In_Scope_Around
;
1968 -----------------------
1969 -- Make_Adjust_Call --
1970 -----------------------
1972 function Make_Adjust_Call
1975 Flist_Ref
: Node_Id
;
1976 With_Attach
: Node_Id
;
1977 Allocator
: Boolean := False) return List_Id
1979 Loc
: constant Source_Ptr
:= Sloc
(Ref
);
1980 Res
: constant List_Id
:= New_List
;
1983 Cref
: Node_Id
:= Ref
;
1985 Attach
: Node_Id
:= With_Attach
;
1988 if Is_Class_Wide_Type
(Typ
) then
1989 Utyp
:= Underlying_Type
(Base_Type
(Root_Type
(Typ
)));
1991 Utyp
:= Underlying_Type
(Base_Type
(Typ
));
1994 Set_Assignment_OK
(Cref
);
1996 -- Deal with non-tagged derivation of private views
1998 if Is_Untagged_Derivation
(Typ
) then
1999 Utyp
:= Underlying_Type
(Root_Type
(Base_Type
(Typ
)));
2000 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
2001 Set_Assignment_OK
(Cref
);
2002 -- To prevent problems with UC see 1.156 RH ???
2005 -- If the underlying_type is a subtype, we are dealing with
2006 -- the completion of a private type. We need to access
2007 -- the base type and generate a conversion to it.
2009 if Utyp
/= Base_Type
(Utyp
) then
2010 pragma Assert
(Is_Private_Type
(Typ
));
2011 Utyp
:= Base_Type
(Utyp
);
2012 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
2015 -- If the object is unanalyzed, set its expected type for use
2016 -- in Convert_View in case an additional conversion is needed.
2018 if No
(Etype
(Cref
))
2019 and then Nkind
(Cref
) /= N_Unchecked_Type_Conversion
2021 Set_Etype
(Cref
, Typ
);
2024 -- We do not need to attach to one of the Global Final Lists
2025 -- the objects whose type is Finalize_Storage_Only
2027 if Finalize_Storage_Only
(Typ
)
2028 and then (Global_Flist_Ref
(Flist_Ref
)
2029 or else Entity
(Constant_Value
(RTE
(RE_Garbage_Collected
)))
2032 Attach
:= Make_Integer_Literal
(Loc
, 0);
2035 -- Special case for allocators: need initialization of the chain
2036 -- pointers. For the 0 case, reset them to null.
2039 pragma Assert
(Nkind
(Attach
) = N_Integer_Literal
);
2041 if Intval
(Attach
) = 0 then
2042 Set_Intval
(Attach
, Uint_4
);
2047 -- Deep_Adjust (Flist_Ref, Ref, Attach);
2049 if Has_Controlled_Component
(Utyp
)
2050 or else Is_Class_Wide_Type
(Typ
)
2052 if Is_Tagged_Type
(Utyp
) then
2053 Proc
:= Find_Prim_Op
(Utyp
, TSS_Deep_Adjust
);
2056 Proc
:= TSS
(Utyp
, TSS_Deep_Adjust
);
2059 Cref
:= Convert_View
(Proc
, Cref
, 2);
2062 Make_Procedure_Call_Statement
(Loc
,
2063 Name
=> New_Reference_To
(Proc
, Loc
),
2064 Parameter_Associations
=>
2065 New_List
(Flist_Ref
, Cref
, Attach
)));
2068 -- if With_Attach then
2069 -- Attach_To_Final_List (Ref, Flist_Ref);
2073 else -- Is_Controlled (Utyp)
2075 Proc
:= Find_Prim_Op
(Utyp
, Name_Of
(Adjust_Case
));
2076 Cref
:= Convert_View
(Proc
, Cref
);
2077 Cref2
:= New_Copy_Tree
(Cref
);
2080 Make_Procedure_Call_Statement
(Loc
,
2081 Name
=> New_Reference_To
(Proc
, Loc
),
2082 Parameter_Associations
=> New_List
(Cref2
)));
2084 Append_To
(Res
, Make_Attach_Call
(Cref
, Flist_Ref
, Attach
));
2088 end Make_Adjust_Call
;
2090 ----------------------
2091 -- Make_Attach_Call --
2092 ----------------------
2095 -- System.FI.Attach_To_Final_List (Flist, Ref, Nb_Link)
2097 function Make_Attach_Call
2099 Flist_Ref
: Node_Id
;
2100 With_Attach
: Node_Id
) return Node_Id
2102 Loc
: constant Source_Ptr
:= Sloc
(Obj_Ref
);
2105 -- Optimization: If the number of links is statically '0', don't
2106 -- call the attach_proc.
2108 if Nkind
(With_Attach
) = N_Integer_Literal
2109 and then Intval
(With_Attach
) = Uint_0
2111 return Make_Null_Statement
(Loc
);
2115 Make_Procedure_Call_Statement
(Loc
,
2116 Name
=> New_Reference_To
(RTE
(RE_Attach_To_Final_List
), Loc
),
2117 Parameter_Associations
=> New_List
(
2119 OK_Convert_To
(RTE
(RE_Finalizable
), Obj_Ref
),
2121 end Make_Attach_Call
;
2133 Is_Master
: Boolean;
2134 Is_Protected_Subprogram
: Boolean;
2135 Is_Task_Allocation_Block
: Boolean;
2136 Is_Asynchronous_Call_Block
: Boolean) return Node_Id
2138 Loc
: constant Source_Ptr
:= Sloc
(Clean
);
2139 Stmt
: constant List_Id
:= New_List
;
2145 Param_Type
: Entity_Id
;
2146 Pid
: Entity_Id
:= Empty
;
2147 Cancel_Param
: Entity_Id
;
2151 if Restricted_Profile
then
2153 (Stmt
, Build_Runtime_Call
(Loc
, RE_Complete_Restricted_Task
));
2155 Append_To
(Stmt
, Build_Runtime_Call
(Loc
, RE_Complete_Task
));
2158 elsif Is_Master
then
2159 if Restriction_Active
(No_Task_Hierarchy
) = False then
2160 Append_To
(Stmt
, Build_Runtime_Call
(Loc
, RE_Complete_Master
));
2163 elsif Is_Protected_Subprogram
then
2165 -- Add statements to the cleanup handler of the (ordinary)
2166 -- subprogram expanded to implement a protected subprogram,
2167 -- unlocking the protected object parameter and undeferring abort.
2168 -- If this is a protected procedure, and the object contains
2169 -- entries, this also calls the entry service routine.
2171 -- NOTE: This cleanup handler references _object, a parameter
2172 -- to the procedure.
2174 -- Find the _object parameter representing the protected object
2176 Spec
:= Parent
(Corresponding_Spec
(N
));
2178 Param
:= First
(Parameter_Specifications
(Spec
));
2180 Param_Type
:= Etype
(Parameter_Type
(Param
));
2182 if Ekind
(Param_Type
) = E_Record_Type
then
2183 Pid
:= Corresponding_Concurrent_Type
(Param_Type
);
2186 exit when No
(Param
) or else Present
(Pid
);
2190 pragma Assert
(Present
(Param
));
2192 -- If the associated protected object declares entries,
2193 -- a protected procedure has to service entry queues.
2194 -- In this case, add
2196 -- Service_Entries (_object._object'Access);
2198 -- _object is the record used to implement the protected object.
2199 -- It is a parameter to the protected subprogram.
2201 if Nkind
(Specification
(N
)) = N_Procedure_Specification
2202 and then Has_Entries
(Pid
)
2205 or else Restriction_Active
(No_Entry_Queue
) = False
2206 or else Number_Entries
(Pid
) > 1
2208 Name
:= New_Reference_To
(RTE
(RE_Service_Entries
), Loc
);
2210 Name
:= New_Reference_To
(RTE
(RE_Service_Entry
), Loc
);
2214 Make_Procedure_Call_Statement
(Loc
,
2216 Parameter_Associations
=> New_List
(
2217 Make_Attribute_Reference
(Loc
,
2219 Make_Selected_Component
(Loc
,
2220 Prefix
=> New_Reference_To
(
2221 Defining_Identifier
(Param
), Loc
),
2223 Make_Identifier
(Loc
, Name_uObject
)),
2224 Attribute_Name
=> Name_Unchecked_Access
))));
2227 -- Unlock (_object._object'Access);
2229 -- object is the record used to implement the protected object.
2230 -- It is a parameter to the protected subprogram.
2232 -- If the protected object is controlled (i.e it has entries or
2233 -- needs finalization for interrupt handling), call
2234 -- Unlock_Entries, except if the protected object follows the
2235 -- ravenscar profile, in which case call Unlock_Entry, otherwise
2236 -- call the simplified version, Unlock.
2238 if Has_Entries
(Pid
)
2239 or else Has_Interrupt_Handler
(Pid
)
2240 or else (Has_Attach_Handler
(Pid
)
2241 and then not Restricted_Profile
)
2242 or else (Ada_Version
>= Ada_05
2243 and then Present
(Interface_List
(Parent
(Pid
))))
2246 or else Restriction_Active
(No_Entry_Queue
) = False
2247 or else Number_Entries
(Pid
) > 1
2249 Name
:= New_Reference_To
(RTE
(RE_Unlock_Entries
), Loc
);
2251 Name
:= New_Reference_To
(RTE
(RE_Unlock_Entry
), Loc
);
2255 Name
:= New_Reference_To
(RTE
(RE_Unlock
), Loc
);
2259 Make_Procedure_Call_Statement
(Loc
,
2261 Parameter_Associations
=> New_List
(
2262 Make_Attribute_Reference
(Loc
,
2264 Make_Selected_Component
(Loc
,
2266 New_Reference_To
(Defining_Identifier
(Param
), Loc
),
2268 Make_Identifier
(Loc
, Name_uObject
)),
2269 Attribute_Name
=> Name_Unchecked_Access
))));
2272 if Abort_Allowed
then
2277 Make_Procedure_Call_Statement
(Loc
,
2280 RTE
(RE_Abort_Undefer
), Loc
),
2281 Parameter_Associations
=> Empty_List
));
2284 elsif Is_Task_Allocation_Block
then
2286 -- Add a call to Expunge_Unactivated_Tasks to the cleanup
2287 -- handler of a block created for the dynamic allocation of
2290 -- Expunge_Unactivated_Tasks (_chain);
2292 -- where _chain is the list of tasks created by the allocator
2293 -- but not yet activated. This list will be empty unless
2294 -- the block completes abnormally.
2296 -- This only applies to dynamically allocated tasks;
2297 -- other unactivated tasks are completed by Complete_Task or
2300 -- NOTE: This cleanup handler references _chain, a local
2304 Make_Procedure_Call_Statement
(Loc
,
2307 RTE
(RE_Expunge_Unactivated_Tasks
), Loc
),
2308 Parameter_Associations
=> New_List
(
2309 New_Reference_To
(Activation_Chain_Entity
(N
), Loc
))));
2311 elsif Is_Asynchronous_Call_Block
then
2313 -- Add a call to attempt to cancel the asynchronous entry call
2314 -- whenever the block containing the abortable part is exited.
2316 -- NOTE: This cleanup handler references C, a local object
2318 -- Get the argument to the Cancel procedure
2319 Cancel_Param
:= Entry_Cancel_Parameter
(Entity
(Identifier
(N
)));
2321 -- If it is of type Communication_Block, this must be a
2322 -- protected entry call.
2324 if Is_RTE
(Etype
(Cancel_Param
), RE_Communication_Block
) then
2328 -- if Enqueued (Cancel_Parameter) then
2330 Make_Implicit_If_Statement
(Clean
,
2331 Condition
=> Make_Function_Call
(Loc
,
2332 Name
=> New_Reference_To
(
2333 RTE
(RE_Enqueued
), Loc
),
2334 Parameter_Associations
=> New_List
(
2335 New_Reference_To
(Cancel_Param
, Loc
))),
2336 Then_Statements
=> New_List
(
2338 -- Cancel_Protected_Entry_Call (Cancel_Param);
2340 Make_Procedure_Call_Statement
(Loc
,
2341 Name
=> New_Reference_To
(
2342 RTE
(RE_Cancel_Protected_Entry_Call
), Loc
),
2343 Parameter_Associations
=> New_List
(
2344 New_Reference_To
(Cancel_Param
, Loc
))))));
2346 -- Asynchronous delay
2348 elsif Is_RTE
(Etype
(Cancel_Param
), RE_Delay_Block
) then
2350 Make_Procedure_Call_Statement
(Loc
,
2351 Name
=> New_Reference_To
(RTE
(RE_Cancel_Async_Delay
), Loc
),
2352 Parameter_Associations
=> New_List
(
2353 Make_Attribute_Reference
(Loc
,
2354 Prefix
=> New_Reference_To
(Cancel_Param
, Loc
),
2355 Attribute_Name
=> Name_Unchecked_Access
))));
2360 -- Append call to Cancel_Task_Entry_Call (C);
2363 Make_Procedure_Call_Statement
(Loc
,
2364 Name
=> New_Reference_To
(
2365 RTE
(RE_Cancel_Task_Entry_Call
),
2367 Parameter_Associations
=> New_List
(
2368 New_Reference_To
(Cancel_Param
, Loc
))));
2373 if Present
(Flist
) then
2375 Make_Procedure_Call_Statement
(Loc
,
2376 Name
=> New_Reference_To
(RTE
(RE_Finalize_List
), Loc
),
2377 Parameter_Associations
=> New_List
(
2378 New_Reference_To
(Flist
, Loc
))));
2381 if Present
(Mark
) then
2383 Make_Procedure_Call_Statement
(Loc
,
2384 Name
=> New_Reference_To
(RTE
(RE_SS_Release
), Loc
),
2385 Parameter_Associations
=> New_List
(
2386 New_Reference_To
(Mark
, Loc
))));
2390 Make_Subprogram_Body
(Loc
,
2392 Make_Procedure_Specification
(Loc
,
2393 Defining_Unit_Name
=> Clean
),
2395 Declarations
=> New_List
,
2397 Handled_Statement_Sequence
=>
2398 Make_Handled_Sequence_Of_Statements
(Loc
,
2399 Statements
=> Stmt
));
2401 if Present
(Flist
) or else Is_Task
or else Is_Master
then
2402 Wrap_Cleanup_Procedure
(Sbody
);
2405 -- We do not want debug information for _Clean routines,
2406 -- since it just confuses the debugging operation unless
2407 -- we are debugging generated code.
2409 if not Debug_Generated_Code
then
2410 Set_Debug_Info_Off
(Clean
, True);
2416 --------------------------
2417 -- Make_Deep_Array_Body --
2418 --------------------------
2420 -- Array components are initialized and adjusted in the normal order
2421 -- and finalized in the reverse order. Exceptions are handled and
2422 -- Program_Error is re-raise in the Adjust and Finalize case
2423 -- (RM 7.6.1(12)). Generate the following code :
2425 -- procedure Deep_<P> -- with <P> being Initialize or Adjust or Finalize
2426 -- (L : in out Finalizable_Ptr;
2430 -- for J1 in Typ'First (1) .. Typ'Last (1) loop
2431 -- ^ reverse ^ -- in the finalization case
2433 -- for J2 in Typ'First (n) .. Typ'Last (n) loop
2434 -- Make_<P>_Call (Typ, V (J1, .. , Jn), L, V);
2438 -- exception -- not in the
2439 -- when others => raise Program_Error; -- Initialize case
2442 function Make_Deep_Array_Body
2443 (Prim
: Final_Primitives
;
2444 Typ
: Entity_Id
) return List_Id
2446 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
2448 Index_List
: constant List_Id
:= New_List
;
2449 -- Stores the list of references to the indexes (one per dimension)
2451 function One_Component
return List_Id
;
2452 -- Create one statement to initialize/adjust/finalize one array
2453 -- component, designated by a full set of indices.
2455 function One_Dimension
(N
: Int
) return List_Id
;
2456 -- Create loop to deal with one dimension of the array. The single
2457 -- statement in the body of the loop initializes the inner dimensions if
2458 -- any, or else a single component.
2464 function One_Component
return List_Id
is
2465 Comp_Typ
: constant Entity_Id
:= Component_Type
(Typ
);
2466 Comp_Ref
: constant Node_Id
:=
2467 Make_Indexed_Component
(Loc
,
2468 Prefix
=> Make_Identifier
(Loc
, Name_V
),
2469 Expressions
=> Index_List
);
2472 -- Set the etype of the component Reference, which is used to
2473 -- determine whether a conversion to a parent type is needed.
2475 Set_Etype
(Comp_Ref
, Comp_Typ
);
2478 when Initialize_Case
=>
2479 return Make_Init_Call
(Comp_Ref
, Comp_Typ
,
2480 Make_Identifier
(Loc
, Name_L
),
2481 Make_Identifier
(Loc
, Name_B
));
2484 return Make_Adjust_Call
(Comp_Ref
, Comp_Typ
,
2485 Make_Identifier
(Loc
, Name_L
),
2486 Make_Identifier
(Loc
, Name_B
));
2488 when Finalize_Case
=>
2489 return Make_Final_Call
(Comp_Ref
, Comp_Typ
,
2490 Make_Identifier
(Loc
, Name_B
));
2498 function One_Dimension
(N
: Int
) return List_Id
is
2502 if N
> Number_Dimensions
(Typ
) then
2503 return One_Component
;
2507 Make_Defining_Identifier
(Loc
, New_External_Name
('J', N
));
2509 Append_To
(Index_List
, New_Reference_To
(Index
, Loc
));
2512 Make_Implicit_Loop_Statement
(Typ
,
2513 Identifier
=> Empty
,
2515 Make_Iteration_Scheme
(Loc
,
2516 Loop_Parameter_Specification
=>
2517 Make_Loop_Parameter_Specification
(Loc
,
2518 Defining_Identifier
=> Index
,
2519 Discrete_Subtype_Definition
=>
2520 Make_Attribute_Reference
(Loc
,
2521 Prefix
=> Make_Identifier
(Loc
, Name_V
),
2522 Attribute_Name
=> Name_Range
,
2523 Expressions
=> New_List
(
2524 Make_Integer_Literal
(Loc
, N
))),
2525 Reverse_Present
=> Prim
= Finalize_Case
)),
2526 Statements
=> One_Dimension
(N
+ 1)));
2530 -- Start of processing for Make_Deep_Array_Body
2533 return One_Dimension
(1);
2534 end Make_Deep_Array_Body
;
2536 --------------------
2537 -- Make_Deep_Proc --
2538 --------------------
2541 -- procedure DEEP_<prim>
2542 -- (L : IN OUT Finalizable_Ptr; -- not for Finalize
2543 -- V : IN OUT <typ>;
2544 -- B : IN Short_Short_Integer) is
2547 -- exception -- Finalize and Adjust Cases only
2548 -- raise Program_Error; -- idem
2551 function Make_Deep_Proc
2552 (Prim
: Final_Primitives
;
2554 Stmts
: List_Id
) return Entity_Id
2556 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
2558 Proc_Name
: Entity_Id
;
2559 Handler
: List_Id
:= No_List
;
2563 if Prim
= Finalize_Case
then
2564 Formals
:= New_List
;
2565 Type_B
:= Standard_Boolean
;
2568 Formals
:= New_List
(
2569 Make_Parameter_Specification
(Loc
,
2570 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_L
),
2572 Out_Present
=> True,
2574 New_Reference_To
(RTE
(RE_Finalizable_Ptr
), Loc
)));
2575 Type_B
:= Standard_Short_Short_Integer
;
2579 Make_Parameter_Specification
(Loc
,
2580 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_V
),
2582 Out_Present
=> True,
2583 Parameter_Type
=> New_Reference_To
(Typ
, Loc
)));
2586 Make_Parameter_Specification
(Loc
,
2587 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_B
),
2588 Parameter_Type
=> New_Reference_To
(Type_B
, Loc
)));
2590 if Prim
= Finalize_Case
or else Prim
= Adjust_Case
then
2591 Handler
:= New_List
(
2592 Make_Exception_Handler
(Loc
,
2593 Exception_Choices
=> New_List
(Make_Others_Choice
(Loc
)),
2594 Statements
=> New_List
(
2595 Make_Raise_Program_Error
(Loc
,
2596 Reason
=> PE_Finalize_Raised_Exception
))));
2600 Make_Defining_Identifier
(Loc
,
2601 Chars
=> Make_TSS_Name
(Typ
, Deep_Name_Of
(Prim
)));
2604 Make_Subprogram_Body
(Loc
,
2606 Make_Procedure_Specification
(Loc
,
2607 Defining_Unit_Name
=> Proc_Name
,
2608 Parameter_Specifications
=> Formals
),
2610 Declarations
=> Empty_List
,
2611 Handled_Statement_Sequence
=>
2612 Make_Handled_Sequence_Of_Statements
(Loc
,
2613 Statements
=> Stmts
,
2614 Exception_Handlers
=> Handler
)));
2619 ---------------------------
2620 -- Make_Deep_Record_Body --
2621 ---------------------------
2623 -- The Deep procedures call the appropriate Controlling proc on the
2624 -- the controller component. In the init case, it also attach the
2625 -- controller to the current finalization list.
2627 function Make_Deep_Record_Body
2628 (Prim
: Final_Primitives
;
2629 Typ
: Entity_Id
) return List_Id
2631 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
2632 Controller_Typ
: Entity_Id
;
2633 Obj_Ref
: constant Node_Id
:= Make_Identifier
(Loc
, Name_V
);
2634 Controller_Ref
: constant Node_Id
:=
2635 Make_Selected_Component
(Loc
,
2638 Make_Identifier
(Loc
, Name_uController
));
2639 Res
: constant List_Id
:= New_List
;
2642 if Is_Inherently_Limited_Type
(Typ
) then
2643 Controller_Typ
:= RTE
(RE_Limited_Record_Controller
);
2645 Controller_Typ
:= RTE
(RE_Record_Controller
);
2649 when Initialize_Case
=>
2650 Append_List_To
(Res
,
2652 Ref
=> Controller_Ref
,
2653 Typ
=> Controller_Typ
,
2654 Flist_Ref
=> Make_Identifier
(Loc
, Name_L
),
2655 With_Attach
=> Make_Identifier
(Loc
, Name_B
)));
2657 -- When the type is also a controlled type by itself,
2658 -- Initialize it and attach it to the finalization chain
2660 if Is_Controlled
(Typ
) then
2662 Make_Procedure_Call_Statement
(Loc
,
2663 Name
=> New_Reference_To
(
2664 Find_Prim_Op
(Typ
, Name_Of
(Prim
)), Loc
),
2665 Parameter_Associations
=>
2666 New_List
(New_Copy_Tree
(Obj_Ref
))));
2668 Append_To
(Res
, Make_Attach_Call
(
2669 Obj_Ref
=> New_Copy_Tree
(Obj_Ref
),
2670 Flist_Ref
=> Make_Identifier
(Loc
, Name_L
),
2671 With_Attach
=> Make_Identifier
(Loc
, Name_B
)));
2675 Append_List_To
(Res
,
2676 Make_Adjust_Call
(Controller_Ref
, Controller_Typ
,
2677 Make_Identifier
(Loc
, Name_L
),
2678 Make_Identifier
(Loc
, Name_B
)));
2680 -- When the type is also a controlled type by itself,
2681 -- Adjust it it and attach it to the finalization chain
2683 if Is_Controlled
(Typ
) then
2685 Make_Procedure_Call_Statement
(Loc
,
2686 Name
=> New_Reference_To
(
2687 Find_Prim_Op
(Typ
, Name_Of
(Prim
)), Loc
),
2688 Parameter_Associations
=>
2689 New_List
(New_Copy_Tree
(Obj_Ref
))));
2691 Append_To
(Res
, Make_Attach_Call
(
2692 Obj_Ref
=> New_Copy_Tree
(Obj_Ref
),
2693 Flist_Ref
=> Make_Identifier
(Loc
, Name_L
),
2694 With_Attach
=> Make_Identifier
(Loc
, Name_B
)));
2697 when Finalize_Case
=>
2698 if Is_Controlled
(Typ
) then
2700 Make_Implicit_If_Statement
(Obj_Ref
,
2701 Condition
=> Make_Identifier
(Loc
, Name_B
),
2702 Then_Statements
=> New_List
(
2703 Make_Procedure_Call_Statement
(Loc
,
2704 Name
=> New_Reference_To
(RTE
(RE_Finalize_One
), Loc
),
2705 Parameter_Associations
=> New_List
(
2706 OK_Convert_To
(RTE
(RE_Finalizable
),
2707 New_Copy_Tree
(Obj_Ref
))))),
2709 Else_Statements
=> New_List
(
2710 Make_Procedure_Call_Statement
(Loc
,
2711 Name
=> New_Reference_To
(
2712 Find_Prim_Op
(Typ
, Name_Of
(Prim
)), Loc
),
2713 Parameter_Associations
=>
2714 New_List
(New_Copy_Tree
(Obj_Ref
))))));
2717 Append_List_To
(Res
,
2718 Make_Final_Call
(Controller_Ref
, Controller_Typ
,
2719 Make_Identifier
(Loc
, Name_B
)));
2722 end Make_Deep_Record_Body
;
2724 ----------------------
2725 -- Make_Final_Call --
2726 ----------------------
2728 function Make_Final_Call
2731 With_Detach
: Node_Id
) return List_Id
2733 Loc
: constant Source_Ptr
:= Sloc
(Ref
);
2734 Res
: constant List_Id
:= New_List
;
2741 if Is_Class_Wide_Type
(Typ
) then
2742 Utyp
:= Root_Type
(Typ
);
2745 elsif Is_Concurrent_Type
(Typ
) then
2746 Utyp
:= Corresponding_Record_Type
(Typ
);
2747 Cref
:= Convert_Concurrent
(Ref
, Typ
);
2749 elsif Is_Private_Type
(Typ
)
2750 and then Present
(Full_View
(Typ
))
2751 and then Is_Concurrent_Type
(Full_View
(Typ
))
2753 Utyp
:= Corresponding_Record_Type
(Full_View
(Typ
));
2754 Cref
:= Convert_Concurrent
(Ref
, Full_View
(Typ
));
2760 Utyp
:= Underlying_Type
(Base_Type
(Utyp
));
2761 Set_Assignment_OK
(Cref
);
2763 -- Deal with non-tagged derivation of private views. If the parent is
2764 -- now known to be protected, the finalization routine is the one
2765 -- defined on the corresponding record of the ancestor (corresponding
2766 -- records do not automatically inherit operations, but maybe they
2769 if Is_Untagged_Derivation
(Typ
) then
2770 if Is_Protected_Type
(Typ
) then
2771 Utyp
:= Corresponding_Record_Type
(Root_Type
(Base_Type
(Typ
)));
2773 Utyp
:= Underlying_Type
(Root_Type
(Base_Type
(Typ
)));
2776 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
2778 -- We need to set Assignment_OK to prevent problems with unchecked
2779 -- conversions, where we do not want them to be converted back in the
2780 -- case of untagged record derivation (see code in Make_*_Call
2781 -- procedures for similar situations).
2783 Set_Assignment_OK
(Cref
);
2786 -- If the underlying_type is a subtype, we are dealing with
2787 -- the completion of a private type. We need to access
2788 -- the base type and generate a conversion to it.
2790 if Utyp
/= Base_Type
(Utyp
) then
2791 pragma Assert
(Is_Private_Type
(Typ
));
2792 Utyp
:= Base_Type
(Utyp
);
2793 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
2797 -- Deep_Finalize (Ref, With_Detach);
2799 if Has_Controlled_Component
(Utyp
)
2800 or else Is_Class_Wide_Type
(Typ
)
2802 if Is_Tagged_Type
(Utyp
) then
2803 Proc
:= Find_Prim_Op
(Utyp
, TSS_Deep_Finalize
);
2805 Proc
:= TSS
(Utyp
, TSS_Deep_Finalize
);
2808 Cref
:= Convert_View
(Proc
, Cref
);
2811 Make_Procedure_Call_Statement
(Loc
,
2812 Name
=> New_Reference_To
(Proc
, Loc
),
2813 Parameter_Associations
=>
2814 New_List
(Cref
, With_Detach
)));
2817 -- if With_Detach then
2818 -- Finalize_One (Ref);
2824 Proc
:= Find_Prim_Op
(Utyp
, Name_Of
(Finalize_Case
));
2826 if Chars
(With_Detach
) = Chars
(Standard_True
) then
2828 Make_Procedure_Call_Statement
(Loc
,
2829 Name
=> New_Reference_To
(RTE
(RE_Finalize_One
), Loc
),
2830 Parameter_Associations
=> New_List
(
2831 OK_Convert_To
(RTE
(RE_Finalizable
), Cref
))));
2833 elsif Chars
(With_Detach
) = Chars
(Standard_False
) then
2835 Make_Procedure_Call_Statement
(Loc
,
2836 Name
=> New_Reference_To
(Proc
, Loc
),
2837 Parameter_Associations
=>
2838 New_List
(Convert_View
(Proc
, Cref
))));
2841 Cref2
:= New_Copy_Tree
(Cref
);
2843 Make_Implicit_If_Statement
(Ref
,
2844 Condition
=> With_Detach
,
2845 Then_Statements
=> New_List
(
2846 Make_Procedure_Call_Statement
(Loc
,
2847 Name
=> New_Reference_To
(RTE
(RE_Finalize_One
), Loc
),
2848 Parameter_Associations
=> New_List
(
2849 OK_Convert_To
(RTE
(RE_Finalizable
), Cref
)))),
2851 Else_Statements
=> New_List
(
2852 Make_Procedure_Call_Statement
(Loc
,
2853 Name
=> New_Reference_To
(Proc
, Loc
),
2854 Parameter_Associations
=>
2855 New_List
(Convert_View
(Proc
, Cref2
))))));
2860 end Make_Final_Call
;
2862 --------------------
2863 -- Make_Init_Call --
2864 --------------------
2866 function Make_Init_Call
2869 Flist_Ref
: Node_Id
;
2870 With_Attach
: Node_Id
) return List_Id
2872 Loc
: constant Source_Ptr
:= Sloc
(Ref
);
2874 Res
: constant List_Id
:= New_List
;
2879 Attach
: Node_Id
:= With_Attach
;
2882 if Is_Concurrent_Type
(Typ
) then
2884 Utyp
:= Corresponding_Record_Type
(Typ
);
2885 Cref
:= Convert_Concurrent
(Ref
, Typ
);
2887 elsif Is_Private_Type
(Typ
)
2888 and then Present
(Full_View
(Typ
))
2889 and then Is_Concurrent_Type
(Underlying_Type
(Typ
))
2892 Utyp
:= Corresponding_Record_Type
(Underlying_Type
(Typ
));
2893 Cref
:= Convert_Concurrent
(Ref
, Underlying_Type
(Typ
));
2901 Utyp
:= Underlying_Type
(Base_Type
(Utyp
));
2903 Set_Assignment_OK
(Cref
);
2905 -- Deal with non-tagged derivation of private views
2907 if Is_Untagged_Derivation
(Typ
)
2908 and then not Is_Conc
2910 Utyp
:= Underlying_Type
(Root_Type
(Base_Type
(Typ
)));
2911 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
2912 Set_Assignment_OK
(Cref
);
2913 -- To prevent problems with UC see 1.156 RH ???
2916 -- If the underlying_type is a subtype, we are dealing with
2917 -- the completion of a private type. We need to access
2918 -- the base type and generate a conversion to it.
2920 if Utyp
/= Base_Type
(Utyp
) then
2921 pragma Assert
(Is_Private_Type
(Typ
));
2922 Utyp
:= Base_Type
(Utyp
);
2923 Cref
:= Unchecked_Convert_To
(Utyp
, Cref
);
2926 -- We do not need to attach to one of the Global Final Lists
2927 -- the objects whose type is Finalize_Storage_Only
2929 if Finalize_Storage_Only
(Typ
)
2930 and then (Global_Flist_Ref
(Flist_Ref
)
2931 or else Entity
(Constant_Value
(RTE
(RE_Garbage_Collected
)))
2934 Attach
:= Make_Integer_Literal
(Loc
, 0);
2938 -- Deep_Initialize (Ref, Flist_Ref);
2940 if Has_Controlled_Component
(Utyp
) then
2941 Proc
:= TSS
(Utyp
, Deep_Name_Of
(Initialize_Case
));
2943 Cref
:= Convert_View
(Proc
, Cref
, 2);
2946 Make_Procedure_Call_Statement
(Loc
,
2947 Name
=> New_Reference_To
(Proc
, Loc
),
2948 Parameter_Associations
=> New_List
(
2954 -- Attach_To_Final_List (Ref, Flist_Ref);
2955 -- Initialize (Ref);
2957 else -- Is_Controlled (Utyp)
2958 Proc
:= Find_Prim_Op
(Utyp
, Name_Of
(Initialize_Case
));
2959 Check_Visibly_Controlled
(Initialize_Case
, Typ
, Proc
, Cref
);
2961 Cref
:= Convert_View
(Proc
, Cref
);
2962 Cref2
:= New_Copy_Tree
(Cref
);
2965 Make_Procedure_Call_Statement
(Loc
,
2966 Name
=> New_Reference_To
(Proc
, Loc
),
2967 Parameter_Associations
=> New_List
(Cref2
)));
2970 Make_Attach_Call
(Cref
, Flist_Ref
, Attach
));
2976 --------------------------
2977 -- Make_Transient_Block --
2978 --------------------------
2980 -- If finalization is involved, this function just wraps the instruction
2981 -- into a block whose name is the transient block entity, and then
2982 -- Expand_Cleanup_Actions (called on the expansion of the handled
2983 -- sequence of statements will do the necessary expansions for
2986 function Make_Transient_Block
2988 Action
: Node_Id
) return Node_Id
2990 Flist
: constant Entity_Id
:= Finalization_Chain_Entity
(Current_Scope
);
2991 Decls
: constant List_Id
:= New_List
;
2992 Par
: constant Node_Id
:= Parent
(Action
);
2993 Instrs
: constant List_Id
:= New_List
(Action
);
2997 -- Case where only secondary stack use is involved
2999 if Uses_Sec_Stack
(Current_Scope
)
3001 and then Nkind
(Action
) /= N_Return_Statement
3002 and then Nkind
(Par
) /= N_Exception_Handler
3009 S
:= Scope
(Current_Scope
);
3013 -- At the outer level, no need to release the sec stack
3015 if S
= Standard_Standard
then
3016 Set_Uses_Sec_Stack
(Current_Scope
, False);
3019 -- In a function, only release the sec stack if the
3020 -- function does not return on the sec stack otherwise
3021 -- the result may be lost. The caller is responsible for
3024 elsif K
= E_Function
then
3025 Set_Uses_Sec_Stack
(Current_Scope
, False);
3027 if not Requires_Transient_Scope
(Etype
(S
)) then
3028 if not Functions_Return_By_DSP_On_Target
then
3029 Set_Uses_Sec_Stack
(S
, True);
3030 Check_Restriction
(No_Secondary_Stack
, Action
);
3036 -- In a loop or entry we should install a block encompassing
3037 -- all the construct. For now just release right away.
3039 elsif K
= E_Loop
or else K
= E_Entry
then
3042 -- In a procedure or a block, we release on exit of the
3043 -- procedure or block. ??? memory leak can be created by
3046 elsif K
= E_Procedure
3049 if not Functions_Return_By_DSP_On_Target
then
3050 Set_Uses_Sec_Stack
(S
, True);
3051 Check_Restriction
(No_Secondary_Stack
, Action
);
3054 Set_Uses_Sec_Stack
(Current_Scope
, False);
3064 -- Insert actions stuck in the transient scopes as well as all
3065 -- freezing nodes needed by those actions
3067 Insert_Actions_In_Scope_Around
(Action
);
3070 Last_Inserted
: Node_Id
:= Prev
(Action
);
3073 if Present
(Last_Inserted
) then
3074 Freeze_All
(First_Entity
(Current_Scope
), Last_Inserted
);
3079 Make_Block_Statement
(Loc
,
3080 Identifier
=> New_Reference_To
(Current_Scope
, Loc
),
3081 Declarations
=> Decls
,
3082 Handled_Statement_Sequence
=>
3083 Make_Handled_Sequence_Of_Statements
(Loc
, Statements
=> Instrs
),
3084 Has_Created_Identifier
=> True);
3086 -- When the transient scope was established, we pushed the entry for
3087 -- the transient scope onto the scope stack, so that the scope was
3088 -- active for the installation of finalizable entities etc. Now we
3089 -- must remove this entry, since we have constructed a proper block.
3094 end Make_Transient_Block
;
3096 ------------------------
3097 -- Node_To_Be_Wrapped --
3098 ------------------------
3100 function Node_To_Be_Wrapped
return Node_Id
is
3102 return Scope_Stack
.Table
(Scope_Stack
.Last
).Node_To_Be_Wrapped
;
3103 end Node_To_Be_Wrapped
;
3105 ----------------------------
3106 -- Set_Node_To_Be_Wrapped --
3107 ----------------------------
3109 procedure Set_Node_To_Be_Wrapped
(N
: Node_Id
) is
3111 Scope_Stack
.Table
(Scope_Stack
.Last
).Node_To_Be_Wrapped
:= N
;
3112 end Set_Node_To_Be_Wrapped
;
3114 ----------------------------------
3115 -- Store_After_Actions_In_Scope --
3116 ----------------------------------
3118 procedure Store_After_Actions_In_Scope
(L
: List_Id
) is
3119 SE
: Scope_Stack_Entry
renames Scope_Stack
.Table
(Scope_Stack
.Last
);
3122 if Present
(SE
.Actions_To_Be_Wrapped_After
) then
3123 Insert_List_Before_And_Analyze
(
3124 First
(SE
.Actions_To_Be_Wrapped_After
), L
);
3127 SE
.Actions_To_Be_Wrapped_After
:= L
;
3129 if Is_List_Member
(SE
.Node_To_Be_Wrapped
) then
3130 Set_Parent
(L
, Parent
(SE
.Node_To_Be_Wrapped
));
3132 Set_Parent
(L
, SE
.Node_To_Be_Wrapped
);
3137 end Store_After_Actions_In_Scope
;
3139 -----------------------------------
3140 -- Store_Before_Actions_In_Scope --
3141 -----------------------------------
3143 procedure Store_Before_Actions_In_Scope
(L
: List_Id
) is
3144 SE
: Scope_Stack_Entry
renames Scope_Stack
.Table
(Scope_Stack
.Last
);
3147 if Present
(SE
.Actions_To_Be_Wrapped_Before
) then
3148 Insert_List_After_And_Analyze
(
3149 Last
(SE
.Actions_To_Be_Wrapped_Before
), L
);
3152 SE
.Actions_To_Be_Wrapped_Before
:= L
;
3154 if Is_List_Member
(SE
.Node_To_Be_Wrapped
) then
3155 Set_Parent
(L
, Parent
(SE
.Node_To_Be_Wrapped
));
3157 Set_Parent
(L
, SE
.Node_To_Be_Wrapped
);
3162 end Store_Before_Actions_In_Scope
;
3164 --------------------------------
3165 -- Wrap_Transient_Declaration --
3166 --------------------------------
3168 -- If a transient scope has been established during the processing of the
3169 -- Expression of an Object_Declaration, it is not possible to wrap the
3170 -- declaration into a transient block as usual case, otherwise the object
3171 -- would be itself declared in the wrong scope. Therefore, all entities (if
3172 -- any) defined in the transient block are moved to the proper enclosing
3173 -- scope, furthermore, if they are controlled variables they are finalized
3174 -- right after the declaration. The finalization list of the transient
3175 -- scope is defined as a renaming of the enclosing one so during their
3176 -- initialization they will be attached to the proper finalization
3177 -- list. For instance, the following declaration :
3179 -- X : Typ := F (G (A), G (B));
3181 -- (where G(A) and G(B) return controlled values, expanded as _v1 and _v2)
3182 -- is expanded into :
3184 -- _local_final_list_1 : Finalizable_Ptr;
3185 -- X : Typ := [ complex Expression-Action ];
3186 -- Finalize_One(_v1);
3187 -- Finalize_One (_v2);
3189 procedure Wrap_Transient_Declaration
(N
: Node_Id
) is
3191 LC
: Entity_Id
:= Empty
;
3193 Loc
: constant Source_Ptr
:= Sloc
(N
);
3194 Enclosing_S
: Entity_Id
;
3196 Next_N
: constant Node_Id
:= Next
(N
);
3200 Enclosing_S
:= Scope
(S
);
3202 -- Insert Actions kept in the Scope stack
3204 Insert_Actions_In_Scope_Around
(N
);
3206 -- If the declaration is consuming some secondary stack, mark the
3207 -- Enclosing scope appropriately.
3209 Uses_SS
:= Uses_Sec_Stack
(S
);
3212 -- Create a List controller and rename the final list to be its
3213 -- internal final pointer:
3214 -- Lxxx : Simple_List_Controller;
3215 -- Fxxx : Finalizable_Ptr renames Lxxx.F;
3217 if Present
(Finalization_Chain_Entity
(S
)) then
3218 LC
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('L'));
3221 Make_Object_Declaration
(Loc
,
3222 Defining_Identifier
=> LC
,
3223 Object_Definition
=>
3224 New_Reference_To
(RTE
(RE_Simple_List_Controller
), Loc
)),
3226 Make_Object_Renaming_Declaration
(Loc
,
3227 Defining_Identifier
=> Finalization_Chain_Entity
(S
),
3228 Subtype_Mark
=> New_Reference_To
(RTE
(RE_Finalizable_Ptr
), Loc
),
3230 Make_Selected_Component
(Loc
,
3231 Prefix
=> New_Reference_To
(LC
, Loc
),
3232 Selector_Name
=> Make_Identifier
(Loc
, Name_F
))));
3234 -- Put the declaration at the beginning of the declaration part
3235 -- to make sure it will be before all other actions that have been
3236 -- inserted before N.
3238 Insert_List_Before_And_Analyze
(First
(List_Containing
(N
)), Nodes
);
3240 -- Generate the Finalization calls by finalizing the list
3241 -- controller right away. It will be re-finalized on scope
3242 -- exit but it doesn't matter. It cannot be done when the
3243 -- call initializes a renaming object though because in this
3244 -- case, the object becomes a pointer to the temporary and thus
3245 -- increases its life span.
3247 if Nkind
(N
) = N_Object_Renaming_Declaration
3248 and then Controlled_Type
(Etype
(Defining_Identifier
(N
)))
3255 Ref
=> New_Reference_To
(LC
, Loc
),
3257 With_Detach
=> New_Reference_To
(Standard_False
, Loc
));
3258 if Present
(Next_N
) then
3259 Insert_List_Before_And_Analyze
(Next_N
, Nodes
);
3261 Append_List_To
(List_Containing
(N
), Nodes
);
3266 -- Put the local entities back in the enclosing scope, and set the
3267 -- Is_Public flag appropriately.
3269 Transfer_Entities
(S
, Enclosing_S
);
3271 -- Mark the enclosing dynamic scope so that the sec stack will be
3272 -- released upon its exit unless this is a function that returns on
3273 -- the sec stack in which case this will be done by the caller.
3276 S
:= Enclosing_Dynamic_Scope
(S
);
3278 if Ekind
(S
) = E_Function
3279 and then Requires_Transient_Scope
(Etype
(S
))
3283 Set_Uses_Sec_Stack
(S
);
3284 Check_Restriction
(No_Secondary_Stack
, N
);
3287 end Wrap_Transient_Declaration
;
3289 -------------------------------
3290 -- Wrap_Transient_Expression --
3291 -------------------------------
3293 -- Insert actions before <Expression>:
3295 -- (lines marked with <CTRL> are expanded only in presence of Controlled
3296 -- objects needing finalization)
3300 -- _M : constant Mark_Id := SS_Mark;
3301 -- Local_Final_List : System.FI.Finalizable_Ptr; <CTRL>
3303 -- procedure _Clean is
3306 -- System.FI.Finalize_List (Local_Final_List); <CTRL>
3312 -- _E := <Expression>;
3317 -- then expression is replaced by _E
3319 procedure Wrap_Transient_Expression
(N
: Node_Id
) is
3320 Loc
: constant Source_Ptr
:= Sloc
(N
);
3321 E
: constant Entity_Id
:=
3322 Make_Defining_Identifier
(Loc
, New_Internal_Name
('E'));
3323 Etyp
: constant Entity_Id
:= Etype
(N
);
3326 Insert_Actions
(N
, New_List
(
3327 Make_Object_Declaration
(Loc
,
3328 Defining_Identifier
=> E
,
3329 Object_Definition
=> New_Reference_To
(Etyp
, Loc
)),
3331 Make_Transient_Block
(Loc
,
3333 Make_Assignment_Statement
(Loc
,
3334 Name
=> New_Reference_To
(E
, Loc
),
3335 Expression
=> Relocate_Node
(N
)))));
3337 Rewrite
(N
, New_Reference_To
(E
, Loc
));
3338 Analyze_And_Resolve
(N
, Etyp
);
3339 end Wrap_Transient_Expression
;
3341 ------------------------------
3342 -- Wrap_Transient_Statement --
3343 ------------------------------
3345 -- Transform <Instruction> into
3347 -- (lines marked with <CTRL> are expanded only in presence of Controlled
3348 -- objects needing finalization)
3351 -- _M : Mark_Id := SS_Mark;
3352 -- Local_Final_List : System.FI.Finalizable_Ptr ; <CTRL>
3354 -- procedure _Clean is
3357 -- System.FI.Finalize_List (Local_Final_List); <CTRL>
3368 procedure Wrap_Transient_Statement
(N
: Node_Id
) is
3369 Loc
: constant Source_Ptr
:= Sloc
(N
);
3370 New_Statement
: constant Node_Id
:= Relocate_Node
(N
);
3373 Rewrite
(N
, Make_Transient_Block
(Loc
, New_Statement
));
3375 -- With the scope stack back to normal, we can call analyze on the
3376 -- resulting block. At this point, the transient scope is being
3377 -- treated like a perfectly normal scope, so there is nothing
3378 -- special about it.
3380 -- Note: Wrap_Transient_Statement is called with the node already
3381 -- analyzed (i.e. Analyzed (N) is True). This is important, since
3382 -- otherwise we would get a recursive processing of the node when
3383 -- we do this Analyze call.
3386 end Wrap_Transient_Statement
;