1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2014, 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 with Atree
; use Atree
;
27 with Checks
; use Checks
;
28 with Einfo
; use Einfo
;
29 with Elists
; use Elists
;
30 with Errout
; use Errout
;
31 with Exp_Ch3
; use Exp_Ch3
;
32 with Exp_Ch6
; use Exp_Ch6
;
33 with Exp_Ch11
; use Exp_Ch11
;
34 with Exp_Dbug
; use Exp_Dbug
;
35 with Exp_Disp
; use Exp_Disp
;
36 with Exp_Sel
; use Exp_Sel
;
37 with Exp_Smem
; use Exp_Smem
;
38 with Exp_Tss
; use Exp_Tss
;
39 with Exp_Util
; use Exp_Util
;
40 with Freeze
; use Freeze
;
42 with Itypes
; use Itypes
;
43 with Namet
; use Namet
;
44 with Nlists
; use Nlists
;
45 with Nmake
; use Nmake
;
47 with Restrict
; use Restrict
;
48 with Rident
; use Rident
;
49 with Rtsfind
; use Rtsfind
;
51 with Sem_Aux
; use Sem_Aux
;
52 with Sem_Ch6
; use Sem_Ch6
;
53 with Sem_Ch8
; use Sem_Ch8
;
54 with Sem_Ch9
; use Sem_Ch9
;
55 with Sem_Ch11
; use Sem_Ch11
;
56 with Sem_Elab
; use Sem_Elab
;
57 with Sem_Eval
; use Sem_Eval
;
58 with Sem_Res
; use Sem_Res
;
59 with Sem_Util
; use Sem_Util
;
60 with Sinfo
; use Sinfo
;
61 with Snames
; use Snames
;
62 with Stand
; use Stand
;
63 with Stringt
; use Stringt
;
64 with Targparm
; use Targparm
;
65 with Tbuild
; use Tbuild
;
66 with Uintp
; use Uintp
;
68 package body Exp_Ch9
is
70 -- The following constant establishes the upper bound for the index of
71 -- an entry family. It is used to limit the allocated size of protected
72 -- types with defaulted discriminant of an integer type, when the bound
73 -- of some entry family depends on a discriminant. The limitation to entry
74 -- families of 128K should be reasonable in all cases, and is a documented
75 -- implementation restriction.
77 Entry_Family_Bound
: constant Int
:= 2**16;
79 -----------------------
80 -- Local Subprograms --
81 -----------------------
83 function Actual_Index_Expression
87 Tsk
: Entity_Id
) return Node_Id
;
88 -- Compute the index position for an entry call. Tsk is the target task. If
89 -- the bounds of some entry family depend on discriminants, the expression
90 -- computed by this function uses the discriminants of the target task.
92 procedure Add_Object_Pointer
96 -- Prepend an object pointer declaration to the declaration list Decls.
97 -- This object pointer is initialized to a type conversion of the System.
98 -- Address pointer passed to entry barrier functions and entry body
101 procedure Add_Formal_Renamings
106 -- Create renaming declarations for the formals, inside the procedure that
107 -- implements an entry body. The renamings make the original names of the
108 -- formals accessible to gdb, and serve no other purpose.
109 -- Spec is the specification of the procedure being built.
110 -- Decls is the list of declarations to be enhanced.
111 -- Ent is the entity for the original entry body.
113 function Build_Accept_Body
(Astat
: Node_Id
) return Node_Id
;
114 -- Transform accept statement into a block with added exception handler.
115 -- Used both for simple accept statements and for accept alternatives in
116 -- select statements. Astat is the accept statement.
118 function Build_Barrier_Function
121 Pid
: Node_Id
) return Node_Id
;
122 -- Build the function body returning the value of the barrier expression
123 -- for the specified entry body.
125 function Build_Barrier_Function_Specification
127 Def_Id
: Entity_Id
) return Node_Id
;
128 -- Build a specification for a function implementing the protected entry
129 -- barrier of the specified entry body.
131 function Build_Corresponding_Record
134 Loc
: Source_Ptr
) return Node_Id
;
135 -- Common to tasks and protected types. Copy discriminant specifications,
136 -- build record declaration. N is the type declaration, Ctyp is the
137 -- concurrent entity (task type or protected type).
139 function Build_Dispatching_Tag_Check
141 N
: Node_Id
) return Node_Id
;
142 -- Utility to create the tree to check whether the dispatching call in
143 -- a timed entry call, a conditional entry call, or an asynchronous
144 -- transfer of control is a call to a primitive of a non-synchronized type.
145 -- K is the temporary that holds the tagged kind of the target object, and
146 -- N is the enclosing construct.
148 function Build_Entry_Count_Expression
149 (Concurrent_Type
: Node_Id
;
150 Component_List
: List_Id
;
151 Loc
: Source_Ptr
) return Node_Id
;
152 -- Compute number of entries for concurrent object. This is a count of
153 -- simple entries, followed by an expression that computes the length
154 -- of the range of each entry family. A single array with that size is
155 -- allocated for each concurrent object of the type.
157 function Build_Find_Body_Index
(Typ
: Entity_Id
) return Node_Id
;
158 -- Build the function that translates the entry index in the call
159 -- (which depends on the size of entry families) into an index into the
160 -- Entry_Bodies_Array, to determine the body and barrier function used
161 -- in a protected entry call. A pointer to this function appears in every
164 function Build_Find_Body_Index_Spec
(Typ
: Entity_Id
) return Node_Id
;
165 -- Build subprogram declaration for previous one
167 function Build_Lock_Free_Protected_Subprogram_Body
170 Unprot_Spec
: Node_Id
) return Node_Id
;
171 -- N denotes a subprogram body of protected type Prot_Typ. Unprot_Spec is
172 -- the subprogram specification of the unprotected version of N. Transform
173 -- N such that it invokes the unprotected version of the body.
175 function Build_Lock_Free_Unprotected_Subprogram_Body
177 Prot_Typ
: Node_Id
) return Node_Id
;
178 -- N denotes a subprogram body of protected type Prot_Typ. Build a version
179 -- of N where the original statements of N are synchronized through atomic
180 -- actions such as compare and exchange. Prior to invoking this routine, it
181 -- has been established that N can be implemented in a lock-free fashion.
183 function Build_Parameter_Block
187 Decls
: List_Id
) return Entity_Id
;
188 -- Generate an access type for each actual parameter in the list Actuals.
189 -- Create an encapsulating record that contains all the actuals and return
190 -- its type. Generate:
191 -- type Ann1 is access all <actual1-type>
193 -- type AnnN is access all <actualN-type>
194 -- type Pnn is record
200 procedure Build_PPC_Wrapper
(E
: Entity_Id
; Decl
: Node_Id
);
201 -- Build body of wrapper procedure for an entry or entry family that has
202 -- pre/postconditions. The body gathers the PPC's and expands them in the
203 -- usual way, and performs the entry call itself. This way preconditions
204 -- are evaluated before the call is queued. E is the entry in question,
205 -- and Decl is the enclosing synchronized type declaration at whose freeze
206 -- point the generated body is analyzed.
208 function Build_Protected_Entry
211 Pid
: Node_Id
) return Node_Id
;
212 -- Build the procedure implementing the statement sequence of the specified
215 function Build_Protected_Entry_Specification
218 Ent_Id
: Entity_Id
) return Node_Id
;
219 -- Build a specification for the procedure implementing the statements of
220 -- the specified entry body. Add attributes associating it with the entry
221 -- defining identifier Ent_Id.
223 function Build_Protected_Spec
225 Obj_Type
: Entity_Id
;
227 Unprotected
: Boolean := False) return List_Id
;
228 -- Utility shared by Build_Protected_Sub_Spec and Expand_Access_Protected_
229 -- Subprogram_Type. Builds signature of protected subprogram, adding the
230 -- formal that corresponds to the object itself. For an access to protected
231 -- subprogram, there is no object type to specify, so the parameter has
232 -- type Address and mode In. An indirect call through such a pointer will
233 -- convert the address to a reference to the actual object. The object is
234 -- a limited record and therefore a by_reference type.
236 function Build_Protected_Subprogram_Body
239 N_Op_Spec
: Node_Id
) return Node_Id
;
240 -- This function is used to construct the protected version of a protected
241 -- subprogram. Its statement sequence first defers abort, then locks the
242 -- associated protected object, and then enters a block that contains a
243 -- call to the unprotected version of the subprogram (for details, see
244 -- Build_Unprotected_Subprogram_Body). This block statement requires a
245 -- cleanup handler that unlocks the object in all cases. For details,
246 -- see Exp_Ch7.Expand_Cleanup_Actions.
248 function Build_Renamed_Formal_Declaration
252 Renamed_Formal
: Node_Id
) return Node_Id
;
253 -- Create a renaming declaration for a formal, within a protected entry
254 -- body or an accept body. The renamed object is a component of the
255 -- parameter block that is a parameter in the entry call.
257 -- In Ada 2012, if the formal is an incomplete tagged type, the renaming
258 -- does not dereference the corresponding component to prevent an illegal
259 -- use of the incomplete type (AI05-0151).
261 function Build_Selected_Name
263 Selector
: Entity_Id
;
264 Append_Char
: Character := ' ') return Name_Id
;
265 -- Build a name in the form of Prefix__Selector, with an optional character
266 -- appended. This is used for internal subprograms generated for operations
267 -- of protected types, including barrier functions. For the subprograms
268 -- generated for entry bodies and entry barriers, the generated name
269 -- includes a sequence number that makes names unique in the presence of
270 -- entry overloading. This is necessary because entry body procedures and
271 -- barrier functions all have the same signature.
273 procedure Build_Simple_Entry_Call
278 -- Some comments here would be useful ???
280 function Build_Task_Proc_Specification
(T
: Entity_Id
) return Node_Id
;
281 -- This routine constructs a specification for the procedure that we will
282 -- build for the task body for task type T. The spec has the form:
284 -- procedure tnameB (_Task : access tnameV);
286 -- where name is the character name taken from the task type entity that
287 -- is passed as the argument to the procedure, and tnameV is the task
288 -- value type that is associated with the task type.
290 function Build_Unprotected_Subprogram_Body
292 Pid
: Node_Id
) return Node_Id
;
293 -- This routine constructs the unprotected version of a protected
294 -- subprogram body, which is contains all of the code in the
295 -- original, unexpanded body. This is the version of the protected
296 -- subprogram that is called from all protected operations on the same
297 -- object, including the protected version of the same subprogram.
299 procedure Build_Wrapper_Bodies
303 -- Ada 2005 (AI-345): Typ is either a concurrent type or the corresponding
304 -- record of a concurrent type. N is the insertion node where all bodies
305 -- will be placed. This routine builds the bodies of the subprograms which
306 -- serve as an indirection mechanism to overriding primitives of concurrent
307 -- types, entries and protected procedures. Any new body is analyzed.
309 procedure Build_Wrapper_Specs
313 -- Ada 2005 (AI-345): Typ is either a concurrent type or the corresponding
314 -- record of a concurrent type. N is the insertion node where all specs
315 -- will be placed. This routine builds the specs of the subprograms which
316 -- serve as an indirection mechanism to overriding primitives of concurrent
317 -- types, entries and protected procedures. Any new spec is analyzed.
319 procedure Collect_Entry_Families
322 Current_Node
: in out Node_Id
;
323 Conctyp
: Entity_Id
);
324 -- For each entry family in a concurrent type, create an anonymous array
325 -- type of the right size, and add a component to the corresponding_record.
327 function Concurrent_Object
328 (Spec_Id
: Entity_Id
;
329 Conc_Typ
: Entity_Id
) return Entity_Id
;
330 -- Given a subprogram entity Spec_Id and concurrent type Conc_Typ, return
331 -- the entity associated with the concurrent object in the Protected_Body_
332 -- Subprogram or the Task_Body_Procedure of Spec_Id. The returned entity
333 -- denotes formal parameter _O, _object or _task.
335 function Copy_Result_Type
(Res
: Node_Id
) return Node_Id
;
336 -- Copy the result type of a function specification, when building the
337 -- internal operation corresponding to a protected function, or when
338 -- expanding an access to protected function. If the result is an anonymous
339 -- access to subprogram itself, we need to create a new signature with the
340 -- same parameter names and the same resolved types, but with new entities
343 procedure Debug_Private_Data_Declarations
(Decls
: List_Id
);
344 -- Decls is a list which may contain the declarations created by Install_
345 -- Private_Data_Declarations. All generated entities are marked as needing
346 -- debug info and debug nodes are manually generation where necessary. This
347 -- step of the expansion must to be done after private data has been moved
348 -- to its final resting scope to ensure proper visibility of debug objects.
350 procedure Ensure_Statement_Present
(Loc
: Source_Ptr
; Alt
: Node_Id
);
351 -- If control flow optimizations are suppressed, and Alt is an accept,
352 -- delay, or entry call alternative with no trailing statements, insert
353 -- a null trailing statement with the given Loc (which is the sloc of
354 -- the accept, delay, or entry call statement). There might not be any
355 -- generated code for the accept, delay, or entry call itself (the effect
356 -- of these statements is part of the general processsing done for the
357 -- enclosing selective accept, timed entry call, or asynchronous select),
358 -- and the null statement is there to carry the sloc of that statement to
359 -- the back-end for trace-based coverage analysis purposes.
361 procedure Extract_Dispatching_Call
363 Call_Ent
: out Entity_Id
;
364 Object
: out Entity_Id
;
365 Actuals
: out List_Id
;
366 Formals
: out List_Id
);
367 -- Given a dispatching call, extract the entity of the name of the call,
368 -- its actual dispatching object, its actual parameters and the formal
369 -- parameters of the overridden interface-level version. If the type of
370 -- the dispatching object is an access type then an explicit dereference
371 -- is returned in Object.
373 procedure Extract_Entry
375 Concval
: out Node_Id
;
377 Index
: out Node_Id
);
378 -- Given an entry call, returns the associated concurrent object, the entry
379 -- name, and the entry family index.
381 function Family_Offset
386 Cap
: Boolean) return Node_Id
;
387 -- Compute (Hi - Lo) for two entry family indexes. Hi is the index in an
388 -- accept statement, or the upper bound in the discrete subtype of an entry
389 -- declaration. Lo is the corresponding lower bound. Ttyp is the concurrent
390 -- type of the entry. If Cap is true, the result is capped according to
391 -- Entry_Family_Bound.
398 Cap
: Boolean) return Node_Id
;
399 -- Compute (Hi - Lo) + 1 Max 0, to determine the number of entries in a
400 -- family, and handle properly the superflat case. This is equivalent to
401 -- the use of 'Length on the index type, but must use Family_Offset to
402 -- handle properly the case of bounds that depend on discriminants. If
403 -- Cap is true, the result is capped according to Entry_Family_Bound.
405 procedure Find_Enclosing_Context
407 Context
: out Node_Id
;
408 Context_Id
: out Entity_Id
;
409 Context_Decls
: out List_Id
);
410 -- Subsidiary routine to procedures Build_Activation_Chain_Entity and
411 -- Build_Master_Entity. Given an arbitrary node in the tree, find the
412 -- nearest enclosing body, block, package or return statement and return
413 -- its constituents. Context is the enclosing construct, Context_Id is
414 -- the scope of Context_Id and Context_Decls is the declarative list of
417 function Index_Object
(Spec_Id
: Entity_Id
) return Entity_Id
;
418 -- Given a subprogram identifier, return the entity which is associated
419 -- with the protection entry index in the Protected_Body_Subprogram or
420 -- the Task_Body_Procedure of Spec_Id. The returned entity denotes formal
423 function Is_Exception_Safe
(Subprogram
: Node_Id
) return Boolean;
424 -- Tell whether a given subprogram cannot raise an exception
426 function Is_Potentially_Large_Family
427 (Base_Index
: Entity_Id
;
430 Hi
: Node_Id
) return Boolean;
432 function Is_Private_Primitive_Subprogram
(Id
: Entity_Id
) return Boolean;
433 -- Determine whether Id is a function or a procedure and is marked as a
434 -- private primitive.
436 function Null_Statements
(Stats
: List_Id
) return Boolean;
437 -- Used to check DO-END sequence. Checks for equivalent of DO NULL; END.
438 -- Allows labels, and pragma Warnings/Unreferenced in the sequence as well
439 -- to still count as null. Returns True for a null sequence. The argument
440 -- is the list of statements from the DO-END sequence.
442 function Parameter_Block_Pack
448 Stmts
: List_Id
) return Entity_Id
;
449 -- Set the components of the generated parameter block with the values
450 -- of the actual parameters. Generate aliased temporaries to capture the
451 -- values for types that are passed by copy. Otherwise generate a reference
452 -- to the actual's value. Return the address of the aggregate block.
454 -- Jnn1 : alias <formal-type1>;
455 -- Jnn1 := <actual1>;
458 -- Jnn1'unchecked_access;
459 -- <actual2>'reference;
462 function Parameter_Block_Unpack
466 Formals
: List_Id
) return List_Id
;
467 -- Retrieve the values of the components from the parameter block and
468 -- assign then to the original actual parameters. Generate:
469 -- <actual1> := P.<formal1>;
471 -- <actualN> := P.<formalN>;
473 function Trivial_Accept_OK
return Boolean;
474 -- If there is no DO-END block for an accept, or if the DO-END block has
475 -- only null statements, then it is possible to do the Rendezvous with much
476 -- less overhead using the Accept_Trivial routine in the run-time library.
477 -- However, this is not always a valid optimization. Whether it is valid or
478 -- not depends on the Task_Dispatching_Policy. The issue is whether a full
479 -- rescheduling action is required or not. In FIFO_Within_Priorities, such
480 -- a rescheduling is required, so this optimization is not allowed. This
481 -- function returns True if the optimization is permitted.
483 -----------------------------
484 -- Actual_Index_Expression --
485 -----------------------------
487 function Actual_Index_Expression
491 Tsk
: Entity_Id
) return Node_Id
493 Ttyp
: constant Entity_Id
:= Etype
(Tsk
);
501 function Actual_Family_Offset
(Hi
, Lo
: Node_Id
) return Node_Id
;
502 -- Compute difference between bounds of entry family
504 --------------------------
505 -- Actual_Family_Offset --
506 --------------------------
508 function Actual_Family_Offset
(Hi
, Lo
: Node_Id
) return Node_Id
is
510 function Actual_Discriminant_Ref
(Bound
: Node_Id
) return Node_Id
;
511 -- Replace a reference to a discriminant with a selected component
512 -- denoting the discriminant of the target task.
514 -----------------------------
515 -- Actual_Discriminant_Ref --
516 -----------------------------
518 function Actual_Discriminant_Ref
(Bound
: Node_Id
) return Node_Id
is
519 Typ
: constant Entity_Id
:= Etype
(Bound
);
523 if not Is_Entity_Name
(Bound
)
524 or else Ekind
(Entity
(Bound
)) /= E_Discriminant
526 if Nkind
(Bound
) = N_Attribute_Reference
then
529 B
:= New_Copy_Tree
(Bound
);
534 Make_Selected_Component
(Sloc
,
535 Prefix
=> New_Copy_Tree
(Tsk
),
536 Selector_Name
=> New_Occurrence_Of
(Entity
(Bound
), Sloc
));
538 Analyze_And_Resolve
(B
, Typ
);
542 Make_Attribute_Reference
(Sloc
,
543 Attribute_Name
=> Name_Pos
,
544 Prefix
=> New_Occurrence_Of
(Etype
(Bound
), Sloc
),
545 Expressions
=> New_List
(B
));
546 end Actual_Discriminant_Ref
;
548 -- Start of processing for Actual_Family_Offset
552 Make_Op_Subtract
(Sloc
,
553 Left_Opnd
=> Actual_Discriminant_Ref
(Hi
),
554 Right_Opnd
=> Actual_Discriminant_Ref
(Lo
));
555 end Actual_Family_Offset
;
557 -- Start of processing for Actual_Index_Expression
560 -- The queues of entries and entry families appear in textual order in
561 -- the associated record. The entry index is computed as the sum of the
562 -- number of queues for all entries that precede the designated one, to
563 -- which is added the index expression, if this expression denotes a
564 -- member of a family.
566 -- The following is a place holder for the count of simple entries
568 Num
:= Make_Integer_Literal
(Sloc
, 1);
570 -- We construct an expression which is a series of addition operations.
571 -- See comments in Entry_Index_Expression, which is identical in
574 if Present
(Index
) then
575 S
:= Etype
(Discrete_Subtype_Definition
(Declaration_Node
(Ent
)));
582 Actual_Family_Offset
(
583 Make_Attribute_Reference
(Sloc
,
584 Attribute_Name
=> Name_Pos
,
585 Prefix
=> New_Occurrence_Of
(Base_Type
(S
), Sloc
),
586 Expressions
=> New_List
(Relocate_Node
(Index
))),
587 Type_Low_Bound
(S
)));
592 -- Now add lengths of preceding entries and entry families
594 Prev
:= First_Entity
(Ttyp
);
596 while Chars
(Prev
) /= Chars
(Ent
)
597 or else (Ekind
(Prev
) /= Ekind
(Ent
))
598 or else not Sem_Ch6
.Type_Conformant
(Ent
, Prev
)
600 if Ekind
(Prev
) = E_Entry
then
601 Set_Intval
(Num
, Intval
(Num
) + 1);
603 elsif Ekind
(Prev
) = E_Entry_Family
then
605 Etype
(Discrete_Subtype_Definition
(Declaration_Node
(Prev
)));
607 -- The need for the following full view retrieval stems from this
608 -- complex case of nested generics and tasking:
611 -- type Formal_Index is range <>;
614 -- type Index is private;
621 -- type Index is new Formal_Index range 1 .. 10;
624 -- package body Outer is
626 -- entry Fam (Index); -- (2)
629 -- package body Inner is -- (3)
637 -- We are currently building the index expression for the entry
638 -- call "T.E" (1). Part of the expansion must mention the range
639 -- of the discrete type "Index" (2) of entry family "Fam".
641 -- However only the private view of type "Index" is available to
642 -- the inner generic (3) because there was no prior mention of
643 -- the type inside "Inner". This visibility requirement is
644 -- implicit and cannot be detected during the construction of
645 -- the generic trees and needs special handling.
648 and then Is_Private_Type
(S
)
649 and then Present
(Full_View
(S
))
654 Lo
:= Type_Low_Bound
(S
);
655 Hi
:= Type_High_Bound
(S
);
663 Actual_Family_Offset
(Hi
, Lo
),
665 Make_Integer_Literal
(Sloc
, 1)));
667 -- Other components are anonymous types to be ignored
677 end Actual_Index_Expression
;
679 --------------------------
680 -- Add_Formal_Renamings --
681 --------------------------
683 procedure Add_Formal_Renamings
689 Ptr
: constant Entity_Id
:=
691 (Next
(First
(Parameter_Specifications
(Spec
))));
692 -- The name of the formal that holds the address of the parameter block
699 Renamed_Formal
: Node_Id
;
702 Formal
:= First_Formal
(Ent
);
703 while Present
(Formal
) loop
704 Comp
:= Entry_Component
(Formal
);
706 Make_Defining_Identifier
(Sloc
(Formal
),
707 Chars
=> Chars
(Formal
));
708 Set_Etype
(New_F
, Etype
(Formal
));
709 Set_Scope
(New_F
, Ent
);
711 -- Now we set debug info needed on New_F even though it does not come
712 -- from source, so that the debugger will get the right information
713 -- for these generated names.
715 Set_Debug_Info_Needed
(New_F
);
717 if Ekind
(Formal
) = E_In_Parameter
then
718 Set_Ekind
(New_F
, E_Constant
);
720 Set_Ekind
(New_F
, E_Variable
);
721 Set_Extra_Constrained
(New_F
, Extra_Constrained
(Formal
));
724 Set_Actual_Subtype
(New_F
, Actual_Subtype
(Formal
));
727 Make_Selected_Component
(Loc
,
729 Unchecked_Convert_To
(Entry_Parameters_Type
(Ent
),
730 Make_Identifier
(Loc
, Chars
(Ptr
))),
731 Selector_Name
=> New_Occurrence_Of
(Comp
, Loc
));
734 Build_Renamed_Formal_Declaration
735 (New_F
, Formal
, Comp
, Renamed_Formal
);
737 Append
(Decl
, Decls
);
738 Set_Renamed_Object
(Formal
, New_F
);
739 Next_Formal
(Formal
);
741 end Add_Formal_Renamings
;
743 ------------------------
744 -- Add_Object_Pointer --
745 ------------------------
747 procedure Add_Object_Pointer
749 Conc_Typ
: Entity_Id
;
752 Rec_Typ
: constant Entity_Id
:= Corresponding_Record_Type
(Conc_Typ
);
757 -- Create the renaming declaration for the Protection object of a
758 -- protected type. _Object is used by Complete_Entry_Body.
759 -- ??? An attempt to make this a renaming was unsuccessful.
761 -- Build the entity for the access type
764 Make_Defining_Identifier
(Loc
,
765 New_External_Name
(Chars
(Rec_Typ
), 'P'));
768 -- _object : poVP := poVP!O;
771 Make_Object_Declaration
(Loc
,
772 Defining_Identifier
=>
773 Make_Defining_Identifier
(Loc
, Name_uObject
),
775 New_Occurrence_Of
(Obj_Ptr
, Loc
),
777 Unchecked_Convert_To
(Obj_Ptr
, Make_Identifier
(Loc
, Name_uO
)));
778 Set_Debug_Info_Needed
(Defining_Identifier
(Decl
));
779 Prepend_To
(Decls
, Decl
);
782 -- type poVP is access poV;
785 Make_Full_Type_Declaration
(Loc
,
786 Defining_Identifier
=>
789 Make_Access_To_Object_Definition
(Loc
,
790 Subtype_Indication
=>
791 New_Occurrence_Of
(Rec_Typ
, Loc
)));
792 Set_Debug_Info_Needed
(Defining_Identifier
(Decl
));
793 Prepend_To
(Decls
, Decl
);
794 end Add_Object_Pointer
;
796 -----------------------
797 -- Build_Accept_Body --
798 -----------------------
800 function Build_Accept_Body
(Astat
: Node_Id
) return Node_Id
is
801 Loc
: constant Source_Ptr
:= Sloc
(Astat
);
802 Stats
: constant Node_Id
:= Handled_Statement_Sequence
(Astat
);
809 -- At the end of the statement sequence, Complete_Rendezvous is called.
810 -- A label skipping the Complete_Rendezvous, and all other accept
811 -- processing, has already been added for the expansion of requeue
812 -- statements. The Sloc is copied from the last statement since it
813 -- is really part of this last statement.
817 (Sloc
(Last
(Statements
(Stats
))), RE_Complete_Rendezvous
);
818 Insert_Before
(Last
(Statements
(Stats
)), Call
);
821 -- If exception handlers are present, then append Complete_Rendezvous
822 -- calls to the handlers, and construct the required outer block. As
823 -- above, the Sloc is copied from the last statement in the sequence.
825 if Present
(Exception_Handlers
(Stats
)) then
826 Hand
:= First
(Exception_Handlers
(Stats
));
827 while Present
(Hand
) loop
830 (Sloc
(Last
(Statements
(Hand
))), RE_Complete_Rendezvous
);
831 Append
(Call
, Statements
(Hand
));
837 Make_Handled_Sequence_Of_Statements
(Loc
,
838 Statements
=> New_List
(
839 Make_Block_Statement
(Loc
,
840 Handled_Statement_Sequence
=> Stats
)));
846 -- At this stage we know that the new statement sequence does
847 -- not have an exception handler part, so we supply one to call
848 -- Exceptional_Complete_Rendezvous. This handler is
850 -- when all others =>
851 -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
853 -- We handle Abort_Signal to make sure that we properly catch the abort
854 -- case and wake up the caller.
856 Ohandle
:= Make_Others_Choice
(Loc
);
857 Set_All_Others
(Ohandle
);
859 Set_Exception_Handlers
(New_S
,
861 Make_Implicit_Exception_Handler
(Loc
,
862 Exception_Choices
=> New_List
(Ohandle
),
864 Statements
=> New_List
(
865 Make_Procedure_Call_Statement
(Sloc
(Stats
),
866 Name
=> New_Occurrence_Of
(
867 RTE
(RE_Exceptional_Complete_Rendezvous
), Sloc
(Stats
)),
868 Parameter_Associations
=> New_List
(
869 Make_Function_Call
(Sloc
(Stats
),
870 Name
=> New_Occurrence_Of
(
871 RTE
(RE_Get_GNAT_Exception
), Sloc
(Stats
)))))))));
873 Set_Parent
(New_S
, Astat
); -- temp parent for Analyze call
874 Analyze_Exception_Handlers
(Exception_Handlers
(New_S
));
875 Expand_Exception_Handlers
(New_S
);
877 -- Exceptional_Complete_Rendezvous must be called with abort
878 -- still deferred, which is the case for a "when all others" handler.
881 end Build_Accept_Body
;
883 -----------------------------------
884 -- Build_Activation_Chain_Entity --
885 -----------------------------------
887 procedure Build_Activation_Chain_Entity
(N
: Node_Id
) is
888 function Has_Activation_Chain
(Stmt
: Node_Id
) return Boolean;
889 -- Determine whether an extended return statement has an activation
892 --------------------------
893 -- Has_Activation_Chain --
894 --------------------------
896 function Has_Activation_Chain
(Stmt
: Node_Id
) return Boolean is
900 Decl
:= First
(Return_Object_Declarations
(Stmt
));
901 while Present
(Decl
) loop
902 if Nkind
(Decl
) = N_Object_Declaration
903 and then Chars
(Defining_Identifier
(Decl
)) = Name_uChain
912 end Has_Activation_Chain
;
917 Context_Id
: Entity_Id
;
920 -- Start of processing for Build_Activation_Chain_Entity
923 -- Activation chain is never used for sequential elaboration policy, see
924 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
926 if Partition_Elaboration_Policy
= 'S' then
930 Find_Enclosing_Context
(N
, Context
, Context_Id
, Decls
);
932 -- If activation chain entity has not been declared already, create one
934 if Nkind
(Context
) = N_Extended_Return_Statement
935 or else No
(Activation_Chain_Entity
(Context
))
937 -- Since extended return statements do not store the entity of the
938 -- chain, examine the return object declarations to avoid creating
941 if Nkind
(Context
) = N_Extended_Return_Statement
942 and then Has_Activation_Chain
(Context
)
948 Loc
: constant Source_Ptr
:= Sloc
(Context
);
953 Chain
:= Make_Defining_Identifier
(Sloc
(N
), Name_uChain
);
955 -- Note: An extended return statement is not really a task
956 -- activator, but it does have an activation chain on which to
957 -- store the tasks temporarily. On successful return, the tasks
958 -- on this chain are moved to the chain passed in by the caller.
959 -- We do not build an Activation_Chain_Entity for an extended
960 -- return statement, because we do not want to build a call to
961 -- Activate_Tasks. Task activation is the responsibility of the
964 if Nkind
(Context
) /= N_Extended_Return_Statement
then
965 Set_Activation_Chain_Entity
(Context
, Chain
);
969 Make_Object_Declaration
(Loc
,
970 Defining_Identifier
=> Chain
,
971 Aliased_Present
=> True,
973 New_Occurrence_Of
(RTE
(RE_Activation_Chain
), Loc
));
975 Prepend_To
(Decls
, Decl
);
977 -- Ensure that _chain appears in the proper scope of the context
979 if Context_Id
/= Current_Scope
then
980 Push_Scope
(Context_Id
);
988 end Build_Activation_Chain_Entity
;
990 ----------------------------
991 -- Build_Barrier_Function --
992 ----------------------------
994 function Build_Barrier_Function
997 Pid
: Node_Id
) return Node_Id
999 Ent_Formals
: constant Node_Id
:= Entry_Body_Formal_Part
(N
);
1000 Cond
: constant Node_Id
:= Condition
(Ent_Formals
);
1001 Loc
: constant Source_Ptr
:= Sloc
(Cond
);
1002 Func_Id
: constant Entity_Id
:= Barrier_Function
(Ent
);
1003 Op_Decls
: constant List_Id
:= New_List
;
1005 Func_Body
: Node_Id
;
1008 -- Add a declaration for the Protection object, renaming declarations
1009 -- for the discriminals and privals and finally a declaration for the
1010 -- entry family index (if applicable).
1012 Install_Private_Data_Declarations
(Sloc
(N
),
1018 Family
=> Ekind
(Ent
) = E_Entry_Family
);
1020 -- If compiling with -fpreserve-control-flow, make sure we insert an
1021 -- IF statement so that the back-end knows to generate a conditional
1022 -- branch instruction, even if the condition is just the name of a
1023 -- boolean object. Note that Expand_N_If_Statement knows to preserve
1024 -- such redundant IF statements under -fpreserve-control-flow
1025 -- (whether coming from this routine, or directly from source).
1027 if Opt
.Suppress_Control_Flow_Optimizations
then
1028 Stmt
:= Make_Implicit_If_Statement
(Cond
,
1030 Then_Statements
=> New_List
(
1031 Make_Simple_Return_Statement
(Loc
,
1032 New_Occurrence_Of
(Standard_True
, Loc
))),
1033 Else_Statements
=> New_List
(
1034 Make_Simple_Return_Statement
(Loc
,
1035 New_Occurrence_Of
(Standard_False
, Loc
))));
1038 Stmt
:= Make_Simple_Return_Statement
(Loc
, Cond
);
1041 -- Note: the condition in the barrier function needs to be properly
1042 -- processed for the C/Fortran boolean possibility, but this happens
1043 -- automatically since the return statement does this normalization.
1046 Make_Subprogram_Body
(Loc
,
1048 Build_Barrier_Function_Specification
(Loc
,
1049 Make_Defining_Identifier
(Loc
, Chars
(Func_Id
))),
1050 Declarations
=> Op_Decls
,
1051 Handled_Statement_Sequence
=>
1052 Make_Handled_Sequence_Of_Statements
(Loc
,
1053 Statements
=> New_List
(Stmt
)));
1054 Set_Is_Entry_Barrier_Function
(Func_Body
);
1057 end Build_Barrier_Function
;
1059 ------------------------------------------
1060 -- Build_Barrier_Function_Specification --
1061 ------------------------------------------
1063 function Build_Barrier_Function_Specification
1065 Def_Id
: Entity_Id
) return Node_Id
1068 Set_Debug_Info_Needed
(Def_Id
);
1070 return Make_Function_Specification
(Loc
,
1071 Defining_Unit_Name
=> Def_Id
,
1072 Parameter_Specifications
=> New_List
(
1073 Make_Parameter_Specification
(Loc
,
1074 Defining_Identifier
=>
1075 Make_Defining_Identifier
(Loc
, Name_uO
),
1077 New_Occurrence_Of
(RTE
(RE_Address
), Loc
)),
1079 Make_Parameter_Specification
(Loc
,
1080 Defining_Identifier
=>
1081 Make_Defining_Identifier
(Loc
, Name_uE
),
1083 New_Occurrence_Of
(RTE
(RE_Protected_Entry_Index
), Loc
))),
1085 Result_Definition
=>
1086 New_Occurrence_Of
(Standard_Boolean
, Loc
));
1087 end Build_Barrier_Function_Specification
;
1089 --------------------------
1090 -- Build_Call_With_Task --
1091 --------------------------
1093 function Build_Call_With_Task
1095 E
: Entity_Id
) return Node_Id
1097 Loc
: constant Source_Ptr
:= Sloc
(N
);
1100 Make_Function_Call
(Loc
,
1101 Name
=> New_Occurrence_Of
(E
, Loc
),
1102 Parameter_Associations
=> New_List
(Concurrent_Ref
(N
)));
1103 end Build_Call_With_Task
;
1105 -----------------------------
1106 -- Build_Class_Wide_Master --
1107 -----------------------------
1109 procedure Build_Class_Wide_Master
(Typ
: Entity_Id
) is
1110 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
1111 Master_Id
: Entity_Id
;
1112 Master_Scope
: Entity_Id
;
1114 Related_Node
: Node_Id
;
1118 -- Nothing to do if there is no task hierarchy
1120 if Restriction_Active
(No_Task_Hierarchy
) then
1124 -- Find the declaration that created the access type. It is either a
1125 -- type declaration, or an object declaration with an access definition,
1126 -- in which case the type is anonymous.
1128 if Is_Itype
(Typ
) then
1129 Related_Node
:= Associated_Node_For_Itype
(Typ
);
1131 Related_Node
:= Parent
(Typ
);
1134 Master_Scope
:= Find_Master_Scope
(Typ
);
1136 -- Nothing to do if the master scope already contains a _master entity.
1137 -- The only exception to this is the following scenario:
1140 -- Transient_Scope_1
1143 -- Transient_Scope_2
1146 -- In this case the source scope is marked as having the master entity
1147 -- even though the actual declaration appears inside an inner scope. If
1148 -- the second transient scope requires a _master, it cannot use the one
1149 -- already declared because the entity is not visible.
1151 Name_Id
:= Make_Identifier
(Loc
, Name_uMaster
);
1153 if not Has_Master_Entity
(Master_Scope
)
1154 or else No
(Current_Entity_In_Scope
(Name_Id
))
1157 Master_Decl
: Node_Id
;
1160 Set_Has_Master_Entity
(Master_Scope
);
1163 -- _master : constant Integer := Current_Master.all;
1166 Make_Object_Declaration
(Loc
,
1167 Defining_Identifier
=>
1168 Make_Defining_Identifier
(Loc
, Name_uMaster
),
1169 Constant_Present
=> True,
1170 Object_Definition
=>
1171 New_Occurrence_Of
(Standard_Integer
, Loc
),
1173 Make_Explicit_Dereference
(Loc
,
1174 New_Occurrence_Of
(RTE
(RE_Current_Master
), Loc
)));
1176 Insert_Action
(Related_Node
, Master_Decl
);
1177 Analyze
(Master_Decl
);
1179 -- Mark the containing scope as a task master. Masters associated
1180 -- with return statements are already marked at this stage (see
1181 -- Analyze_Subprogram_Body).
1183 if Ekind
(Current_Scope
) /= E_Return_Statement
then
1185 Par
: Node_Id
:= Related_Node
;
1188 while Nkind
(Par
) /= N_Compilation_Unit
loop
1189 Par
:= Parent
(Par
);
1191 -- If we fall off the top, we are at the outer level,
1192 -- and the environment task is our effective master,
1193 -- so nothing to mark.
1195 if Nkind_In
(Par
, N_Block_Statement
,
1199 Set_Is_Task_Master
(Par
);
1209 Make_Defining_Identifier
(Loc
,
1210 New_External_Name
(Chars
(Typ
), 'M'));
1213 -- Mnn renames _master;
1216 Make_Object_Renaming_Declaration
(Loc
,
1217 Defining_Identifier
=> Master_Id
,
1218 Subtype_Mark
=> New_Occurrence_Of
(Standard_Integer
, Loc
),
1221 Insert_Action
(Related_Node
, Ren_Decl
);
1223 Set_Master_Id
(Typ
, Master_Id
);
1224 end Build_Class_Wide_Master
;
1226 --------------------------------
1227 -- Build_Corresponding_Record --
1228 --------------------------------
1230 function Build_Corresponding_Record
1233 Loc
: Source_Ptr
) return Node_Id
1235 Rec_Ent
: constant Entity_Id
:=
1236 Make_Defining_Identifier
1237 (Loc
, New_External_Name
(Chars
(Ctyp
), 'V'));
1240 New_Disc
: Entity_Id
;
1244 Set_Corresponding_Record_Type
(Ctyp
, Rec_Ent
);
1245 Set_Ekind
(Rec_Ent
, E_Record_Type
);
1246 Set_Has_Delayed_Freeze
(Rec_Ent
, Has_Delayed_Freeze
(Ctyp
));
1247 Set_Is_Concurrent_Record_Type
(Rec_Ent
, True);
1248 Set_Corresponding_Concurrent_Type
(Rec_Ent
, Ctyp
);
1249 Set_Stored_Constraint
(Rec_Ent
, No_Elist
);
1252 -- Use discriminals to create list of discriminants for record, and
1253 -- create new discriminals for use in default expressions, etc. It is
1254 -- worth noting that a task discriminant gives rise to 5 entities;
1256 -- a) The original discriminant.
1257 -- b) The discriminal for use in the task.
1258 -- c) The discriminant of the corresponding record.
1259 -- d) The discriminal for the init proc of the corresponding record.
1260 -- e) The local variable that renames the discriminant in the procedure
1261 -- for the task body.
1263 -- In fact the discriminals b) are used in the renaming declarations
1264 -- for e). See details in einfo (Handling of Discriminants).
1266 if Present
(Discriminant_Specifications
(N
)) then
1268 Disc
:= First_Discriminant
(Ctyp
);
1270 while Present
(Disc
) loop
1271 New_Disc
:= CR_Discriminant
(Disc
);
1274 Make_Discriminant_Specification
(Loc
,
1275 Defining_Identifier
=> New_Disc
,
1276 Discriminant_Type
=>
1277 New_Occurrence_Of
(Etype
(Disc
), Loc
),
1279 New_Copy
(Discriminant_Default_Value
(Disc
))));
1281 Next_Discriminant
(Disc
);
1288 -- Now we can construct the record type declaration. Note that this
1289 -- record is "limited tagged". It is "limited" to reflect the underlying
1290 -- limitedness of the task or protected object that it represents, and
1291 -- ensuring for example that it is properly passed by reference. It is
1292 -- "tagged" to give support to dispatching calls through interfaces. We
1293 -- propagate here the list of interfaces covered by the concurrent type
1294 -- (Ada 2005: AI-345).
1297 Make_Full_Type_Declaration
(Loc
,
1298 Defining_Identifier
=> Rec_Ent
,
1299 Discriminant_Specifications
=> Dlist
,
1301 Make_Record_Definition
(Loc
,
1303 Make_Component_List
(Loc
,
1304 Component_Items
=> Cdecls
),
1306 Ada_Version
>= Ada_2005
and then Is_Tagged_Type
(Ctyp
),
1307 Interface_List
=> Interface_List
(N
),
1308 Limited_Present
=> True));
1309 end Build_Corresponding_Record
;
1311 ---------------------------------
1312 -- Build_Dispatching_Tag_Check --
1313 ---------------------------------
1315 function Build_Dispatching_Tag_Check
1317 N
: Node_Id
) return Node_Id
1319 Loc
: constant Source_Ptr
:= Sloc
(N
);
1326 New_Occurrence_Of
(K
, Loc
),
1328 New_Occurrence_Of
(RTE
(RE_TK_Limited_Tagged
), Loc
)),
1332 New_Occurrence_Of
(K
, Loc
),
1334 New_Occurrence_Of
(RTE
(RE_TK_Tagged
), Loc
)));
1335 end Build_Dispatching_Tag_Check
;
1337 ----------------------------------
1338 -- Build_Entry_Count_Expression --
1339 ----------------------------------
1341 function Build_Entry_Count_Expression
1342 (Concurrent_Type
: Node_Id
;
1343 Component_List
: List_Id
;
1344 Loc
: Source_Ptr
) return Node_Id
1356 -- Count number of non-family entries
1359 Ent
:= First_Entity
(Concurrent_Type
);
1360 while Present
(Ent
) loop
1361 if Ekind
(Ent
) = E_Entry
then
1368 Ecount
:= Make_Integer_Literal
(Loc
, Eindx
);
1370 -- Loop through entry families building the addition nodes
1372 Ent
:= First_Entity
(Concurrent_Type
);
1373 Comp
:= First
(Component_List
);
1374 while Present
(Ent
) loop
1375 if Ekind
(Ent
) = E_Entry_Family
then
1376 while Chars
(Ent
) /= Chars
(Defining_Identifier
(Comp
)) loop
1380 Typ
:= Etype
(Discrete_Subtype_Definition
(Parent
(Ent
)));
1381 Hi
:= Type_High_Bound
(Typ
);
1382 Lo
:= Type_Low_Bound
(Typ
);
1383 Large
:= Is_Potentially_Large_Family
1384 (Base_Type
(Typ
), Concurrent_Type
, Lo
, Hi
);
1387 Left_Opnd
=> Ecount
,
1388 Right_Opnd
=> Family_Size
1389 (Loc
, Hi
, Lo
, Concurrent_Type
, Large
));
1396 end Build_Entry_Count_Expression
;
1398 -----------------------
1399 -- Build_Entry_Names --
1400 -----------------------
1402 procedure Build_Entry_Names
1404 Obj_Typ
: Entity_Id
;
1407 Loc
: constant Source_Ptr
:= Sloc
(Obj_Ref
);
1408 Data
: Entity_Id
:= Empty
;
1409 Index
: Entity_Id
:= Empty
;
1410 Typ
: Entity_Id
:= Obj_Typ
;
1412 procedure Build_Entry_Name
(Comp_Id
: Entity_Id
);
1413 -- Given an entry [family], create a static string which denotes the
1414 -- name of Comp_Id and assign it to the underlying data structure which
1415 -- contains the entry names of a concurrent object.
1417 function Object_Reference
return Node_Id
;
1418 -- Return a reference to field _object or _task_id depending on the
1419 -- concurrent object being processed.
1421 ----------------------
1422 -- Build_Entry_Name --
1423 ----------------------
1425 procedure Build_Entry_Name
(Comp_Id
: Entity_Id
) is
1426 function Build_Range
(Def
: Node_Id
) return Node_Id
;
1427 -- Given a discrete subtype definition of an entry family, generate a
1428 -- range node which covers the range of Def's type.
1430 procedure Create_Index_And_Data
;
1431 -- Generate the declarations of variables Index and Data. Subsequent
1432 -- calls do nothing.
1434 function Increment_Index
return Node_Id
;
1435 -- Increment the index used in the assignment of string names to the
1438 function Name_Declaration
(Def_Id
: Entity_Id
) return Node_Id
;
1439 -- Given the name of a temporary variable, create the following
1440 -- declaration for it:
1442 -- Def_Id : aliased constant String := <String_Name_From_Buffer>;
1444 function Set_Entry_Name
(Def_Id
: Entity_Id
) return Node_Id
;
1445 -- Given the name of a temporary variable, place it in the array of
1446 -- string names. Generate:
1448 -- Data (Index) := Def_Id'Unchecked_Access;
1454 function Build_Range
(Def
: Node_Id
) return Node_Id
is
1455 High
: Node_Id
:= Type_High_Bound
(Etype
(Def
));
1456 Low
: Node_Id
:= Type_Low_Bound
(Etype
(Def
));
1459 -- If a bound references a discriminant, generate an identifier
1460 -- with the same name. Resolution will map it to the formals of
1463 if Is_Entity_Name
(Low
)
1464 and then Ekind
(Entity
(Low
)) = E_Discriminant
1467 Make_Selected_Component
(Loc
,
1468 Prefix
=> New_Copy_Tree
(Obj_Ref
),
1469 Selector_Name
=> Make_Identifier
(Loc
, Chars
(Low
)));
1471 Low
:= New_Copy_Tree
(Low
);
1474 if Is_Entity_Name
(High
)
1475 and then Ekind
(Entity
(High
)) = E_Discriminant
1478 Make_Selected_Component
(Loc
,
1479 Prefix
=> New_Copy_Tree
(Obj_Ref
),
1480 Selector_Name
=> Make_Identifier
(Loc
, Chars
(High
)));
1482 High
:= New_Copy_Tree
(High
);
1488 High_Bound
=> High
);
1491 ---------------------------
1492 -- Create_Index_And_Data --
1493 ---------------------------
1495 procedure Create_Index_And_Data
is
1497 if No
(Index
) and then No
(Data
) then
1504 if Is_Protected_Type
(Typ
) then
1505 Count
:= RO_PE_Number_Of_Entries
;
1506 Data_Typ
:= RE_Protected_Entry_Names_Array
;
1508 Count
:= RO_ST_Number_Of_Entries
;
1509 Data_Typ
:= RE_Task_Entry_Names_Array
;
1512 -- Step 1: Generate the declaration of the index variable:
1514 -- Index : Entry_Index := 1;
1516 Index
:= Make_Temporary
(Loc
, 'I');
1519 Make_Object_Declaration
(Loc
,
1520 Defining_Identifier
=> Index
,
1521 Object_Definition
=>
1522 New_Occurrence_Of
(RTE
(RE_Entry_Index
), Loc
),
1523 Expression
=> Make_Integer_Literal
(Loc
, 1)));
1525 -- Step 2: Generate the declaration of an array to house all
1528 -- Size : constant Entry_Index := <Count> (Obj_Ref);
1529 -- Data : aliased <Data_Typ> := (1 .. Size => null);
1531 Size
:= Make_Temporary
(Loc
, 'S');
1534 Make_Object_Declaration
(Loc
,
1535 Defining_Identifier
=> Size
,
1536 Constant_Present
=> True,
1537 Object_Definition
=>
1538 New_Occurrence_Of
(RTE
(RE_Entry_Index
), Loc
),
1540 Make_Function_Call
(Loc
,
1542 New_Occurrence_Of
(RTE
(Count
), Loc
),
1543 Parameter_Associations
=>
1544 New_List
(Object_Reference
))));
1546 Data
:= Make_Temporary
(Loc
, 'A');
1549 Make_Object_Declaration
(Loc
,
1550 Defining_Identifier
=> Data
,
1551 Aliased_Present
=> True,
1552 Object_Definition
=>
1553 New_Occurrence_Of
(RTE
(Data_Typ
), Loc
),
1555 Make_Aggregate
(Loc
,
1556 Component_Associations
=> New_List
(
1557 Make_Component_Association
(Loc
,
1558 Choices
=> New_List
(
1561 Make_Integer_Literal
(Loc
, 1),
1563 New_Occurrence_Of
(Size
, Loc
))),
1564 Expression
=> Make_Null
(Loc
))))));
1567 end Create_Index_And_Data
;
1569 ---------------------
1570 -- Increment_Index --
1571 ---------------------
1573 function Increment_Index
return Node_Id
is
1576 Make_Assignment_Statement
(Loc
,
1577 Name
=> New_Occurrence_Of
(Index
, Loc
),
1580 Left_Opnd
=> New_Occurrence_Of
(Index
, Loc
),
1581 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1)));
1582 end Increment_Index
;
1584 ----------------------
1585 -- Name_Declaration --
1586 ----------------------
1588 function Name_Declaration
(Def_Id
: Entity_Id
) return Node_Id
is
1591 Make_Object_Declaration
(Loc
,
1592 Defining_Identifier
=> Def_Id
,
1593 Aliased_Present
=> True,
1594 Constant_Present
=> True,
1595 Object_Definition
=>
1596 New_Occurrence_Of
(Standard_String
, Loc
),
1598 Make_String_Literal
(Loc
, String_From_Name_Buffer
));
1599 end Name_Declaration
;
1601 --------------------
1602 -- Set_Entry_Name --
1603 --------------------
1605 function Set_Entry_Name
(Def_Id
: Entity_Id
) return Node_Id
is
1608 Make_Assignment_Statement
(Loc
,
1610 Make_Indexed_Component
(Loc
,
1611 Prefix
=> New_Occurrence_Of
(Data
, Loc
),
1612 Expressions
=> New_List
(New_Occurrence_Of
(Index
, Loc
))),
1615 Make_Attribute_Reference
(Loc
,
1616 Prefix
=> New_Occurrence_Of
(Def_Id
, Loc
),
1617 Attribute_Name
=> Name_Unchecked_Access
));
1622 Temp_Id
: Entity_Id
;
1625 -- Start of processing for Build_Entry_Name
1628 if Ekind
(Comp_Id
) = E_Entry_Family
then
1629 Subt_Def
:= Discrete_Subtype_Definition
(Parent
(Comp_Id
));
1631 Create_Index_And_Data
;
1633 -- Step 1: Create the string name of the entry family.
1635 -- Temp : aliased constant String := "name ()";
1637 Temp_Id
:= Make_Temporary
(Loc
, 'S');
1638 Get_Name_String
(Chars
(Comp_Id
));
1639 Add_Char_To_Name_Buffer
(' ');
1640 Add_Char_To_Name_Buffer
('(');
1641 Add_Char_To_Name_Buffer
(')');
1643 Append_To
(Stmts
, Name_Declaration
(Temp_Id
));
1646 -- for Member in Family_Low .. Family_High loop
1647 -- Set_Entry_Name (...);
1648 -- Index := Index + 1;
1652 Make_Loop_Statement
(Loc
,
1654 Make_Iteration_Scheme
(Loc
,
1655 Loop_Parameter_Specification
=>
1656 Make_Loop_Parameter_Specification
(Loc
,
1657 Defining_Identifier
=>
1658 Make_Temporary
(Loc
, 'L'),
1659 Discrete_Subtype_Definition
=>
1660 Build_Range
(Subt_Def
))),
1662 Statements
=> New_List
(
1663 Set_Entry_Name
(Temp_Id
),
1665 End_Label
=> Empty
));
1670 Create_Index_And_Data
;
1672 -- Step 1: Create the string name of the entry. Generate:
1673 -- Temp : aliased constant String := "name";
1675 Temp_Id
:= Make_Temporary
(Loc
, 'S');
1676 Get_Name_String
(Chars
(Comp_Id
));
1678 Append_To
(Stmts
, Name_Declaration
(Temp_Id
));
1680 -- Step 2: Associate the string name with the underlying data
1683 Append_To
(Stmts
, Set_Entry_Name
(Temp_Id
));
1684 Append_To
(Stmts
, Increment_Index
);
1686 end Build_Entry_Name
;
1688 ----------------------
1689 -- Object_Reference --
1690 ----------------------
1692 function Object_Reference
return Node_Id
is
1693 Conc_Typ
: constant Entity_Id
:= Corresponding_Record_Type
(Typ
);
1698 if Is_Protected_Type
(Typ
) then
1699 Field
:= Name_uObject
;
1701 Field
:= Name_uTask_Id
;
1705 Make_Selected_Component
(Loc
,
1707 Unchecked_Convert_To
(Conc_Typ
, New_Copy_Tree
(Obj_Ref
)),
1708 Selector_Name
=> Make_Identifier
(Loc
, Field
));
1710 if Is_Protected_Type
(Typ
) then
1712 Make_Attribute_Reference
(Loc
,
1714 Attribute_Name
=> Name_Unchecked_Access
);
1718 end Object_Reference
;
1725 -- Start of processing for Build_Entry_Names
1728 -- Retrieve the original concurrent type
1730 if Is_Concurrent_Record_Type
(Typ
) then
1731 Typ
:= Corresponding_Concurrent_Type
(Typ
);
1734 pragma Assert
(Is_Concurrent_Type
(Typ
));
1736 -- Nothing to do if the type has no entries
1738 if not Has_Entries
(Typ
) then
1742 -- Avoid generating entry names for a protected type with only one entry
1744 if Is_Protected_Type
(Typ
)
1745 and then Find_Protection_Type
(Base_Type
(Typ
)) /=
1746 RTE
(RE_Protection_Entries
)
1751 -- Step 1: Populate the array with statically generated strings denoting
1752 -- entries and entry family names.
1754 Comp
:= First_Entity
(Typ
);
1755 while Present
(Comp
) loop
1756 if Comes_From_Source
(Comp
)
1757 and then Ekind_In
(Comp
, E_Entry
, E_Entry_Family
)
1759 Build_Entry_Name
(Comp
);
1765 -- Step 2: Associate the array with the related concurrent object:
1767 -- Set_Entry_Names (Obj_Ref, <Data>'Unchecked_Access);
1769 if Present
(Data
) then
1770 if Is_Protected_Type
(Typ
) then
1771 Proc
:= RO_PE_Set_Entry_Names
;
1773 Proc
:= RO_ST_Set_Entry_Names
;
1777 Make_Procedure_Call_Statement
(Loc
,
1778 Name
=> New_Occurrence_Of
(RTE
(Proc
), Loc
),
1779 Parameter_Associations
=> New_List
(
1781 Make_Attribute_Reference
(Loc
,
1782 Prefix
=> New_Occurrence_Of
(Data
, Loc
),
1783 Attribute_Name
=> Name_Unchecked_Access
))));
1785 end Build_Entry_Names
;
1787 ---------------------------
1788 -- Build_Parameter_Block --
1789 ---------------------------
1791 function Build_Parameter_Block
1795 Decls
: List_Id
) return Entity_Id
1801 Has_Comp
: Boolean := False;
1805 Actual
:= First
(Actuals
);
1807 Formal
:= Defining_Identifier
(First
(Formals
));
1809 while Present
(Actual
) loop
1810 if not Is_Controlling_Actual
(Actual
) then
1813 -- type Ann is access all <actual-type>
1815 Comp_Nam
:= Make_Temporary
(Loc
, 'A');
1818 Make_Full_Type_Declaration
(Loc
,
1819 Defining_Identifier
=> Comp_Nam
,
1821 Make_Access_To_Object_Definition
(Loc
,
1822 All_Present
=> True,
1823 Constant_Present
=> Ekind
(Formal
) = E_In_Parameter
,
1824 Subtype_Indication
=>
1825 New_Occurrence_Of
(Etype
(Actual
), Loc
))));
1831 Make_Component_Declaration
(Loc
,
1832 Defining_Identifier
=>
1833 Make_Defining_Identifier
(Loc
, Chars
(Formal
)),
1834 Component_Definition
=>
1835 Make_Component_Definition
(Loc
,
1838 Subtype_Indication
=>
1839 New_Occurrence_Of
(Comp_Nam
, Loc
))));
1844 Next_Actual
(Actual
);
1845 Next_Formal_With_Extras
(Formal
);
1848 Rec_Nam
:= Make_Temporary
(Loc
, 'P');
1853 -- type Pnn is record
1858 -- where Pnn is a parameter wrapping record, Param1 .. ParamN are
1859 -- the original parameter names and Ann1 .. AnnN are the access to
1863 Make_Full_Type_Declaration
(Loc
,
1864 Defining_Identifier
=>
1867 Make_Record_Definition
(Loc
,
1869 Make_Component_List
(Loc
, Comps
))));
1872 -- type Pnn is null record;
1875 Make_Full_Type_Declaration
(Loc
,
1876 Defining_Identifier
=>
1879 Make_Record_Definition
(Loc
,
1880 Null_Present
=> True,
1881 Component_List
=> Empty
)));
1885 end Build_Parameter_Block
;
1887 --------------------------------------
1888 -- Build_Renamed_Formal_Declaration --
1889 --------------------------------------
1891 function Build_Renamed_Formal_Declaration
1895 Renamed_Formal
: Node_Id
) return Node_Id
1897 Loc
: constant Source_Ptr
:= Sloc
(New_F
);
1901 -- If the formal is a tagged incomplete type, it is already passed
1902 -- by reference, so it is sufficient to rename the pointer component
1903 -- that corresponds to the actual. Otherwise we need to dereference
1904 -- the pointer component to obtain the actual.
1906 if Is_Incomplete_Type
(Etype
(Formal
))
1907 and then Is_Tagged_Type
(Etype
(Formal
))
1910 Make_Object_Renaming_Declaration
(Loc
,
1911 Defining_Identifier
=> New_F
,
1912 Subtype_Mark
=> New_Occurrence_Of
(Etype
(Comp
), Loc
),
1913 Name
=> Renamed_Formal
);
1917 Make_Object_Renaming_Declaration
(Loc
,
1918 Defining_Identifier
=> New_F
,
1919 Subtype_Mark
=> New_Occurrence_Of
(Etype
(Formal
), Loc
),
1921 Make_Explicit_Dereference
(Loc
, Renamed_Formal
));
1925 end Build_Renamed_Formal_Declaration
;
1927 -----------------------
1928 -- Build_PPC_Wrapper --
1929 -----------------------
1931 procedure Build_PPC_Wrapper
(E
: Entity_Id
; Decl
: Node_Id
) is
1932 Loc
: constant Source_Ptr
:= Sloc
(E
);
1933 Synch_Type
: constant Entity_Id
:= Scope
(E
);
1935 Wrapper_Id
: constant Entity_Id
:=
1936 Make_Defining_Identifier
(Loc
,
1937 Chars
=> New_External_Name
(Chars
(E
), 'E'));
1938 -- the wrapper procedure name
1940 Wrapper_Body
: Node_Id
;
1942 Synch_Id
: constant Entity_Id
:=
1943 Make_Defining_Identifier
(Loc
,
1944 Chars
=> New_External_Name
(Chars
(Scope
(E
)), 'A'));
1945 -- The parameter that designates the synchronized object in the call
1947 Actuals
: constant List_Id
:= New_List
;
1948 -- The actuals in the entry call
1950 Decls
: constant List_Id
:= New_List
;
1952 Entry_Call
: Node_Id
;
1953 Entry_Name
: Node_Id
;
1956 -- The specification of the wrapper procedure
1960 -- Only build the wrapper if entry has pre/postconditions.
1961 -- Should this be done unconditionally instead ???
1967 P
:= Pre_Post_Conditions
(Contract
(E
));
1973 -- Transfer ppc pragmas to the declarations of the wrapper
1975 while Present
(P
) loop
1976 if Nam_In
(Pragma_Name
(P
), Name_Precondition
,
1979 Append
(Relocate_Node
(P
), Decls
);
1980 Set_Analyzed
(Last
(Decls
), False);
1983 P
:= Next_Pragma
(P
);
1987 -- First formal is synchronized object
1990 Make_Parameter_Specification
(Loc
,
1991 Defining_Identifier
=> Synch_Id
,
1992 Out_Present
=> True,
1994 Parameter_Type
=> New_Occurrence_Of
(Scope
(E
), Loc
)));
1997 Make_Selected_Component
(Loc
,
1998 Prefix
=> New_Occurrence_Of
(Synch_Id
, Loc
),
1999 Selector_Name
=> New_Occurrence_Of
(E
, Loc
));
2001 -- If entity is entry family, second formal is the corresponding index,
2002 -- and entry name is an indexed component.
2004 if Ekind
(E
) = E_Entry_Family
then
2006 Index
: constant Entity_Id
:=
2007 Make_Defining_Identifier
(Loc
, Name_I
);
2010 Make_Parameter_Specification
(Loc
,
2011 Defining_Identifier
=> Index
,
2013 New_Occurrence_Of
(Entry_Index_Type
(E
), Loc
)));
2016 Make_Indexed_Component
(Loc
,
2017 Prefix
=> Entry_Name
,
2018 Expressions
=> New_List
(New_Occurrence_Of
(Index
, Loc
)));
2023 Make_Procedure_Call_Statement
(Loc
,
2025 Parameter_Associations
=> Actuals
);
2027 -- Now add formals that match those of the entry, and build actuals for
2028 -- the nested entry call.
2032 New_Form
: Entity_Id
;
2033 Parm_Spec
: Node_Id
;
2036 Form
:= First_Formal
(E
);
2037 while Present
(Form
) loop
2038 New_Form
:= Make_Defining_Identifier
(Loc
, Chars
(Form
));
2040 Make_Parameter_Specification
(Loc
,
2041 Defining_Identifier
=> New_Form
,
2042 Out_Present
=> Out_Present
(Parent
(Form
)),
2043 In_Present
=> In_Present
(Parent
(Form
)),
2044 Parameter_Type
=> New_Occurrence_Of
(Etype
(Form
), Loc
));
2046 Append
(Parm_Spec
, Specs
);
2047 Append
(New_Occurrence_Of
(New_Form
, Loc
), Actuals
);
2052 -- Add renaming declarations for the discriminants of the enclosing
2053 -- type, which may be visible in the preconditions.
2055 if Has_Discriminants
(Synch_Type
) then
2061 D
:= First_Discriminant
(Synch_Type
);
2062 while Present
(D
) loop
2064 Make_Object_Renaming_Declaration
(Loc
,
2065 Defining_Identifier
=>
2066 Make_Defining_Identifier
(Loc
, Chars
(D
)),
2067 Subtype_Mark
=> New_Occurrence_Of
(Etype
(D
), Loc
),
2069 Make_Selected_Component
(Loc
,
2070 Prefix
=> New_Occurrence_Of
(Synch_Id
, Loc
),
2071 Selector_Name
=> Make_Identifier
(Loc
, Chars
(D
))));
2072 Prepend
(Decl
, Decls
);
2073 Next_Discriminant
(D
);
2078 Set_PPC_Wrapper
(E
, Wrapper_Id
);
2080 Make_Subprogram_Body
(Loc
,
2082 Make_Procedure_Specification
(Loc
,
2083 Defining_Unit_Name
=> Wrapper_Id
,
2084 Parameter_Specifications
=> Specs
),
2085 Declarations
=> Decls
,
2086 Handled_Statement_Sequence
=>
2087 Make_Handled_Sequence_Of_Statements
(Loc
,
2088 Statements
=> New_List
(Entry_Call
)));
2090 -- The wrapper body is analyzed when the enclosing type is frozen
2092 Append_Freeze_Action
(Defining_Entity
(Decl
), Wrapper_Body
);
2093 end Build_PPC_Wrapper
;
2095 --------------------------
2096 -- Build_Wrapper_Bodies --
2097 --------------------------
2099 procedure Build_Wrapper_Bodies
2104 Rec_Typ
: Entity_Id
;
2106 function Build_Wrapper_Body
2108 Subp_Id
: Entity_Id
;
2109 Obj_Typ
: Entity_Id
;
2110 Formals
: List_Id
) return Node_Id
;
2111 -- Ada 2005 (AI-345): Build the body that wraps a primitive operation
2112 -- associated with a protected or task type. Subp_Id is the subprogram
2113 -- name which will be wrapped. Obj_Typ is the type of the new formal
2114 -- parameter which handles dispatching and object notation. Formals are
2115 -- the original formals of Subp_Id which will be explicitly replicated.
2117 ------------------------
2118 -- Build_Wrapper_Body --
2119 ------------------------
2121 function Build_Wrapper_Body
2123 Subp_Id
: Entity_Id
;
2124 Obj_Typ
: Entity_Id
;
2125 Formals
: List_Id
) return Node_Id
2127 Body_Spec
: Node_Id
;
2130 Body_Spec
:= Build_Wrapper_Spec
(Subp_Id
, Obj_Typ
, Formals
);
2132 -- The subprogram is not overriding or is not a primitive declared
2133 -- between two views.
2135 if No
(Body_Spec
) then
2140 Actuals
: List_Id
:= No_List
;
2142 First_Form
: Node_Id
;
2147 -- Map formals to actuals. Use the list built for the wrapper
2148 -- spec, skipping the object notation parameter.
2150 First_Form
:= First
(Parameter_Specifications
(Body_Spec
));
2152 Formal
:= First_Form
;
2155 if Present
(Formal
) then
2156 Actuals
:= New_List
;
2157 while Present
(Formal
) loop
2159 Make_Identifier
(Loc
,
2160 Chars
=> Chars
(Defining_Identifier
(Formal
))));
2165 -- Special processing for primitives declared between a private
2166 -- type and its completion: the wrapper needs a properly typed
2167 -- parameter if the wrapped operation has a controlling first
2168 -- parameter. Note that this might not be the case for a function
2169 -- with a controlling result.
2171 if Is_Private_Primitive_Subprogram
(Subp_Id
) then
2172 if No
(Actuals
) then
2173 Actuals
:= New_List
;
2176 if Is_Controlling_Formal
(First_Formal
(Subp_Id
)) then
2177 Prepend_To
(Actuals
,
2178 Unchecked_Convert_To
2179 (Corresponding_Concurrent_Type
(Obj_Typ
),
2180 Make_Identifier
(Loc
, Name_uO
)));
2183 Prepend_To
(Actuals
,
2184 Make_Identifier
(Loc
,
2185 Chars
=> Chars
(Defining_Identifier
(First_Form
))));
2188 Nam
:= New_Occurrence_Of
(Subp_Id
, Loc
);
2190 -- An access-to-variable object parameter requires an explicit
2191 -- dereference in the unchecked conversion. This case occurs
2192 -- when a protected entry wrapper must override an interface
2193 -- level procedure with interface access as first parameter.
2195 -- O.all.Subp_Id (Formal_1, ..., Formal_N)
2197 if Nkind
(Parameter_Type
(First_Form
)) =
2201 Make_Explicit_Dereference
(Loc
,
2202 Prefix
=> Make_Identifier
(Loc
, Name_uO
));
2204 Conv_Id
:= Make_Identifier
(Loc
, Name_uO
);
2208 Make_Selected_Component
(Loc
,
2210 Unchecked_Convert_To
2211 (Corresponding_Concurrent_Type
(Obj_Typ
), Conv_Id
),
2212 Selector_Name
=> New_Occurrence_Of
(Subp_Id
, Loc
));
2215 -- Create the subprogram body. For a function, the call to the
2216 -- actual subprogram has to be converted to the corresponding
2217 -- record if it is a controlling result.
2219 if Ekind
(Subp_Id
) = E_Function
then
2225 Make_Function_Call
(Loc
,
2227 Parameter_Associations
=> Actuals
);
2229 if Has_Controlling_Result
(Subp_Id
) then
2231 Unchecked_Convert_To
2232 (Corresponding_Record_Type
(Etype
(Subp_Id
)), Res
);
2236 Make_Subprogram_Body
(Loc
,
2237 Specification
=> Body_Spec
,
2238 Declarations
=> Empty_List
,
2239 Handled_Statement_Sequence
=>
2240 Make_Handled_Sequence_Of_Statements
(Loc
,
2241 Statements
=> New_List
(
2242 Make_Simple_Return_Statement
(Loc
, Res
))));
2247 Make_Subprogram_Body
(Loc
,
2248 Specification
=> Body_Spec
,
2249 Declarations
=> Empty_List
,
2250 Handled_Statement_Sequence
=>
2251 Make_Handled_Sequence_Of_Statements
(Loc
,
2252 Statements
=> New_List
(
2253 Make_Procedure_Call_Statement
(Loc
,
2255 Parameter_Associations
=> Actuals
))));
2258 end Build_Wrapper_Body
;
2260 -- Start of processing for Build_Wrapper_Bodies
2263 if Is_Concurrent_Type
(Typ
) then
2264 Rec_Typ
:= Corresponding_Record_Type
(Typ
);
2269 -- Generate wrapper bodies for a concurrent type which implements an
2272 if Present
(Interfaces
(Rec_Typ
)) then
2274 Insert_Nod
: Node_Id
;
2276 Prim_Elmt
: Elmt_Id
;
2277 Prim_Decl
: Node_Id
;
2279 Wrap_Body
: Node_Id
;
2280 Wrap_Id
: Entity_Id
;
2285 -- Examine all primitive operations of the corresponding record
2286 -- type, looking for wrapper specs. Generate bodies in order to
2289 Prim_Elmt
:= First_Elmt
(Primitive_Operations
(Rec_Typ
));
2290 while Present
(Prim_Elmt
) loop
2291 Prim
:= Node
(Prim_Elmt
);
2293 if (Ekind
(Prim
) = E_Function
2294 or else Ekind
(Prim
) = E_Procedure
)
2295 and then Is_Primitive_Wrapper
(Prim
)
2297 Subp
:= Wrapped_Entity
(Prim
);
2298 Prim_Decl
:= Parent
(Parent
(Prim
));
2301 Build_Wrapper_Body
(Loc
,
2304 Formals
=> Parameter_Specifications
(Parent
(Subp
)));
2305 Wrap_Id
:= Defining_Unit_Name
(Specification
(Wrap_Body
));
2307 Set_Corresponding_Spec
(Wrap_Body
, Prim
);
2308 Set_Corresponding_Body
(Prim_Decl
, Wrap_Id
);
2310 Insert_After
(Insert_Nod
, Wrap_Body
);
2311 Insert_Nod
:= Wrap_Body
;
2313 Analyze
(Wrap_Body
);
2316 Next_Elmt
(Prim_Elmt
);
2320 end Build_Wrapper_Bodies
;
2322 ------------------------
2323 -- Build_Wrapper_Spec --
2324 ------------------------
2326 function Build_Wrapper_Spec
2327 (Subp_Id
: Entity_Id
;
2328 Obj_Typ
: Entity_Id
;
2329 Formals
: List_Id
) return Node_Id
2331 Loc
: constant Source_Ptr
:= Sloc
(Subp_Id
);
2332 First_Param
: Node_Id
;
2334 Iface_Elmt
: Elmt_Id
;
2335 Iface_Op
: Entity_Id
;
2336 Iface_Op_Elmt
: Elmt_Id
;
2338 function Overriding_Possible
2339 (Iface_Op
: Entity_Id
;
2340 Wrapper
: Entity_Id
) return Boolean;
2341 -- Determine whether a primitive operation can be overridden by Wrapper.
2342 -- Iface_Op is the candidate primitive operation of an interface type,
2343 -- Wrapper is the generated entry wrapper.
2345 function Replicate_Formals
2347 Formals
: List_Id
) return List_Id
;
2348 -- An explicit parameter replication is required due to the Is_Entry_
2349 -- Formal flag being set for all the formals of an entry. The explicit
2350 -- replication removes the flag that would otherwise cause a different
2351 -- path of analysis.
2353 -------------------------
2354 -- Overriding_Possible --
2355 -------------------------
2357 function Overriding_Possible
2358 (Iface_Op
: Entity_Id
;
2359 Wrapper
: Entity_Id
) return Boolean
2361 Iface_Op_Spec
: constant Node_Id
:= Parent
(Iface_Op
);
2362 Wrapper_Spec
: constant Node_Id
:= Parent
(Wrapper
);
2364 function Type_Conformant_Parameters
2365 (Iface_Op_Params
: List_Id
;
2366 Wrapper_Params
: List_Id
) return Boolean;
2367 -- Determine whether the parameters of the generated entry wrapper
2368 -- and those of a primitive operation are type conformant. During
2369 -- this check, the first parameter of the primitive operation is
2370 -- skipped if it is a controlling argument: protected functions
2371 -- may have a controlling result.
2373 --------------------------------
2374 -- Type_Conformant_Parameters --
2375 --------------------------------
2377 function Type_Conformant_Parameters
2378 (Iface_Op_Params
: List_Id
;
2379 Wrapper_Params
: List_Id
) return Boolean
2381 Iface_Op_Param
: Node_Id
;
2382 Iface_Op_Typ
: Entity_Id
;
2383 Wrapper_Param
: Node_Id
;
2384 Wrapper_Typ
: Entity_Id
;
2387 -- Skip the first (controlling) parameter of primitive operation
2389 Iface_Op_Param
:= First
(Iface_Op_Params
);
2391 if Present
(First_Formal
(Iface_Op
))
2392 and then Is_Controlling_Formal
(First_Formal
(Iface_Op
))
2394 Iface_Op_Param
:= Next
(Iface_Op_Param
);
2397 Wrapper_Param
:= First
(Wrapper_Params
);
2398 while Present
(Iface_Op_Param
)
2399 and then Present
(Wrapper_Param
)
2401 Iface_Op_Typ
:= Find_Parameter_Type
(Iface_Op_Param
);
2402 Wrapper_Typ
:= Find_Parameter_Type
(Wrapper_Param
);
2404 -- The two parameters must be mode conformant
2406 if not Conforming_Types
2407 (Iface_Op_Typ
, Wrapper_Typ
, Mode_Conformant
)
2412 Next
(Iface_Op_Param
);
2413 Next
(Wrapper_Param
);
2416 -- One of the lists is longer than the other
2418 if Present
(Iface_Op_Param
) or else Present
(Wrapper_Param
) then
2423 end Type_Conformant_Parameters
;
2425 -- Start of processing for Overriding_Possible
2428 if Chars
(Iface_Op
) /= Chars
(Wrapper
) then
2432 -- If an inherited subprogram is implemented by a protected procedure
2433 -- or an entry, then the first parameter of the inherited subprogram
2434 -- shall be of mode OUT or IN OUT, or access-to-variable parameter.
2436 if Ekind
(Iface_Op
) = E_Procedure
2437 and then Present
(Parameter_Specifications
(Iface_Op_Spec
))
2440 Obj_Param
: constant Node_Id
:=
2441 First
(Parameter_Specifications
(Iface_Op_Spec
));
2443 if not Out_Present
(Obj_Param
)
2444 and then Nkind
(Parameter_Type
(Obj_Param
)) /=
2453 Type_Conformant_Parameters
(
2454 Parameter_Specifications
(Iface_Op_Spec
),
2455 Parameter_Specifications
(Wrapper_Spec
));
2456 end Overriding_Possible
;
2458 -----------------------
2459 -- Replicate_Formals --
2460 -----------------------
2462 function Replicate_Formals
2464 Formals
: List_Id
) return List_Id
2466 New_Formals
: constant List_Id
:= New_List
;
2468 Param_Type
: Node_Id
;
2471 Formal
:= First
(Formals
);
2473 -- Skip the object parameter when dealing with primitives declared
2474 -- between two views.
2476 if Is_Private_Primitive_Subprogram
(Subp_Id
)
2477 and then not Has_Controlling_Result
(Subp_Id
)
2479 Formal
:= Next
(Formal
);
2482 while Present
(Formal
) loop
2484 -- Create an explicit copy of the entry parameter
2486 -- When creating the wrapper subprogram for a primitive operation
2487 -- of a protected interface we must construct an equivalent
2488 -- signature to that of the overriding operation. For regular
2489 -- parameters we can just use the type of the formal, but for
2490 -- access to subprogram parameters we need to reanalyze the
2491 -- parameter type to create local entities for the signature of
2492 -- the subprogram type. Using the entities of the overriding
2493 -- subprogram will result in out-of-scope errors in the back-end.
2495 if Nkind
(Parameter_Type
(Formal
)) = N_Access_Definition
then
2496 Param_Type
:= Copy_Separate_Tree
(Parameter_Type
(Formal
));
2499 New_Occurrence_Of
(Etype
(Parameter_Type
(Formal
)), Loc
);
2502 Append_To
(New_Formals
,
2503 Make_Parameter_Specification
(Loc
,
2504 Defining_Identifier
=>
2505 Make_Defining_Identifier
(Loc
,
2506 Chars
=> Chars
(Defining_Identifier
(Formal
))),
2507 In_Present
=> In_Present
(Formal
),
2508 Out_Present
=> Out_Present
(Formal
),
2509 Parameter_Type
=> Param_Type
));
2515 end Replicate_Formals
;
2517 -- Start of processing for Build_Wrapper_Spec
2520 -- There is no point in building wrappers for non-tagged concurrent
2523 pragma Assert
(Is_Tagged_Type
(Obj_Typ
));
2525 -- An entry or a protected procedure can override a routine where the
2526 -- controlling formal is either IN OUT, OUT or is of access-to-variable
2527 -- type. Since the wrapper must have the exact same signature as that of
2528 -- the overridden subprogram, we try to find the overriding candidate
2529 -- and use its controlling formal.
2531 First_Param
:= Empty
;
2533 -- Check every implemented interface
2535 if Present
(Interfaces
(Obj_Typ
)) then
2536 Iface_Elmt
:= First_Elmt
(Interfaces
(Obj_Typ
));
2537 Search
: while Present
(Iface_Elmt
) loop
2538 Iface
:= Node
(Iface_Elmt
);
2540 -- Check every interface primitive
2542 if Present
(Primitive_Operations
(Iface
)) then
2543 Iface_Op_Elmt
:= First_Elmt
(Primitive_Operations
(Iface
));
2544 while Present
(Iface_Op_Elmt
) loop
2545 Iface_Op
:= Node
(Iface_Op_Elmt
);
2547 -- Ignore predefined primitives
2549 if not Is_Predefined_Dispatching_Operation
(Iface_Op
) then
2550 Iface_Op
:= Ultimate_Alias
(Iface_Op
);
2552 -- The current primitive operation can be overridden by
2553 -- the generated entry wrapper.
2555 if Overriding_Possible
(Iface_Op
, Subp_Id
) then
2557 First
(Parameter_Specifications
(Parent
(Iface_Op
)));
2563 Next_Elmt
(Iface_Op_Elmt
);
2567 Next_Elmt
(Iface_Elmt
);
2571 -- Ada 2012 (AI05-0090-1): If no interface primitive is covered by
2572 -- this subprogram and this is not a primitive declared between two
2573 -- views then force the generation of a wrapper. As an optimization,
2574 -- previous versions of the frontend avoid generating the wrapper;
2575 -- however, the wrapper facilitates locating and reporting an error
2576 -- when a duplicate declaration is found later. See example in
2580 and then not Is_Private_Primitive_Subprogram
(Subp_Id
)
2583 (Corresponding_Concurrent_Type
(Obj_Typ
))
2586 Make_Parameter_Specification
(Loc
,
2587 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_uO
),
2589 Out_Present
=> False,
2590 Parameter_Type
=> New_Occurrence_Of
(Obj_Typ
, Loc
));
2592 -- For entries and procedures of protected types the mode of
2593 -- the controlling argument must be in-out.
2597 Make_Parameter_Specification
(Loc
,
2598 Defining_Identifier
=>
2599 Make_Defining_Identifier
(Loc
,
2602 Out_Present
=> (Ekind
(Subp_Id
) /= E_Function
),
2603 Parameter_Type
=> New_Occurrence_Of
(Obj_Typ
, Loc
));
2608 Wrapper_Id
: constant Entity_Id
:=
2609 Make_Defining_Identifier
(Loc
, Chars
(Subp_Id
));
2610 New_Formals
: List_Id
;
2611 Obj_Param
: Node_Id
;
2612 Obj_Param_Typ
: Entity_Id
;
2615 -- Minimum decoration is needed to catch the entity in
2616 -- Sem_Ch6.Override_Dispatching_Operation.
2618 if Ekind
(Subp_Id
) = E_Function
then
2619 Set_Ekind
(Wrapper_Id
, E_Function
);
2621 Set_Ekind
(Wrapper_Id
, E_Procedure
);
2624 Set_Is_Primitive_Wrapper
(Wrapper_Id
);
2625 Set_Wrapped_Entity
(Wrapper_Id
, Subp_Id
);
2626 Set_Is_Private_Primitive
(Wrapper_Id
,
2627 Is_Private_Primitive_Subprogram
(Subp_Id
));
2629 -- Process the formals
2631 New_Formals
:= Replicate_Formals
(Loc
, Formals
);
2633 -- A function with a controlling result and no first controlling
2634 -- formal needs no additional parameter.
2636 if Has_Controlling_Result
(Subp_Id
)
2638 (No
(First_Formal
(Subp_Id
))
2639 or else not Is_Controlling_Formal
(First_Formal
(Subp_Id
)))
2643 -- Routine Subp_Id has been found to override an interface primitive.
2644 -- If the interface operation has an access parameter, create a copy
2645 -- of it, with the same null exclusion indicator if present.
2647 elsif Present
(First_Param
) then
2648 if Nkind
(Parameter_Type
(First_Param
)) = N_Access_Definition
then
2650 Make_Access_Definition
(Loc
,
2652 New_Occurrence_Of
(Obj_Typ
, Loc
));
2653 Set_Null_Exclusion_Present
(Obj_Param_Typ
,
2654 Null_Exclusion_Present
(Parameter_Type
(First_Param
)));
2657 Obj_Param_Typ
:= New_Occurrence_Of
(Obj_Typ
, Loc
);
2661 Make_Parameter_Specification
(Loc
,
2662 Defining_Identifier
=>
2663 Make_Defining_Identifier
(Loc
,
2665 In_Present
=> In_Present
(First_Param
),
2666 Out_Present
=> Out_Present
(First_Param
),
2667 Parameter_Type
=> Obj_Param_Typ
);
2669 Prepend_To
(New_Formals
, Obj_Param
);
2671 -- If we are dealing with a primitive declared between two views,
2672 -- implemented by a synchronized operation, we need to create
2673 -- a default parameter. The mode of the parameter must match that
2674 -- of the primitive operation.
2677 pragma Assert
(Is_Private_Primitive_Subprogram
(Subp_Id
));
2679 Make_Parameter_Specification
(Loc
,
2680 Defining_Identifier
=>
2681 Make_Defining_Identifier
(Loc
, Name_uO
),
2682 In_Present
=> In_Present
(Parent
(First_Entity
(Subp_Id
))),
2683 Out_Present
=> Ekind
(Subp_Id
) /= E_Function
,
2684 Parameter_Type
=> New_Occurrence_Of
(Obj_Typ
, Loc
));
2685 Prepend_To
(New_Formals
, Obj_Param
);
2688 -- Build the final spec. If it is a function with a controlling
2689 -- result, it is a primitive operation of the corresponding
2690 -- record type, so mark the spec accordingly.
2692 if Ekind
(Subp_Id
) = E_Function
then
2697 if Has_Controlling_Result
(Subp_Id
) then
2700 (Corresponding_Record_Type
(Etype
(Subp_Id
)), Loc
);
2702 Res_Def
:= New_Copy
(Result_Definition
(Parent
(Subp_Id
)));
2706 Make_Function_Specification
(Loc
,
2707 Defining_Unit_Name
=> Wrapper_Id
,
2708 Parameter_Specifications
=> New_Formals
,
2709 Result_Definition
=> Res_Def
);
2713 Make_Procedure_Specification
(Loc
,
2714 Defining_Unit_Name
=> Wrapper_Id
,
2715 Parameter_Specifications
=> New_Formals
);
2718 end Build_Wrapper_Spec
;
2720 -------------------------
2721 -- Build_Wrapper_Specs --
2722 -------------------------
2724 procedure Build_Wrapper_Specs
2730 Rec_Typ
: Entity_Id
;
2731 procedure Scan_Declarations
(L
: List_Id
);
2732 -- Common processing for visible and private declarations
2733 -- of a protected type.
2735 procedure Scan_Declarations
(L
: List_Id
) is
2737 Wrap_Decl
: Node_Id
;
2738 Wrap_Spec
: Node_Id
;
2746 while Present
(Decl
) loop
2749 if Nkind
(Decl
) = N_Entry_Declaration
2750 and then Ekind
(Defining_Identifier
(Decl
)) = E_Entry
2754 (Subp_Id
=> Defining_Identifier
(Decl
),
2756 Formals
=> Parameter_Specifications
(Decl
));
2758 elsif Nkind
(Decl
) = N_Subprogram_Declaration
then
2761 (Subp_Id
=> Defining_Unit_Name
(Specification
(Decl
)),
2764 Parameter_Specifications
(Specification
(Decl
)));
2767 if Present
(Wrap_Spec
) then
2769 Make_Subprogram_Declaration
(Loc
,
2770 Specification
=> Wrap_Spec
);
2772 Insert_After
(N
, Wrap_Decl
);
2775 Analyze
(Wrap_Decl
);
2780 end Scan_Declarations
;
2782 -- start of processing for Build_Wrapper_Specs
2785 if Is_Protected_Type
(Typ
) then
2786 Def
:= Protected_Definition
(Parent
(Typ
));
2787 else pragma Assert
(Is_Task_Type
(Typ
));
2788 Def
:= Task_Definition
(Parent
(Typ
));
2791 Rec_Typ
:= Corresponding_Record_Type
(Typ
);
2793 -- Generate wrapper specs for a concurrent type which implements an
2794 -- interface. Operations in both the visible and private parts may
2795 -- implement progenitor operations.
2797 if Present
(Interfaces
(Rec_Typ
))
2798 and then Present
(Def
)
2800 Scan_Declarations
(Visible_Declarations
(Def
));
2801 Scan_Declarations
(Private_Declarations
(Def
));
2803 end Build_Wrapper_Specs
;
2805 ---------------------------
2806 -- Build_Find_Body_Index --
2807 ---------------------------
2809 function Build_Find_Body_Index
(Typ
: Entity_Id
) return Node_Id
is
2810 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
2813 Has_F
: Boolean := False;
2815 If_St
: Node_Id
:= Empty
;
2818 Decls
: List_Id
:= New_List
;
2821 Siz
: Node_Id
:= Empty
;
2823 procedure Add_If_Clause
(Expr
: Node_Id
);
2824 -- Add test for range of current entry
2826 function Convert_Discriminant_Ref
(Bound
: Node_Id
) return Node_Id
;
2827 -- If a bound of an entry is given by a discriminant, retrieve the
2828 -- actual value of the discriminant from the enclosing object.
2834 procedure Add_If_Clause
(Expr
: Node_Id
) is
2836 Stats
: constant List_Id
:=
2838 Make_Simple_Return_Statement
(Loc
,
2839 Expression
=> Make_Integer_Literal
(Loc
, Index
+ 1)));
2842 -- Index for current entry body
2846 -- Compute total length of entry queues so far
2854 Right_Opnd
=> Expr
);
2859 Left_Opnd
=> Make_Identifier
(Loc
, Name_uE
),
2862 -- Map entry queue indexes in the range of the current family
2863 -- into the current index, that designates the entry body.
2867 Make_Implicit_If_Statement
(Typ
,
2869 Then_Statements
=> Stats
,
2870 Elsif_Parts
=> New_List
);
2874 Append_To
(Elsif_Parts
(If_St
),
2875 Make_Elsif_Part
(Loc
,
2877 Then_Statements
=> Stats
));
2881 ------------------------------
2882 -- Convert_Discriminant_Ref --
2883 ------------------------------
2885 function Convert_Discriminant_Ref
(Bound
: Node_Id
) return Node_Id
is
2889 if Is_Entity_Name
(Bound
)
2890 and then Ekind
(Entity
(Bound
)) = E_Discriminant
2893 Make_Selected_Component
(Loc
,
2895 Unchecked_Convert_To
(Corresponding_Record_Type
(Typ
),
2896 Make_Explicit_Dereference
(Loc
,
2897 Make_Identifier
(Loc
, Name_uObject
))),
2898 Selector_Name
=> Make_Identifier
(Loc
, Chars
(Bound
)));
2899 Set_Etype
(B
, Etype
(Entity
(Bound
)));
2901 B
:= New_Copy_Tree
(Bound
);
2905 end Convert_Discriminant_Ref
;
2907 -- Start of processing for Build_Find_Body_Index
2910 Spec
:= Build_Find_Body_Index_Spec
(Typ
);
2912 Ent
:= First_Entity
(Typ
);
2913 while Present
(Ent
) loop
2914 if Ekind
(Ent
) = E_Entry_Family
then
2924 -- If the protected type has no entry families, there is a one-one
2925 -- correspondence between entry queue and entry body.
2928 Make_Simple_Return_Statement
(Loc
,
2929 Expression
=> Make_Identifier
(Loc
, Name_uE
));
2932 -- Suppose entries e1, e2, ... have size l1, l2, ... we generate
2935 -- if E <= l1 then return 1;
2936 -- elsif E <= l1 + l2 then return 2;
2941 Ent
:= First_Entity
(Typ
);
2943 Add_Object_Pointer
(Loc
, Typ
, Decls
);
2945 while Present
(Ent
) loop
2946 if Ekind
(Ent
) = E_Entry
then
2947 Add_If_Clause
(Make_Integer_Literal
(Loc
, 1));
2949 elsif Ekind
(Ent
) = E_Entry_Family
then
2950 E_Typ
:= Etype
(Discrete_Subtype_Definition
(Parent
(Ent
)));
2951 Hi
:= Convert_Discriminant_Ref
(Type_High_Bound
(E_Typ
));
2952 Lo
:= Convert_Discriminant_Ref
(Type_Low_Bound
(E_Typ
));
2953 Add_If_Clause
(Family_Size
(Loc
, Hi
, Lo
, Typ
, False));
2962 Make_Simple_Return_Statement
(Loc
,
2963 Expression
=> Make_Integer_Literal
(Loc
, 1));
2965 elsif Nkind
(Ret
) = N_If_Statement
then
2967 -- Ranges are in increasing order, so last one doesn't need guard
2970 Nod
: constant Node_Id
:= Last
(Elsif_Parts
(Ret
));
2973 Set_Else_Statements
(Ret
, Then_Statements
(Nod
));
2979 Make_Subprogram_Body
(Loc
,
2980 Specification
=> Spec
,
2981 Declarations
=> Decls
,
2982 Handled_Statement_Sequence
=>
2983 Make_Handled_Sequence_Of_Statements
(Loc
,
2984 Statements
=> New_List
(Ret
)));
2985 end Build_Find_Body_Index
;
2987 --------------------------------
2988 -- Build_Find_Body_Index_Spec --
2989 --------------------------------
2991 function Build_Find_Body_Index_Spec
(Typ
: Entity_Id
) return Node_Id
is
2992 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
2993 Id
: constant Entity_Id
:=
2994 Make_Defining_Identifier
(Loc
,
2995 Chars
=> New_External_Name
(Chars
(Typ
), 'F'));
2996 Parm1
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uO
);
2997 Parm2
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uE
);
3001 Make_Function_Specification
(Loc
,
3002 Defining_Unit_Name
=> Id
,
3003 Parameter_Specifications
=> New_List
(
3004 Make_Parameter_Specification
(Loc
,
3005 Defining_Identifier
=> Parm1
,
3007 New_Occurrence_Of
(RTE
(RE_Address
), Loc
)),
3009 Make_Parameter_Specification
(Loc
,
3010 Defining_Identifier
=> Parm2
,
3012 New_Occurrence_Of
(RTE
(RE_Protected_Entry_Index
), Loc
))),
3014 Result_Definition
=> New_Occurrence_Of
(
3015 RTE
(RE_Protected_Entry_Index
), Loc
));
3016 end Build_Find_Body_Index_Spec
;
3018 -----------------------------------------------
3019 -- Build_Lock_Free_Protected_Subprogram_Body --
3020 -----------------------------------------------
3022 function Build_Lock_Free_Protected_Subprogram_Body
3025 Unprot_Spec
: Node_Id
) return Node_Id
3027 Actuals
: constant List_Id
:= New_List
;
3028 Loc
: constant Source_Ptr
:= Sloc
(N
);
3029 Spec
: constant Node_Id
:= Specification
(N
);
3030 Unprot_Id
: constant Entity_Id
:= Defining_Unit_Name
(Unprot_Spec
);
3032 Prot_Spec
: Node_Id
;
3036 -- Create the protected version of the body
3039 Build_Protected_Sub_Specification
(N
, Prot_Typ
, Protected_Mode
);
3041 -- Build the actual parameters which appear in the call to the
3042 -- unprotected version of the body.
3044 Formal
:= First
(Parameter_Specifications
(Prot_Spec
));
3045 while Present
(Formal
) loop
3047 Make_Identifier
(Loc
, Chars
(Defining_Identifier
(Formal
))));
3052 -- Function case, generate:
3053 -- return <Unprot_Func_Call>;
3055 if Nkind
(Spec
) = N_Function_Specification
then
3057 Make_Simple_Return_Statement
(Loc
,
3059 Make_Function_Call
(Loc
,
3061 Make_Identifier
(Loc
, Chars
(Unprot_Id
)),
3062 Parameter_Associations
=> Actuals
));
3064 -- Procedure case, call the unprotected version
3068 Make_Procedure_Call_Statement
(Loc
,
3070 Make_Identifier
(Loc
, Chars
(Unprot_Id
)),
3071 Parameter_Associations
=> Actuals
);
3075 Make_Subprogram_Body
(Loc
,
3076 Declarations
=> Empty_List
,
3077 Specification
=> Prot_Spec
,
3078 Handled_Statement_Sequence
=>
3079 Make_Handled_Sequence_Of_Statements
(Loc
,
3080 Statements
=> New_List
(Stmt
)));
3081 end Build_Lock_Free_Protected_Subprogram_Body
;
3083 -------------------------------------------------
3084 -- Build_Lock_Free_Unprotected_Subprogram_Body --
3085 -------------------------------------------------
3087 -- Procedures which meet the lock-free implementation requirements and
3088 -- reference a unique scalar component Comp are expanded in the following
3091 -- procedure P (...) is
3092 -- Expected_Comp : constant Comp_Type :=
3094 -- (System.Atomic_Primitives.Lock_Free_Read_N
3095 -- (_Object.Comp'Address));
3099 -- <original declarations before the object renaming declaration
3102 -- Desired_Comp : Comp_Type := Expected_Comp;
3103 -- Comp : Comp_Type renames Desired_Comp;
3105 -- <original delarations after the object renaming declaration
3109 -- <original statements>
3110 -- exit when System.Atomic_Primitives.Lock_Free_Try_Write_N
3111 -- (_Object.Comp'Address,
3112 -- Interfaces.Unsigned_N (Expected_Comp),
3113 -- Interfaces.Unsigned_N (Desired_Comp));
3118 -- Each return and raise statement of P is transformed into an atomic
3121 -- if System.Atomic_Primitives.Lock_Free_Try_Write_N
3122 -- (_Object.Comp'Address,
3123 -- Interfaces.Unsigned_N (Expected_Comp),
3124 -- Interfaces.Unsigned_N (Desired_Comp));
3126 -- <original statement>
3131 -- Functions which meet the lock-free implementation requirements and
3132 -- reference a unique scalar component Comp are expanded in the following
3135 -- function F (...) return ... is
3136 -- <original declarations before the object renaming declaration
3139 -- Expected_Comp : constant Comp_Type :=
3141 -- (System.Atomic_Primitives.Lock_Free_Read_N
3142 -- (_Object.Comp'Address));
3143 -- Comp : Comp_Type renames Expected_Comp;
3145 -- <original delarations after the object renaming declaration of
3149 -- <original statements>
3152 function Build_Lock_Free_Unprotected_Subprogram_Body
3154 Prot_Typ
: Node_Id
) return Node_Id
3156 function Referenced_Component
(N
: Node_Id
) return Entity_Id
;
3157 -- Subprograms which meet the lock-free implementation criteria are
3158 -- allowed to reference only one unique component. Return the prival
3159 -- of the said component.
3161 --------------------------
3162 -- Referenced_Component --
3163 --------------------------
3165 function Referenced_Component
(N
: Node_Id
) return Entity_Id
is
3168 Source_Comp
: Entity_Id
:= Empty
;
3171 -- Find the unique source component which N references in its
3174 for Index
in 1 .. Lock_Free_Subprogram_Table
.Last
loop
3176 Element
: Lock_Free_Subprogram
renames
3177 Lock_Free_Subprogram_Table
.Table
(Index
);
3179 if Element
.Sub_Body
= N
then
3180 Source_Comp
:= Element
.Comp_Id
;
3186 if No
(Source_Comp
) then
3190 -- Find the prival which corresponds to the source component within
3191 -- the declarations of N.
3193 Decl
:= First
(Declarations
(N
));
3194 while Present
(Decl
) loop
3196 -- Privals appear as object renamings
3198 if Nkind
(Decl
) = N_Object_Renaming_Declaration
then
3199 Comp
:= Defining_Identifier
(Decl
);
3201 if Present
(Prival_Link
(Comp
))
3202 and then Prival_Link
(Comp
) = Source_Comp
3212 end Referenced_Component
;
3216 Comp
: constant Entity_Id
:= Referenced_Component
(N
);
3217 Loc
: constant Source_Ptr
:= Sloc
(N
);
3218 Hand_Stmt_Seq
: Node_Id
:= Handled_Statement_Sequence
(N
);
3219 Decls
: List_Id
:= Declarations
(N
);
3221 -- Start of processing for Build_Lock_Free_Unprotected_Subprogram_Body
3224 -- Add renamings for the protection object, discriminals, privals and
3225 -- the entry index constant for use by debugger.
3227 Debug_Private_Data_Declarations
(Decls
);
3229 -- Perform the lock-free expansion when the subprogram references a
3230 -- protected component.
3232 if Present
(Comp
) then
3233 Protected_Component_Ref
: declare
3234 Comp_Decl
: constant Node_Id
:= Parent
(Comp
);
3235 Comp_Sel_Nam
: constant Node_Id
:= Name
(Comp_Decl
);
3236 Comp_Type
: constant Entity_Id
:= Etype
(Comp
);
3238 Is_Procedure
: constant Boolean :=
3239 Ekind
(Corresponding_Spec
(N
)) = E_Procedure
;
3240 -- Indicates if N is a protected procedure body
3242 Block_Decls
: List_Id
;
3243 Try_Write
: Entity_Id
;
3244 Desired_Comp
: Entity_Id
;
3247 Label_Id
: Entity_Id
:= Empty
;
3249 Expected_Comp
: Entity_Id
;
3252 New_Copy_List
(Statements
(Hand_Stmt_Seq
));
3254 Unsigned
: Entity_Id
;
3256 function Process_Node
(N
: Node_Id
) return Traverse_Result
;
3257 -- Transform a single node if it is a return statement, a raise
3258 -- statement or a reference to Comp.
3260 procedure Process_Stmts
(Stmts
: List_Id
);
3261 -- Given a statement sequence Stmts, wrap any return or raise
3262 -- statements in the following manner:
3264 -- if System.Atomic_Primitives.Lock_Free_Try_Write_N
3265 -- (_Object.Comp'Address,
3266 -- Interfaces.Unsigned_N (Expected_Comp),
3267 -- Interfaces.Unsigned_N (Desired_Comp))
3278 function Process_Node
(N
: Node_Id
) return Traverse_Result
is
3280 procedure Wrap_Statement
(Stmt
: Node_Id
);
3281 -- Wrap an arbitrary statement inside an if statement where the
3282 -- condition does an atomic check on the state of the object.
3284 --------------------
3285 -- Wrap_Statement --
3286 --------------------
3288 procedure Wrap_Statement
(Stmt
: Node_Id
) is
3290 -- The first time through, create the declaration of a label
3291 -- which is used to skip the remainder of source statements
3292 -- if the state of the object has changed.
3294 if No
(Label_Id
) then
3296 Make_Identifier
(Loc
, New_External_Name
('L', 0));
3297 Set_Entity
(Label_Id
,
3298 Make_Defining_Identifier
(Loc
, Chars
(Label_Id
)));
3302 -- if System.Atomic_Primitives.Lock_Free_Try_Write_N
3303 -- (_Object.Comp'Address,
3304 -- Interfaces.Unsigned_N (Expected_Comp),
3305 -- Interfaces.Unsigned_N (Desired_Comp))
3313 Make_Implicit_If_Statement
(N
,
3315 Make_Function_Call
(Loc
,
3317 New_Occurrence_Of
(Try_Write
, Loc
),
3318 Parameter_Associations
=> New_List
(
3319 Make_Attribute_Reference
(Loc
,
3320 Prefix
=> Relocate_Node
(Comp_Sel_Nam
),
3321 Attribute_Name
=> Name_Address
),
3323 Unchecked_Convert_To
(Unsigned
,
3324 New_Occurrence_Of
(Expected_Comp
, Loc
)),
3326 Unchecked_Convert_To
(Unsigned
,
3327 New_Occurrence_Of
(Desired_Comp
, Loc
)))),
3329 Then_Statements
=> New_List
(Relocate_Node
(Stmt
)),
3331 Else_Statements
=> New_List
(
3332 Make_Goto_Statement
(Loc
,
3334 New_Occurrence_Of
(Entity
(Label_Id
), Loc
)))));
3337 -- Start of processing for Process_Node
3340 -- Wrap each return and raise statement that appear inside a
3341 -- procedure. Skip the last return statement which is added by
3342 -- default since it is transformed into an exit statement.
3345 and then ((Nkind
(N
) = N_Simple_Return_Statement
3346 and then N
/= Last
(Stmts
))
3347 or else Nkind
(N
) = N_Extended_Return_Statement
3348 or else (Nkind_In
(N
, N_Raise_Constraint_Error
,
3349 N_Raise_Program_Error
,
3351 N_Raise_Storage_Error
)
3352 and then Comes_From_Source
(N
)))
3360 Set_Analyzed
(N
, False);
3365 procedure Process_Nodes
is new Traverse_Proc
(Process_Node
);
3371 procedure Process_Stmts
(Stmts
: List_Id
) is
3374 Stmt
:= First
(Stmts
);
3375 while Present
(Stmt
) loop
3376 Process_Nodes
(Stmt
);
3381 -- Start of processing for Protected_Component_Ref
3384 -- Get the type size
3386 if Known_Static_Esize
(Comp_Type
) then
3387 Typ_Size
:= UI_To_Int
(Esize
(Comp_Type
));
3389 -- If the Esize (Object_Size) is unknown at compile time, look at
3390 -- the RM_Size (Value_Size) since it may have been set by an
3391 -- explicit representation clause.
3393 elsif Known_Static_RM_Size
(Comp_Type
) then
3394 Typ_Size
:= UI_To_Int
(RM_Size
(Comp_Type
));
3396 -- Should not happen since this has already been checked in
3397 -- Allows_Lock_Free_Implementation (see Sem_Ch9).
3400 raise Program_Error
;
3403 -- Retrieve all relevant atomic routines and types
3407 Try_Write
:= RTE
(RE_Lock_Free_Try_Write_8
);
3408 Read
:= RTE
(RE_Lock_Free_Read_8
);
3409 Unsigned
:= RTE
(RE_Uint8
);
3412 Try_Write
:= RTE
(RE_Lock_Free_Try_Write_16
);
3413 Read
:= RTE
(RE_Lock_Free_Read_16
);
3414 Unsigned
:= RTE
(RE_Uint16
);
3417 Try_Write
:= RTE
(RE_Lock_Free_Try_Write_32
);
3418 Read
:= RTE
(RE_Lock_Free_Read_32
);
3419 Unsigned
:= RTE
(RE_Uint32
);
3422 Try_Write
:= RTE
(RE_Lock_Free_Try_Write_64
);
3423 Read
:= RTE
(RE_Lock_Free_Read_64
);
3424 Unsigned
:= RTE
(RE_Uint64
);
3427 raise Program_Error
;
3431 -- Expected_Comp : constant Comp_Type :=
3433 -- (System.Atomic_Primitives.Lock_Free_Read_N
3434 -- (_Object.Comp'Address));
3437 Make_Defining_Identifier
(Loc
,
3438 New_External_Name
(Chars
(Comp
), Suffix
=> "_saved"));
3441 Make_Object_Declaration
(Loc
,
3442 Defining_Identifier
=> Expected_Comp
,
3443 Object_Definition
=> New_Occurrence_Of
(Comp_Type
, Loc
),
3444 Constant_Present
=> True,
3446 Unchecked_Convert_To
(Comp_Type
,
3447 Make_Function_Call
(Loc
,
3448 Name
=> New_Occurrence_Of
(Read
, Loc
),
3449 Parameter_Associations
=> New_List
(
3450 Make_Attribute_Reference
(Loc
,
3451 Prefix
=> Relocate_Node
(Comp_Sel_Nam
),
3452 Attribute_Name
=> Name_Address
)))));
3454 -- Protected procedures
3456 if Is_Procedure
then
3457 -- Move the original declarations inside the generated block
3459 Block_Decls
:= Decls
;
3461 -- Reset the declarations list of the protected procedure to
3462 -- contain only Decl.
3464 Decls
:= New_List
(Decl
);
3467 -- Desired_Comp : Comp_Type := Expected_Comp;
3470 Make_Defining_Identifier
(Loc
,
3471 New_External_Name
(Chars
(Comp
), Suffix
=> "_current"));
3473 -- Insert the declarations of Expected_Comp and Desired_Comp in
3474 -- the block declarations right before the renaming of the
3475 -- protected component.
3477 Insert_Before
(Comp_Decl
,
3478 Make_Object_Declaration
(Loc
,
3479 Defining_Identifier
=> Desired_Comp
,
3480 Object_Definition
=> New_Occurrence_Of
(Comp_Type
, Loc
),
3482 New_Occurrence_Of
(Expected_Comp
, Loc
)));
3484 -- Protected function
3487 Desired_Comp
:= Expected_Comp
;
3489 -- Insert the declaration of Expected_Comp in the function
3490 -- declarations right before the renaming of the protected
3493 Insert_Before
(Comp_Decl
, Decl
);
3496 -- Rewrite the protected component renaming declaration to be a
3497 -- renaming of Desired_Comp.
3500 -- Comp : Comp_Type renames Desired_Comp;
3503 Make_Object_Renaming_Declaration
(Loc
,
3504 Defining_Identifier
=>
3505 Defining_Identifier
(Comp_Decl
),
3507 New_Occurrence_Of
(Comp_Type
, Loc
),
3509 New_Occurrence_Of
(Desired_Comp
, Loc
)));
3511 -- Wrap any return or raise statements in Stmts in same the manner
3512 -- described in Process_Stmts.
3514 Process_Stmts
(Stmts
);
3517 -- exit when System.Atomic_Primitives.Lock_Free_Try_Write_N
3518 -- (_Object.Comp'Address,
3519 -- Interfaces.Unsigned_N (Expected_Comp),
3520 -- Interfaces.Unsigned_N (Desired_Comp))
3522 if Is_Procedure
then
3524 Make_Exit_Statement
(Loc
,
3526 Make_Function_Call
(Loc
,
3528 New_Occurrence_Of
(Try_Write
, Loc
),
3529 Parameter_Associations
=> New_List
(
3530 Make_Attribute_Reference
(Loc
,
3531 Prefix
=> Relocate_Node
(Comp_Sel_Nam
),
3532 Attribute_Name
=> Name_Address
),
3534 Unchecked_Convert_To
(Unsigned
,
3535 New_Occurrence_Of
(Expected_Comp
, Loc
)),
3537 Unchecked_Convert_To
(Unsigned
,
3538 New_Occurrence_Of
(Desired_Comp
, Loc
)))));
3540 -- Small optimization: transform the default return statement
3541 -- of a procedure into the atomic exit statement.
3543 if Nkind
(Last
(Stmts
)) = N_Simple_Return_Statement
then
3544 Rewrite
(Last
(Stmts
), Stmt
);
3546 Append_To
(Stmts
, Stmt
);
3550 -- Create the declaration of the label used to skip the rest of
3551 -- the source statements when the object state changes.
3553 if Present
(Label_Id
) then
3554 Label
:= Make_Label
(Loc
, Label_Id
);
3556 Make_Implicit_Label_Declaration
(Loc
,
3557 Defining_Identifier
=> Entity
(Label_Id
),
3558 Label_Construct
=> Label
));
3559 Append_To
(Stmts
, Label
);
3571 if Is_Procedure
then
3574 Make_Loop_Statement
(Loc
,
3575 Statements
=> New_List
(
3576 Make_Block_Statement
(Loc
,
3577 Declarations
=> Block_Decls
,
3578 Handled_Statement_Sequence
=>
3579 Make_Handled_Sequence_Of_Statements
(Loc
,
3580 Statements
=> Stmts
))),
3581 End_Label
=> Empty
));
3585 Make_Handled_Sequence_Of_Statements
(Loc
, Statements
=> Stmts
);
3586 end Protected_Component_Ref
;
3589 -- Make an unprotected version of the subprogram for use within the same
3590 -- object, with new name and extra parameter representing the object.
3593 Make_Subprogram_Body
(Loc
,
3595 Build_Protected_Sub_Specification
(N
, Prot_Typ
, Unprotected_Mode
),
3596 Declarations
=> Decls
,
3597 Handled_Statement_Sequence
=> Hand_Stmt_Seq
);
3598 end Build_Lock_Free_Unprotected_Subprogram_Body
;
3600 -------------------------
3601 -- Build_Master_Entity --
3602 -------------------------
3604 procedure Build_Master_Entity
(Obj_Or_Typ
: Entity_Id
) is
3605 Loc
: constant Source_Ptr
:= Sloc
(Obj_Or_Typ
);
3607 Context_Id
: Entity_Id
;
3613 if Is_Itype
(Obj_Or_Typ
) then
3614 Par
:= Associated_Node_For_Itype
(Obj_Or_Typ
);
3616 Par
:= Parent
(Obj_Or_Typ
);
3619 -- When creating a master for a record component which is either a task
3620 -- or access-to-task, the enclosing record is the master scope and the
3621 -- proper insertion point is the component list.
3623 if Is_Record_Type
(Current_Scope
) then
3625 Context_Id
:= Current_Scope
;
3626 Decls
:= List_Containing
(Context
);
3628 -- Default case for object declarations and access types. Note that the
3629 -- context is updated to the nearest enclosing body, block, package or
3630 -- return statement.
3633 Find_Enclosing_Context
(Par
, Context
, Context_Id
, Decls
);
3636 -- Do not create a master if one already exists or there is no task
3639 if Has_Master_Entity
(Context_Id
)
3640 or else Restriction_Active
(No_Task_Hierarchy
)
3645 -- Create a master, generate:
3646 -- _Master : constant Master_Id := Current_Master.all;
3649 Make_Object_Declaration
(Loc
,
3650 Defining_Identifier
=>
3651 Make_Defining_Identifier
(Loc
, Name_uMaster
),
3652 Constant_Present
=> True,
3653 Object_Definition
=> New_Occurrence_Of
(RTE
(RE_Master_Id
), Loc
),
3655 Make_Explicit_Dereference
(Loc
,
3656 New_Occurrence_Of
(RTE
(RE_Current_Master
), Loc
)));
3658 -- The master is inserted at the start of the declarative list of the
3661 Prepend_To
(Decls
, Decl
);
3663 -- In certain cases where transient scopes are involved, the immediate
3664 -- scope is not always the proper master scope. Ensure that the master
3665 -- declaration and entity appear in the same context.
3667 if Context_Id
/= Current_Scope
then
3668 Push_Scope
(Context_Id
);
3675 -- Mark the enclosing scope and its associated construct as being task
3678 Set_Has_Master_Entity
(Context_Id
);
3680 while Present
(Context
)
3681 and then Nkind
(Context
) /= N_Compilation_Unit
3683 if Nkind_In
(Context
, N_Block_Statement
,
3687 Set_Is_Task_Master
(Context
);
3690 elsif Nkind
(Parent
(Context
)) = N_Subunit
then
3691 Context
:= Corresponding_Stub
(Parent
(Context
));
3694 Context
:= Parent
(Context
);
3696 end Build_Master_Entity
;
3698 ---------------------------
3699 -- Build_Master_Renaming --
3700 ---------------------------
3702 procedure Build_Master_Renaming
3703 (Ptr_Typ
: Entity_Id
;
3704 Ins_Nod
: Node_Id
:= Empty
)
3706 Loc
: constant Source_Ptr
:= Sloc
(Ptr_Typ
);
3708 Master_Decl
: Node_Id
;
3709 Master_Id
: Entity_Id
;
3712 -- Nothing to do if there is no task hierarchy
3714 if Restriction_Active
(No_Task_Hierarchy
) then
3718 -- Determine the proper context to insert the master renaming
3720 if Present
(Ins_Nod
) then
3722 elsif Is_Itype
(Ptr_Typ
) then
3723 Context
:= Associated_Node_For_Itype
(Ptr_Typ
);
3725 Context
:= Parent
(Ptr_Typ
);
3729 -- <Ptr_Typ>M : Master_Id renames _Master;
3732 Make_Defining_Identifier
(Loc
,
3733 New_External_Name
(Chars
(Ptr_Typ
), 'M'));
3736 Make_Object_Renaming_Declaration
(Loc
,
3737 Defining_Identifier
=> Master_Id
,
3738 Subtype_Mark
=> New_Occurrence_Of
(RTE
(RE_Master_Id
), Loc
),
3739 Name
=> Make_Identifier
(Loc
, Name_uMaster
));
3741 Insert_Action
(Context
, Master_Decl
);
3743 -- The renamed master now services the access type
3745 Set_Master_Id
(Ptr_Typ
, Master_Id
);
3746 end Build_Master_Renaming
;
3748 -----------------------------------------
3749 -- Build_Private_Protected_Declaration --
3750 -----------------------------------------
3752 function Build_Private_Protected_Declaration
3753 (N
: Node_Id
) return Entity_Id
3755 Loc
: constant Source_Ptr
:= Sloc
(N
);
3756 Body_Id
: constant Entity_Id
:= Defining_Entity
(N
);
3761 Spec_Id
: Entity_Id
;
3764 Formal
:= First_Formal
(Body_Id
);
3766 -- The protected operation always has at least one formal, namely the
3767 -- object itself, but it is only placed in the parameter list if
3768 -- expansion is enabled.
3770 if Present
(Formal
) or else Expander_Active
then
3771 Plist
:= Copy_Parameter_List
(Body_Id
);
3776 if Nkind
(Specification
(N
)) = N_Procedure_Specification
then
3778 Make_Procedure_Specification
(Loc
,
3779 Defining_Unit_Name
=>
3780 Make_Defining_Identifier
(Sloc
(Body_Id
),
3781 Chars
=> Chars
(Body_Id
)),
3782 Parameter_Specifications
=>
3786 Make_Function_Specification
(Loc
,
3787 Defining_Unit_Name
=>
3788 Make_Defining_Identifier
(Sloc
(Body_Id
),
3789 Chars
=> Chars
(Body_Id
)),
3790 Parameter_Specifications
=> Plist
,
3791 Result_Definition
=>
3792 New_Occurrence_Of
(Etype
(Body_Id
), Loc
));
3795 Decl
:= Make_Subprogram_Declaration
(Loc
, Specification
=> New_Spec
);
3796 Insert_Before
(N
, Decl
);
3797 Spec_Id
:= Defining_Unit_Name
(New_Spec
);
3799 -- Indicate that the entity comes from source, to ensure that cross-
3800 -- reference information is properly generated. The body itself is
3801 -- rewritten during expansion, and the body entity will not appear in
3802 -- calls to the operation.
3804 Set_Comes_From_Source
(Spec_Id
, True);
3806 Set_Has_Completion
(Spec_Id
);
3807 Set_Convention
(Spec_Id
, Convention_Protected
);
3809 end Build_Private_Protected_Declaration
;
3811 ---------------------------
3812 -- Build_Protected_Entry --
3813 ---------------------------
3815 function Build_Protected_Entry
3818 Pid
: Node_Id
) return Node_Id
3820 Loc
: constant Source_Ptr
:= Sloc
(N
);
3822 Decls
: constant List_Id
:= Declarations
(N
);
3823 End_Lab
: constant Node_Id
:=
3824 End_Label
(Handled_Statement_Sequence
(N
));
3825 End_Loc
: constant Source_Ptr
:=
3826 Sloc
(Last
(Statements
(Handled_Statement_Sequence
(N
))));
3827 -- Used for the generated call to Complete_Entry_Body
3829 Han_Loc
: Source_Ptr
;
3830 -- Used for the exception handler, inserted at end of the body
3832 Op_Decls
: constant List_Id
:= New_List
;
3840 -- Set the source location on the exception handler only when debugging
3841 -- the expanded code (see Make_Implicit_Exception_Handler).
3843 if Debug_Generated_Code
then
3846 -- Otherwise the inserted code should not be visible to the debugger
3849 Han_Loc
:= No_Location
;
3853 Make_Defining_Identifier
(Loc
,
3854 Chars
=> Chars
(Protected_Body_Subprogram
(Ent
)));
3856 Build_Protected_Entry_Specification
(Loc
, Edef
, Empty
);
3858 -- Add the following declarations:
3860 -- type poVP is access poV;
3861 -- _object : poVP := poVP (_O);
3863 -- where _O is the formal parameter associated with the concurrent
3864 -- object. These declarations are needed for Complete_Entry_Body.
3866 Add_Object_Pointer
(Loc
, Pid
, Op_Decls
);
3868 -- Add renamings for all formals, the Protection object, discriminals,
3869 -- privals and the entry index constant for use by debugger.
3871 Add_Formal_Renamings
(Espec
, Op_Decls
, Ent
, Loc
);
3872 Debug_Private_Data_Declarations
(Decls
);
3874 -- Put the declarations and the statements from the entry
3878 Make_Block_Statement
(Loc
,
3879 Declarations
=> Decls
,
3880 Handled_Statement_Sequence
=>
3881 Handled_Statement_Sequence
(N
)));
3883 case Corresponding_Runtime_Package
(Pid
) is
3884 when System_Tasking_Protected_Objects_Entries
=>
3885 Append_To
(Op_Stats
,
3886 Make_Procedure_Call_Statement
(End_Loc
,
3888 New_Occurrence_Of
(RTE
(RE_Complete_Entry_Body
), Loc
),
3889 Parameter_Associations
=> New_List
(
3890 Make_Attribute_Reference
(End_Loc
,
3892 Make_Selected_Component
(End_Loc
,
3894 Make_Identifier
(End_Loc
, Name_uObject
),
3896 Make_Identifier
(End_Loc
, Name_uObject
)),
3897 Attribute_Name
=> Name_Unchecked_Access
))));
3899 when System_Tasking_Protected_Objects_Single_Entry
=>
3901 -- Historically, a call to Complete_Single_Entry_Body was
3902 -- inserted, but it was a null procedure.
3907 raise Program_Error
;
3910 -- When exceptions can not be propagated, we never need to call
3911 -- Exception_Complete_Entry_Body
3913 if No_Exception_Handlers_Set
then
3915 Make_Subprogram_Body
(Loc
,
3916 Specification
=> Espec
,
3917 Declarations
=> Op_Decls
,
3918 Handled_Statement_Sequence
=>
3919 Make_Handled_Sequence_Of_Statements
(Loc
,
3920 Statements
=> Op_Stats
,
3921 End_Label
=> End_Lab
));
3924 Ohandle
:= Make_Others_Choice
(Loc
);
3925 Set_All_Others
(Ohandle
);
3927 case Corresponding_Runtime_Package
(Pid
) is
3928 when System_Tasking_Protected_Objects_Entries
=>
3931 (RTE
(RE_Exceptional_Complete_Entry_Body
), Loc
);
3933 when System_Tasking_Protected_Objects_Single_Entry
=>
3936 (RTE
(RE_Exceptional_Complete_Single_Entry_Body
), Loc
);
3939 raise Program_Error
;
3942 -- Establish link between subprogram body entity and source entry
3944 Set_Corresponding_Protected_Entry
(Edef
, Ent
);
3946 -- Create body of entry procedure. The renaming declarations are
3947 -- placed ahead of the block that contains the actual entry body.
3950 Make_Subprogram_Body
(Loc
,
3951 Specification
=> Espec
,
3952 Declarations
=> Op_Decls
,
3953 Handled_Statement_Sequence
=>
3954 Make_Handled_Sequence_Of_Statements
(Loc
,
3955 Statements
=> Op_Stats
,
3956 End_Label
=> End_Lab
,
3957 Exception_Handlers
=> New_List
(
3958 Make_Implicit_Exception_Handler
(Han_Loc
,
3959 Exception_Choices
=> New_List
(Ohandle
),
3961 Statements
=> New_List
(
3962 Make_Procedure_Call_Statement
(Han_Loc
,
3964 Parameter_Associations
=> New_List
(
3965 Make_Attribute_Reference
(Han_Loc
,
3967 Make_Selected_Component
(Han_Loc
,
3969 Make_Identifier
(Han_Loc
, Name_uObject
),
3971 Make_Identifier
(Han_Loc
, Name_uObject
)),
3972 Attribute_Name
=> Name_Unchecked_Access
),
3974 Make_Function_Call
(Han_Loc
,
3975 Name
=> New_Occurrence_Of
(
3976 RTE
(RE_Get_GNAT_Exception
), Loc
)))))))));
3978 end Build_Protected_Entry
;
3980 -----------------------------------------
3981 -- Build_Protected_Entry_Specification --
3982 -----------------------------------------
3984 function Build_Protected_Entry_Specification
3987 Ent_Id
: Entity_Id
) return Node_Id
3989 P
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uP
);
3992 Set_Debug_Info_Needed
(Def_Id
);
3994 if Present
(Ent_Id
) then
3995 Append_Elmt
(P
, Accept_Address
(Ent_Id
));
3999 Make_Procedure_Specification
(Loc
,
4000 Defining_Unit_Name
=> Def_Id
,
4001 Parameter_Specifications
=> New_List
(
4002 Make_Parameter_Specification
(Loc
,
4003 Defining_Identifier
=>
4004 Make_Defining_Identifier
(Loc
, Name_uO
),
4006 New_Occurrence_Of
(RTE
(RE_Address
), Loc
)),
4008 Make_Parameter_Specification
(Loc
,
4009 Defining_Identifier
=> P
,
4011 New_Occurrence_Of
(RTE
(RE_Address
), Loc
)),
4013 Make_Parameter_Specification
(Loc
,
4014 Defining_Identifier
=>
4015 Make_Defining_Identifier
(Loc
, Name_uE
),
4017 New_Occurrence_Of
(RTE
(RE_Protected_Entry_Index
), Loc
))));
4018 end Build_Protected_Entry_Specification
;
4020 --------------------------
4021 -- Build_Protected_Spec --
4022 --------------------------
4024 function Build_Protected_Spec
4026 Obj_Type
: Entity_Id
;
4028 Unprotected
: Boolean := False) return List_Id
4030 Loc
: constant Source_Ptr
:= Sloc
(N
);
4033 New_Plist
: List_Id
;
4034 New_Param
: Node_Id
;
4037 New_Plist
:= New_List
;
4039 Formal
:= First_Formal
(Ident
);
4040 while Present
(Formal
) loop
4042 Make_Parameter_Specification
(Loc
,
4043 Defining_Identifier
=>
4044 Make_Defining_Identifier
(Sloc
(Formal
), Chars
(Formal
)),
4045 In_Present
=> In_Present
(Parent
(Formal
)),
4046 Out_Present
=> Out_Present
(Parent
(Formal
)),
4047 Parameter_Type
=> New_Occurrence_Of
(Etype
(Formal
), Loc
));
4050 Set_Protected_Formal
(Formal
, Defining_Identifier
(New_Param
));
4053 Append
(New_Param
, New_Plist
);
4054 Next_Formal
(Formal
);
4057 -- If the subprogram is a procedure and the context is not an access
4058 -- to protected subprogram, the parameter is in-out. Otherwise it is
4062 Make_Parameter_Specification
(Loc
,
4063 Defining_Identifier
=>
4064 Make_Defining_Identifier
(Loc
, Name_uObject
),
4067 (Etype
(Ident
) = Standard_Void_Type
4068 and then not Is_RTE
(Obj_Type
, RE_Address
)),
4070 New_Occurrence_Of
(Obj_Type
, Loc
));
4071 Set_Debug_Info_Needed
(Defining_Identifier
(Decl
));
4072 Prepend_To
(New_Plist
, Decl
);
4075 end Build_Protected_Spec
;
4077 ---------------------------------------
4078 -- Build_Protected_Sub_Specification --
4079 ---------------------------------------
4081 function Build_Protected_Sub_Specification
4083 Prot_Typ
: Entity_Id
;
4084 Mode
: Subprogram_Protection_Mode
) return Node_Id
4086 Loc
: constant Source_Ptr
:= Sloc
(N
);
4090 New_Plist
: List_Id
;
4093 Append_Chr
: constant array (Subprogram_Protection_Mode
) of Character :=
4094 (Dispatching_Mode
=> ' ',
4095 Protected_Mode
=> 'P',
4096 Unprotected_Mode
=> 'N');
4099 if Ekind
(Defining_Unit_Name
(Specification
(N
))) =
4102 Decl
:= Unit_Declaration_Node
(Corresponding_Spec
(N
));
4107 Def_Id
:= Defining_Unit_Name
(Specification
(Decl
));
4110 Build_Protected_Spec
4111 (Decl
, Corresponding_Record_Type
(Prot_Typ
), Def_Id
,
4112 Mode
= Unprotected_Mode
);
4114 Make_Defining_Identifier
(Loc
,
4115 Chars
=> Build_Selected_Name
(Prot_Typ
, Def_Id
, Append_Chr
(Mode
)));
4117 -- The unprotected operation carries the user code, and debugging
4118 -- information must be generated for it, even though this spec does
4119 -- not come from source. It is also convenient to allow gdb to step
4120 -- into the protected operation, even though it only contains lock/
4123 Set_Debug_Info_Needed
(New_Id
);
4125 -- If a pragma Eliminate applies to the source entity, the internal
4126 -- subprograms will be eliminated as well.
4128 Set_Is_Eliminated
(New_Id
, Is_Eliminated
(Def_Id
));
4130 if Nkind
(Specification
(Decl
)) = N_Procedure_Specification
then
4132 Make_Procedure_Specification
(Loc
,
4133 Defining_Unit_Name
=> New_Id
,
4134 Parameter_Specifications
=> New_Plist
);
4136 -- Create a new specification for the anonymous subprogram type
4140 Make_Function_Specification
(Loc
,
4141 Defining_Unit_Name
=> New_Id
,
4142 Parameter_Specifications
=> New_Plist
,
4143 Result_Definition
=>
4144 Copy_Result_Type
(Result_Definition
(Specification
(Decl
))));
4146 Set_Return_Present
(Defining_Unit_Name
(New_Spec
));
4150 end Build_Protected_Sub_Specification
;
4152 -------------------------------------
4153 -- Build_Protected_Subprogram_Body --
4154 -------------------------------------
4156 function Build_Protected_Subprogram_Body
4159 N_Op_Spec
: Node_Id
) return Node_Id
4161 Loc
: constant Source_Ptr
:= Sloc
(N
);
4163 P_Op_Spec
: Node_Id
;
4166 Unprot_Call
: Node_Id
;
4168 Lock_Name
: Node_Id
;
4169 Lock_Stmt
: Node_Id
;
4171 Return_Stmt
: Node_Id
:= Empty
; -- init to avoid gcc 3 warning
4172 Pre_Stmts
: List_Id
:= No_List
; -- init to avoid gcc 3 warning
4174 Object_Parm
: Node_Id
;
4179 Op_Spec
:= Specification
(N
);
4180 Exc_Safe
:= Is_Exception_Safe
(N
);
4183 Build_Protected_Sub_Specification
(N
, Pid
, Protected_Mode
);
4185 -- Build a list of the formal parameters of the protected version of
4186 -- the subprogram to use as the actual parameters of the unprotected
4189 Uactuals
:= New_List
;
4190 Pformal
:= First
(Parameter_Specifications
(P_Op_Spec
));
4191 while Present
(Pformal
) loop
4192 Append_To
(Uactuals
,
4193 Make_Identifier
(Loc
, Chars
(Defining_Identifier
(Pformal
))));
4197 -- Make a call to the unprotected version of the subprogram built above
4198 -- for use by the protected version built below.
4200 if Nkind
(Op_Spec
) = N_Function_Specification
then
4202 R
:= Make_Temporary
(Loc
, 'R');
4204 Make_Object_Declaration
(Loc
,
4205 Defining_Identifier
=> R
,
4206 Constant_Present
=> True,
4207 Object_Definition
=> New_Copy
(Result_Definition
(N_Op_Spec
)),
4209 Make_Function_Call
(Loc
,
4210 Name
=> Make_Identifier
(Loc
,
4211 Chars
=> Chars
(Defining_Unit_Name
(N_Op_Spec
))),
4212 Parameter_Associations
=> Uactuals
));
4215 Make_Simple_Return_Statement
(Loc
,
4216 Expression
=> New_Occurrence_Of
(R
, Loc
));
4219 Unprot_Call
:= Make_Simple_Return_Statement
(Loc
,
4220 Expression
=> Make_Function_Call
(Loc
,
4222 Make_Identifier
(Loc
,
4223 Chars
=> Chars
(Defining_Unit_Name
(N_Op_Spec
))),
4224 Parameter_Associations
=> Uactuals
));
4227 Lock_Kind
:= RE_Lock_Read_Only
;
4231 Make_Procedure_Call_Statement
(Loc
,
4233 Make_Identifier
(Loc
, Chars
(Defining_Unit_Name
(N_Op_Spec
))),
4234 Parameter_Associations
=> Uactuals
);
4236 Lock_Kind
:= RE_Lock
;
4239 -- Wrap call in block that will be covered by an at_end handler
4241 if not Exc_Safe
then
4242 Unprot_Call
:= Make_Block_Statement
(Loc
,
4243 Handled_Statement_Sequence
=>
4244 Make_Handled_Sequence_Of_Statements
(Loc
,
4245 Statements
=> New_List
(Unprot_Call
)));
4248 -- Make the protected subprogram body. This locks the protected
4249 -- object and calls the unprotected version of the subprogram.
4251 case Corresponding_Runtime_Package
(Pid
) is
4252 when System_Tasking_Protected_Objects_Entries
=>
4253 Lock_Name
:= New_Occurrence_Of
(RTE
(RE_Lock_Entries
), Loc
);
4255 when System_Tasking_Protected_Objects_Single_Entry
=>
4256 Lock_Name
:= New_Occurrence_Of
(RTE
(RE_Lock_Entry
), Loc
);
4258 when System_Tasking_Protected_Objects
=>
4259 Lock_Name
:= New_Occurrence_Of
(RTE
(Lock_Kind
), Loc
);
4262 raise Program_Error
;
4266 Make_Attribute_Reference
(Loc
,
4268 Make_Selected_Component
(Loc
,
4269 Prefix
=> Make_Identifier
(Loc
, Name_uObject
),
4270 Selector_Name
=> Make_Identifier
(Loc
, Name_uObject
)),
4271 Attribute_Name
=> Name_Unchecked_Access
);
4273 Lock_Stmt
:= Make_Procedure_Call_Statement
(Loc
,
4275 Parameter_Associations
=> New_List
(Object_Parm
));
4277 if Abort_Allowed
then
4279 Make_Procedure_Call_Statement
(Loc
,
4280 Name
=> New_Occurrence_Of
(RTE
(RE_Abort_Defer
), Loc
),
4281 Parameter_Associations
=> Empty_List
),
4285 Stmts
:= New_List
(Lock_Stmt
);
4288 if not Exc_Safe
then
4289 Append
(Unprot_Call
, Stmts
);
4291 if Nkind
(Op_Spec
) = N_Function_Specification
then
4293 Stmts
:= Empty_List
;
4295 Append
(Unprot_Call
, Stmts
);
4298 -- Historical note: Previously, call the the cleanup was inserted
4299 -- here. This is now done by Build_Protected_Subprogram_Call_Cleanup,
4300 -- which is also shared by the 'not Exc_Safe' path.
4302 Build_Protected_Subprogram_Call_Cleanup
(Op_Spec
, Pid
, Loc
, Stmts
);
4304 if Nkind
(Op_Spec
) = N_Function_Specification
then
4305 Append
(Return_Stmt
, Stmts
);
4306 Append
(Make_Block_Statement
(Loc
,
4307 Declarations
=> New_List
(Unprot_Call
),
4308 Handled_Statement_Sequence
=>
4309 Make_Handled_Sequence_Of_Statements
(Loc
,
4310 Statements
=> Stmts
)), Pre_Stmts
);
4316 Make_Subprogram_Body
(Loc
,
4317 Declarations
=> Empty_List
,
4318 Specification
=> P_Op_Spec
,
4319 Handled_Statement_Sequence
=>
4320 Make_Handled_Sequence_Of_Statements
(Loc
, Statements
=> Stmts
));
4322 -- Mark this subprogram as a protected subprogram body so that the
4323 -- cleanup will be inserted. This is done only in the 'not Exc_Safe'
4324 -- path as otherwise the cleanup has already been inserted.
4326 if not Exc_Safe
then
4327 Set_Is_Protected_Subprogram_Body
(Sub_Body
);
4331 end Build_Protected_Subprogram_Body
;
4333 -------------------------------------
4334 -- Build_Protected_Subprogram_Call --
4335 -------------------------------------
4337 procedure Build_Protected_Subprogram_Call
4341 External
: Boolean := True)
4343 Loc
: constant Source_Ptr
:= Sloc
(N
);
4344 Sub
: constant Entity_Id
:= Entity
(Name
);
4350 New_Sub
:= New_Occurrence_Of
(External_Subprogram
(Sub
), Loc
);
4353 New_Occurrence_Of
(Protected_Body_Subprogram
(Sub
), Loc
);
4356 if Present
(Parameter_Associations
(N
)) then
4357 Params
:= New_Copy_List_Tree
(Parameter_Associations
(N
));
4362 -- If the type is an untagged derived type, convert to the root type,
4363 -- which is the one on which the operations are defined.
4365 if Nkind
(Rec
) = N_Unchecked_Type_Conversion
4366 and then not Is_Tagged_Type
(Etype
(Rec
))
4367 and then Is_Derived_Type
(Etype
(Rec
))
4369 Set_Etype
(Rec
, Root_Type
(Etype
(Rec
)));
4370 Set_Subtype_Mark
(Rec
,
4371 New_Occurrence_Of
(Root_Type
(Etype
(Rec
)), Sloc
(N
)));
4374 Prepend
(Rec
, Params
);
4376 if Ekind
(Sub
) = E_Procedure
then
4378 Make_Procedure_Call_Statement
(Loc
,
4380 Parameter_Associations
=> Params
));
4383 pragma Assert
(Ekind
(Sub
) = E_Function
);
4385 Make_Function_Call
(Loc
,
4387 Parameter_Associations
=> Params
));
4391 and then Nkind
(Rec
) = N_Unchecked_Type_Conversion
4392 and then Is_Entity_Name
(Expression
(Rec
))
4393 and then Is_Shared_Passive
(Entity
(Expression
(Rec
)))
4395 Add_Shared_Var_Lock_Procs
(N
);
4397 end Build_Protected_Subprogram_Call
;
4399 ---------------------------------------------
4400 -- Build_Protected_Subprogram_Call_Cleanup --
4401 ---------------------------------------------
4403 procedure Build_Protected_Subprogram_Call_Cleanup
4412 -- If the associated protected object has entries, a protected
4413 -- procedure has to service entry queues. In this case generate:
4415 -- Service_Entries (_object._object'Access);
4417 if Nkind
(Op_Spec
) = N_Procedure_Specification
4418 and then Has_Entries
(Conc_Typ
)
4420 case Corresponding_Runtime_Package
(Conc_Typ
) is
4421 when System_Tasking_Protected_Objects_Entries
=>
4422 Nam
:= New_Occurrence_Of
(RTE
(RE_Service_Entries
), Loc
);
4424 when System_Tasking_Protected_Objects_Single_Entry
=>
4425 Nam
:= New_Occurrence_Of
(RTE
(RE_Service_Entry
), Loc
);
4428 raise Program_Error
;
4432 Make_Procedure_Call_Statement
(Loc
,
4434 Parameter_Associations
=> New_List
(
4435 Make_Attribute_Reference
(Loc
,
4437 Make_Selected_Component
(Loc
,
4438 Prefix
=> Make_Identifier
(Loc
, Name_uObject
),
4439 Selector_Name
=> Make_Identifier
(Loc
, Name_uObject
)),
4440 Attribute_Name
=> Name_Unchecked_Access
))));
4444 -- Unlock (_object._object'Access);
4446 case Corresponding_Runtime_Package
(Conc_Typ
) is
4447 when System_Tasking_Protected_Objects_Entries
=>
4448 Nam
:= New_Occurrence_Of
(RTE
(RE_Unlock_Entries
), Loc
);
4450 when System_Tasking_Protected_Objects_Single_Entry
=>
4451 Nam
:= New_Occurrence_Of
(RTE
(RE_Unlock_Entry
), Loc
);
4453 when System_Tasking_Protected_Objects
=>
4454 Nam
:= New_Occurrence_Of
(RTE
(RE_Unlock
), Loc
);
4457 raise Program_Error
;
4461 Make_Procedure_Call_Statement
(Loc
,
4463 Parameter_Associations
=> New_List
(
4464 Make_Attribute_Reference
(Loc
,
4466 Make_Selected_Component
(Loc
,
4467 Prefix
=> Make_Identifier
(Loc
, Name_uObject
),
4468 Selector_Name
=> Make_Identifier
(Loc
, Name_uObject
)),
4469 Attribute_Name
=> Name_Unchecked_Access
))));
4475 if Abort_Allowed
then
4477 Make_Procedure_Call_Statement
(Loc
,
4479 New_Occurrence_Of
(RTE
(RE_Abort_Undefer
), Loc
),
4480 Parameter_Associations
=> Empty_List
));
4482 end Build_Protected_Subprogram_Call_Cleanup
;
4484 -------------------------
4485 -- Build_Selected_Name --
4486 -------------------------
4488 function Build_Selected_Name
4489 (Prefix
: Entity_Id
;
4490 Selector
: Entity_Id
;
4491 Append_Char
: Character := ' ') return Name_Id
4493 Select_Buffer
: String (1 .. Hostparm
.Max_Name_Length
);
4494 Select_Len
: Natural;
4497 Get_Name_String
(Chars
(Selector
));
4498 Select_Len
:= Name_Len
;
4499 Select_Buffer
(1 .. Select_Len
) := Name_Buffer
(1 .. Name_Len
);
4500 Get_Name_String
(Chars
(Prefix
));
4502 -- If scope is anonymous type, discard suffix to recover name of
4503 -- single protected object. Otherwise use protected type name.
4505 if Name_Buffer
(Name_Len
) = 'T' then
4506 Name_Len
:= Name_Len
- 1;
4509 Add_Str_To_Name_Buffer
("__");
4510 for J
in 1 .. Select_Len
loop
4511 Add_Char_To_Name_Buffer
(Select_Buffer
(J
));
4514 -- Now add the Append_Char if specified. The encoding to follow
4515 -- depends on the type of entity. If Append_Char is either 'N' or 'P',
4516 -- then the entity is associated to a protected type subprogram.
4517 -- Otherwise, it is a protected type entry. For each case, the
4518 -- encoding to follow for the suffix is documented in exp_dbug.ads.
4520 -- It would be better to encapsulate this as a routine in Exp_Dbug ???
4522 if Append_Char
/= ' ' then
4523 if Append_Char
= 'P' or Append_Char
= 'N' then
4524 Add_Char_To_Name_Buffer
(Append_Char
);
4527 Add_Str_To_Name_Buffer
((1 => '_', 2 => Append_Char
));
4528 return New_External_Name
(Name_Find
, ' ', -1);
4533 end Build_Selected_Name
;
4535 -----------------------------
4536 -- Build_Simple_Entry_Call --
4537 -----------------------------
4539 -- A task entry call is converted to a call to Call_Simple
4542 -- P : parms := (parm, parm, parm);
4544 -- Call_Simple (acceptor-task, entry-index, P'Address);
4550 -- Here Pnn is an aggregate of the type constructed for the entry to hold
4551 -- the parameters, and the constructed aggregate value contains either the
4552 -- parameters or, in the case of non-elementary types, references to these
4553 -- parameters. Then the address of this aggregate is passed to the runtime
4554 -- routine, along with the task id value and the task entry index value.
4555 -- Pnn is only required if parameters are present.
4557 -- The assignments after the call are present only in the case of in-out
4558 -- or out parameters for elementary types, and are used to assign back the
4559 -- resulting values of such parameters.
4561 -- Note: the reason that we insert a block here is that in the context
4562 -- of selects, conditional entry calls etc. the entry call statement
4563 -- appears on its own, not as an element of a list.
4565 -- A protected entry call is converted to a Protected_Entry_Call:
4568 -- P : E1_Params := (param, param, param);
4570 -- Bnn : Communications_Block;
4573 -- P : E1_Params := (param, param, param);
4574 -- Bnn : Communications_Block;
4577 -- Protected_Entry_Call (
4578 -- Object => po._object'Access,
4579 -- E => <entry index>;
4580 -- Uninterpreted_Data => P'Address;
4581 -- Mode => Simple_Call;
4588 procedure Build_Simple_Entry_Call
4597 -- If call has been inlined, nothing left to do
4599 if Nkind
(N
) = N_Block_Statement
then
4603 -- Convert entry call to Call_Simple call
4606 Loc
: constant Source_Ptr
:= Sloc
(N
);
4607 Parms
: constant List_Id
:= Parameter_Associations
(N
);
4608 Stats
: constant List_Id
:= New_List
;
4611 Comm_Name
: Entity_Id
;
4615 Ent_Acc
: Entity_Id
;
4617 Iface_Tag
: Entity_Id
;
4618 Iface_Typ
: Entity_Id
;
4631 -- Simple entry and entry family cases merge here
4633 Ent
:= Entity
(Ename
);
4634 Ent_Acc
:= Entry_Parameters_Type
(Ent
);
4635 Conctyp
:= Etype
(Concval
);
4637 -- If prefix is an access type, dereference to obtain the task type
4639 if Is_Access_Type
(Conctyp
) then
4640 Conctyp
:= Designated_Type
(Conctyp
);
4643 -- Special case for protected subprogram calls
4645 if Is_Protected_Type
(Conctyp
)
4646 and then Is_Subprogram
(Entity
(Ename
))
4648 if not Is_Eliminated
(Entity
(Ename
)) then
4649 Build_Protected_Subprogram_Call
4650 (N
, Ename
, Convert_Concurrent
(Concval
, Conctyp
));
4657 -- First parameter is the Task_Id value from the task value or the
4658 -- Object from the protected object value, obtained by selecting
4659 -- the _Task_Id or _Object from the result of doing an unchecked
4660 -- conversion to convert the value to the corresponding record type.
4662 if Nkind
(Concval
) = N_Function_Call
4663 and then Is_Task_Type
(Conctyp
)
4664 and then Ada_Version
>= Ada_2005
4667 ExpR
: constant Node_Id
:= Relocate_Node
(Concval
);
4668 Obj
: constant Entity_Id
:= Make_Temporary
(Loc
, 'F', ExpR
);
4673 Make_Object_Declaration
(Loc
,
4674 Defining_Identifier
=> Obj
,
4675 Object_Definition
=> New_Occurrence_Of
(Conctyp
, Loc
),
4676 Expression
=> ExpR
);
4677 Set_Etype
(Obj
, Conctyp
);
4678 Decls
:= New_List
(Decl
);
4679 Rewrite
(Concval
, New_Occurrence_Of
(Obj
, Loc
));
4686 Parm1
:= Concurrent_Ref
(Concval
);
4688 -- Second parameter is the entry index, computed by the routine
4689 -- provided for this purpose. The value of this expression is
4690 -- assigned to an intermediate variable to assure that any entry
4691 -- family index expressions are evaluated before the entry
4694 if not Is_Protected_Type
(Conctyp
)
4696 Corresponding_Runtime_Package
(Conctyp
) =
4697 System_Tasking_Protected_Objects_Entries
4699 X
:= Make_Defining_Identifier
(Loc
, Name_uX
);
4702 Make_Object_Declaration
(Loc
,
4703 Defining_Identifier
=> X
,
4704 Object_Definition
=>
4705 New_Occurrence_Of
(RTE
(RE_Task_Entry_Index
), Loc
),
4706 Expression
=> Actual_Index_Expression
(
4707 Loc
, Entity
(Ename
), Index
, Concval
));
4709 Append_To
(Decls
, Xdecl
);
4710 Parm2
:= New_Occurrence_Of
(X
, Loc
);
4717 -- The third parameter is the packaged parameters. If there are
4718 -- none, then it is just the null address, since nothing is passed.
4721 Parm3
:= New_Occurrence_Of
(RTE
(RE_Null_Address
), Loc
);
4724 -- Case of parameters present, where third argument is the address
4725 -- of a packaged record containing the required parameter values.
4728 -- First build a list of parameter values, which are references to
4729 -- objects of the parameter types.
4733 Actual
:= First_Actual
(N
);
4734 Formal
:= First_Formal
(Ent
);
4735 while Present
(Actual
) loop
4737 -- If it is a by_copy_type, copy it to a new variable. The
4738 -- packaged record has a field that points to this variable.
4740 if Is_By_Copy_Type
(Etype
(Actual
)) then
4742 Make_Object_Declaration
(Loc
,
4743 Defining_Identifier
=> Make_Temporary
(Loc
, 'J'),
4744 Aliased_Present
=> True,
4745 Object_Definition
=>
4746 New_Occurrence_Of
(Etype
(Formal
), Loc
));
4748 -- Mark the object as not needing initialization since the
4749 -- initialization is performed separately, avoiding errors
4750 -- on cases such as formals of null-excluding access types.
4752 Set_No_Initialization
(N_Node
);
4754 -- We must make an assignment statement separate for the
4755 -- case of limited type. We cannot assign it unless the
4756 -- Assignment_OK flag is set first. An out formal of an
4757 -- access type must also be initialized from the actual,
4758 -- as stated in RM 6.4.1 (13).
4760 if Ekind
(Formal
) /= E_Out_Parameter
4761 or else Is_Access_Type
(Etype
(Formal
))
4764 New_Occurrence_Of
(Defining_Identifier
(N_Node
), Loc
);
4765 Set_Assignment_OK
(N_Var
);
4767 Make_Assignment_Statement
(Loc
,
4769 Expression
=> Relocate_Node
(Actual
)));
4772 Append
(N_Node
, Decls
);
4775 Make_Attribute_Reference
(Loc
,
4776 Attribute_Name
=> Name_Unchecked_Access
,
4778 New_Occurrence_Of
(Defining_Identifier
(N_Node
), Loc
)));
4780 -- If it is a VM_By_Copy_Actual, copy it to a new variable
4782 elsif Is_VM_By_Copy_Actual
(Actual
) then
4784 Make_Object_Declaration
(Loc
,
4785 Defining_Identifier
=> Make_Temporary
(Loc
, 'J'),
4786 Aliased_Present
=> True,
4787 Object_Definition
=>
4788 New_Occurrence_Of
(Etype
(Formal
), Loc
),
4789 Expression
=> New_Copy_Tree
(Actual
));
4790 Set_Assignment_OK
(N_Node
);
4792 Append
(N_Node
, Decls
);
4795 Make_Attribute_Reference
(Loc
,
4796 Attribute_Name
=> Name_Unchecked_Access
,
4798 New_Occurrence_Of
(Defining_Identifier
(N_Node
), Loc
)));
4801 -- Interface class-wide formal
4803 if Ada_Version
>= Ada_2005
4804 and then Ekind
(Etype
(Formal
)) = E_Class_Wide_Type
4805 and then Is_Interface
(Etype
(Formal
))
4807 Iface_Typ
:= Etype
(Etype
(Formal
));
4810 -- formal_iface_type! (actual.iface_tag)'reference
4813 Find_Interface_Tag
(Etype
(Actual
), Iface_Typ
);
4814 pragma Assert
(Present
(Iface_Tag
));
4817 Make_Reference
(Loc
,
4818 Unchecked_Convert_To
(Iface_Typ
,
4819 Make_Selected_Component
(Loc
,
4821 Relocate_Node
(Actual
),
4823 New_Occurrence_Of
(Iface_Tag
, Loc
)))));
4829 Make_Reference
(Loc
, Relocate_Node
(Actual
)));
4833 Next_Actual
(Actual
);
4834 Next_Formal_With_Extras
(Formal
);
4837 -- Now build the declaration of parameters initialized with the
4838 -- aggregate containing this constructed parameter list.
4840 P
:= Make_Defining_Identifier
(Loc
, Name_uP
);
4843 Make_Object_Declaration
(Loc
,
4844 Defining_Identifier
=> P
,
4845 Object_Definition
=>
4846 New_Occurrence_Of
(Designated_Type
(Ent_Acc
), Loc
),
4848 Make_Aggregate
(Loc
, Expressions
=> Plist
));
4851 Make_Attribute_Reference
(Loc
,
4852 Prefix
=> New_Occurrence_Of
(P
, Loc
),
4853 Attribute_Name
=> Name_Address
);
4855 Append
(Pdecl
, Decls
);
4858 -- Now we can create the call, case of protected type
4860 if Is_Protected_Type
(Conctyp
) then
4861 case Corresponding_Runtime_Package
(Conctyp
) is
4862 when System_Tasking_Protected_Objects_Entries
=>
4864 -- Change the type of the index declaration
4866 Set_Object_Definition
(Xdecl
,
4867 New_Occurrence_Of
(RTE
(RE_Protected_Entry_Index
), Loc
));
4869 -- Some additional declarations for protected entry calls
4875 -- Bnn : Communications_Block;
4877 Comm_Name
:= Make_Temporary
(Loc
, 'B');
4880 Make_Object_Declaration
(Loc
,
4881 Defining_Identifier
=> Comm_Name
,
4882 Object_Definition
=>
4884 (RTE
(RE_Communication_Block
), Loc
)));
4886 -- Some additional statements for protected entry calls
4888 -- Protected_Entry_Call (
4889 -- Object => po._object'Access,
4890 -- E => <entry index>;
4891 -- Uninterpreted_Data => P'Address;
4892 -- Mode => Simple_Call;
4896 Make_Procedure_Call_Statement
(Loc
,
4898 New_Occurrence_Of
(RTE
(RE_Protected_Entry_Call
), Loc
),
4900 Parameter_Associations
=> New_List
(
4901 Make_Attribute_Reference
(Loc
,
4902 Attribute_Name
=> Name_Unchecked_Access
,
4906 New_Occurrence_Of
(RTE
(RE_Simple_Call
), Loc
),
4907 New_Occurrence_Of
(Comm_Name
, Loc
)));
4909 when System_Tasking_Protected_Objects_Single_Entry
=>
4910 -- Protected_Single_Entry_Call (
4911 -- Object => po._object'Access,
4912 -- Uninterpreted_Data => P'Address);
4915 Make_Procedure_Call_Statement
(Loc
,
4916 Name
=> New_Occurrence_Of
(
4917 RTE
(RE_Protected_Single_Entry_Call
), Loc
),
4919 Parameter_Associations
=> New_List
(
4920 Make_Attribute_Reference
(Loc
,
4921 Attribute_Name
=> Name_Unchecked_Access
,
4926 raise Program_Error
;
4929 -- Case of task type
4933 Make_Procedure_Call_Statement
(Loc
,
4934 Name
=> New_Occurrence_Of
(RTE
(RE_Call_Simple
), Loc
),
4935 Parameter_Associations
=> New_List
(Parm1
, Parm2
, Parm3
));
4939 Append_To
(Stats
, Call
);
4941 -- If there are out or in/out parameters by copy add assignment
4942 -- statements for the result values.
4944 if Present
(Parms
) then
4945 Actual
:= First_Actual
(N
);
4946 Formal
:= First_Formal
(Ent
);
4948 Set_Assignment_OK
(Actual
);
4949 while Present
(Actual
) loop
4950 if (Is_By_Copy_Type
(Etype
(Actual
))
4951 or else Is_VM_By_Copy_Actual
(Actual
))
4952 and then Ekind
(Formal
) /= E_In_Parameter
4955 Make_Assignment_Statement
(Loc
,
4956 Name
=> New_Copy
(Actual
),
4958 Make_Explicit_Dereference
(Loc
,
4959 Make_Selected_Component
(Loc
,
4960 Prefix
=> New_Occurrence_Of
(P
, Loc
),
4962 Make_Identifier
(Loc
, Chars
(Formal
)))));
4964 -- In all cases (including limited private types) we want
4965 -- the assignment to be valid.
4967 Set_Assignment_OK
(Name
(N_Node
));
4969 -- If the call is the triggering alternative in an
4970 -- asynchronous select, or the entry_call alternative of a
4971 -- conditional entry call, the assignments for in-out
4972 -- parameters are incorporated into the statement list that
4973 -- follows, so that there are executed only if the entry
4976 if (Nkind
(Parent
(N
)) = N_Triggering_Alternative
4977 and then N
= Triggering_Statement
(Parent
(N
)))
4979 (Nkind
(Parent
(N
)) = N_Entry_Call_Alternative
4980 and then N
= Entry_Call_Statement
(Parent
(N
)))
4982 if No
(Statements
(Parent
(N
))) then
4983 Set_Statements
(Parent
(N
), New_List
);
4986 Prepend
(N_Node
, Statements
(Parent
(N
)));
4989 Insert_After
(Call
, N_Node
);
4993 Next_Actual
(Actual
);
4994 Next_Formal_With_Extras
(Formal
);
4998 -- Finally, create block and analyze it
5001 Make_Block_Statement
(Loc
,
5002 Declarations
=> Decls
,
5003 Handled_Statement_Sequence
=>
5004 Make_Handled_Sequence_Of_Statements
(Loc
,
5005 Statements
=> Stats
)));
5009 end Build_Simple_Entry_Call
;
5011 --------------------------------
5012 -- Build_Task_Activation_Call --
5013 --------------------------------
5015 procedure Build_Task_Activation_Call
(N
: Node_Id
) is
5016 Loc
: constant Source_Ptr
:= Sloc
(N
);
5023 -- For sequential elaboration policy, all the tasks will be activated at
5024 -- the end of the elaboration.
5026 if Partition_Elaboration_Policy
= 'S' then
5030 -- Get the activation chain entity. Except in the case of a package
5031 -- body, this is in the node that was passed. For a package body, we
5032 -- have to find the corresponding package declaration node.
5034 if Nkind
(N
) = N_Package_Body
then
5035 P
:= Corresponding_Spec
(N
);
5038 exit when Nkind
(P
) = N_Package_Declaration
;
5041 Chain
:= Activation_Chain_Entity
(P
);
5044 Chain
:= Activation_Chain_Entity
(N
);
5047 if Present
(Chain
) then
5048 if Restricted_Profile
then
5049 Name
:= New_Occurrence_Of
5050 (RTE
(RE_Activate_Restricted_Tasks
), Loc
);
5052 Name
:= New_Occurrence_Of
5053 (RTE
(RE_Activate_Tasks
), Loc
);
5057 Make_Procedure_Call_Statement
(Loc
,
5059 Parameter_Associations
=>
5060 New_List
(Make_Attribute_Reference
(Loc
,
5061 Prefix
=> New_Occurrence_Of
(Chain
, Loc
),
5062 Attribute_Name
=> Name_Unchecked_Access
)));
5064 if Nkind
(N
) = N_Package_Declaration
then
5065 if Present
(Corresponding_Body
(N
)) then
5068 elsif Present
(Private_Declarations
(Specification
(N
))) then
5069 Append
(Call
, Private_Declarations
(Specification
(N
)));
5072 Append
(Call
, Visible_Declarations
(Specification
(N
)));
5076 if Present
(Handled_Statement_Sequence
(N
)) then
5078 -- The call goes at the start of the statement sequence after
5079 -- the start of exception range label if one is present.
5085 Stm
:= First
(Statements
(Handled_Statement_Sequence
(N
)));
5087 -- A special case, skip exception range label if one is
5088 -- present (from front end zcx processing).
5090 if Nkind
(Stm
) = N_Label
and then Exception_Junk
(Stm
) then
5094 -- Another special case, if the first statement is a block
5095 -- from optimization of a local raise to a goto, then the
5096 -- call goes inside this block.
5098 if Nkind
(Stm
) = N_Block_Statement
5099 and then Exception_Junk
(Stm
)
5102 First
(Statements
(Handled_Statement_Sequence
(Stm
)));
5105 -- Insertion point is after any exception label pushes,
5106 -- since we want it covered by any local handlers.
5108 while Nkind
(Stm
) in N_Push_xxx_Label
loop
5112 -- Now we have the proper insertion point
5114 Insert_Before
(Stm
, Call
);
5118 Set_Handled_Statement_Sequence
(N
,
5119 Make_Handled_Sequence_Of_Statements
(Loc
,
5120 Statements
=> New_List
(Call
)));
5125 Check_Task_Activation
(N
);
5127 end Build_Task_Activation_Call
;
5129 -------------------------------
5130 -- Build_Task_Allocate_Block --
5131 -------------------------------
5133 procedure Build_Task_Allocate_Block
5138 T
: constant Entity_Id
:= Entity
(Expression
(N
));
5139 Init
: constant Entity_Id
:= Base_Init_Proc
(T
);
5140 Loc
: constant Source_Ptr
:= Sloc
(N
);
5141 Chain
: constant Entity_Id
:=
5142 Make_Defining_Identifier
(Loc
, Name_uChain
);
5143 Blkent
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A');
5148 Make_Block_Statement
(Loc
,
5149 Identifier
=> New_Occurrence_Of
(Blkent
, Loc
),
5150 Declarations
=> New_List
(
5152 -- _Chain : Activation_Chain;
5154 Make_Object_Declaration
(Loc
,
5155 Defining_Identifier
=> Chain
,
5156 Aliased_Present
=> True,
5157 Object_Definition
=>
5158 New_Occurrence_Of
(RTE
(RE_Activation_Chain
), Loc
))),
5160 Handled_Statement_Sequence
=>
5161 Make_Handled_Sequence_Of_Statements
(Loc
,
5163 Statements
=> New_List
(
5167 Make_Procedure_Call_Statement
(Loc
,
5168 Name
=> New_Occurrence_Of
(Init
, Loc
),
5169 Parameter_Associations
=> Args
),
5171 -- Activate_Tasks (_Chain);
5173 Make_Procedure_Call_Statement
(Loc
,
5174 Name
=> New_Occurrence_Of
(RTE
(RE_Activate_Tasks
), Loc
),
5175 Parameter_Associations
=> New_List
(
5176 Make_Attribute_Reference
(Loc
,
5177 Prefix
=> New_Occurrence_Of
(Chain
, Loc
),
5178 Attribute_Name
=> Name_Unchecked_Access
))))),
5180 Has_Created_Identifier
=> True,
5181 Is_Task_Allocation_Block
=> True);
5184 Make_Implicit_Label_Declaration
(Loc
,
5185 Defining_Identifier
=> Blkent
,
5186 Label_Construct
=> Block
));
5188 Append_To
(Actions
, Block
);
5190 Set_Activation_Chain_Entity
(Block
, Chain
);
5191 end Build_Task_Allocate_Block
;
5193 -----------------------------------------------
5194 -- Build_Task_Allocate_Block_With_Init_Stmts --
5195 -----------------------------------------------
5197 procedure Build_Task_Allocate_Block_With_Init_Stmts
5200 Init_Stmts
: List_Id
)
5202 Loc
: constant Source_Ptr
:= Sloc
(N
);
5203 Chain
: constant Entity_Id
:=
5204 Make_Defining_Identifier
(Loc
, Name_uChain
);
5205 Blkent
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A');
5209 Append_To
(Init_Stmts
,
5210 Make_Procedure_Call_Statement
(Loc
,
5211 Name
=> New_Occurrence_Of
(RTE
(RE_Activate_Tasks
), Loc
),
5212 Parameter_Associations
=> New_List
(
5213 Make_Attribute_Reference
(Loc
,
5214 Prefix
=> New_Occurrence_Of
(Chain
, Loc
),
5215 Attribute_Name
=> Name_Unchecked_Access
))));
5218 Make_Block_Statement
(Loc
,
5219 Identifier
=> New_Occurrence_Of
(Blkent
, Loc
),
5220 Declarations
=> New_List
(
5222 -- _Chain : Activation_Chain;
5224 Make_Object_Declaration
(Loc
,
5225 Defining_Identifier
=> Chain
,
5226 Aliased_Present
=> True,
5227 Object_Definition
=>
5228 New_Occurrence_Of
(RTE
(RE_Activation_Chain
), Loc
))),
5230 Handled_Statement_Sequence
=>
5231 Make_Handled_Sequence_Of_Statements
(Loc
, Init_Stmts
),
5233 Has_Created_Identifier
=> True,
5234 Is_Task_Allocation_Block
=> True);
5237 Make_Implicit_Label_Declaration
(Loc
,
5238 Defining_Identifier
=> Blkent
,
5239 Label_Construct
=> Block
));
5241 Append_To
(Actions
, Block
);
5243 Set_Activation_Chain_Entity
(Block
, Chain
);
5244 end Build_Task_Allocate_Block_With_Init_Stmts
;
5246 -----------------------------------
5247 -- Build_Task_Proc_Specification --
5248 -----------------------------------
5250 function Build_Task_Proc_Specification
(T
: Entity_Id
) return Node_Id
is
5251 Loc
: constant Source_Ptr
:= Sloc
(T
);
5252 Spec_Id
: Entity_Id
;
5255 -- Case of explicit task type, suffix TB
5257 if Comes_From_Source
(T
) then
5259 Make_Defining_Identifier
(Loc
, New_External_Name
(Chars
(T
), "TB"));
5261 -- Case of anonymous task type, suffix B
5265 Make_Defining_Identifier
(Loc
, New_External_Name
(Chars
(T
), 'B'));
5268 Set_Is_Internal
(Spec_Id
);
5270 -- Associate the procedure with the task, if this is the declaration
5271 -- (and not the body) of the procedure.
5273 if No
(Task_Body_Procedure
(T
)) then
5274 Set_Task_Body_Procedure
(T
, Spec_Id
);
5278 Make_Procedure_Specification
(Loc
,
5279 Defining_Unit_Name
=> Spec_Id
,
5280 Parameter_Specifications
=> New_List
(
5281 Make_Parameter_Specification
(Loc
,
5282 Defining_Identifier
=>
5283 Make_Defining_Identifier
(Loc
, Name_uTask
),
5285 Make_Access_Definition
(Loc
,
5287 New_Occurrence_Of
(Corresponding_Record_Type
(T
), Loc
)))));
5288 end Build_Task_Proc_Specification
;
5290 ---------------------------------------
5291 -- Build_Unprotected_Subprogram_Body --
5292 ---------------------------------------
5294 function Build_Unprotected_Subprogram_Body
5296 Pid
: Node_Id
) return Node_Id
5298 Decls
: constant List_Id
:= Declarations
(N
);
5301 -- Add renamings for the Protection object, discriminals, privals and
5302 -- the entry index constant for use by debugger.
5304 Debug_Private_Data_Declarations
(Decls
);
5306 -- Make an unprotected version of the subprogram for use within the same
5307 -- object, with a new name and an additional parameter representing the
5311 Make_Subprogram_Body
(Sloc
(N
),
5313 Build_Protected_Sub_Specification
(N
, Pid
, Unprotected_Mode
),
5314 Declarations
=> Decls
,
5315 Handled_Statement_Sequence
=> Handled_Statement_Sequence
(N
));
5316 end Build_Unprotected_Subprogram_Body
;
5318 ----------------------------
5319 -- Collect_Entry_Families --
5320 ----------------------------
5322 procedure Collect_Entry_Families
5325 Current_Node
: in out Node_Id
;
5326 Conctyp
: Entity_Id
)
5329 Efam_Decl
: Node_Id
;
5330 Efam_Type
: Entity_Id
;
5333 Efam
:= First_Entity
(Conctyp
);
5334 while Present
(Efam
) loop
5335 if Ekind
(Efam
) = E_Entry_Family
then
5336 Efam_Type
:= Make_Temporary
(Loc
, 'F');
5341 (Etype
(Discrete_Subtype_Definition
(Parent
(Efam
))));
5343 Bas_Decl
: Node_Id
:= Empty
;
5348 (Discrete_Subtype_Definition
(Parent
(Efam
)), Lo
, Hi
);
5350 if Is_Potentially_Large_Family
(Bas
, Conctyp
, Lo
, Hi
) then
5351 Bas
:= Make_Temporary
(Loc
, 'B');
5354 Make_Subtype_Declaration
(Loc
,
5355 Defining_Identifier
=> Bas
,
5356 Subtype_Indication
=>
5357 Make_Subtype_Indication
(Loc
,
5359 New_Occurrence_Of
(Standard_Integer
, Loc
),
5361 Make_Range_Constraint
(Loc
,
5362 Range_Expression
=> Make_Range
(Loc
,
5363 Make_Integer_Literal
5364 (Loc
, -Entry_Family_Bound
),
5365 Make_Integer_Literal
5366 (Loc
, Entry_Family_Bound
- 1)))));
5368 Insert_After
(Current_Node
, Bas_Decl
);
5369 Current_Node
:= Bas_Decl
;
5374 Make_Full_Type_Declaration
(Loc
,
5375 Defining_Identifier
=> Efam_Type
,
5377 Make_Unconstrained_Array_Definition
(Loc
,
5379 (New_List
(New_Occurrence_Of
(Bas
, Loc
))),
5381 Component_Definition
=>
5382 Make_Component_Definition
(Loc
,
5383 Aliased_Present
=> False,
5384 Subtype_Indication
=>
5385 New_Occurrence_Of
(Standard_Character
, Loc
))));
5388 Insert_After
(Current_Node
, Efam_Decl
);
5389 Current_Node
:= Efam_Decl
;
5390 Analyze
(Efam_Decl
);
5393 Make_Component_Declaration
(Loc
,
5394 Defining_Identifier
=>
5395 Make_Defining_Identifier
(Loc
, Chars
(Efam
)),
5397 Component_Definition
=>
5398 Make_Component_Definition
(Loc
,
5399 Aliased_Present
=> False,
5400 Subtype_Indication
=>
5401 Make_Subtype_Indication
(Loc
,
5403 New_Occurrence_Of
(Efam_Type
, Loc
),
5406 Make_Index_Or_Discriminant_Constraint
(Loc
,
5407 Constraints
=> New_List
(
5409 (Etype
(Discrete_Subtype_Definition
5410 (Parent
(Efam
))), Loc
)))))));
5416 end Collect_Entry_Families
;
5418 -----------------------
5419 -- Concurrent_Object --
5420 -----------------------
5422 function Concurrent_Object
5423 (Spec_Id
: Entity_Id
;
5424 Conc_Typ
: Entity_Id
) return Entity_Id
5427 -- Parameter _O or _object
5429 if Is_Protected_Type
(Conc_Typ
) then
5430 return First_Formal
(Protected_Body_Subprogram
(Spec_Id
));
5435 pragma Assert
(Is_Task_Type
(Conc_Typ
));
5436 return First_Formal
(Task_Body_Procedure
(Conc_Typ
));
5438 end Concurrent_Object
;
5440 ----------------------
5441 -- Copy_Result_Type --
5442 ----------------------
5444 function Copy_Result_Type
(Res
: Node_Id
) return Node_Id
is
5445 New_Res
: constant Node_Id
:= New_Copy_Tree
(Res
);
5450 -- If the result type is an access_to_subprogram, we must create new
5451 -- entities for its spec.
5453 if Nkind
(New_Res
) = N_Access_Definition
5454 and then Present
(Access_To_Subprogram_Definition
(New_Res
))
5456 -- Provide new entities for the formals
5458 Par_Spec
:= First
(Parameter_Specifications
5459 (Access_To_Subprogram_Definition
(New_Res
)));
5460 while Present
(Par_Spec
) loop
5461 Formal
:= Defining_Identifier
(Par_Spec
);
5462 Set_Defining_Identifier
(Par_Spec
,
5463 Make_Defining_Identifier
(Sloc
(Formal
), Chars
(Formal
)));
5469 end Copy_Result_Type
;
5471 --------------------
5472 -- Concurrent_Ref --
5473 --------------------
5475 -- The expression returned for a reference to a concurrent object has the
5478 -- taskV!(name)._Task_Id
5482 -- objectV!(name)._Object
5484 -- for a protected object. For the case of an access to a concurrent
5485 -- object, there is an extra explicit dereference:
5487 -- taskV!(name.all)._Task_Id
5488 -- objectV!(name.all)._Object
5490 -- here taskV and objectV are the types for the associated records, which
5491 -- contain the required _Task_Id and _Object fields for tasks and protected
5492 -- objects, respectively.
5494 -- For the case of a task type name, the expression is
5498 -- i.e. a call to the Self function which returns precisely this Task_Id
5500 -- For the case of a protected type name, the expression is
5504 -- which is a renaming of the _object field of the current object
5505 -- record, passed into protected operations as a parameter.
5507 function Concurrent_Ref
(N
: Node_Id
) return Node_Id
is
5508 Loc
: constant Source_Ptr
:= Sloc
(N
);
5509 Ntyp
: constant Entity_Id
:= Etype
(N
);
5513 function Is_Current_Task
(T
: Entity_Id
) return Boolean;
5514 -- Check whether the reference is to the immediately enclosing task
5515 -- type, or to an outer one (rare but legal).
5517 ---------------------
5518 -- Is_Current_Task --
5519 ---------------------
5521 function Is_Current_Task
(T
: Entity_Id
) return Boolean is
5525 Scop
:= Current_Scope
;
5526 while Present
(Scop
)
5527 and then Scop
/= Standard_Standard
5533 elsif Is_Task_Type
(Scop
) then
5536 -- If this is a procedure nested within the task type, we must
5537 -- assume that it can be called from an inner task, and therefore
5538 -- cannot treat it as a local reference.
5540 elsif Is_Overloadable
(Scop
) and then In_Open_Scopes
(T
) then
5544 Scop
:= Scope
(Scop
);
5548 -- We know that we are within the task body, so should have found it
5551 raise Program_Error
;
5552 end Is_Current_Task
;
5554 -- Start of processing for Concurrent_Ref
5557 if Is_Access_Type
(Ntyp
) then
5558 Dtyp
:= Designated_Type
(Ntyp
);
5560 if Is_Protected_Type
(Dtyp
) then
5561 Sel
:= Name_uObject
;
5563 Sel
:= Name_uTask_Id
;
5567 Make_Selected_Component
(Loc
,
5569 Unchecked_Convert_To
(Corresponding_Record_Type
(Dtyp
),
5570 Make_Explicit_Dereference
(Loc
, N
)),
5571 Selector_Name
=> Make_Identifier
(Loc
, Sel
));
5573 elsif Is_Entity_Name
(N
) and then Is_Concurrent_Type
(Entity
(N
)) then
5574 if Is_Task_Type
(Entity
(N
)) then
5576 if Is_Current_Task
(Entity
(N
)) then
5578 Make_Function_Call
(Loc
,
5579 Name
=> New_Occurrence_Of
(RTE
(RE_Self
), Loc
));
5584 T_Self
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T');
5585 T_Body
: constant Node_Id
:=
5586 Parent
(Corresponding_Body
(Parent
(Entity
(N
))));
5590 Make_Object_Declaration
(Loc
,
5591 Defining_Identifier
=> T_Self
,
5592 Object_Definition
=>
5593 New_Occurrence_Of
(RTE
(RO_ST_Task_Id
), Loc
),
5595 Make_Function_Call
(Loc
,
5596 Name
=> New_Occurrence_Of
(RTE
(RE_Self
), Loc
)));
5597 Prepend
(Decl
, Declarations
(T_Body
));
5599 Set_Scope
(T_Self
, Entity
(N
));
5600 return New_Occurrence_Of
(T_Self
, Loc
);
5605 pragma Assert
(Is_Protected_Type
(Entity
(N
)));
5608 New_Occurrence_Of
(Find_Protection_Object
(Current_Scope
), Loc
);
5612 if Is_Protected_Type
(Ntyp
) then
5613 Sel
:= Name_uObject
;
5615 elsif Is_Task_Type
(Ntyp
) then
5616 Sel
:= Name_uTask_Id
;
5619 raise Program_Error
;
5623 Make_Selected_Component
(Loc
,
5625 Unchecked_Convert_To
(Corresponding_Record_Type
(Ntyp
),
5627 Selector_Name
=> Make_Identifier
(Loc
, Sel
));
5631 ------------------------
5632 -- Convert_Concurrent --
5633 ------------------------
5635 function Convert_Concurrent
5637 Typ
: Entity_Id
) return Node_Id
5640 if not Is_Concurrent_Type
(Typ
) then
5644 Unchecked_Convert_To
5645 (Corresponding_Record_Type
(Typ
), New_Copy_Tree
(N
));
5647 end Convert_Concurrent
;
5649 -------------------------------------
5650 -- Debug_Private_Data_Declarations --
5651 -------------------------------------
5653 procedure Debug_Private_Data_Declarations
(Decls
: List_Id
) is
5654 Debug_Nod
: Node_Id
;
5658 Decl
:= First
(Decls
);
5659 while Present
(Decl
) and then not Comes_From_Source
(Decl
) loop
5660 -- Declaration for concurrent entity _object and its access type,
5661 -- along with the entry index subtype:
5662 -- type prot_typVP is access prot_typV;
5663 -- _object : prot_typVP := prot_typV (_O);
5664 -- subtype Jnn is <Type of Index> range Low .. High;
5666 if Nkind_In
(Decl
, N_Full_Type_Declaration
, N_Object_Declaration
) then
5667 Set_Debug_Info_Needed
(Defining_Identifier
(Decl
));
5669 -- Declaration for the Protection object, discriminals, privals and
5670 -- entry index constant:
5671 -- conc_typR : protection_typ renames _object._object;
5672 -- discr_nameD : discr_typ renames _object.discr_name;
5673 -- discr_nameD : discr_typ renames _task.discr_name;
5674 -- prival_name : comp_typ renames _object.comp_name;
5675 -- J : constant Jnn :=
5676 -- Jnn'Val (_E - <Index expression> + Jnn'Pos (Jnn'First));
5678 elsif Nkind
(Decl
) = N_Object_Renaming_Declaration
then
5679 Set_Debug_Info_Needed
(Defining_Identifier
(Decl
));
5680 Debug_Nod
:= Debug_Renaming_Declaration
(Decl
);
5682 if Present
(Debug_Nod
) then
5683 Insert_After
(Decl
, Debug_Nod
);
5689 end Debug_Private_Data_Declarations
;
5691 ------------------------------
5692 -- Ensure_Statement_Present --
5693 ------------------------------
5695 procedure Ensure_Statement_Present
(Loc
: Source_Ptr
; Alt
: Node_Id
) is
5699 if Opt
.Suppress_Control_Flow_Optimizations
5700 and then Is_Empty_List
(Statements
(Alt
))
5702 Stmt
:= Make_Null_Statement
(Loc
);
5704 -- Mark NULL statement as coming from source so that it is not
5705 -- eliminated by GIGI.
5707 -- Another covert channel. If this is a requirement, it must be
5708 -- documented in sinfo/einfo ???
5710 Set_Comes_From_Source
(Stmt
, True);
5712 Set_Statements
(Alt
, New_List
(Stmt
));
5714 end Ensure_Statement_Present
;
5716 ----------------------------
5717 -- Entry_Index_Expression --
5718 ----------------------------
5720 function Entry_Index_Expression
5724 Ttyp
: Entity_Id
) return Node_Id
5734 -- The queues of entries and entry families appear in textual order in
5735 -- the associated record. The entry index is computed as the sum of the
5736 -- number of queues for all entries that precede the designated one, to
5737 -- which is added the index expression, if this expression denotes a
5738 -- member of a family.
5740 -- The following is a place holder for the count of simple entries
5742 Num
:= Make_Integer_Literal
(Sloc
, 1);
5744 -- We construct an expression which is a series of addition operations.
5745 -- The first operand is the number of single entries that precede this
5746 -- one, the second operand is the index value relative to the start of
5747 -- the referenced family, and the remaining operands are the lengths of
5748 -- the entry families that precede this entry, i.e. the constructed
5751 -- number_simple_entries +
5752 -- (s'pos (index-value) - s'pos (family'first)) + 1 +
5753 -- family'length + ...
5755 -- where index-value is the given index value, and s is the index
5756 -- subtype (we have to use pos because the subtype might be an
5757 -- enumeration type preventing direct subtraction). Note that the task
5758 -- entry array is one-indexed.
5760 -- The upper bound of the entry family may be a discriminant, so we
5761 -- retrieve the lower bound explicitly to compute offset, rather than
5762 -- using the index subtype which may mention a discriminant.
5764 if Present
(Index
) then
5765 S
:= Etype
(Discrete_Subtype_Definition
(Declaration_Node
(Ent
)));
5774 Make_Attribute_Reference
(Sloc
,
5775 Attribute_Name
=> Name_Pos
,
5776 Prefix
=> New_Occurrence_Of
(Base_Type
(S
), Sloc
),
5777 Expressions
=> New_List
(Relocate_Node
(Index
))),
5785 -- Now add lengths of preceding entries and entry families
5787 Prev
:= First_Entity
(Ttyp
);
5789 while Chars
(Prev
) /= Chars
(Ent
)
5790 or else (Ekind
(Prev
) /= Ekind
(Ent
))
5791 or else not Sem_Ch6
.Type_Conformant
(Ent
, Prev
)
5793 if Ekind
(Prev
) = E_Entry
then
5794 Set_Intval
(Num
, Intval
(Num
) + 1);
5796 elsif Ekind
(Prev
) = E_Entry_Family
then
5798 Etype
(Discrete_Subtype_Definition
(Declaration_Node
(Prev
)));
5799 Lo
:= Type_Low_Bound
(S
);
5800 Hi
:= Type_High_Bound
(S
);
5805 Right_Opnd
=> Family_Size
(Sloc
, Hi
, Lo
, Ttyp
, False));
5807 -- Other components are anonymous types to be ignored
5817 end Entry_Index_Expression
;
5819 ---------------------------
5820 -- Establish_Task_Master --
5821 ---------------------------
5823 procedure Establish_Task_Master
(N
: Node_Id
) is
5827 if Restriction_Active
(No_Task_Hierarchy
) = False then
5828 Call
:= Build_Runtime_Call
(Sloc
(N
), RE_Enter_Master
);
5830 -- The block may have no declarations (and nevertheless be a task
5831 -- master) if it contains a call that may return an object that
5834 if No
(Declarations
(N
)) then
5835 Set_Declarations
(N
, New_List
(Call
));
5837 Prepend_To
(Declarations
(N
), Call
);
5842 end Establish_Task_Master
;
5844 --------------------------------
5845 -- Expand_Accept_Declarations --
5846 --------------------------------
5848 -- Part of the expansion of an accept statement involves the creation of
5849 -- a declaration that can be referenced from the statement sequence of
5854 -- This declaration is inserted immediately before the accept statement
5855 -- and it is important that it be inserted before the statements of the
5856 -- statement sequence are analyzed. Thus it would be too late to create
5857 -- this declaration in the Expand_N_Accept_Statement routine, which is
5858 -- why there is a separate procedure to be called directly from Sem_Ch9.
5860 -- Ann is used to hold the address of the record containing the parameters
5861 -- (see Expand_N_Entry_Call for more details on how this record is built).
5862 -- References to the parameters do an unchecked conversion of this address
5863 -- to a pointer to the required record type, and then access the field that
5864 -- holds the value of the required parameter. The entity for the address
5865 -- variable is held as the top stack element (i.e. the last element) of the
5866 -- Accept_Address stack in the corresponding entry entity, and this element
5867 -- must be set in place before the statements are processed.
5869 -- The above description applies to the case of a stand alone accept
5870 -- statement, i.e. one not appearing as part of a select alternative.
5872 -- For the case of an accept that appears as part of a select alternative
5873 -- of a selective accept, we must still create the declaration right away,
5874 -- since Ann is needed immediately, but there is an important difference:
5876 -- The declaration is inserted before the selective accept, not before
5877 -- the accept statement (which is not part of a list anyway, and so would
5878 -- not accommodate inserted declarations)
5880 -- We only need one address variable for the entire selective accept. So
5881 -- the Ann declaration is created only for the first accept alternative,
5882 -- and subsequent accept alternatives reference the same Ann variable.
5884 -- We can distinguish the two cases by seeing whether the accept statement
5885 -- is part of a list. If not, then it must be in an accept alternative.
5887 -- To expand the requeue statement, a label is provided at the end of the
5888 -- accept statement or alternative of which it is a part, so that the
5889 -- statement can be skipped after the requeue is complete. This label is
5890 -- created here rather than during the expansion of the accept statement,
5891 -- because it will be needed by any requeue statements within the accept,
5892 -- which are expanded before the accept.
5894 procedure Expand_Accept_Declarations
(N
: Node_Id
; Ent
: Entity_Id
) is
5895 Loc
: constant Source_Ptr
:= Sloc
(N
);
5896 Stats
: constant Node_Id
:= Handled_Statement_Sequence
(N
);
5897 Ann
: Entity_Id
:= Empty
;
5904 if Expander_Active
then
5906 -- If we have no handled statement sequence, we may need to build
5907 -- a dummy sequence consisting of a null statement. This can be
5908 -- skipped if the trivial accept optimization is permitted.
5910 if not Trivial_Accept_OK
5912 (No
(Stats
) or else Null_Statements
(Statements
(Stats
)))
5914 Set_Handled_Statement_Sequence
(N
,
5915 Make_Handled_Sequence_Of_Statements
(Loc
,
5916 Statements
=> New_List
(Make_Null_Statement
(Loc
))));
5919 -- Create and declare two labels to be placed at the end of the
5920 -- accept statement. The first label is used to allow requeues to
5921 -- skip the remainder of entry processing. The second label is used
5922 -- to skip the remainder of entry processing if the rendezvous
5923 -- completes in the middle of the accept body.
5925 if Present
(Handled_Statement_Sequence
(N
)) then
5930 Ent
:= Make_Temporary
(Loc
, 'L');
5931 Lab
:= Make_Label
(Loc
, New_Occurrence_Of
(Ent
, Loc
));
5933 Make_Implicit_Label_Declaration
(Loc
,
5934 Defining_Identifier
=> Ent
,
5935 Label_Construct
=> Lab
);
5936 Append
(Lab
, Statements
(Handled_Statement_Sequence
(N
)));
5938 Ent
:= Make_Temporary
(Loc
, 'L');
5939 Lab
:= Make_Label
(Loc
, New_Occurrence_Of
(Ent
, Loc
));
5941 Make_Implicit_Label_Declaration
(Loc
,
5942 Defining_Identifier
=> Ent
,
5943 Label_Construct
=> Lab
);
5944 Append
(Lab
, Statements
(Handled_Statement_Sequence
(N
)));
5952 -- Case of stand alone accept statement
5954 if Is_List_Member
(N
) then
5956 if Present
(Handled_Statement_Sequence
(N
)) then
5957 Ann
:= Make_Temporary
(Loc
, 'A');
5960 Make_Object_Declaration
(Loc
,
5961 Defining_Identifier
=> Ann
,
5962 Object_Definition
=>
5963 New_Occurrence_Of
(RTE
(RE_Address
), Loc
));
5965 Insert_Before_And_Analyze
(N
, Adecl
);
5966 Insert_Before_And_Analyze
(N
, Ldecl
);
5967 Insert_Before_And_Analyze
(N
, Ldecl2
);
5970 -- Case of accept statement which is in an accept alternative
5974 Acc_Alt
: constant Node_Id
:= Parent
(N
);
5975 Sel_Acc
: constant Node_Id
:= Parent
(Acc_Alt
);
5979 pragma Assert
(Nkind
(Acc_Alt
) = N_Accept_Alternative
);
5980 pragma Assert
(Nkind
(Sel_Acc
) = N_Selective_Accept
);
5982 -- ??? Consider a single label for select statements
5984 if Present
(Handled_Statement_Sequence
(N
)) then
5986 Statements
(Handled_Statement_Sequence
(N
)));
5990 Statements
(Handled_Statement_Sequence
(N
)));
5994 -- Find first accept alternative of the selective accept. A
5995 -- valid selective accept must have at least one accept in it.
5997 Alt
:= First
(Select_Alternatives
(Sel_Acc
));
5999 while Nkind
(Alt
) /= N_Accept_Alternative
loop
6003 -- If this is the first accept statement, then we have to
6004 -- create the Ann variable, as for the stand alone case, except
6005 -- that it is inserted before the selective accept. Similarly,
6006 -- a label for requeue expansion must be declared.
6008 if N
= Accept_Statement
(Alt
) then
6009 Ann
:= Make_Temporary
(Loc
, 'A');
6011 Make_Object_Declaration
(Loc
,
6012 Defining_Identifier
=> Ann
,
6013 Object_Definition
=>
6014 New_Occurrence_Of
(RTE
(RE_Address
), Loc
));
6016 Insert_Before_And_Analyze
(Sel_Acc
, Adecl
);
6018 -- If this is not the first accept statement, then find the Ann
6019 -- variable allocated by the first accept and use it.
6023 Node
(Last_Elmt
(Accept_Address
6024 (Entity
(Entry_Direct_Name
(Accept_Statement
(Alt
))))));
6029 -- Merge here with Ann either created or referenced, and Adecl
6030 -- pointing to the corresponding declaration. Remaining processing
6031 -- is the same for the two cases.
6033 if Present
(Ann
) then
6034 Append_Elmt
(Ann
, Accept_Address
(Ent
));
6035 Set_Debug_Info_Needed
(Ann
);
6038 -- Create renaming declarations for the entry formals. Each reference
6039 -- to a formal becomes a dereference of a component of the parameter
6040 -- block, whose address is held in Ann. These declarations are
6041 -- eventually inserted into the accept block, and analyzed there so
6042 -- that they have the proper scope for gdb and do not conflict with
6043 -- other declarations.
6045 if Present
(Parameter_Specifications
(N
))
6046 and then Present
(Handled_Statement_Sequence
(N
))
6053 Renamed_Formal
: Node_Id
;
6057 Formal
:= First_Formal
(Ent
);
6059 while Present
(Formal
) loop
6060 Comp
:= Entry_Component
(Formal
);
6061 New_F
:= Make_Defining_Identifier
(Loc
, Chars
(Formal
));
6063 Set_Etype
(New_F
, Etype
(Formal
));
6064 Set_Scope
(New_F
, Ent
);
6066 -- Now we set debug info needed on New_F even though it does
6067 -- not come from source, so that the debugger will get the
6068 -- right information for these generated names.
6070 Set_Debug_Info_Needed
(New_F
);
6072 if Ekind
(Formal
) = E_In_Parameter
then
6073 Set_Ekind
(New_F
, E_Constant
);
6075 Set_Ekind
(New_F
, E_Variable
);
6076 Set_Extra_Constrained
(New_F
, Extra_Constrained
(Formal
));
6079 Set_Actual_Subtype
(New_F
, Actual_Subtype
(Formal
));
6082 Make_Selected_Component
(Loc
,
6084 Unchecked_Convert_To
(
6085 Entry_Parameters_Type
(Ent
),
6086 New_Occurrence_Of
(Ann
, Loc
)),
6088 New_Occurrence_Of
(Comp
, Loc
));
6091 Build_Renamed_Formal_Declaration
6092 (New_F
, Formal
, Comp
, Renamed_Formal
);
6094 if No
(Declarations
(N
)) then
6095 Set_Declarations
(N
, New_List
);
6098 Append
(Decl
, Declarations
(N
));
6099 Set_Renamed_Object
(Formal
, New_F
);
6100 Next_Formal
(Formal
);
6107 end Expand_Accept_Declarations
;
6109 ---------------------------------------------
6110 -- Expand_Access_Protected_Subprogram_Type --
6111 ---------------------------------------------
6113 procedure Expand_Access_Protected_Subprogram_Type
(N
: Node_Id
) is
6114 Loc
: constant Source_Ptr
:= Sloc
(N
);
6116 T
: constant Entity_Id
:= Defining_Identifier
(N
);
6117 D_T
: constant Entity_Id
:= Designated_Type
(T
);
6118 D_T2
: constant Entity_Id
:= Make_Temporary
(Loc
, 'D');
6119 E_T
: constant Entity_Id
:= Make_Temporary
(Loc
, 'E');
6120 P_List
: constant List_Id
:= Build_Protected_Spec
6121 (N
, RTE
(RE_Address
), D_T
, False);
6127 -- Create access to subprogram with full signature
6129 if Etype
(D_T
) /= Standard_Void_Type
then
6131 Make_Access_Function_Definition
(Loc
,
6132 Parameter_Specifications
=> P_List
,
6133 Result_Definition
=>
6134 Copy_Result_Type
(Result_Definition
(Type_Definition
(N
))));
6138 Make_Access_Procedure_Definition
(Loc
,
6139 Parameter_Specifications
=> P_List
);
6143 Make_Full_Type_Declaration
(Loc
,
6144 Defining_Identifier
=> D_T2
,
6145 Type_Definition
=> Def1
);
6147 Insert_After_And_Analyze
(N
, Decl1
);
6149 -- Associate the access to subprogram with its original access to
6150 -- protected subprogram type. Needed by the backend to know that this
6151 -- type corresponds with an access to protected subprogram type.
6153 Set_Original_Access_Type
(D_T2
, T
);
6155 -- Create Equivalent_Type, a record with two components for an access to
6156 -- object and an access to subprogram.
6159 Make_Component_Declaration
(Loc
,
6160 Defining_Identifier
=> Make_Temporary
(Loc
, 'P'),
6161 Component_Definition
=>
6162 Make_Component_Definition
(Loc
,
6163 Aliased_Present
=> False,
6164 Subtype_Indication
=>
6165 New_Occurrence_Of
(RTE
(RE_Address
), Loc
))),
6167 Make_Component_Declaration
(Loc
,
6168 Defining_Identifier
=> Make_Temporary
(Loc
, 'S'),
6169 Component_Definition
=>
6170 Make_Component_Definition
(Loc
,
6171 Aliased_Present
=> False,
6172 Subtype_Indication
=> New_Occurrence_Of
(D_T2
, Loc
))));
6175 Make_Full_Type_Declaration
(Loc
,
6176 Defining_Identifier
=> E_T
,
6178 Make_Record_Definition
(Loc
,
6180 Make_Component_List
(Loc
, Component_Items
=> Comps
)));
6182 Insert_After_And_Analyze
(Decl1
, Decl2
);
6183 Set_Equivalent_Type
(T
, E_T
);
6184 end Expand_Access_Protected_Subprogram_Type
;
6186 --------------------------
6187 -- Expand_Entry_Barrier --
6188 --------------------------
6190 procedure Expand_Entry_Barrier
(N
: Node_Id
; Ent
: Entity_Id
) is
6191 Cond
: constant Node_Id
:=
6192 Condition
(Entry_Body_Formal_Part
(N
));
6193 Prot
: constant Entity_Id
:= Scope
(Ent
);
6194 Spec_Decl
: constant Node_Id
:= Parent
(Prot
);
6197 Body_Decl
: Node_Id
;
6199 function Is_Global_Entity
(N
: Node_Id
) return Traverse_Result
;
6200 -- Check whether entity in Barrier is external to protected type.
6201 -- If so, barrier may not be properly synchronized.
6203 ----------------------
6204 -- Is_Global_Entity --
6205 ----------------------
6207 function Is_Global_Entity
(N
: Node_Id
) return Traverse_Result
is
6212 if Is_Entity_Name
(N
) and then Present
(Entity
(N
)) then
6216 if Ekind
(E
) = E_Variable
then
6217 if Scope
(E
) = Func
then
6220 -- A protected call from a barrier to another object is ok
6222 elsif Ekind
(Etype
(E
)) = E_Protected_Type
then
6225 -- If the variable is within the package body we consider
6226 -- this safe. This is a common (if dubious) idiom.
6228 elsif S
= Scope
(Prot
)
6229 and then Ekind_In
(S
, E_Package
, E_Generic_Package
)
6230 and then Nkind
(Parent
(E
)) = N_Object_Declaration
6231 and then Nkind
(Parent
(Parent
(E
))) = N_Package_Body
6236 Error_Msg_N
("potentially unsynchronized barrier?", N
);
6237 Error_Msg_N
("\& should be private component of type?", N
);
6243 end Is_Global_Entity
;
6245 procedure Check_Unprotected_Barrier
is
6246 new Traverse_Proc
(Is_Global_Entity
);
6248 -- Start of processing for Expand_Entry_Barrier
6251 if No_Run_Time_Mode
then
6252 Error_Msg_CRT
("entry barrier", N
);
6256 -- The body of the entry barrier must be analyzed in the context of the
6257 -- protected object, but its scope is external to it, just as any other
6258 -- unprotected version of a protected operation. The specification has
6259 -- been produced when the protected type declaration was elaborated. We
6260 -- build the body, insert it in the enclosing scope, but analyze it in
6261 -- the current context. A more uniform approach would be to treat the
6262 -- barrier just as a protected function, and discard the protected
6263 -- version of it because it is never called.
6265 if Expander_Active
then
6266 B_F
:= Build_Barrier_Function
(N
, Ent
, Prot
);
6267 Func
:= Barrier_Function
(Ent
);
6268 Set_Corresponding_Spec
(B_F
, Func
);
6270 Body_Decl
:= Parent
(Corresponding_Body
(Spec_Decl
));
6272 if Nkind
(Parent
(Body_Decl
)) = N_Subunit
then
6273 Body_Decl
:= Corresponding_Stub
(Parent
(Body_Decl
));
6276 Insert_Before_And_Analyze
(Body_Decl
, B_F
);
6278 Set_Discriminals
(Spec_Decl
);
6279 Set_Scope
(Func
, Scope
(Prot
));
6282 Analyze_And_Resolve
(Cond
, Any_Boolean
);
6285 -- The Ravenscar profile restricts barriers to simple variables declared
6286 -- within the protected object. We also allow Boolean constants, since
6287 -- these appear in several published examples and are also allowed by
6290 -- Note that after analysis variables in this context will be replaced
6291 -- by the corresponding prival, that is to say a renaming of a selected
6292 -- component of the form _Object.Var. If expansion is disabled, as
6293 -- within a generic, we check that the entity appears in the current
6296 if Is_Entity_Name
(Cond
) then
6298 -- A small optimization of useless renamings. If the scope of the
6299 -- entity of the condition is not the barrier function, then the
6300 -- condition does not reference any of the generated renamings
6301 -- within the function.
6303 if Expander_Active
and then Scope
(Entity
(Cond
)) /= Func
then
6304 Set_Declarations
(B_F
, Empty_List
);
6307 if Entity
(Cond
) = Standard_False
6309 Entity
(Cond
) = Standard_True
6313 elsif not Expander_Active
6314 and then Scope
(Entity
(Cond
)) = Current_Scope
6318 -- Check for case of _object.all.field (note that the explicit
6319 -- dereference gets inserted by analyze/expand of _object.field)
6321 elsif Present
(Renamed_Object
(Entity
(Cond
)))
6323 Nkind
(Renamed_Object
(Entity
(Cond
))) = N_Selected_Component
6327 (Prefix
(Renamed_Object
(Entity
(Cond
))))) = Name_uObject
6333 -- It is not a boolean variable or literal, so check the restriction.
6334 -- Note that it is safe to be calling Check_Restriction from here, even
6335 -- though this is part of the expander, since Expand_Entry_Barrier is
6336 -- called from Sem_Ch9 even in -gnatc mode.
6338 Check_Restriction
(Simple_Barriers
, Cond
);
6340 -- Emit warning if barrier contains global entities and is thus
6341 -- potentially unsynchronized.
6343 Check_Unprotected_Barrier
(Cond
);
6344 end Expand_Entry_Barrier
;
6346 ------------------------------
6347 -- Expand_N_Abort_Statement --
6348 ------------------------------
6350 -- Expand abort T1, T2, .. Tn; into:
6351 -- Abort_Tasks (Task_List'(1 => T1.Task_Id, 2 => T2.Task_Id ...))
6353 procedure Expand_N_Abort_Statement
(N
: Node_Id
) is
6354 Loc
: constant Source_Ptr
:= Sloc
(N
);
6355 Tlist
: constant List_Id
:= Names
(N
);
6361 Aggr
:= Make_Aggregate
(Loc
, Component_Associations
=> New_List
);
6364 Tasknm
:= First
(Tlist
);
6366 while Present
(Tasknm
) loop
6369 -- A task interface class-wide type object is being aborted. Retrieve
6370 -- its _task_id by calling a dispatching routine.
6372 if Ada_Version
>= Ada_2005
6373 and then Ekind
(Etype
(Tasknm
)) = E_Class_Wide_Type
6374 and then Is_Interface
(Etype
(Tasknm
))
6375 and then Is_Task_Interface
(Etype
(Tasknm
))
6377 Append_To
(Component_Associations
(Aggr
),
6378 Make_Component_Association
(Loc
,
6379 Choices
=> New_List
(Make_Integer_Literal
(Loc
, Count
)),
6382 -- Task_Id (Tasknm._disp_get_task_id)
6384 Make_Unchecked_Type_Conversion
(Loc
,
6386 New_Occurrence_Of
(RTE
(RO_ST_Task_Id
), Loc
),
6388 Make_Selected_Component
(Loc
,
6389 Prefix
=> New_Copy_Tree
(Tasknm
),
6391 Make_Identifier
(Loc
, Name_uDisp_Get_Task_Id
)))));
6394 Append_To
(Component_Associations
(Aggr
),
6395 Make_Component_Association
(Loc
,
6396 Choices
=> New_List
(Make_Integer_Literal
(Loc
, Count
)),
6397 Expression
=> Concurrent_Ref
(Tasknm
)));
6404 Make_Procedure_Call_Statement
(Loc
,
6405 Name
=> New_Occurrence_Of
(RTE
(RE_Abort_Tasks
), Loc
),
6406 Parameter_Associations
=> New_List
(
6407 Make_Qualified_Expression
(Loc
,
6408 Subtype_Mark
=> New_Occurrence_Of
(RTE
(RE_Task_List
), Loc
),
6409 Expression
=> Aggr
))));
6412 end Expand_N_Abort_Statement
;
6414 -------------------------------
6415 -- Expand_N_Accept_Statement --
6416 -------------------------------
6418 -- This procedure handles expansion of accept statements that stand alone,
6419 -- i.e. they are not part of an accept alternative. The expansion of
6420 -- accept statement in accept alternatives is handled by the routines
6421 -- Expand_N_Accept_Alternative and Expand_N_Selective_Accept. The
6422 -- following description applies only to stand alone accept statements.
6424 -- If there is no handled statement sequence, or only null statements, then
6425 -- this is called a trivial accept, and the expansion is:
6427 -- Accept_Trivial (entry-index)
6429 -- If there is a handled statement sequence, then the expansion is:
6436 -- Accept_Call (entry-index, Ann);
6437 -- Renaming_Declarations for formals
6438 -- <statement sequence from N_Accept_Statement node>
6439 -- Complete_Rendezvous;
6444 -- <exception handler from N_Accept_Statement node>
6445 -- Complete_Rendezvous;
6447 -- <exception handler from N_Accept_Statement node>
6448 -- Complete_Rendezvous;
6453 -- when all others =>
6454 -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
6457 -- The first three declarations were already inserted ahead of the accept
6458 -- statement by the Expand_Accept_Declarations procedure, which was called
6459 -- directly from the semantics during analysis of the accept statement,
6460 -- before analyzing its contained statements.
6462 -- The declarations from the N_Accept_Statement, as noted in Sinfo, come
6463 -- from possible expansion activity (the original source of course does
6464 -- not have any declarations associated with the accept statement, since
6465 -- an accept statement has no declarative part). In particular, if the
6466 -- expander is active, the first such declaration is the declaration of
6467 -- the Accept_Params_Ptr entity (see Sem_Ch9.Analyze_Accept_Statement).
6469 -- The two blocks are merged into a single block if the inner block has
6470 -- no exception handlers, but otherwise two blocks are required, since
6471 -- exceptions might be raised in the exception handlers of the inner
6472 -- block, and Exceptional_Complete_Rendezvous must be called.
6474 procedure Expand_N_Accept_Statement
(N
: Node_Id
) is
6475 Loc
: constant Source_Ptr
:= Sloc
(N
);
6476 Stats
: constant Node_Id
:= Handled_Statement_Sequence
(N
);
6477 Ename
: constant Node_Id
:= Entry_Direct_Name
(N
);
6478 Eindx
: constant Node_Id
:= Entry_Index
(N
);
6479 Eent
: constant Entity_Id
:= Entity
(Ename
);
6480 Acstack
: constant Elist_Id
:= Accept_Address
(Eent
);
6481 Ann
: constant Entity_Id
:= Node
(Last_Elmt
(Acstack
));
6482 Ttyp
: constant Entity_Id
:= Etype
(Scope
(Eent
));
6488 -- If the accept statement is not part of a list, then its parent must
6489 -- be an accept alternative, and, as described above, we do not do any
6490 -- expansion for such accept statements at this level.
6492 if not Is_List_Member
(N
) then
6493 pragma Assert
(Nkind
(Parent
(N
)) = N_Accept_Alternative
);
6496 -- Trivial accept case (no statement sequence, or null statements).
6497 -- If the accept statement has declarations, then just insert them
6498 -- before the procedure call.
6500 elsif Trivial_Accept_OK
6501 and then (No
(Stats
) or else Null_Statements
(Statements
(Stats
)))
6503 -- Remove declarations for renamings, because the parameter block
6504 -- will not be assigned.
6511 D
:= First
(Declarations
(N
));
6512 while Present
(D
) loop
6514 if Nkind
(D
) = N_Object_Renaming_Declaration
then
6522 if Present
(Declarations
(N
)) then
6523 Insert_Actions
(N
, Declarations
(N
));
6527 Make_Procedure_Call_Statement
(Loc
,
6528 Name
=> New_Occurrence_Of
(RTE
(RE_Accept_Trivial
), Loc
),
6529 Parameter_Associations
=> New_List
(
6530 Entry_Index_Expression
(Loc
, Entity
(Ename
), Eindx
, Ttyp
))));
6534 -- Discard Entry_Address that was created for it, so it will not be
6535 -- emitted if this accept statement is in the statement part of a
6536 -- delay alternative.
6538 if Present
(Stats
) then
6539 Remove_Last_Elmt
(Acstack
);
6542 -- Case of statement sequence present
6545 -- Construct the block, using the declarations from the accept
6546 -- statement if any to initialize the declarations of the block.
6548 Blkent
:= Make_Temporary
(Loc
, 'A');
6549 Set_Ekind
(Blkent
, E_Block
);
6550 Set_Etype
(Blkent
, Standard_Void_Type
);
6551 Set_Scope
(Blkent
, Current_Scope
);
6554 Make_Block_Statement
(Loc
,
6555 Identifier
=> New_Occurrence_Of
(Blkent
, Loc
),
6556 Declarations
=> Declarations
(N
),
6557 Handled_Statement_Sequence
=> Build_Accept_Body
(N
));
6559 -- For the analysis of the generated declarations, the parent node
6560 -- must be properly set.
6562 Set_Parent
(Block
, Parent
(N
));
6564 -- Prepend call to Accept_Call to main statement sequence If the
6565 -- accept has exception handlers, the statement sequence is wrapped
6566 -- in a block. Insert call and renaming declarations in the
6567 -- declarations of the block, so they are elaborated before the
6571 Make_Procedure_Call_Statement
(Loc
,
6572 Name
=> New_Occurrence_Of
(RTE
(RE_Accept_Call
), Loc
),
6573 Parameter_Associations
=> New_List
(
6574 Entry_Index_Expression
(Loc
, Entity
(Ename
), Eindx
, Ttyp
),
6575 New_Occurrence_Of
(Ann
, Loc
)));
6577 if Parent
(Stats
) = N
then
6578 Prepend
(Call
, Statements
(Stats
));
6580 Set_Declarations
(Parent
(Stats
), New_List
(Call
));
6585 Push_Scope
(Blkent
);
6593 D
:= First
(Declarations
(N
));
6594 while Present
(D
) loop
6597 if Nkind
(D
) = N_Object_Renaming_Declaration
then
6599 -- The renaming declarations for the formals were created
6600 -- during analysis of the accept statement, and attached to
6601 -- the list of declarations. Place them now in the context
6602 -- of the accept block or subprogram.
6605 Typ
:= Entity
(Subtype_Mark
(D
));
6606 Insert_After
(Call
, D
);
6609 -- If the formal is class_wide, it does not have an actual
6610 -- subtype. The analysis of the renaming declaration creates
6611 -- one, but we need to retain the class-wide nature of the
6614 if Is_Class_Wide_Type
(Typ
) then
6615 Set_Etype
(Defining_Identifier
(D
), Typ
);
6626 -- Replace the accept statement by the new block
6631 -- Last step is to unstack the Accept_Address value
6633 Remove_Last_Elmt
(Acstack
);
6635 end Expand_N_Accept_Statement
;
6637 ----------------------------------
6638 -- Expand_N_Asynchronous_Select --
6639 ----------------------------------
6641 -- This procedure assumes that the trigger statement is an entry call or
6642 -- a dispatching procedure call. A delay alternative should already have
6643 -- been expanded into an entry call to the appropriate delay object Wait
6646 -- If the trigger is a task entry call, the select is implemented with
6647 -- a Task_Entry_Call:
6652 -- P : parms := (parm, parm, parm);
6654 -- -- Clean is added by Exp_Ch7.Expand_Cleanup_Actions
6656 -- procedure _clean is
6659 -- Cancel_Task_Entry_Call (C);
6666 -- (<acceptor-task>, -- Acceptor
6667 -- <entry-index>, -- E
6668 -- P'Address, -- Uninterpreted_Data
6669 -- Asynchronous_Call, -- Mode
6670 -- B); -- Rendezvous_Successful
6677 -- _clean; -- Added by Exp_Ch7.Expand_Cleanup_Actions
6680 -- when Abort_Signal => Abort_Undefer;
6687 -- <triggered-statements>
6691 -- Note that Build_Simple_Entry_Call is used to expand the entry of the
6692 -- asynchronous entry call (by Expand_N_Entry_Call_Statement procedure)
6696 -- P : parms := (parm, parm, parm);
6698 -- Call_Simple (acceptor-task, entry-index, P'Address);
6704 -- so the task at hand is to convert the latter expansion into the former
6706 -- If the trigger is a protected entry call, the select is implemented
6707 -- with Protected_Entry_Call:
6710 -- P : E1_Params := (param, param, param);
6711 -- Bnn : Communications_Block;
6716 -- -- Clean is added by Exp_Ch7.Expand_Cleanup_Actions
6718 -- procedure _clean is
6721 -- if Enqueued (Bnn) then
6722 -- Cancel_Protected_Entry_Call (Bnn);
6729 -- Protected_Entry_Call
6730 -- (po._object'Access, -- Object
6731 -- <entry index>, -- E
6732 -- P'Address, -- Uninterpreted_Data
6733 -- Asynchronous_Call, -- Mode
6736 -- if Enqueued (Bnn) then
6740 -- _clean; -- Added by Exp_Ch7.Expand_Cleanup_Actions
6743 -- when Abort_Signal => Abort_Undefer;
6746 -- if not Cancelled (Bnn) then
6747 -- <triggered-statements>
6751 -- Build_Simple_Entry_Call is used to expand the all to a simple protected
6755 -- P : E1_Params := (param, param, param);
6756 -- Bnn : Communications_Block;
6759 -- Protected_Entry_Call
6760 -- (po._object'Access, -- Object
6761 -- <entry index>, -- E
6762 -- P'Address, -- Uninterpreted_Data
6763 -- Simple_Call, -- Mode
6770 -- Ada 2005 (AI-345): If the trigger is a dispatching call, the select is
6774 -- B : Boolean := False;
6775 -- Bnn : Communication_Block;
6776 -- C : Ada.Tags.Prim_Op_Kind;
6777 -- D : System.Storage_Elements.Dummy_Communication_Block;
6778 -- K : Ada.Tags.Tagged_Kind :=
6779 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
6780 -- P : Parameters := (Param1 .. ParamN);
6785 -- if K = Ada.Tags.TK_Limited_Tagged
6786 -- or else K = Ada.Tags.TK_Tagged
6788 -- <dispatching-call>;
6789 -- <triggering-statements>;
6793 -- Ada.Tags.Get_Offset_Index
6794 -- (Ada.Tags.Tag (<object>), DT_Position (<dispatching-call>));
6796 -- _Disp_Get_Prim_Op_Kind (<object>, S, C);
6798 -- if C = POK_Protected_Entry then
6800 -- procedure _clean is
6802 -- if Enqueued (Bnn) then
6803 -- Cancel_Protected_Entry_Call (Bnn);
6809 -- _Disp_Asynchronous_Select
6810 -- (<object>, S, P'Address, D, B);
6811 -- Bnn := Communication_Block (D);
6813 -- Param1 := P.Param1;
6815 -- ParamN := P.ParamN;
6817 -- if Enqueued (Bnn) then
6818 -- <abortable-statements>
6821 -- _clean; -- Added by Exp_Ch7.Expand_Cleanup_Actions
6824 -- when Abort_Signal => Abort_Undefer;
6827 -- if not Cancelled (Bnn) then
6828 -- <triggering-statements>
6831 -- elsif C = POK_Task_Entry then
6833 -- procedure _clean is
6835 -- Cancel_Task_Entry_Call (U);
6841 -- _Disp_Asynchronous_Select
6842 -- (<object>, S, P'Address, D, B);
6843 -- Bnn := Communication_Bloc (D);
6845 -- Param1 := P.Param1;
6847 -- ParamN := P.ParamN;
6852 -- <abortable-statements>
6854 -- _clean; -- Added by Exp_Ch7.Expand_Cleanup_Actions
6857 -- when Abort_Signal => Abort_Undefer;
6861 -- <triggering-statements>
6866 -- <dispatching-call>;
6867 -- <triggering-statements>
6872 -- The job is to convert this to the asynchronous form
6874 -- If the trigger is a delay statement, it will have been expanded into
6875 -- a call to one of the GNARL delay procedures. This routine will convert
6876 -- this into a protected entry call on a delay object and then continue
6877 -- processing as for a protected entry call trigger. This requires
6878 -- declaring a Delay_Block object and adding a pointer to this object to
6879 -- the parameter list of the delay procedure to form the parameter list of
6880 -- the entry call. This object is used by the runtime to queue the delay
6883 -- For a description of the use of P and the assignments after the call,
6884 -- see Expand_N_Entry_Call_Statement.
6886 procedure Expand_N_Asynchronous_Select
(N
: Node_Id
) is
6887 Loc
: constant Source_Ptr
:= Sloc
(N
);
6888 Abrt
: constant Node_Id
:= Abortable_Part
(N
);
6889 Trig
: constant Node_Id
:= Triggering_Alternative
(N
);
6891 Abort_Block_Ent
: Entity_Id
;
6892 Abortable_Block
: Node_Id
;
6895 Blk_Ent
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A');
6896 Blk_Typ
: Entity_Id
;
6898 Call_Ent
: Entity_Id
;
6899 Cancel_Param
: Entity_Id
;
6900 Cleanup_Block
: Node_Id
;
6901 Cleanup_Block_Ent
: Entity_Id
;
6902 Cleanup_Stmts
: List_Id
;
6903 Conc_Typ_Stmts
: List_Id
;
6905 Dblock_Ent
: Entity_Id
;
6910 Enqueue_Call
: Node_Id
;
6913 Handler_Stmt
: Node_Id
;
6915 Lim_Typ_Stmts
: List_Id
;
6921 ProtE_Stmts
: List_Id
;
6922 ProtP_Stmts
: List_Id
;
6925 TaskE_Stmts
: List_Id
;
6928 B
: Entity_Id
; -- Call status flag
6929 Bnn
: Entity_Id
; -- Communication block
6930 C
: Entity_Id
; -- Call kind
6931 K
: Entity_Id
; -- Tagged kind
6932 P
: Entity_Id
; -- Parameter block
6933 S
: Entity_Id
; -- Primitive operation slot
6934 T
: Entity_Id
; -- Additional status flag
6936 procedure Rewrite_Abortable_Part
;
6937 -- If the trigger is a dispatching call, the expansion inserts multiple
6938 -- copies of the abortable part. This is both inefficient, and may lead
6939 -- to duplicate definitions that the back-end will reject, when the
6940 -- abortable part includes loops. This procedure rewrites the abortable
6941 -- part into a call to a generated procedure.
6943 ----------------------------
6944 -- Rewrite_Abortable_Part --
6945 ----------------------------
6947 procedure Rewrite_Abortable_Part
is
6948 Proc
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uA
);
6953 Make_Subprogram_Body
(Loc
,
6955 Make_Procedure_Specification
(Loc
, Defining_Unit_Name
=> Proc
),
6956 Declarations
=> New_List
,
6957 Handled_Statement_Sequence
=>
6958 Make_Handled_Sequence_Of_Statements
(Loc
, Astats
));
6959 Insert_Before
(N
, Decl
);
6962 -- Rewrite abortable part into a call to this procedure.
6966 Make_Procedure_Call_Statement
(Loc
,
6967 Name
=> New_Occurrence_Of
(Proc
, Loc
)));
6968 end Rewrite_Abortable_Part
;
6971 Process_Statements_For_Controlled_Objects
(Trig
);
6972 Process_Statements_For_Controlled_Objects
(Abrt
);
6974 Ecall
:= Triggering_Statement
(Trig
);
6976 Ensure_Statement_Present
(Sloc
(Ecall
), Trig
);
6978 -- Retrieve Astats and Tstats now because the finalization machinery may
6979 -- wrap them in blocks.
6981 Astats
:= Statements
(Abrt
);
6982 Tstats
:= Statements
(Trig
);
6984 -- The arguments in the call may require dynamic allocation, and the
6985 -- call statement may have been transformed into a block. The block
6986 -- may contain additional declarations for internal entities, and the
6987 -- original call is found by sequential search.
6989 if Nkind
(Ecall
) = N_Block_Statement
then
6990 Ecall
:= First
(Statements
(Handled_Statement_Sequence
(Ecall
)));
6991 while not Nkind_In
(Ecall
, N_Procedure_Call_Statement
,
6992 N_Entry_Call_Statement
)
6998 -- This is either a dispatching call or a delay statement used as a
6999 -- trigger which was expanded into a procedure call.
7001 if Nkind
(Ecall
) = N_Procedure_Call_Statement
then
7002 if Ada_Version
>= Ada_2005
7004 (No
(Original_Node
(Ecall
))
7005 or else not Nkind_In
(Original_Node
(Ecall
),
7006 N_Delay_Relative_Statement
,
7007 N_Delay_Until_Statement
))
7009 Extract_Dispatching_Call
(Ecall
, Call_Ent
, Obj
, Actuals
, Formals
);
7011 Rewrite_Abortable_Part
;
7015 -- Call status flag processing, generate:
7016 -- B : Boolean := False;
7018 B
:= Build_B
(Loc
, Decls
);
7020 -- Communication block processing, generate:
7021 -- Bnn : Communication_Block;
7023 Bnn
:= Make_Temporary
(Loc
, 'B');
7025 Make_Object_Declaration
(Loc
,
7026 Defining_Identifier
=> Bnn
,
7027 Object_Definition
=>
7028 New_Occurrence_Of
(RTE
(RE_Communication_Block
), Loc
)));
7030 -- Call kind processing, generate:
7031 -- C : Ada.Tags.Prim_Op_Kind;
7033 C
:= Build_C
(Loc
, Decls
);
7035 -- Tagged kind processing, generate:
7036 -- K : Ada.Tags.Tagged_Kind :=
7037 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
7039 -- Dummy communication block, generate:
7040 -- D : Dummy_Communication_Block;
7043 Make_Object_Declaration
(Loc
,
7044 Defining_Identifier
=>
7045 Make_Defining_Identifier
(Loc
, Name_uD
),
7046 Object_Definition
=>
7048 (RTE
(RE_Dummy_Communication_Block
), Loc
)));
7050 K
:= Build_K
(Loc
, Decls
, Obj
);
7052 -- Parameter block processing
7054 Blk_Typ
:= Build_Parameter_Block
7055 (Loc
, Actuals
, Formals
, Decls
);
7056 P
:= Parameter_Block_Pack
7057 (Loc
, Blk_Typ
, Actuals
, Formals
, Decls
, Stmts
);
7059 -- Dispatch table slot processing, generate:
7062 S
:= Build_S
(Loc
, Decls
);
7064 -- Additional status flag processing, generate:
7067 T
:= Make_Temporary
(Loc
, 'T');
7069 Make_Object_Declaration
(Loc
,
7070 Defining_Identifier
=> T
,
7071 Object_Definition
=>
7072 New_Occurrence_Of
(Standard_Boolean
, Loc
)));
7074 ------------------------------
7075 -- Protected entry handling --
7076 ------------------------------
7079 -- Param1 := P.Param1;
7081 -- ParamN := P.ParamN;
7083 Cleanup_Stmts
:= Parameter_Block_Unpack
(Loc
, P
, Actuals
, Formals
);
7086 -- Bnn := Communication_Block (D);
7088 Prepend_To
(Cleanup_Stmts
,
7089 Make_Assignment_Statement
(Loc
,
7090 Name
=> New_Occurrence_Of
(Bnn
, Loc
),
7092 Make_Unchecked_Type_Conversion
(Loc
,
7094 New_Occurrence_Of
(RTE
(RE_Communication_Block
), Loc
),
7095 Expression
=> Make_Identifier
(Loc
, Name_uD
))));
7098 -- _Disp_Asynchronous_Select (<object>, S, P'Address, D, B);
7100 Prepend_To
(Cleanup_Stmts
,
7101 Make_Procedure_Call_Statement
(Loc
,
7105 (Etype
(Etype
(Obj
)), Name_uDisp_Asynchronous_Select
),
7107 Parameter_Associations
=>
7109 New_Copy_Tree
(Obj
), -- <object>
7110 New_Occurrence_Of
(S
, Loc
), -- S
7111 Make_Attribute_Reference
(Loc
, -- P'Address
7112 Prefix
=> New_Occurrence_Of
(P
, Loc
),
7113 Attribute_Name
=> Name_Address
),
7114 Make_Identifier
(Loc
, Name_uD
), -- D
7115 New_Occurrence_Of
(B
, Loc
)))); -- B
7118 -- if Enqueued (Bnn) then
7119 -- <abortable-statements>
7122 Append_To
(Cleanup_Stmts
,
7123 Make_Implicit_If_Statement
(N
,
7125 Make_Function_Call
(Loc
,
7127 New_Occurrence_Of
(RTE
(RE_Enqueued
), Loc
),
7128 Parameter_Associations
=>
7129 New_List
(New_Occurrence_Of
(Bnn
, Loc
))),
7132 New_Copy_List_Tree
(Astats
)));
7134 -- Wrap the statements in a block. Exp_Ch7.Expand_Cleanup_Actions
7135 -- will then generate a _clean for the communication block Bnn.
7139 -- procedure _clean is
7141 -- if Enqueued (Bnn) then
7142 -- Cancel_Protected_Entry_Call (Bnn);
7151 Cleanup_Block_Ent
:= Make_Temporary
(Loc
, 'C');
7153 Build_Cleanup_Block
(Loc
, Cleanup_Block_Ent
, Cleanup_Stmts
, Bnn
);
7155 -- Wrap the cleanup block in an exception handling block
7161 -- when Abort_Signal => Abort_Undefer;
7164 Abort_Block_Ent
:= Make_Temporary
(Loc
, 'A');
7167 Make_Implicit_Label_Declaration
(Loc
,
7168 Defining_Identifier
=> Abort_Block_Ent
),
7171 (Loc
, Abort_Block_Ent
, Cleanup_Block_Ent
, Cleanup_Block
));
7174 -- if not Cancelled (Bnn) then
7175 -- <triggering-statements>
7178 Append_To
(ProtE_Stmts
,
7179 Make_Implicit_If_Statement
(N
,
7183 Make_Function_Call
(Loc
,
7185 New_Occurrence_Of
(RTE
(RE_Cancelled
), Loc
),
7186 Parameter_Associations
=>
7187 New_List
(New_Occurrence_Of
(Bnn
, Loc
)))),
7190 New_Copy_List_Tree
(Tstats
)));
7192 -------------------------
7193 -- Task entry handling --
7194 -------------------------
7197 -- Param1 := P.Param1;
7199 -- ParamN := P.ParamN;
7201 TaskE_Stmts
:= Parameter_Block_Unpack
(Loc
, P
, Actuals
, Formals
);
7204 -- Bnn := Communication_Block (D);
7206 Append_To
(TaskE_Stmts
,
7207 Make_Assignment_Statement
(Loc
,
7209 New_Occurrence_Of
(Bnn
, Loc
),
7211 Make_Unchecked_Type_Conversion
(Loc
,
7213 New_Occurrence_Of
(RTE
(RE_Communication_Block
), Loc
),
7214 Expression
=> Make_Identifier
(Loc
, Name_uD
))));
7217 -- _Disp_Asynchronous_Select (<object>, S, P'Address, D, B);
7219 Prepend_To
(TaskE_Stmts
,
7220 Make_Procedure_Call_Statement
(Loc
,
7223 Find_Prim_Op
(Etype
(Etype
(Obj
)),
7224 Name_uDisp_Asynchronous_Select
),
7227 Parameter_Associations
=>
7229 New_Copy_Tree
(Obj
), -- <object>
7230 New_Occurrence_Of
(S
, Loc
), -- S
7231 Make_Attribute_Reference
(Loc
, -- P'Address
7232 Prefix
=> New_Occurrence_Of
(P
, Loc
),
7233 Attribute_Name
=> Name_Address
),
7234 Make_Identifier
(Loc
, Name_uD
), -- D
7235 New_Occurrence_Of
(B
, Loc
)))); -- B
7240 Prepend_To
(TaskE_Stmts
,
7241 Make_Procedure_Call_Statement
(Loc
,
7242 Name
=> New_Occurrence_Of
(RTE
(RE_Abort_Defer
), Loc
),
7243 Parameter_Associations
=> No_List
));
7247 -- <abortable-statements>
7249 Cleanup_Stmts
:= New_Copy_List_Tree
(Astats
);
7251 Prepend_To
(Cleanup_Stmts
,
7252 Make_Procedure_Call_Statement
(Loc
,
7253 Name
=> New_Occurrence_Of
(RTE
(RE_Abort_Undefer
), Loc
),
7254 Parameter_Associations
=> No_List
));
7256 -- Wrap the statements in a block. Exp_Ch7.Expand_Cleanup_Actions
7257 -- will generate a _clean for the additional status flag.
7261 -- procedure _clean is
7263 -- Cancel_Task_Entry_Call (U);
7271 Cleanup_Block_Ent
:= Make_Temporary
(Loc
, 'C');
7273 Build_Cleanup_Block
(Loc
, Cleanup_Block_Ent
, Cleanup_Stmts
, T
);
7275 -- Wrap the cleanup block in an exception handling block
7281 -- when Abort_Signal => Abort_Undefer;
7284 Abort_Block_Ent
:= Make_Temporary
(Loc
, 'A');
7286 Append_To
(TaskE_Stmts
,
7287 Make_Implicit_Label_Declaration
(Loc
,
7288 Defining_Identifier
=> Abort_Block_Ent
));
7290 Append_To
(TaskE_Stmts
,
7292 (Loc
, Abort_Block_Ent
, Cleanup_Block_Ent
, Cleanup_Block
));
7296 -- <triggering-statements>
7299 Append_To
(TaskE_Stmts
,
7300 Make_Implicit_If_Statement
(N
,
7302 Make_Op_Not
(Loc
, Right_Opnd
=> New_Occurrence_Of
(T
, Loc
)),
7305 New_Copy_List_Tree
(Tstats
)));
7307 ----------------------------------
7308 -- Protected procedure handling --
7309 ----------------------------------
7312 -- <dispatching-call>;
7313 -- <triggering-statements>
7315 ProtP_Stmts
:= New_Copy_List_Tree
(Tstats
);
7316 Prepend_To
(ProtP_Stmts
, New_Copy_Tree
(Ecall
));
7319 -- S := Ada.Tags.Get_Offset_Index
7320 -- (Ada.Tags.Tag (<object>), DT_Position (Call_Ent));
7323 New_List
(Build_S_Assignment
(Loc
, S
, Obj
, Call_Ent
));
7326 -- _Disp_Get_Prim_Op_Kind (<object>, S, C);
7328 Append_To
(Conc_Typ_Stmts
,
7329 Make_Procedure_Call_Statement
(Loc
,
7332 (Find_Prim_Op
(Etype
(Etype
(Obj
)),
7333 Name_uDisp_Get_Prim_Op_Kind
),
7335 Parameter_Associations
=>
7337 New_Copy_Tree
(Obj
),
7338 New_Occurrence_Of
(S
, Loc
),
7339 New_Occurrence_Of
(C
, Loc
))));
7342 -- if C = POK_Procedure_Entry then
7344 -- elsif C = POK_Task_Entry then
7350 Append_To
(Conc_Typ_Stmts
,
7351 Make_Implicit_If_Statement
(N
,
7355 New_Occurrence_Of
(C
, Loc
),
7357 New_Occurrence_Of
(RTE
(RE_POK_Protected_Entry
), Loc
)),
7364 Make_Elsif_Part
(Loc
,
7368 New_Occurrence_Of
(C
, Loc
),
7370 New_Occurrence_Of
(RTE
(RE_POK_Task_Entry
), Loc
)),
7379 -- <dispatching-call>;
7380 -- <triggering-statements>
7382 Lim_Typ_Stmts
:= New_Copy_List_Tree
(Tstats
);
7383 Prepend_To
(Lim_Typ_Stmts
, New_Copy_Tree
(Ecall
));
7386 -- if K = Ada.Tags.TK_Limited_Tagged
7387 -- or else K = Ada.Tags.TK_Tagged
7395 Make_Implicit_If_Statement
(N
,
7396 Condition
=> Build_Dispatching_Tag_Check
(K
, N
),
7397 Then_Statements
=> Lim_Typ_Stmts
,
7398 Else_Statements
=> Conc_Typ_Stmts
));
7401 Make_Block_Statement
(Loc
,
7404 Handled_Statement_Sequence
=>
7405 Make_Handled_Sequence_Of_Statements
(Loc
, Stmts
)));
7410 -- Delay triggering statement processing
7413 -- Add a Delay_Block object to the parameter list of the delay
7414 -- procedure to form the parameter list of the Wait entry call.
7416 Dblock_Ent
:= Make_Temporary
(Loc
, 'D');
7418 Pdef
:= Entity
(Name
(Ecall
));
7420 if Is_RTE
(Pdef
, RO_CA_Delay_For
) then
7422 New_Occurrence_Of
(RTE
(RE_Enqueue_Duration
), Loc
);
7424 elsif Is_RTE
(Pdef
, RO_CA_Delay_Until
) then
7426 New_Occurrence_Of
(RTE
(RE_Enqueue_Calendar
), Loc
);
7428 else pragma Assert
(Is_RTE
(Pdef
, RO_RT_Delay_Until
));
7429 Enqueue_Call
:= New_Occurrence_Of
(RTE
(RE_Enqueue_RT
), Loc
);
7432 Append_To
(Parameter_Associations
(Ecall
),
7433 Make_Attribute_Reference
(Loc
,
7434 Prefix
=> New_Occurrence_Of
(Dblock_Ent
, Loc
),
7435 Attribute_Name
=> Name_Unchecked_Access
));
7437 -- Create the inner block to protect the abortable part
7439 Hdle
:= New_List
(Build_Abort_Block_Handler
(Loc
));
7442 Make_Procedure_Call_Statement
(Loc
,
7443 Name
=> New_Occurrence_Of
(RTE
(RE_Abort_Undefer
), Loc
)));
7446 Make_Block_Statement
(Loc
,
7447 Identifier
=> New_Occurrence_Of
(Blk_Ent
, Loc
),
7448 Handled_Statement_Sequence
=>
7449 Make_Handled_Sequence_Of_Statements
(Loc
,
7450 Statements
=> Astats
),
7451 Has_Created_Identifier
=> True,
7452 Is_Asynchronous_Call_Block
=> True);
7454 -- Append call to if Enqueue (When, DB'Unchecked_Access) then
7457 Make_Implicit_If_Statement
(N
,
7459 Make_Function_Call
(Loc
,
7460 Name
=> Enqueue_Call
,
7461 Parameter_Associations
=> Parameter_Associations
(Ecall
)),
7463 New_List
(Make_Block_Statement
(Loc
,
7464 Handled_Statement_Sequence
=>
7465 Make_Handled_Sequence_Of_Statements
(Loc
,
7466 Statements
=> New_List
(
7467 Make_Implicit_Label_Declaration
(Loc
,
7468 Defining_Identifier
=> Blk_Ent
,
7469 Label_Construct
=> Abortable_Block
),
7471 Exception_Handlers
=> Hdle
)))));
7473 Stmts
:= New_List
(Ecall
);
7475 -- Construct statement sequence for new block
7478 Make_Implicit_If_Statement
(N
,
7480 Make_Function_Call
(Loc
,
7481 Name
=> New_Occurrence_Of
(
7482 RTE
(RE_Timed_Out
), Loc
),
7483 Parameter_Associations
=> New_List
(
7484 Make_Attribute_Reference
(Loc
,
7485 Prefix
=> New_Occurrence_Of
(Dblock_Ent
, Loc
),
7486 Attribute_Name
=> Name_Unchecked_Access
))),
7487 Then_Statements
=> Tstats
));
7489 -- The result is the new block
7491 Set_Entry_Cancel_Parameter
(Blk_Ent
, Dblock_Ent
);
7494 Make_Block_Statement
(Loc
,
7495 Declarations
=> New_List
(
7496 Make_Object_Declaration
(Loc
,
7497 Defining_Identifier
=> Dblock_Ent
,
7498 Aliased_Present
=> True,
7499 Object_Definition
=>
7500 New_Occurrence_Of
(RTE
(RE_Delay_Block
), Loc
))),
7502 Handled_Statement_Sequence
=>
7503 Make_Handled_Sequence_Of_Statements
(Loc
, Stmts
)));
7513 Extract_Entry
(Ecall
, Concval
, Ename
, Index
);
7514 Build_Simple_Entry_Call
(Ecall
, Concval
, Ename
, Index
);
7516 Stmts
:= Statements
(Handled_Statement_Sequence
(Ecall
));
7517 Decls
:= Declarations
(Ecall
);
7519 if Is_Protected_Type
(Etype
(Concval
)) then
7521 -- Get the declarations of the block expanded from the entry call
7523 Decl
:= First
(Decls
);
7524 while Present
(Decl
)
7525 and then (Nkind
(Decl
) /= N_Object_Declaration
7526 or else not Is_RTE
(Etype
(Object_Definition
(Decl
)),
7527 RE_Communication_Block
))
7532 pragma Assert
(Present
(Decl
));
7533 Cancel_Param
:= Defining_Identifier
(Decl
);
7535 -- Change the mode of the Protected_Entry_Call call
7537 -- Protected_Entry_Call (
7538 -- Object => po._object'Access,
7539 -- E => <entry index>;
7540 -- Uninterpreted_Data => P'Address;
7541 -- Mode => Asynchronous_Call;
7544 -- Skip assignments to temporaries created for in-out parameters
7546 -- This makes unwarranted assumptions about the shape of the expanded
7547 -- tree for the call, and should be cleaned up ???
7549 Stmt
:= First
(Stmts
);
7550 while Nkind
(Stmt
) /= N_Procedure_Call_Statement
loop
7556 Param
:= First
(Parameter_Associations
(Call
));
7557 while Present
(Param
)
7558 and then not Is_RTE
(Etype
(Param
), RE_Call_Modes
)
7563 pragma Assert
(Present
(Param
));
7564 Rewrite
(Param
, New_Occurrence_Of
(RTE
(RE_Asynchronous_Call
), Loc
));
7567 -- Append an if statement to execute the abortable part
7570 -- if Enqueued (Bnn) then
7573 Make_Implicit_If_Statement
(N
,
7575 Make_Function_Call
(Loc
,
7576 Name
=> New_Occurrence_Of
(RTE
(RE_Enqueued
), Loc
),
7577 Parameter_Associations
=> New_List
(
7578 New_Occurrence_Of
(Cancel_Param
, Loc
))),
7579 Then_Statements
=> Astats
));
7582 Make_Block_Statement
(Loc
,
7583 Identifier
=> New_Occurrence_Of
(Blk_Ent
, Loc
),
7584 Handled_Statement_Sequence
=>
7585 Make_Handled_Sequence_Of_Statements
(Loc
, Statements
=> Stmts
),
7586 Has_Created_Identifier
=> True,
7587 Is_Asynchronous_Call_Block
=> True);
7589 -- For the VM call Update_Exception instead of Abort_Undefer.
7590 -- See 4jexcept.ads for an explanation.
7592 if VM_Target
= No_VM
then
7593 if Exception_Mechanism
= Back_End_Exceptions
then
7595 -- Aborts are not deferred at beginning of exception handlers
7598 Handler_Stmt
:= Make_Null_Statement
(Loc
);
7601 Handler_Stmt
:= Make_Procedure_Call_Statement
(Loc
,
7602 Name
=> New_Occurrence_Of
(RTE
(RE_Abort_Undefer
), Loc
),
7603 Parameter_Associations
=> No_List
);
7606 Handler_Stmt
:= Make_Procedure_Call_Statement
(Loc
,
7607 Name
=> New_Occurrence_Of
(RTE
(RE_Update_Exception
), Loc
),
7608 Parameter_Associations
=> New_List
(
7609 Make_Function_Call
(Loc
,
7610 Name
=> New_Occurrence_Of
7611 (RTE
(RE_Current_Target_Exception
), Loc
))));
7615 Make_Block_Statement
(Loc
,
7616 Handled_Statement_Sequence
=>
7617 Make_Handled_Sequence_Of_Statements
(Loc
,
7618 Statements
=> New_List
(
7619 Make_Implicit_Label_Declaration
(Loc
,
7620 Defining_Identifier
=> Blk_Ent
,
7621 Label_Construct
=> Abortable_Block
),
7626 Exception_Handlers
=> New_List
(
7627 Make_Implicit_Exception_Handler
(Loc
,
7629 -- when Abort_Signal =>
7630 -- Abort_Undefer.all;
7632 Exception_Choices
=>
7633 New_List
(New_Occurrence_Of
(Stand
.Abort_Signal
, Loc
)),
7634 Statements
=> New_List
(Handler_Stmt
))))),
7636 -- if not Cancelled (Bnn) then
7637 -- triggered statements
7640 Make_Implicit_If_Statement
(N
,
7641 Condition
=> Make_Op_Not
(Loc
,
7643 Make_Function_Call
(Loc
,
7644 Name
=> New_Occurrence_Of
(RTE
(RE_Cancelled
), Loc
),
7645 Parameter_Associations
=> New_List
(
7646 New_Occurrence_Of
(Cancel_Param
, Loc
)))),
7647 Then_Statements
=> Tstats
));
7649 -- Asynchronous task entry call
7656 B
:= Make_Defining_Identifier
(Loc
, Name_uB
);
7658 -- Insert declaration of B in declarations of existing block
7661 Make_Object_Declaration
(Loc
,
7662 Defining_Identifier
=> B
,
7663 Object_Definition
=>
7664 New_Occurrence_Of
(Standard_Boolean
, Loc
)));
7666 Cancel_Param
:= Make_Defining_Identifier
(Loc
, Name_uC
);
7668 -- Insert declaration of C in declarations of existing block
7671 Make_Object_Declaration
(Loc
,
7672 Defining_Identifier
=> Cancel_Param
,
7673 Object_Definition
=>
7674 New_Occurrence_Of
(Standard_Boolean
, Loc
)));
7676 -- Remove and save the call to Call_Simple
7678 Stmt
:= First
(Stmts
);
7680 -- Skip assignments to temporaries created for in-out parameters.
7681 -- This makes unwarranted assumptions about the shape of the expanded
7682 -- tree for the call, and should be cleaned up ???
7684 while Nkind
(Stmt
) /= N_Procedure_Call_Statement
loop
7690 -- Create the inner block to protect the abortable part
7692 Hdle
:= New_List
(Build_Abort_Block_Handler
(Loc
));
7695 Make_Procedure_Call_Statement
(Loc
,
7696 Name
=> New_Occurrence_Of
(RTE
(RE_Abort_Undefer
), Loc
)));
7699 Make_Block_Statement
(Loc
,
7700 Identifier
=> New_Occurrence_Of
(Blk_Ent
, Loc
),
7701 Handled_Statement_Sequence
=>
7702 Make_Handled_Sequence_Of_Statements
(Loc
, Statements
=> Astats
),
7703 Has_Created_Identifier
=> True,
7704 Is_Asynchronous_Call_Block
=> True);
7707 Make_Block_Statement
(Loc
,
7708 Handled_Statement_Sequence
=>
7709 Make_Handled_Sequence_Of_Statements
(Loc
,
7710 Statements
=> New_List
(
7711 Make_Implicit_Label_Declaration
(Loc
,
7712 Defining_Identifier
=> Blk_Ent
,
7713 Label_Construct
=> Abortable_Block
),
7715 Exception_Handlers
=> Hdle
)));
7717 -- Create new call statement
7719 Params
:= Parameter_Associations
(Call
);
7722 New_Occurrence_Of
(RTE
(RE_Asynchronous_Call
), Loc
));
7723 Append_To
(Params
, New_Occurrence_Of
(B
, Loc
));
7726 Make_Procedure_Call_Statement
(Loc
,
7727 Name
=> New_Occurrence_Of
(RTE
(RE_Task_Entry_Call
), Loc
),
7728 Parameter_Associations
=> Params
));
7730 -- Construct statement sequence for new block
7733 Make_Implicit_If_Statement
(N
,
7735 Make_Op_Not
(Loc
, New_Occurrence_Of
(Cancel_Param
, Loc
)),
7736 Then_Statements
=> Tstats
));
7738 -- Protected the call against abort
7741 Make_Procedure_Call_Statement
(Loc
,
7742 Name
=> New_Occurrence_Of
(RTE
(RE_Abort_Defer
), Loc
),
7743 Parameter_Associations
=> Empty_List
));
7746 Set_Entry_Cancel_Parameter
(Blk_Ent
, Cancel_Param
);
7748 -- The result is the new block
7751 Make_Block_Statement
(Loc
,
7752 Declarations
=> Decls
,
7753 Handled_Statement_Sequence
=>
7754 Make_Handled_Sequence_Of_Statements
(Loc
, Stmts
)));
7757 end Expand_N_Asynchronous_Select
;
7759 -------------------------------------
7760 -- Expand_N_Conditional_Entry_Call --
7761 -------------------------------------
7763 -- The conditional task entry call is converted to a call to
7768 -- P : parms := (parm, parm, parm);
7772 -- (<acceptor-task>, -- Acceptor
7773 -- <entry-index>, -- E
7774 -- P'Address, -- Uninterpreted_Data
7775 -- Conditional_Call, -- Mode
7776 -- B); -- Rendezvous_Successful
7781 -- normal-statements
7787 -- For a description of the use of P and the assignments after the call,
7788 -- see Expand_N_Entry_Call_Statement. Note that the entry call of the
7789 -- conditional entry call has already been expanded (by the Expand_N_Entry
7790 -- _Call_Statement procedure) as follows:
7793 -- P : parms := (parm, parm, parm);
7795 -- ... info for in-out parameters
7796 -- Call_Simple (acceptor-task, entry-index, P'Address);
7802 -- so the task at hand is to convert the latter expansion into the former
7804 -- The conditional protected entry call is converted to a call to
7805 -- Protected_Entry_Call:
7808 -- P : parms := (parm, parm, parm);
7809 -- Bnn : Communications_Block;
7812 -- Protected_Entry_Call
7813 -- (po._object'Access, -- Object
7814 -- <entry index>, -- E
7815 -- P'Address, -- Uninterpreted_Data
7816 -- Conditional_Call, -- Mode
7821 -- if Cancelled (Bnn) then
7824 -- normal-statements
7828 -- Ada 2005 (AI-345): A dispatching conditional entry call is converted
7832 -- B : Boolean := False;
7833 -- C : Ada.Tags.Prim_Op_Kind;
7834 -- K : Ada.Tags.Tagged_Kind :=
7835 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
7836 -- P : Parameters := (Param1 .. ParamN);
7840 -- if K = Ada.Tags.TK_Limited_Tagged
7841 -- or else K = Ada.Tags.TK_Tagged
7843 -- <dispatching-call>;
7844 -- <triggering-statements>
7848 -- Ada.Tags.Get_Offset_Index
7849 -- (Ada.Tags.Tag (<object>), DT_Position (<dispatching-call>));
7851 -- _Disp_Conditional_Select (<object>, S, P'Address, C, B);
7853 -- if C = POK_Protected_Entry
7854 -- or else C = POK_Task_Entry
7856 -- Param1 := P.Param1;
7858 -- ParamN := P.ParamN;
7862 -- if C = POK_Procedure
7863 -- or else C = POK_Protected_Procedure
7864 -- or else C = POK_Task_Procedure
7866 -- <dispatching-call>;
7869 -- <triggering-statements>
7871 -- <else-statements>
7876 procedure Expand_N_Conditional_Entry_Call
(N
: Node_Id
) is
7877 Loc
: constant Source_Ptr
:= Sloc
(N
);
7878 Alt
: constant Node_Id
:= Entry_Call_Alternative
(N
);
7879 Blk
: Node_Id
:= Entry_Call_Statement
(Alt
);
7882 Blk_Typ
: Entity_Id
;
7884 Call_Ent
: Entity_Id
;
7885 Conc_Typ_Stmts
: List_Id
;
7889 Lim_Typ_Stmts
: List_Id
;
7896 Transient_Blk
: Node_Id
;
7899 B
: Entity_Id
; -- Call status flag
7900 C
: Entity_Id
; -- Call kind
7901 K
: Entity_Id
; -- Tagged kind
7902 P
: Entity_Id
; -- Parameter block
7903 S
: Entity_Id
; -- Primitive operation slot
7906 Process_Statements_For_Controlled_Objects
(N
);
7908 if Ada_Version
>= Ada_2005
7909 and then Nkind
(Blk
) = N_Procedure_Call_Statement
7911 Extract_Dispatching_Call
(Blk
, Call_Ent
, Obj
, Actuals
, Formals
);
7916 -- Call status flag processing, generate:
7917 -- B : Boolean := False;
7919 B
:= Build_B
(Loc
, Decls
);
7921 -- Call kind processing, generate:
7922 -- C : Ada.Tags.Prim_Op_Kind;
7924 C
:= Build_C
(Loc
, Decls
);
7926 -- Tagged kind processing, generate:
7927 -- K : Ada.Tags.Tagged_Kind :=
7928 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
7930 K
:= Build_K
(Loc
, Decls
, Obj
);
7932 -- Parameter block processing
7934 Blk_Typ
:= Build_Parameter_Block
(Loc
, Actuals
, Formals
, Decls
);
7935 P
:= Parameter_Block_Pack
7936 (Loc
, Blk_Typ
, Actuals
, Formals
, Decls
, Stmts
);
7938 -- Dispatch table slot processing, generate:
7941 S
:= Build_S
(Loc
, Decls
);
7944 -- S := Ada.Tags.Get_Offset_Index
7945 -- (Ada.Tags.Tag (<object>), DT_Position (Call_Ent));
7948 New_List
(Build_S_Assignment
(Loc
, S
, Obj
, Call_Ent
));
7951 -- _Disp_Conditional_Select (<object>, S, P'Address, C, B);
7953 Append_To
(Conc_Typ_Stmts
,
7954 Make_Procedure_Call_Statement
(Loc
,
7957 Find_Prim_Op
(Etype
(Etype
(Obj
)),
7958 Name_uDisp_Conditional_Select
),
7960 Parameter_Associations
=>
7962 New_Copy_Tree
(Obj
), -- <object>
7963 New_Occurrence_Of
(S
, Loc
), -- S
7964 Make_Attribute_Reference
(Loc
, -- P'Address
7965 Prefix
=> New_Occurrence_Of
(P
, Loc
),
7966 Attribute_Name
=> Name_Address
),
7967 New_Occurrence_Of
(C
, Loc
), -- C
7968 New_Occurrence_Of
(B
, Loc
)))); -- B
7971 -- if C = POK_Protected_Entry
7972 -- or else C = POK_Task_Entry
7974 -- Param1 := P.Param1;
7976 -- ParamN := P.ParamN;
7979 Unpack
:= Parameter_Block_Unpack
(Loc
, P
, Actuals
, Formals
);
7981 -- Generate the if statement only when the packed parameters need
7982 -- explicit assignments to their corresponding actuals.
7984 if Present
(Unpack
) then
7985 Append_To
(Conc_Typ_Stmts
,
7986 Make_Implicit_If_Statement
(N
,
7992 New_Occurrence_Of
(C
, Loc
),
7994 New_Occurrence_Of
(RTE
(
7995 RE_POK_Protected_Entry
), Loc
)),
8000 New_Occurrence_Of
(C
, Loc
),
8002 New_Occurrence_Of
(RTE
(RE_POK_Task_Entry
), Loc
))),
8004 Then_Statements
=> Unpack
));
8009 -- if C = POK_Procedure
8010 -- or else C = POK_Protected_Procedure
8011 -- or else C = POK_Task_Procedure
8013 -- <dispatching-call>
8015 -- <normal-statements>
8017 -- <else-statements>
8020 N_Stats
:= New_Copy_List_Tree
(Statements
(Alt
));
8022 Prepend_To
(N_Stats
,
8023 Make_Implicit_If_Statement
(N
,
8029 New_Occurrence_Of
(C
, Loc
),
8031 New_Occurrence_Of
(RTE
(RE_POK_Procedure
), Loc
)),
8038 New_Occurrence_Of
(C
, Loc
),
8040 New_Occurrence_Of
(RTE
(
8041 RE_POK_Protected_Procedure
), Loc
)),
8046 New_Occurrence_Of
(C
, Loc
),
8048 New_Occurrence_Of
(RTE
(
8049 RE_POK_Task_Procedure
), Loc
)))),
8054 Append_To
(Conc_Typ_Stmts
,
8055 Make_Implicit_If_Statement
(N
,
8056 Condition
=> New_Occurrence_Of
(B
, Loc
),
8057 Then_Statements
=> N_Stats
,
8058 Else_Statements
=> Else_Statements
(N
)));
8061 -- <dispatching-call>;
8062 -- <triggering-statements>
8064 Lim_Typ_Stmts
:= New_Copy_List_Tree
(Statements
(Alt
));
8065 Prepend_To
(Lim_Typ_Stmts
, New_Copy_Tree
(Blk
));
8068 -- if K = Ada.Tags.TK_Limited_Tagged
8069 -- or else K = Ada.Tags.TK_Tagged
8077 Make_Implicit_If_Statement
(N
,
8078 Condition
=> Build_Dispatching_Tag_Check
(K
, N
),
8079 Then_Statements
=> Lim_Typ_Stmts
,
8080 Else_Statements
=> Conc_Typ_Stmts
));
8083 Make_Block_Statement
(Loc
,
8086 Handled_Statement_Sequence
=>
8087 Make_Handled_Sequence_Of_Statements
(Loc
, Stmts
)));
8089 -- As described above, the entry alternative is transformed into a
8090 -- block that contains the gnulli call, and possibly assignment
8091 -- statements for in-out parameters. The gnulli call may itself be
8092 -- rewritten into a transient block if some unconstrained parameters
8093 -- require it. We need to retrieve the call to complete its parameter
8098 First_Real_Statement
(Handled_Statement_Sequence
(Blk
));
8100 if Present
(Transient_Blk
)
8101 and then Nkind
(Transient_Blk
) = N_Block_Statement
8103 Blk
:= Transient_Blk
;
8106 Stmts
:= Statements
(Handled_Statement_Sequence
(Blk
));
8107 Stmt
:= First
(Stmts
);
8108 while Nkind
(Stmt
) /= N_Procedure_Call_Statement
loop
8113 Params
:= Parameter_Associations
(Call
);
8115 if Is_RTE
(Entity
(Name
(Call
)), RE_Protected_Entry_Call
) then
8117 -- Substitute Conditional_Entry_Call for Simple_Call parameter
8119 Param
:= First
(Params
);
8120 while Present
(Param
)
8121 and then not Is_RTE
(Etype
(Param
), RE_Call_Modes
)
8126 pragma Assert
(Present
(Param
));
8128 New_Occurrence_Of
(RTE
(RE_Conditional_Call
), Loc
));
8132 -- Find the Communication_Block parameter for the call to the
8133 -- Cancelled function.
8135 Decl
:= First
(Declarations
(Blk
));
8136 while Present
(Decl
)
8137 and then not Is_RTE
(Etype
(Object_Definition
(Decl
)),
8138 RE_Communication_Block
)
8143 -- Add an if statement to execute the else part if the call
8144 -- does not succeed (as indicated by the Cancelled predicate).
8147 Make_Implicit_If_Statement
(N
,
8148 Condition
=> Make_Function_Call
(Loc
,
8149 Name
=> New_Occurrence_Of
(RTE
(RE_Cancelled
), Loc
),
8150 Parameter_Associations
=> New_List
(
8151 New_Occurrence_Of
(Defining_Identifier
(Decl
), Loc
))),
8152 Then_Statements
=> Else_Statements
(N
),
8153 Else_Statements
=> Statements
(Alt
)));
8156 B
:= Make_Defining_Identifier
(Loc
, Name_uB
);
8158 -- Insert declaration of B in declarations of existing block
8160 if No
(Declarations
(Blk
)) then
8161 Set_Declarations
(Blk
, New_List
);
8164 Prepend_To
(Declarations
(Blk
),
8165 Make_Object_Declaration
(Loc
,
8166 Defining_Identifier
=> B
,
8167 Object_Definition
=>
8168 New_Occurrence_Of
(Standard_Boolean
, Loc
)));
8170 -- Create new call statement
8173 New_Occurrence_Of
(RTE
(RE_Conditional_Call
), Loc
));
8174 Append_To
(Params
, New_Occurrence_Of
(B
, Loc
));
8177 Make_Procedure_Call_Statement
(Loc
,
8178 Name
=> New_Occurrence_Of
(RTE
(RE_Task_Entry_Call
), Loc
),
8179 Parameter_Associations
=> Params
));
8181 -- Construct statement sequence for new block
8184 Make_Implicit_If_Statement
(N
,
8185 Condition
=> New_Occurrence_Of
(B
, Loc
),
8186 Then_Statements
=> Statements
(Alt
),
8187 Else_Statements
=> Else_Statements
(N
)));
8190 -- The result is the new block
8193 Make_Block_Statement
(Loc
,
8194 Declarations
=> Declarations
(Blk
),
8195 Handled_Statement_Sequence
=>
8196 Make_Handled_Sequence_Of_Statements
(Loc
, Stmts
)));
8200 end Expand_N_Conditional_Entry_Call
;
8202 ---------------------------------------
8203 -- Expand_N_Delay_Relative_Statement --
8204 ---------------------------------------
8206 -- Delay statement is implemented as a procedure call to Delay_For
8207 -- defined in Ada.Calendar.Delays in order to reduce the overhead of
8208 -- simple delays imposed by the use of Protected Objects.
8210 procedure Expand_N_Delay_Relative_Statement
(N
: Node_Id
) is
8211 Loc
: constant Source_Ptr
:= Sloc
(N
);
8214 Make_Procedure_Call_Statement
(Loc
,
8215 Name
=> New_Occurrence_Of
(RTE
(RO_CA_Delay_For
), Loc
),
8216 Parameter_Associations
=> New_List
(Expression
(N
))));
8218 end Expand_N_Delay_Relative_Statement
;
8220 ------------------------------------
8221 -- Expand_N_Delay_Until_Statement --
8222 ------------------------------------
8224 -- Delay Until statement is implemented as a procedure call to
8225 -- Delay_Until defined in Ada.Calendar.Delays and Ada.Real_Time.Delays.
8227 procedure Expand_N_Delay_Until_Statement
(N
: Node_Id
) is
8228 Loc
: constant Source_Ptr
:= Sloc
(N
);
8232 if Is_RTE
(Base_Type
(Etype
(Expression
(N
))), RO_CA_Time
) then
8233 Typ
:= RTE
(RO_CA_Delay_Until
);
8235 Typ
:= RTE
(RO_RT_Delay_Until
);
8239 Make_Procedure_Call_Statement
(Loc
,
8240 Name
=> New_Occurrence_Of
(Typ
, Loc
),
8241 Parameter_Associations
=> New_List
(Expression
(N
))));
8244 end Expand_N_Delay_Until_Statement
;
8246 -------------------------
8247 -- Expand_N_Entry_Body --
8248 -------------------------
8250 procedure Expand_N_Entry_Body
(N
: Node_Id
) is
8252 -- Associate discriminals with the next protected operation body to be
8255 if Present
(Next_Protected_Operation
(N
)) then
8256 Set_Discriminals
(Parent
(Current_Scope
));
8258 end Expand_N_Entry_Body
;
8260 -----------------------------------
8261 -- Expand_N_Entry_Call_Statement --
8262 -----------------------------------
8264 -- An entry call is expanded into GNARLI calls to implement a simple entry
8265 -- call (see Build_Simple_Entry_Call).
8267 procedure Expand_N_Entry_Call_Statement
(N
: Node_Id
) is
8273 if No_Run_Time_Mode
then
8274 Error_Msg_CRT
("entry call", N
);
8278 -- If this entry call is part of an asynchronous select, don't expand it
8279 -- here; it will be expanded with the select statement. Don't expand
8280 -- timed entry calls either, as they are translated into asynchronous
8283 -- ??? This whole approach is questionable; it may be better to go back
8284 -- to allowing the expansion to take place and then attempting to fix it
8285 -- up in Expand_N_Asynchronous_Select. The tricky part is figuring out
8286 -- whether the expanded call is on a task or protected entry.
8288 if (Nkind
(Parent
(N
)) /= N_Triggering_Alternative
8289 or else N
/= Triggering_Statement
(Parent
(N
)))
8290 and then (Nkind
(Parent
(N
)) /= N_Entry_Call_Alternative
8291 or else N
/= Entry_Call_Statement
(Parent
(N
))
8292 or else Nkind
(Parent
(Parent
(N
))) /= N_Timed_Entry_Call
)
8294 Extract_Entry
(N
, Concval
, Ename
, Index
);
8295 Build_Simple_Entry_Call
(N
, Concval
, Ename
, Index
);
8297 end Expand_N_Entry_Call_Statement
;
8299 --------------------------------
8300 -- Expand_N_Entry_Declaration --
8301 --------------------------------
8303 -- If there are parameters, then first, each of the formals is marked by
8304 -- setting Is_Entry_Formal. Next a record type is built which is used to
8305 -- hold the parameter values. The name of this record type is entryP where
8306 -- entry is the name of the entry, with an additional corresponding access
8307 -- type called entryPA. The record type has matching components for each
8308 -- formal (the component names are the same as the formal names). For
8309 -- elementary types, the component type matches the formal type. For
8310 -- composite types, an access type is declared (with the name formalA)
8311 -- which designates the formal type, and the type of the component is this
8312 -- access type. Finally the Entry_Component of each formal is set to
8313 -- reference the corresponding record component.
8315 procedure Expand_N_Entry_Declaration
(N
: Node_Id
) is
8316 Loc
: constant Source_Ptr
:= Sloc
(N
);
8317 Entry_Ent
: constant Entity_Id
:= Defining_Identifier
(N
);
8318 Components
: List_Id
;
8321 Last_Decl
: Node_Id
;
8322 Component
: Entity_Id
;
8325 Rec_Ent
: Entity_Id
;
8326 Acc_Ent
: Entity_Id
;
8329 Formal
:= First_Formal
(Entry_Ent
);
8332 -- Most processing is done only if parameters are present
8334 if Present
(Formal
) then
8335 Components
:= New_List
;
8337 -- Loop through formals
8339 while Present
(Formal
) loop
8340 Set_Is_Entry_Formal
(Formal
);
8342 Make_Defining_Identifier
(Sloc
(Formal
), Chars
(Formal
));
8343 Set_Entry_Component
(Formal
, Component
);
8344 Set_Entry_Formal
(Component
, Formal
);
8345 Ftype
:= Etype
(Formal
);
8347 -- Declare new access type and then append
8349 Ctype
:= Make_Temporary
(Loc
, 'A');
8352 Make_Full_Type_Declaration
(Loc
,
8353 Defining_Identifier
=> Ctype
,
8355 Make_Access_To_Object_Definition
(Loc
,
8356 All_Present
=> True,
8357 Constant_Present
=> Ekind
(Formal
) = E_In_Parameter
,
8358 Subtype_Indication
=> New_Occurrence_Of
(Ftype
, Loc
)));
8360 Insert_After
(Last_Decl
, Decl
);
8363 Append_To
(Components
,
8364 Make_Component_Declaration
(Loc
,
8365 Defining_Identifier
=> Component
,
8366 Component_Definition
=>
8367 Make_Component_Definition
(Loc
,
8368 Aliased_Present
=> False,
8369 Subtype_Indication
=> New_Occurrence_Of
(Ctype
, Loc
))));
8371 Next_Formal_With_Extras
(Formal
);
8374 -- Create the Entry_Parameter_Record declaration
8376 Rec_Ent
:= Make_Temporary
(Loc
, 'P');
8379 Make_Full_Type_Declaration
(Loc
,
8380 Defining_Identifier
=> Rec_Ent
,
8382 Make_Record_Definition
(Loc
,
8384 Make_Component_List
(Loc
,
8385 Component_Items
=> Components
)));
8387 Insert_After
(Last_Decl
, Decl
);
8390 -- Construct and link in the corresponding access type
8392 Acc_Ent
:= Make_Temporary
(Loc
, 'A');
8394 Set_Entry_Parameters_Type
(Entry_Ent
, Acc_Ent
);
8397 Make_Full_Type_Declaration
(Loc
,
8398 Defining_Identifier
=> Acc_Ent
,
8400 Make_Access_To_Object_Definition
(Loc
,
8401 All_Present
=> True,
8402 Subtype_Indication
=> New_Occurrence_Of
(Rec_Ent
, Loc
)));
8404 Insert_After
(Last_Decl
, Decl
);
8406 end Expand_N_Entry_Declaration
;
8408 -----------------------------
8409 -- Expand_N_Protected_Body --
8410 -----------------------------
8412 -- Protected bodies are expanded to the completion of the subprograms
8413 -- created for the corresponding protected type. These are a protected and
8414 -- unprotected version of each protected subprogram in the object, a
8415 -- function to calculate each entry barrier, and a procedure to execute the
8416 -- sequence of statements of each protected entry body. For example, for
8417 -- protected type ptype:
8420 -- (O : System.Address;
8421 -- E : Protected_Entry_Index)
8424 -- <discriminant renamings>
8425 -- <private object renamings>
8427 -- return <barrier expression>;
8430 -- procedure pprocN (_object : in out poV;...) is
8431 -- <discriminant renamings>
8432 -- <private object renamings>
8434 -- <sequence of statements>
8437 -- procedure pprocP (_object : in out poV;...) is
8438 -- procedure _clean is
8441 -- ptypeS (_object, Pn);
8442 -- Unlock (_object._object'Access);
8443 -- Abort_Undefer.all;
8448 -- Lock (_object._object'Access);
8449 -- pprocN (_object;...);
8454 -- function pfuncN (_object : poV;...) return Return_Type is
8455 -- <discriminant renamings>
8456 -- <private object renamings>
8458 -- <sequence of statements>
8461 -- function pfuncP (_object : poV) return Return_Type is
8462 -- procedure _clean is
8464 -- Unlock (_object._object'Access);
8465 -- Abort_Undefer.all;
8470 -- Lock (_object._object'Access);
8471 -- return pfuncN (_object);
8478 -- (O : System.Address;
8479 -- P : System.Address;
8480 -- E : Protected_Entry_Index)
8482 -- <discriminant renamings>
8483 -- <private object renamings>
8484 -- type poVP is access poV;
8485 -- _Object : ptVP := ptVP!(O);
8489 -- <statement sequence>
8490 -- Complete_Entry_Body (_Object._Object);
8492 -- when all others =>
8493 -- Exceptional_Complete_Entry_Body (
8494 -- _Object._Object, Get_GNAT_Exception);
8498 -- The type poV is the record created for the protected type to hold
8499 -- the state of the protected object.
8501 procedure Expand_N_Protected_Body
(N
: Node_Id
) is
8502 Loc
: constant Source_Ptr
:= Sloc
(N
);
8503 Pid
: constant Entity_Id
:= Corresponding_Spec
(N
);
8505 Lock_Free_Active
: constant Boolean := Uses_Lock_Free
(Pid
);
8506 -- This flag indicates whether the lock free implementation is active
8508 Current_Node
: Node_Id
;
8509 Disp_Op_Body
: Node_Id
;
8510 New_Op_Body
: Node_Id
;
8514 function Build_Dispatching_Subprogram_Body
8517 Prot_Bod
: Node_Id
) return Node_Id
;
8518 -- Build a dispatching version of the protected subprogram body. The
8519 -- newly generated subprogram contains a call to the original protected
8520 -- body. The following code is generated:
8522 -- function <protected-function-name> (Param1 .. ParamN) return
8525 -- return <protected-function-name>P (Param1 .. ParamN);
8526 -- end <protected-function-name>;
8530 -- procedure <protected-procedure-name> (Param1 .. ParamN) is
8532 -- <protected-procedure-name>P (Param1 .. ParamN);
8533 -- end <protected-procedure-name>
8535 ---------------------------------------
8536 -- Build_Dispatching_Subprogram_Body --
8537 ---------------------------------------
8539 function Build_Dispatching_Subprogram_Body
8542 Prot_Bod
: Node_Id
) return Node_Id
8544 Loc
: constant Source_Ptr
:= Sloc
(N
);
8551 -- Generate a specification without a letter suffix in order to
8552 -- override an interface function or procedure.
8554 Spec
:= Build_Protected_Sub_Specification
(N
, Pid
, Dispatching_Mode
);
8556 -- The formal parameters become the actuals of the protected function
8557 -- or procedure call.
8559 Actuals
:= New_List
;
8560 Formal
:= First
(Parameter_Specifications
(Spec
));
8561 while Present
(Formal
) loop
8563 Make_Identifier
(Loc
, Chars
(Defining_Identifier
(Formal
))));
8567 if Nkind
(Spec
) = N_Procedure_Specification
then
8570 Make_Procedure_Call_Statement
(Loc
,
8572 New_Occurrence_Of
(Corresponding_Spec
(Prot_Bod
), Loc
),
8573 Parameter_Associations
=> Actuals
));
8576 pragma Assert
(Nkind
(Spec
) = N_Function_Specification
);
8580 Make_Simple_Return_Statement
(Loc
,
8582 Make_Function_Call
(Loc
,
8584 New_Occurrence_Of
(Corresponding_Spec
(Prot_Bod
), Loc
),
8585 Parameter_Associations
=> Actuals
)));
8589 Make_Subprogram_Body
(Loc
,
8590 Declarations
=> Empty_List
,
8591 Specification
=> Spec
,
8592 Handled_Statement_Sequence
=>
8593 Make_Handled_Sequence_Of_Statements
(Loc
, Stmts
));
8594 end Build_Dispatching_Subprogram_Body
;
8596 -- Start of processing for Expand_N_Protected_Body
8599 if No_Run_Time_Mode
then
8600 Error_Msg_CRT
("protected body", N
);
8604 -- This is the proper body corresponding to a stub. The declarations
8605 -- must be inserted at the point of the stub, which in turn is in the
8606 -- declarative part of the parent unit.
8608 if Nkind
(Parent
(N
)) = N_Subunit
then
8609 Current_Node
:= Corresponding_Stub
(Parent
(N
));
8614 Op_Body
:= First
(Declarations
(N
));
8616 -- The protected body is replaced with the bodies of its
8617 -- protected operations, and the declarations for internal objects
8618 -- that may have been created for entry family bounds.
8620 Rewrite
(N
, Make_Null_Statement
(Sloc
(N
)));
8623 while Present
(Op_Body
) loop
8624 case Nkind
(Op_Body
) is
8625 when N_Subprogram_Declaration
=>
8628 when N_Subprogram_Body
=>
8630 -- Do not create bodies for eliminated operations
8632 if not Is_Eliminated
(Defining_Entity
(Op_Body
))
8633 and then not Is_Eliminated
(Corresponding_Spec
(Op_Body
))
8635 if Lock_Free_Active
then
8637 Build_Lock_Free_Unprotected_Subprogram_Body
8641 Build_Unprotected_Subprogram_Body
(Op_Body
, Pid
);
8644 Insert_After
(Current_Node
, New_Op_Body
);
8645 Current_Node
:= New_Op_Body
;
8646 Analyze
(New_Op_Body
);
8648 -- Build the corresponding protected operation. It may
8649 -- appear that this is needed only if this is a visible
8650 -- operation of the type, or if it is an interrupt handler,
8651 -- and this was the strategy used previously in GNAT.
8653 -- However, the operation may be exported through a 'Access
8654 -- to an external caller. This is the common idiom in code
8655 -- that uses the Ada 2005 Timing_Events package. As a result
8656 -- we need to produce the protected body for both visible
8657 -- and private operations, as well as operations that only
8658 -- have a body in the source, and for which we create a
8659 -- declaration in the protected body itself.
8661 if Present
(Corresponding_Spec
(Op_Body
)) then
8662 if Lock_Free_Active
then
8664 Build_Lock_Free_Protected_Subprogram_Body
8665 (Op_Body
, Pid
, Specification
(New_Op_Body
));
8668 Build_Protected_Subprogram_Body
8669 (Op_Body
, Pid
, Specification
(New_Op_Body
));
8672 Insert_After
(Current_Node
, New_Op_Body
);
8673 Analyze
(New_Op_Body
);
8675 Current_Node
:= New_Op_Body
;
8677 -- Generate an overriding primitive operation body for
8678 -- this subprogram if the protected type implements an
8681 if Ada_Version
>= Ada_2005
8683 Present
(Interfaces
(Corresponding_Record_Type
(Pid
)))
8686 Build_Dispatching_Subprogram_Body
8687 (Op_Body
, Pid
, New_Op_Body
);
8689 Insert_After
(Current_Node
, Disp_Op_Body
);
8690 Analyze
(Disp_Op_Body
);
8692 Current_Node
:= Disp_Op_Body
;
8697 when N_Entry_Body
=>
8698 Op_Id
:= Defining_Identifier
(Op_Body
);
8699 New_Op_Body
:= Build_Protected_Entry
(Op_Body
, Op_Id
, Pid
);
8701 Insert_After
(Current_Node
, New_Op_Body
);
8702 Current_Node
:= New_Op_Body
;
8703 Analyze
(New_Op_Body
);
8705 when N_Implicit_Label_Declaration
=>
8708 when N_Itype_Reference
=>
8709 Insert_After
(Current_Node
, New_Copy
(Op_Body
));
8711 when N_Freeze_Entity
=>
8712 New_Op_Body
:= New_Copy
(Op_Body
);
8714 if Present
(Entity
(Op_Body
))
8715 and then Freeze_Node
(Entity
(Op_Body
)) = Op_Body
8717 Set_Freeze_Node
(Entity
(Op_Body
), New_Op_Body
);
8720 Insert_After
(Current_Node
, New_Op_Body
);
8721 Current_Node
:= New_Op_Body
;
8722 Analyze
(New_Op_Body
);
8725 New_Op_Body
:= New_Copy
(Op_Body
);
8726 Insert_After
(Current_Node
, New_Op_Body
);
8727 Current_Node
:= New_Op_Body
;
8728 Analyze
(New_Op_Body
);
8730 when N_Object_Declaration
=>
8731 pragma Assert
(not Comes_From_Source
(Op_Body
));
8732 New_Op_Body
:= New_Copy
(Op_Body
);
8733 Insert_After
(Current_Node
, New_Op_Body
);
8734 Current_Node
:= New_Op_Body
;
8735 Analyze
(New_Op_Body
);
8738 raise Program_Error
;
8745 -- Finally, create the body of the function that maps an entry index
8746 -- into the corresponding body index, except when there is no entry, or
8747 -- in a Ravenscar-like profile.
8749 if Corresponding_Runtime_Package
(Pid
) =
8750 System_Tasking_Protected_Objects_Entries
8752 New_Op_Body
:= Build_Find_Body_Index
(Pid
);
8753 Insert_After
(Current_Node
, New_Op_Body
);
8754 Current_Node
:= New_Op_Body
;
8755 Analyze
(New_Op_Body
);
8758 -- Ada 2005 (AI-345): Construct the primitive wrapper bodies after the
8759 -- protected body. At this point all wrapper specs have been created,
8760 -- frozen and included in the dispatch table for the protected type.
8762 if Ada_Version
>= Ada_2005
then
8763 Build_Wrapper_Bodies
(Loc
, Pid
, Current_Node
);
8765 end Expand_N_Protected_Body
;
8767 -----------------------------------------
8768 -- Expand_N_Protected_Type_Declaration --
8769 -----------------------------------------
8771 -- First we create a corresponding record type declaration used to
8772 -- represent values of this protected type.
8773 -- The general form of this type declaration is
8775 -- type poV (discriminants) is record
8776 -- _Object : aliased <kind>Protection
8777 -- [(<entry count> [, <handler count>])];
8778 -- [entry_family : array (bounds) of Void;]
8779 -- <private data fields>
8782 -- The discriminants are present only if the corresponding protected type
8783 -- has discriminants, and they exactly mirror the protected type
8784 -- discriminants. The private data fields similarly mirror the private
8785 -- declarations of the protected type.
8787 -- The Object field is always present. It contains RTS specific data used
8788 -- to control the protected object. It is declared as Aliased so that it
8789 -- can be passed as a pointer to the RTS. This allows the protected record
8790 -- to be referenced within RTS data structures. An appropriate Protection
8791 -- type and discriminant are generated.
8793 -- The Service field is present for protected objects with entries. It
8794 -- contains sufficient information to allow the entry service procedure for
8795 -- this object to be called when the object is not known till runtime.
8797 -- One entry_family component is present for each entry family in the
8798 -- task definition (see Expand_N_Task_Type_Declaration).
8800 -- When a protected object is declared, an instance of the protected type
8801 -- value record is created. The elaboration of this declaration creates the
8802 -- correct bounds for the entry families, and also evaluates the priority
8803 -- expression if needed. The initialization routine for the protected type
8804 -- itself then calls Initialize_Protection with appropriate parameters to
8805 -- initialize the value of the Task_Id field. Install_Handlers may be also
8806 -- called if a pragma Attach_Handler applies.
8808 -- Note: this record is passed to the subprograms created by the expansion
8809 -- of protected subprograms and entries. It is an in parameter to protected
8810 -- functions and an in out parameter to procedures and entry bodies. The
8811 -- Entity_Id for this created record type is placed in the
8812 -- Corresponding_Record_Type field of the associated protected type entity.
8814 -- Next we create a procedure specifications for protected subprograms and
8815 -- entry bodies. For each protected subprograms two subprograms are
8816 -- created, an unprotected and a protected version. The unprotected version
8817 -- is called from within other operations of the same protected object.
8819 -- We also build the call to register the procedure if a pragma
8820 -- Interrupt_Handler applies.
8822 -- A single subprogram is created to service all entry bodies; it has an
8823 -- additional boolean out parameter indicating that the previous entry call
8824 -- made by the current task was serviced immediately, i.e. not by proxy.
8825 -- The O parameter contains a pointer to a record object of the type
8826 -- described above. An untyped interface is used here to allow this
8827 -- procedure to be called in places where the type of the object to be
8828 -- serviced is not known. This must be done, for example, when a call that
8829 -- may have been requeued is cancelled; the corresponding object must be
8830 -- serviced, but which object that is not known till runtime.
8833 -- (O : System.Address; P : out Boolean);
8834 -- procedure pprocN (_object : in out poV);
8835 -- procedure pproc (_object : in out poV);
8836 -- function pfuncN (_object : poV);
8837 -- function pfunc (_object : poV);
8840 -- Note that this must come after the record type declaration, since
8841 -- the specs refer to this type.
8843 procedure Expand_N_Protected_Type_Declaration
(N
: Node_Id
) is
8844 Loc
: constant Source_Ptr
:= Sloc
(N
);
8845 Prot_Typ
: constant Entity_Id
:= Defining_Identifier
(N
);
8847 Lock_Free_Active
: constant Boolean := Uses_Lock_Free
(Prot_Typ
);
8848 -- This flag indicates whether the lock free implementation is active
8850 Pdef
: constant Node_Id
:= Protected_Definition
(N
);
8851 -- This contains two lists; one for visible and one for private decls
8855 Discr_Map
: constant Elist_Id
:= New_Elmt_List
;
8859 Comp_Id
: Entity_Id
;
8861 Current_Node
: Node_Id
:= N
;
8862 Entries_Aggr
: Node_Id
;
8863 Body_Id
: Entity_Id
;
8866 Object_Comp
: Node_Id
;
8868 procedure Check_Inlining
(Subp
: Entity_Id
);
8869 -- If the original operation has a pragma Inline, propagate the flag
8870 -- to the internal body, for possible inlining later on. The source
8871 -- operation is invisible to the back-end and is never actually called.
8873 procedure Expand_Entry_Declaration
(Comp
: Entity_Id
);
8874 -- Create the subprograms for the barrier and for the body, and append
8875 -- then to Entry_Bodies_Array.
8877 function Static_Component_Size
(Comp
: Entity_Id
) return Boolean;
8878 -- When compiling under the Ravenscar profile, private components must
8879 -- have a static size, or else a protected object will require heap
8880 -- allocation, violating the corresponding restriction. It is preferable
8881 -- to make this check here, because it provides a better error message
8882 -- than the back-end, which refers to the object as a whole.
8884 procedure Register_Handler
;
8885 -- For a protected operation that is an interrupt handler, add the
8886 -- freeze action that will register it as such.
8888 --------------------
8889 -- Check_Inlining --
8890 --------------------
8892 procedure Check_Inlining
(Subp
: Entity_Id
) is
8894 if Is_Inlined
(Subp
) then
8895 Set_Is_Inlined
(Protected_Body_Subprogram
(Subp
));
8896 Set_Is_Inlined
(Subp
, False);
8900 ---------------------------------
8901 -- Check_Static_Component_Size --
8902 ---------------------------------
8904 function Static_Component_Size
(Comp
: Entity_Id
) return Boolean is
8905 Typ
: constant Entity_Id
:= Etype
(Comp
);
8909 if Is_Scalar_Type
(Typ
) then
8912 elsif Is_Array_Type
(Typ
) then
8913 return Compile_Time_Known_Bounds
(Typ
);
8915 elsif Is_Record_Type
(Typ
) then
8916 C
:= First_Component
(Typ
);
8917 while Present
(C
) loop
8918 if not Static_Component_Size
(C
) then
8927 -- Any other type will be checked by the back-end
8932 end Static_Component_Size
;
8934 ------------------------------
8935 -- Expand_Entry_Declaration --
8936 ------------------------------
8938 procedure Expand_Entry_Declaration
(Comp
: Entity_Id
) is
8943 E_Count
:= E_Count
+ 1;
8944 Comp_Id
:= Defining_Identifier
(Comp
);
8947 Make_Defining_Identifier
(Loc
,
8948 Chars
=> Build_Selected_Name
(Prot_Typ
, Comp_Id
, 'E'));
8950 Make_Subprogram_Declaration
(Loc
,
8952 Build_Protected_Entry_Specification
(Loc
, Edef
, Comp_Id
));
8954 Insert_After
(Current_Node
, Sub
);
8957 -- Build wrapper procedure for pre/postconditions
8959 Build_PPC_Wrapper
(Comp_Id
, N
);
8961 Set_Protected_Body_Subprogram
8962 (Defining_Identifier
(Comp
),
8963 Defining_Unit_Name
(Specification
(Sub
)));
8965 Current_Node
:= Sub
;
8968 Make_Defining_Identifier
(Loc
,
8969 Chars
=> Build_Selected_Name
(Prot_Typ
, Comp_Id
, 'B'));
8971 Make_Subprogram_Declaration
(Loc
,
8973 Build_Barrier_Function_Specification
(Loc
, Bdef
));
8975 Insert_After
(Current_Node
, Sub
);
8977 Set_Protected_Body_Subprogram
(Bdef
, Bdef
);
8978 Set_Barrier_Function
(Comp_Id
, Bdef
);
8979 Set_Scope
(Bdef
, Scope
(Comp_Id
));
8980 Current_Node
:= Sub
;
8982 -- Collect pointers to the protected subprogram and the barrier
8983 -- of the current entry, for insertion into Entry_Bodies_Array.
8985 Append_To
(Expressions
(Entries_Aggr
),
8986 Make_Aggregate
(Loc
,
8987 Expressions
=> New_List
(
8988 Make_Attribute_Reference
(Loc
,
8989 Prefix
=> New_Occurrence_Of
(Bdef
, Loc
),
8990 Attribute_Name
=> Name_Unrestricted_Access
),
8991 Make_Attribute_Reference
(Loc
,
8992 Prefix
=> New_Occurrence_Of
(Edef
, Loc
),
8993 Attribute_Name
=> Name_Unrestricted_Access
))));
8994 end Expand_Entry_Declaration
;
8996 ----------------------
8997 -- Register_Handler --
8998 ----------------------
9000 procedure Register_Handler
is
9002 -- All semantic checks already done in Sem_Prag
9004 Prot_Proc
: constant Entity_Id
:=
9005 Defining_Unit_Name
(Specification
(Current_Node
));
9007 Proc_Address
: constant Node_Id
:=
9008 Make_Attribute_Reference
(Loc
,
9010 New_Occurrence_Of
(Prot_Proc
, Loc
),
9011 Attribute_Name
=> Name_Address
);
9013 RTS_Call
: constant Entity_Id
:=
9014 Make_Procedure_Call_Statement
(Loc
,
9017 (RTE
(RE_Register_Interrupt_Handler
), Loc
),
9018 Parameter_Associations
=> New_List
(Proc_Address
));
9020 Append_Freeze_Action
(Prot_Proc
, RTS_Call
);
9021 end Register_Handler
;
9023 -- Start of processing for Expand_N_Protected_Type_Declaration
9026 if Present
(Corresponding_Record_Type
(Prot_Typ
)) then
9029 Rec_Decl
:= Build_Corresponding_Record
(N
, Prot_Typ
, Loc
);
9032 Cdecls
:= Component_Items
(Component_List
(Type_Definition
(Rec_Decl
)));
9034 Qualify_Entity_Names
(N
);
9036 -- If the type has discriminants, their occurrences in the declaration
9037 -- have been replaced by the corresponding discriminals. For components
9038 -- that are constrained by discriminants, their homologues in the
9039 -- corresponding record type must refer to the discriminants of that
9040 -- record, so we must apply a new renaming to subtypes_indications:
9042 -- protected discriminant => discriminal => record discriminant
9044 -- This replacement is not applied to default expressions, for which
9045 -- the discriminal is correct.
9047 if Has_Discriminants
(Prot_Typ
) then
9053 Disc
:= First_Discriminant
(Prot_Typ
);
9054 Decl
:= First
(Discriminant_Specifications
(Rec_Decl
));
9055 while Present
(Disc
) loop
9056 Append_Elmt
(Discriminal
(Disc
), Discr_Map
);
9057 Append_Elmt
(Defining_Identifier
(Decl
), Discr_Map
);
9058 Next_Discriminant
(Disc
);
9064 -- Fill in the component declarations
9066 -- Add components for entry families. For each entry family, create an
9067 -- anonymous type declaration with the same size, and analyze the type.
9069 Collect_Entry_Families
(Loc
, Cdecls
, Current_Node
, Prot_Typ
);
9071 pragma Assert
(Present
(Pdef
));
9073 -- Add private field components
9075 if Present
(Private_Declarations
(Pdef
)) then
9076 Priv
:= First
(Private_Declarations
(Pdef
));
9077 while Present
(Priv
) loop
9078 if Nkind
(Priv
) = N_Component_Declaration
then
9079 if not Static_Component_Size
(Defining_Identifier
(Priv
)) then
9081 -- When compiling for a restricted profile, the private
9082 -- components must have a static size. If not, this is an
9083 -- error for a single protected declaration, and rates a
9084 -- warning on a protected type declaration.
9086 if not Comes_From_Source
(Prot_Typ
) then
9088 -- It's ok to be checking this restriction at expansion
9089 -- time, because this is only for the restricted profile,
9090 -- which is not subject to strict RM conformance, so it
9091 -- is OK to miss this check in -gnatc mode.
9093 Check_Restriction
(No_Implicit_Heap_Allocations
, Priv
);
9095 elsif Restriction_Active
(No_Implicit_Heap_Allocations
) then
9096 Error_Msg_N
("component has non-static size??", Priv
);
9098 ("\creation of protected object of type& will violate"
9099 & " restriction No_Implicit_Heap_Allocations??",
9104 -- The component definition consists of a subtype indication,
9105 -- or (in Ada 2005) an access definition. Make a copy of the
9106 -- proper definition.
9109 Old_Comp
: constant Node_Id
:= Component_Definition
(Priv
);
9110 Oent
: constant Entity_Id
:= Defining_Identifier
(Priv
);
9112 Nent
: constant Entity_Id
:=
9113 Make_Defining_Identifier
(Sloc
(Oent
),
9114 Chars
=> Chars
(Oent
));
9117 if Present
(Subtype_Indication
(Old_Comp
)) then
9119 Make_Component_Definition
(Sloc
(Oent
),
9120 Aliased_Present
=> False,
9121 Subtype_Indication
=>
9122 New_Copy_Tree
(Subtype_Indication
(Old_Comp
),
9126 Make_Component_Definition
(Sloc
(Oent
),
9127 Aliased_Present
=> False,
9128 Access_Definition
=>
9129 New_Copy_Tree
(Access_Definition
(Old_Comp
),
9134 Make_Component_Declaration
(Loc
,
9135 Defining_Identifier
=> Nent
,
9136 Component_Definition
=> New_Comp
,
9137 Expression
=> Expression
(Priv
));
9139 Set_Has_Per_Object_Constraint
(Nent
,
9140 Has_Per_Object_Constraint
(Oent
));
9142 Append_To
(Cdecls
, New_Priv
);
9145 elsif Nkind
(Priv
) = N_Subprogram_Declaration
then
9147 -- Make the unprotected version of the subprogram available
9148 -- for expansion of intra object calls. There is need for
9149 -- a protected version only if the subprogram is an interrupt
9150 -- handler, otherwise this operation can only be called from
9154 Make_Subprogram_Declaration
(Loc
,
9156 Build_Protected_Sub_Specification
9157 (Priv
, Prot_Typ
, Unprotected_Mode
));
9159 Insert_After
(Current_Node
, Sub
);
9162 Set_Protected_Body_Subprogram
9163 (Defining_Unit_Name
(Specification
(Priv
)),
9164 Defining_Unit_Name
(Specification
(Sub
)));
9165 Check_Inlining
(Defining_Unit_Name
(Specification
(Priv
)));
9166 Current_Node
:= Sub
;
9169 Make_Subprogram_Declaration
(Loc
,
9171 Build_Protected_Sub_Specification
9172 (Priv
, Prot_Typ
, Protected_Mode
));
9174 Insert_After
(Current_Node
, Sub
);
9176 Current_Node
:= Sub
;
9178 if Is_Interrupt_Handler
9179 (Defining_Unit_Name
(Specification
(Priv
)))
9181 if not Restricted_Profile
then
9191 -- Except for the lock-free implementation, append the _Object field
9192 -- with the right type to the component list. We need to compute the
9193 -- number of entries, and in some cases the number of Attach_Handler
9196 if not Lock_Free_Active
then
9199 Num_Attach_Handler
: Int
:= 0;
9200 Protection_Subtype
: Node_Id
;
9201 Entry_Count_Expr
: constant Node_Id
:=
9202 Build_Entry_Count_Expression
9203 (Prot_Typ
, Cdecls
, Loc
);
9206 if Has_Attach_Handler
(Prot_Typ
) then
9207 Ritem
:= First_Rep_Item
(Prot_Typ
);
9208 while Present
(Ritem
) loop
9209 if Nkind
(Ritem
) = N_Pragma
9210 and then Pragma_Name
(Ritem
) = Name_Attach_Handler
9212 Num_Attach_Handler
:= Num_Attach_Handler
+ 1;
9215 Next_Rep_Item
(Ritem
);
9219 -- Determine the proper protection type. There are two special
9220 -- cases: 1) when the protected type has dynamic interrupt
9221 -- handlers, and 2) when it has static handlers and we use a
9222 -- restricted profile.
9224 if Has_Attach_Handler
(Prot_Typ
)
9225 and then not Restricted_Profile
9227 Protection_Subtype
:=
9228 Make_Subtype_Indication
(Loc
,
9231 (RTE
(RE_Static_Interrupt_Protection
), Loc
),
9233 Make_Index_Or_Discriminant_Constraint
(Loc
,
9234 Constraints
=> New_List
(
9236 Make_Integer_Literal
(Loc
, Num_Attach_Handler
))));
9238 elsif Has_Interrupt_Handler
(Prot_Typ
)
9239 and then not Restriction_Active
(No_Dynamic_Attachment
)
9241 Protection_Subtype
:=
9242 Make_Subtype_Indication
(Loc
,
9245 (RTE
(RE_Dynamic_Interrupt_Protection
), Loc
),
9247 Make_Index_Or_Discriminant_Constraint
(Loc
,
9248 Constraints
=> New_List
(Entry_Count_Expr
)));
9251 case Corresponding_Runtime_Package
(Prot_Typ
) is
9252 when System_Tasking_Protected_Objects_Entries
=>
9253 Protection_Subtype
:=
9254 Make_Subtype_Indication
(Loc
,
9257 (RTE
(RE_Protection_Entries
), Loc
),
9259 Make_Index_Or_Discriminant_Constraint
(Loc
,
9260 Constraints
=> New_List
(Entry_Count_Expr
)));
9262 when System_Tasking_Protected_Objects_Single_Entry
=>
9263 Protection_Subtype
:=
9264 New_Occurrence_Of
(RTE
(RE_Protection_Entry
), Loc
);
9266 when System_Tasking_Protected_Objects
=>
9267 Protection_Subtype
:=
9268 New_Occurrence_Of
(RTE
(RE_Protection
), Loc
);
9271 raise Program_Error
;
9276 Make_Component_Declaration
(Loc
,
9277 Defining_Identifier
=>
9278 Make_Defining_Identifier
(Loc
, Name_uObject
),
9279 Component_Definition
=>
9280 Make_Component_Definition
(Loc
,
9281 Aliased_Present
=> True,
9282 Subtype_Indication
=> Protection_Subtype
));
9285 -- Put the _Object component after the private component so that it
9286 -- be finalized early as required by 9.4 (20)
9288 Append_To
(Cdecls
, Object_Comp
);
9291 Insert_After
(Current_Node
, Rec_Decl
);
9292 Current_Node
:= Rec_Decl
;
9294 -- Analyze the record declaration immediately after construction,
9295 -- because the initialization procedure is needed for single object
9296 -- declarations before the next entity is analyzed (the freeze call
9297 -- that generates this initialization procedure is found below).
9299 Analyze
(Rec_Decl
, Suppress
=> All_Checks
);
9301 -- Ada 2005 (AI-345): Construct the primitive entry wrappers before
9302 -- the corresponding record is frozen. If any wrappers are generated,
9303 -- Current_Node is updated accordingly.
9305 if Ada_Version
>= Ada_2005
then
9306 Build_Wrapper_Specs
(Loc
, Prot_Typ
, Current_Node
);
9309 -- Collect pointers to entry bodies and their barriers, to be placed
9310 -- in the Entry_Bodies_Array for the type. For each entry/family we
9311 -- add an expression to the aggregate which is the initial value of
9312 -- this array. The array is declared after all protected subprograms.
9314 if Has_Entries
(Prot_Typ
) then
9315 Entries_Aggr
:= Make_Aggregate
(Loc
, Expressions
=> New_List
);
9317 Entries_Aggr
:= Empty
;
9320 -- Build two new procedure specifications for each protected subprogram;
9321 -- one to call from outside the object and one to call from inside.
9322 -- Build a barrier function and an entry body action procedure
9323 -- specification for each protected entry. Initialize the entry body
9324 -- array. If subprogram is flagged as eliminated, do not generate any
9325 -- internal operations.
9328 Comp
:= First
(Visible_Declarations
(Pdef
));
9329 while Present
(Comp
) loop
9330 if Nkind
(Comp
) = N_Subprogram_Declaration
then
9332 Make_Subprogram_Declaration
(Loc
,
9334 Build_Protected_Sub_Specification
9335 (Comp
, Prot_Typ
, Unprotected_Mode
));
9337 Insert_After
(Current_Node
, Sub
);
9340 Set_Protected_Body_Subprogram
9341 (Defining_Unit_Name
(Specification
(Comp
)),
9342 Defining_Unit_Name
(Specification
(Sub
)));
9343 Check_Inlining
(Defining_Unit_Name
(Specification
(Comp
)));
9345 -- Make the protected version of the subprogram available for
9346 -- expansion of external calls.
9348 Current_Node
:= Sub
;
9351 Make_Subprogram_Declaration
(Loc
,
9353 Build_Protected_Sub_Specification
9354 (Comp
, Prot_Typ
, Protected_Mode
));
9356 Insert_After
(Current_Node
, Sub
);
9359 Current_Node
:= Sub
;
9361 -- Generate an overriding primitive operation specification for
9362 -- this subprogram if the protected type implements an interface.
9364 if Ada_Version
>= Ada_2005
9366 Present
(Interfaces
(Corresponding_Record_Type
(Prot_Typ
)))
9369 Make_Subprogram_Declaration
(Loc
,
9371 Build_Protected_Sub_Specification
9372 (Comp
, Prot_Typ
, Dispatching_Mode
));
9374 Insert_After
(Current_Node
, Sub
);
9377 Current_Node
:= Sub
;
9380 -- If a pragma Interrupt_Handler applies, build and add a call to
9381 -- Register_Interrupt_Handler to the freezing actions of the
9382 -- protected version (Current_Node) of the subprogram:
9384 -- system.interrupts.register_interrupt_handler
9385 -- (prot_procP'address);
9387 if not Restricted_Profile
9388 and then Is_Interrupt_Handler
9389 (Defining_Unit_Name
(Specification
(Comp
)))
9394 elsif Nkind
(Comp
) = N_Entry_Declaration
then
9396 Expand_Entry_Declaration
(Comp
);
9403 -- If there are some private entry declarations, expand it as if they
9404 -- were visible entries.
9406 if Present
(Private_Declarations
(Pdef
)) then
9407 Comp
:= First
(Private_Declarations
(Pdef
));
9408 while Present
(Comp
) loop
9409 if Nkind
(Comp
) = N_Entry_Declaration
then
9410 Expand_Entry_Declaration
(Comp
);
9417 -- Emit declaration for Entry_Bodies_Array, now that the addresses of
9418 -- all protected subprograms have been collected.
9420 if Has_Entries
(Prot_Typ
) then
9422 Make_Defining_Identifier
(Sloc
(Prot_Typ
),
9423 Chars
=> New_External_Name
(Chars
(Prot_Typ
), 'A'));
9425 case Corresponding_Runtime_Package
(Prot_Typ
) is
9426 when System_Tasking_Protected_Objects_Entries
=>
9427 Body_Arr
:= Make_Object_Declaration
(Loc
,
9428 Defining_Identifier
=> Body_Id
,
9429 Aliased_Present
=> True,
9430 Object_Definition
=>
9431 Make_Subtype_Indication
(Loc
,
9432 Subtype_Mark
=> New_Occurrence_Of
(
9433 RTE
(RE_Protected_Entry_Body_Array
), Loc
),
9435 Make_Index_Or_Discriminant_Constraint
(Loc
,
9436 Constraints
=> New_List
(
9438 Make_Integer_Literal
(Loc
, 1),
9439 Make_Integer_Literal
(Loc
, E_Count
))))),
9440 Expression
=> Entries_Aggr
);
9442 when System_Tasking_Protected_Objects_Single_Entry
=>
9443 Body_Arr
:= Make_Object_Declaration
(Loc
,
9444 Defining_Identifier
=> Body_Id
,
9445 Aliased_Present
=> True,
9446 Object_Definition
=> New_Occurrence_Of
9447 (RTE
(RE_Entry_Body
), Loc
),
9448 Expression
=> Remove_Head
(Expressions
(Entries_Aggr
)));
9451 raise Program_Error
;
9454 -- A pointer to this array will be placed in the corresponding record
9455 -- by its initialization procedure so this needs to be analyzed here.
9457 Insert_After
(Current_Node
, Body_Arr
);
9458 Current_Node
:= Body_Arr
;
9461 Set_Entry_Bodies_Array
(Prot_Typ
, Body_Id
);
9463 -- Finally, build the function that maps an entry index into the
9464 -- corresponding body. A pointer to this function is placed in each
9465 -- object of the type. Except for a ravenscar-like profile (no abort,
9466 -- no entry queue, 1 entry)
9468 if Corresponding_Runtime_Package
(Prot_Typ
) =
9469 System_Tasking_Protected_Objects_Entries
9472 Make_Subprogram_Declaration
(Loc
,
9473 Specification
=> Build_Find_Body_Index_Spec
(Prot_Typ
));
9474 Insert_After
(Current_Node
, Sub
);
9478 end Expand_N_Protected_Type_Declaration
;
9480 --------------------------------
9481 -- Expand_N_Requeue_Statement --
9482 --------------------------------
9484 -- A non-dispatching requeue statement is expanded into one of four GNARLI
9485 -- operations, depending on the source and destination (task or protected
9486 -- object). A dispatching requeue statement is expanded into a call to the
9487 -- predefined primitive _Disp_Requeue. In addition, code is generated to
9488 -- jump around the remainder of processing for the original entry and, if
9489 -- the destination is (different) protected object, to attempt to service
9490 -- it. The following illustrates the various cases:
9493 -- (O : System.Address;
9494 -- P : System.Address;
9495 -- E : Protected_Entry_Index)
9497 -- <discriminant renamings>
9498 -- <private object renamings>
9499 -- type poVP is access poV;
9500 -- _object : ptVP := ptVP!(O);
9504 -- <start of statement sequence for entry>
9506 -- -- Requeue from one protected entry body to another protected
9509 -- Requeue_Protected_Entry (
9510 -- _object._object'Access,
9511 -- new._object'Access,
9516 -- <some more of the statement sequence for entry>
9518 -- -- Requeue from an entry body to a task entry
9520 -- Requeue_Protected_To_Task_Entry (
9526 -- <rest of statement sequence for entry>
9527 -- Complete_Entry_Body (_object._object);
9530 -- when all others =>
9531 -- Exceptional_Complete_Entry_Body (
9532 -- _object._object, Get_GNAT_Exception);
9536 -- Requeue of a task entry call to a task entry
9538 -- Accept_Call (E, Ann);
9539 -- <start of statement sequence for accept statement>
9540 -- Requeue_Task_Entry (New._task_id, E, Abort_Present);
9542 -- <rest of statement sequence for accept statement>
9544 -- Complete_Rendezvous;
9547 -- when all others =>
9548 -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
9550 -- Requeue of a task entry call to a protected entry
9552 -- Accept_Call (E, Ann);
9553 -- <start of statement sequence for accept statement>
9554 -- Requeue_Task_To_Protected_Entry (
9555 -- new._object'Access,
9560 -- <rest of statement sequence for accept statement>
9562 -- Complete_Rendezvous;
9565 -- when all others =>
9566 -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
9568 -- Ada 2012 (AI05-0030): Dispatching requeue to an interface primitive
9569 -- marked by pragma Implemented (XXX, By_Entry).
9571 -- The requeue is inside a protected entry:
9574 -- (O : System.Address;
9575 -- P : System.Address;
9576 -- E : Protected_Entry_Index)
9578 -- <discriminant renamings>
9579 -- <private object renamings>
9580 -- type poVP is access poV;
9581 -- _object : ptVP := ptVP!(O);
9585 -- <start of statement sequence for entry>
9588 -- (<interface class-wide object>,
9591 -- Ada.Tags.Get_Offset_Index
9593 -- <interface dispatch table index of target entry>),
9597 -- <rest of statement sequence for entry>
9598 -- Complete_Entry_Body (_object._object);
9601 -- when all others =>
9602 -- Exceptional_Complete_Entry_Body (
9603 -- _object._object, Get_GNAT_Exception);
9607 -- The requeue is inside a task entry:
9609 -- Accept_Call (E, Ann);
9610 -- <start of statement sequence for accept statement>
9612 -- (<interface class-wide object>,
9615 -- Ada.Tags.Get_Offset_Index
9617 -- <interface dispatch table index of target entrt>),
9621 -- <rest of statement sequence for accept statement>
9623 -- Complete_Rendezvous;
9626 -- when all others =>
9627 -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
9629 -- Ada 2012 (AI05-0030): Dispatching requeue to an interface primitive
9630 -- marked by pragma Implemented (XXX, By_Protected_Procedure). The requeue
9631 -- statement is replaced by a dispatching call with actual parameters taken
9632 -- from the inner-most accept statement or entry body.
9634 -- Target.Primitive (Param1, ..., ParamN);
9636 -- Ada 2012 (AI05-0030): Dispatching requeue to an interface primitive
9637 -- marked by pragma Implemented (XXX, By_Any | Optional) or not marked
9641 -- S : constant Offset_Index :=
9642 -- Get_Offset_Index (Tag (Concval), DT_Position (Ename));
9643 -- C : constant Prim_Op_Kind := Get_Prim_Op_Kind (Tag (Concval), S);
9646 -- if C = POK_Protected_Entry
9647 -- or else C = POK_Task_Entry
9649 -- <statements for dispatching requeue>
9651 -- elsif C = POK_Protected_Procedure then
9652 -- <dispatching call equivalent>
9655 -- raise Program_Error;
9659 procedure Expand_N_Requeue_Statement
(N
: Node_Id
) is
9660 Loc
: constant Source_Ptr
:= Sloc
(N
);
9661 Conc_Typ
: Entity_Id
;
9665 Old_Typ
: Entity_Id
;
9667 function Build_Dispatching_Call_Equivalent
return Node_Id
;
9668 -- Ada 2012 (AI05-0030): N denotes a dispatching requeue statement of
9669 -- the form Concval.Ename. It is statically known that Ename is allowed
9670 -- to be implemented by a protected procedure. Create a dispatching call
9671 -- equivalent of Concval.Ename taking the actual parameters from the
9672 -- inner-most accept statement or entry body.
9674 function Build_Dispatching_Requeue
return Node_Id
;
9675 -- Ada 2012 (AI05-0030): N denotes a dispatching requeue statement of
9676 -- the form Concval.Ename. It is statically known that Ename is allowed
9677 -- to be implemented by a protected or a task entry. Create a call to
9678 -- primitive _Disp_Requeue which handles the low-level actions.
9680 function Build_Dispatching_Requeue_To_Any
return Node_Id
;
9681 -- Ada 2012 (AI05-0030): N denotes a dispatching requeue statement of
9682 -- the form Concval.Ename. Ename is either marked by pragma Implemented
9683 -- (XXX, By_Any | Optional) or not marked at all. Create a block which
9684 -- determines at runtime whether Ename denotes an entry or a procedure
9685 -- and perform the appropriate kind of dispatching select.
9687 function Build_Normal_Requeue
return Node_Id
;
9688 -- N denotes a non-dispatching requeue statement to either a task or a
9689 -- protected entry. Build the appropriate runtime call to perform the
9692 function Build_Skip_Statement
(Search
: Node_Id
) return Node_Id
;
9693 -- For a protected entry, create a return statement to skip the rest of
9694 -- the entry body. Otherwise, create a goto statement to skip the rest
9695 -- of a task accept statement. The lookup for the enclosing entry body
9696 -- or accept statement starts from Search.
9698 ---------------------------------------
9699 -- Build_Dispatching_Call_Equivalent --
9700 ---------------------------------------
9702 function Build_Dispatching_Call_Equivalent
return Node_Id
is
9703 Call_Ent
: constant Entity_Id
:= Entity
(Ename
);
9704 Obj
: constant Node_Id
:= Original_Node
(Concval
);
9711 -- Climb the parent chain looking for the inner-most entry body or
9712 -- accept statement.
9715 while Present
(Acc_Ent
)
9716 and then not Nkind_In
(Acc_Ent
, N_Accept_Statement
,
9719 Acc_Ent
:= Parent
(Acc_Ent
);
9722 -- A requeue statement should be housed inside an entry body or an
9723 -- accept statement at some level. If this is not the case, then the
9724 -- tree is malformed.
9726 pragma Assert
(Present
(Acc_Ent
));
9728 -- Recover the list of formal parameters
9730 if Nkind
(Acc_Ent
) = N_Entry_Body
then
9731 Acc_Ent
:= Entry_Body_Formal_Part
(Acc_Ent
);
9734 Formals
:= Parameter_Specifications
(Acc_Ent
);
9736 -- Create the actual parameters for the dispatching call. These are
9737 -- simply copies of the entry body or accept statement formals in the
9738 -- same order as they appear.
9742 if Present
(Formals
) then
9743 Actuals
:= New_List
;
9744 Formal
:= First
(Formals
);
9745 while Present
(Formal
) loop
9747 Make_Identifier
(Loc
, Chars
(Defining_Identifier
(Formal
))));
9753 -- Obj.Call_Ent (Actuals);
9756 Make_Procedure_Call_Statement
(Loc
,
9758 Make_Selected_Component
(Loc
,
9759 Prefix
=> Make_Identifier
(Loc
, Chars
(Obj
)),
9760 Selector_Name
=> Make_Identifier
(Loc
, Chars
(Call_Ent
))),
9762 Parameter_Associations
=> Actuals
);
9763 end Build_Dispatching_Call_Equivalent
;
9765 -------------------------------
9766 -- Build_Dispatching_Requeue --
9767 -------------------------------
9769 function Build_Dispatching_Requeue
return Node_Id
is
9770 Params
: constant List_Id
:= New_List
;
9773 -- Process the "with abort" parameter
9776 New_Occurrence_Of
(Boolean_Literals
(Abort_Present
(N
)), Loc
));
9778 -- Process the entry wrapper's position in the primary dispatch
9779 -- table parameter. Generate:
9781 -- Ada.Tags.Get_Entry_Index
9782 -- (T => To_Tag_Ptr (Obj'Address).all,
9784 -- Ada.Tags.Get_Offset_Index
9785 -- (Ada.Tags.Tag (Concval),
9786 -- <interface dispatch table position of Ename>));
9788 -- Note that Obj'Address is recursively expanded into a call to
9789 -- Base_Address (Obj).
9791 if Tagged_Type_Expansion
then
9793 Make_Function_Call
(Loc
,
9794 Name
=> New_Occurrence_Of
(RTE
(RE_Get_Entry_Index
), Loc
),
9795 Parameter_Associations
=> New_List
(
9797 Make_Explicit_Dereference
(Loc
,
9798 Unchecked_Convert_To
(RTE
(RE_Tag_Ptr
),
9799 Make_Attribute_Reference
(Loc
,
9800 Prefix
=> New_Copy_Tree
(Concval
),
9801 Attribute_Name
=> Name_Address
))),
9803 Make_Function_Call
(Loc
,
9804 Name
=> New_Occurrence_Of
(RTE
(RE_Get_Offset_Index
), Loc
),
9805 Parameter_Associations
=> New_List
(
9806 Unchecked_Convert_To
(RTE
(RE_Tag
), Concval
),
9807 Make_Integer_Literal
(Loc
,
9808 DT_Position
(Entity
(Ename
))))))));
9814 Make_Function_Call
(Loc
,
9815 Name
=> New_Occurrence_Of
(RTE
(RE_Get_Entry_Index
), Loc
),
9816 Parameter_Associations
=> New_List
(
9818 Make_Attribute_Reference
(Loc
,
9820 Attribute_Name
=> Name_Tag
),
9822 Make_Function_Call
(Loc
,
9823 Name
=> New_Occurrence_Of
(RTE
(RE_Get_Offset_Index
), Loc
),
9825 Parameter_Associations
=> New_List
(
9829 Make_Attribute_Reference
(Loc
,
9831 Attribute_Name
=> Name_Tag
),
9835 Make_Attribute_Reference
(Loc
,
9836 Prefix
=> New_Occurrence_Of
(Etype
(Concval
), Loc
),
9837 Attribute_Name
=> Name_Tag
),
9841 Make_Integer_Literal
(Loc
,
9842 DT_Position
(Entity
(Ename
))))))));
9845 -- Specific actuals for protected to XXX requeue
9847 if Is_Protected_Type
(Old_Typ
) then
9849 Make_Attribute_Reference
(Loc
, -- _object'Address
9851 Concurrent_Ref
(New_Occurrence_Of
(Old_Typ
, Loc
)),
9852 Attribute_Name
=> Name_Address
));
9854 Prepend_To
(Params
, -- True
9855 New_Occurrence_Of
(Standard_True
, Loc
));
9857 -- Specific actuals for task to XXX requeue
9860 pragma Assert
(Is_Task_Type
(Old_Typ
));
9862 Prepend_To
(Params
, -- null
9863 New_Occurrence_Of
(RTE
(RE_Null_Address
), Loc
));
9865 Prepend_To
(Params
, -- False
9866 New_Occurrence_Of
(Standard_False
, Loc
));
9869 -- Add the object parameter
9871 Prepend_To
(Params
, New_Copy_Tree
(Concval
));
9874 -- _Disp_Requeue (<Params>);
9876 -- Find entity for Disp_Requeue operation, which belongs to
9877 -- the type and may not be directly visible.
9884 Elmt
:= First_Elmt
(Primitive_Operations
(Etype
(Conc_Typ
)));
9885 while Present
(Elmt
) loop
9887 exit when Chars
(Op
) = Name_uDisp_Requeue
;
9892 Make_Procedure_Call_Statement
(Loc
,
9893 Name
=> New_Occurrence_Of
(Op
, Loc
),
9894 Parameter_Associations
=> Params
);
9896 end Build_Dispatching_Requeue
;
9898 --------------------------------------
9899 -- Build_Dispatching_Requeue_To_Any --
9900 --------------------------------------
9902 function Build_Dispatching_Requeue_To_Any
return Node_Id
is
9903 Call_Ent
: constant Entity_Id
:= Entity
(Ename
);
9904 Obj
: constant Node_Id
:= Original_Node
(Concval
);
9905 Skip
: constant Node_Id
:= Build_Skip_Statement
(N
);
9915 -- Dispatch table slot processing, generate:
9918 S
:= Build_S
(Loc
, Decls
);
9920 -- Call kind processing, generate:
9921 -- C : Ada.Tags.Prim_Op_Kind;
9923 C
:= Build_C
(Loc
, Decls
);
9926 -- S := Ada.Tags.Get_Offset_Index
9927 -- (Ada.Tags.Tag (Obj), DT_Position (Call_Ent));
9929 Append_To
(Stmts
, Build_S_Assignment
(Loc
, S
, Obj
, Call_Ent
));
9932 -- _Disp_Get_Prim_Op_Kind (Obj, S, C);
9935 Make_Procedure_Call_Statement
(Loc
,
9938 Find_Prim_Op
(Etype
(Etype
(Obj
)),
9939 Name_uDisp_Get_Prim_Op_Kind
),
9941 Parameter_Associations
=> New_List
(
9942 New_Copy_Tree
(Obj
),
9943 New_Occurrence_Of
(S
, Loc
),
9944 New_Occurrence_Of
(C
, Loc
))));
9948 -- if C = POK_Protected_Entry
9949 -- or else C = POK_Task_Entry
9952 Make_Implicit_If_Statement
(N
,
9958 New_Occurrence_Of
(C
, Loc
),
9960 New_Occurrence_Of
(RTE
(RE_POK_Protected_Entry
), Loc
)),
9965 New_Occurrence_Of
(C
, Loc
),
9967 New_Occurrence_Of
(RTE
(RE_POK_Task_Entry
), Loc
))),
9969 -- Dispatching requeue equivalent
9971 Then_Statements
=> New_List
(
9972 Build_Dispatching_Requeue
,
9975 -- elsif C = POK_Protected_Procedure then
9977 Elsif_Parts
=> New_List
(
9978 Make_Elsif_Part
(Loc
,
9982 New_Occurrence_Of
(C
, Loc
),
9985 RTE
(RE_POK_Protected_Procedure
), Loc
)),
9987 -- Dispatching call equivalent
9989 Then_Statements
=> New_List
(
9990 Build_Dispatching_Call_Equivalent
))),
9993 -- raise Program_Error;
9996 Else_Statements
=> New_List
(
9997 Make_Raise_Program_Error
(Loc
,
9998 Reason
=> PE_Explicit_Raise
))));
10000 -- Wrap everything into a block
10003 Make_Block_Statement
(Loc
,
10004 Declarations
=> Decls
,
10005 Handled_Statement_Sequence
=>
10006 Make_Handled_Sequence_Of_Statements
(Loc
,
10007 Statements
=> Stmts
));
10008 end Build_Dispatching_Requeue_To_Any
;
10010 --------------------------
10011 -- Build_Normal_Requeue --
10012 --------------------------
10014 function Build_Normal_Requeue
return Node_Id
is
10015 Params
: constant List_Id
:= New_List
;
10020 -- Process the "with abort" parameter
10022 Prepend_To
(Params
,
10023 New_Occurrence_Of
(Boolean_Literals
(Abort_Present
(N
)), Loc
));
10025 -- Add the index expression to the parameters. It is common among all
10028 Prepend_To
(Params
,
10029 Entry_Index_Expression
(Loc
, Entity
(Ename
), Index
, Conc_Typ
));
10031 if Is_Protected_Type
(Old_Typ
) then
10033 Self_Param
: Node_Id
;
10037 Make_Attribute_Reference
(Loc
,
10039 Concurrent_Ref
(New_Occurrence_Of
(Old_Typ
, Loc
)),
10041 Name_Unchecked_Access
);
10043 -- Protected to protected requeue
10045 if Is_Protected_Type
(Conc_Typ
) then
10047 New_Occurrence_Of
(
10048 RTE
(RE_Requeue_Protected_Entry
), Loc
);
10051 Make_Attribute_Reference
(Loc
,
10053 Concurrent_Ref
(Concval
),
10055 Name_Unchecked_Access
);
10057 -- Protected to task requeue
10059 else pragma Assert
(Is_Task_Type
(Conc_Typ
));
10061 New_Occurrence_Of
(
10062 RTE
(RE_Requeue_Protected_To_Task_Entry
), Loc
);
10064 Param
:= Concurrent_Ref
(Concval
);
10067 Prepend_To
(Params
, Param
);
10068 Prepend_To
(Params
, Self_Param
);
10071 else pragma Assert
(Is_Task_Type
(Old_Typ
));
10073 -- Task to protected requeue
10075 if Is_Protected_Type
(Conc_Typ
) then
10077 New_Occurrence_Of
(
10078 RTE
(RE_Requeue_Task_To_Protected_Entry
), Loc
);
10081 Make_Attribute_Reference
(Loc
,
10083 Concurrent_Ref
(Concval
),
10085 Name_Unchecked_Access
);
10087 -- Task to task requeue
10089 else pragma Assert
(Is_Task_Type
(Conc_Typ
));
10091 New_Occurrence_Of
(RTE
(RE_Requeue_Task_Entry
), Loc
);
10093 Param
:= Concurrent_Ref
(Concval
);
10096 Prepend_To
(Params
, Param
);
10100 Make_Procedure_Call_Statement
(Loc
,
10102 Parameter_Associations
=> Params
);
10103 end Build_Normal_Requeue
;
10105 --------------------------
10106 -- Build_Skip_Statement --
10107 --------------------------
10109 function Build_Skip_Statement
(Search
: Node_Id
) return Node_Id
is
10110 Skip_Stmt
: Node_Id
;
10113 -- Build a return statement to skip the rest of the entire body
10115 if Is_Protected_Type
(Old_Typ
) then
10116 Skip_Stmt
:= Make_Simple_Return_Statement
(Loc
);
10118 -- If the requeue is within a task, find the end label of the
10119 -- enclosing accept statement and create a goto statement to it.
10127 -- Climb the parent chain looking for the enclosing accept
10130 Acc
:= Parent
(Search
);
10131 while Present
(Acc
)
10132 and then Nkind
(Acc
) /= N_Accept_Statement
10134 Acc
:= Parent
(Acc
);
10137 -- The last statement is the second label used for completing
10138 -- the rendezvous the usual way. The label we are looking for
10139 -- is right before it.
10142 Prev
(Last
(Statements
(Handled_Statement_Sequence
(Acc
))));
10144 pragma Assert
(Nkind
(Label
) = N_Label
);
10146 -- Generate a goto statement to skip the rest of the accept
10149 Make_Goto_Statement
(Loc
,
10151 New_Occurrence_Of
(Entity
(Identifier
(Label
)), Loc
));
10155 Set_Analyzed
(Skip_Stmt
);
10158 end Build_Skip_Statement
;
10160 -- Start of processing for Expand_N_Requeue_Statement
10163 -- Extract the components of the entry call
10165 Extract_Entry
(N
, Concval
, Ename
, Index
);
10166 Conc_Typ
:= Etype
(Concval
);
10168 -- If the prefix is an access to class-wide type, dereference to get
10169 -- object and entry type.
10171 if Is_Access_Type
(Conc_Typ
) then
10172 Conc_Typ
:= Designated_Type
(Conc_Typ
);
10174 Make_Explicit_Dereference
(Loc
, Relocate_Node
(Concval
)));
10175 Analyze_And_Resolve
(Concval
, Conc_Typ
);
10178 -- Examine the scope stack in order to find nearest enclosing protected
10179 -- or task type. This will constitute our invocation source.
10181 Old_Typ
:= Current_Scope
;
10182 while Present
(Old_Typ
)
10183 and then not Is_Protected_Type
(Old_Typ
)
10184 and then not Is_Task_Type
(Old_Typ
)
10186 Old_Typ
:= Scope
(Old_Typ
);
10189 -- Ada 2012 (AI05-0030): We have a dispatching requeue of the form
10190 -- Concval.Ename where the type of Concval is class-wide concurrent
10193 if Ada_Version
>= Ada_2012
10194 and then Present
(Concval
)
10195 and then Is_Class_Wide_Type
(Conc_Typ
)
10196 and then Is_Concurrent_Interface
(Conc_Typ
)
10199 Has_Impl
: Boolean := False;
10200 Impl_Kind
: Name_Id
:= No_Name
;
10203 -- Check whether the Ename is flagged by pragma Implemented
10205 if Has_Rep_Pragma
(Entity
(Ename
), Name_Implemented
) then
10207 Impl_Kind
:= Implementation_Kind
(Entity
(Ename
));
10210 -- The procedure_or_entry_NAME is guaranteed to be overridden by
10211 -- an entry. Create a call to predefined primitive _Disp_Requeue.
10214 and then Impl_Kind
= Name_By_Entry
10216 Rewrite
(N
, Build_Dispatching_Requeue
);
10218 Insert_After
(N
, Build_Skip_Statement
(N
));
10220 -- The procedure_or_entry_NAME is guaranteed to be overridden by
10221 -- a protected procedure. In this case the requeue is transformed
10222 -- into a dispatching call.
10225 and then Impl_Kind
= Name_By_Protected_Procedure
10227 Rewrite
(N
, Build_Dispatching_Call_Equivalent
);
10230 -- The procedure_or_entry_NAME's implementation kind is either
10231 -- By_Any, Optional, or pragma Implemented was not applied at all.
10232 -- In this case a runtime test determines whether Ename denotes an
10233 -- entry or a protected procedure and performs the appropriate
10237 Rewrite
(N
, Build_Dispatching_Requeue_To_Any
);
10242 -- Processing for regular (non-dispatching) requeues
10245 Rewrite
(N
, Build_Normal_Requeue
);
10247 Insert_After
(N
, Build_Skip_Statement
(N
));
10249 end Expand_N_Requeue_Statement
;
10251 -------------------------------
10252 -- Expand_N_Selective_Accept --
10253 -------------------------------
10255 procedure Expand_N_Selective_Accept
(N
: Node_Id
) is
10256 Loc
: constant Source_Ptr
:= Sloc
(N
);
10257 Alts
: constant List_Id
:= Select_Alternatives
(N
);
10259 -- Note: in the below declarations a lot of new lists are allocated
10260 -- unconditionally which may well not end up being used. That's not
10261 -- a good idea since it wastes space gratuitously ???
10263 Accept_Case
: List_Id
;
10264 Accept_List
: constant List_Id
:= New_List
;
10267 Alt_List
: constant List_Id
:= New_List
;
10268 Alt_Stats
: List_Id
;
10269 Ann
: Entity_Id
:= Empty
;
10271 Check_Guard
: Boolean := True;
10273 Decls
: constant List_Id
:= New_List
;
10274 Stats
: constant List_Id
:= New_List
;
10275 Body_List
: constant List_Id
:= New_List
;
10276 Trailing_List
: constant List_Id
:= New_List
;
10279 Else_Present
: Boolean := False;
10280 Terminate_Alt
: Node_Id
:= Empty
;
10281 Select_Mode
: Node_Id
;
10283 Delay_Case
: List_Id
;
10284 Delay_Count
: Integer := 0;
10285 Delay_Val
: Entity_Id
;
10286 Delay_Index
: Entity_Id
;
10287 Delay_Min
: Entity_Id
;
10288 Delay_Num
: Int
:= 1;
10289 Delay_Alt_List
: List_Id
:= New_List
;
10290 Delay_List
: constant List_Id
:= New_List
;
10294 First_Delay
: Boolean := True;
10295 Guard_Open
: Entity_Id
;
10301 Num_Accept
: Nat
:= 0;
10303 Time_Type
: Entity_Id
;
10304 Select_Call
: Node_Id
;
10306 Qnam
: constant Entity_Id
:=
10307 Make_Defining_Identifier
(Loc
, New_External_Name
('S', 0));
10309 Xnam
: constant Entity_Id
:=
10310 Make_Defining_Identifier
(Loc
, New_External_Name
('J', 1));
10312 -----------------------
10313 -- Local subprograms --
10314 -----------------------
10316 function Accept_Or_Raise
return List_Id
;
10317 -- For the rare case where delay alternatives all have guards, and
10318 -- all of them are closed, it is still possible that there were open
10319 -- accept alternatives with no callers. We must reexamine the
10320 -- Accept_List, and execute a selective wait with no else if some
10321 -- accept is open. If none, we raise program_error.
10323 procedure Add_Accept
(Alt
: Node_Id
);
10324 -- Process a single accept statement in a select alternative. Build
10325 -- procedure for body of accept, and add entry to dispatch table with
10326 -- expression for guard, in preparation for call to run time select.
10328 function Make_And_Declare_Label
(Num
: Int
) return Node_Id
;
10329 -- Manufacture a label using Num as a serial number and declare it.
10330 -- The declaration is appended to Decls. The label marks the trailing
10331 -- statements of an accept or delay alternative.
10333 function Make_Select_Call
(Select_Mode
: Entity_Id
) return Node_Id
;
10334 -- Build call to Selective_Wait runtime routine
10336 procedure Process_Delay_Alternative
(Alt
: Node_Id
; Index
: Int
);
10337 -- Add code to compare value of delay with previous values, and
10338 -- generate case entry for trailing statements.
10340 procedure Process_Accept_Alternative
10344 -- Add code to call corresponding procedure, and branch to
10345 -- trailing statements, if any.
10347 ---------------------
10348 -- Accept_Or_Raise --
10349 ---------------------
10351 function Accept_Or_Raise
return List_Id
is
10354 J
: constant Entity_Id
:= Make_Temporary
(Loc
, 'J');
10357 -- We generate the following:
10359 -- for J in q'range loop
10360 -- if q(J).S /=null_task_entry then
10361 -- selective_wait (simple_mode,...);
10367 -- if no rendez_vous then
10368 -- raise program_error;
10371 -- Note that the code needs to know that the selector name
10372 -- in an Accept_Alternative is named S.
10374 Cond
:= Make_Op_Ne
(Loc
,
10376 Make_Selected_Component
(Loc
,
10378 Make_Indexed_Component
(Loc
,
10379 Prefix
=> New_Occurrence_Of
(Qnam
, Loc
),
10380 Expressions
=> New_List
(New_Occurrence_Of
(J
, Loc
))),
10381 Selector_Name
=> Make_Identifier
(Loc
, Name_S
)),
10383 New_Occurrence_Of
(RTE
(RE_Null_Task_Entry
), Loc
));
10385 Stats
:= New_List
(
10386 Make_Implicit_Loop_Statement
(N
,
10387 Iteration_Scheme
=>
10388 Make_Iteration_Scheme
(Loc
,
10389 Loop_Parameter_Specification
=>
10390 Make_Loop_Parameter_Specification
(Loc
,
10391 Defining_Identifier
=> J
,
10392 Discrete_Subtype_Definition
=>
10393 Make_Attribute_Reference
(Loc
,
10394 Prefix
=> New_Occurrence_Of
(Qnam
, Loc
),
10395 Attribute_Name
=> Name_Range
,
10396 Expressions
=> New_List
(
10397 Make_Integer_Literal
(Loc
, 1))))),
10399 Statements
=> New_List
(
10400 Make_Implicit_If_Statement
(N
,
10402 Then_Statements
=> New_List
(
10404 New_Occurrence_Of
(RTE
(RE_Simple_Mode
), Loc
)),
10405 Make_Exit_Statement
(Loc
))))));
10408 Make_Raise_Program_Error
(Loc
,
10409 Condition
=> Make_Op_Eq
(Loc
,
10410 Left_Opnd
=> New_Occurrence_Of
(Xnam
, Loc
),
10412 New_Occurrence_Of
(RTE
(RE_No_Rendezvous
), Loc
)),
10413 Reason
=> PE_All_Guards_Closed
));
10416 end Accept_Or_Raise
;
10422 procedure Add_Accept
(Alt
: Node_Id
) is
10423 Acc_Stm
: constant Node_Id
:= Accept_Statement
(Alt
);
10424 Ename
: constant Node_Id
:= Entry_Direct_Name
(Acc_Stm
);
10425 Eloc
: constant Source_Ptr
:= Sloc
(Ename
);
10426 Eent
: constant Entity_Id
:= Entity
(Ename
);
10427 Index
: constant Node_Id
:= Entry_Index
(Acc_Stm
);
10428 Null_Body
: Node_Id
;
10429 Proc_Body
: Node_Id
;
10430 PB_Ent
: Entity_Id
;
10436 Ann
:= Node
(Last_Elmt
(Accept_Address
(Eent
)));
10439 if Present
(Condition
(Alt
)) then
10441 Make_If_Expression
(Eloc
, New_List
(
10443 Entry_Index_Expression
(Eloc
, Eent
, Index
, Scope
(Eent
)),
10444 New_Occurrence_Of
(RTE
(RE_Null_Task_Entry
), Eloc
)));
10447 Entry_Index_Expression
10448 (Eloc
, Eent
, Index
, Scope
(Eent
));
10451 if Present
(Handled_Statement_Sequence
(Accept_Statement
(Alt
))) then
10452 Null_Body
:= New_Occurrence_Of
(Standard_False
, Eloc
);
10454 -- Always add call to Abort_Undefer when generating code, since
10455 -- this is what the runtime expects (abort deferred in
10456 -- Selective_Wait). In CodePeer mode this only confuses the
10457 -- analysis with unknown calls, so don't do it.
10459 if not CodePeer_Mode
then
10461 Make_Procedure_Call_Statement
(Eloc
,
10462 Name
=> New_Occurrence_Of
(RTE
(RE_Abort_Undefer
), Eloc
));
10464 (First
(Statements
(Handled_Statement_Sequence
10465 (Accept_Statement
(Alt
)))),
10471 Make_Defining_Identifier
(Eloc
,
10472 New_External_Name
(Chars
(Ename
), 'A', Num_Accept
));
10474 if Comes_From_Source
(Alt
) then
10475 Set_Debug_Info_Needed
(PB_Ent
);
10479 Make_Subprogram_Body
(Eloc
,
10481 Make_Procedure_Specification
(Eloc
,
10482 Defining_Unit_Name
=> PB_Ent
),
10483 Declarations
=> Declarations
(Acc_Stm
),
10484 Handled_Statement_Sequence
=>
10485 Build_Accept_Body
(Accept_Statement
(Alt
)));
10487 -- During the analysis of the body of the accept statement, any
10488 -- zero cost exception handler records were collected in the
10489 -- Accept_Handler_Records field of the N_Accept_Alternative node.
10490 -- This is where we move them to where they belong, namely the
10491 -- newly created procedure.
10493 Set_Handler_Records
(PB_Ent
, Accept_Handler_Records
(Alt
));
10494 Append
(Proc_Body
, Body_List
);
10497 Null_Body
:= New_Occurrence_Of
(Standard_True
, Eloc
);
10499 -- if accept statement has declarations, insert above, given that
10500 -- we are not creating a body for the accept.
10502 if Present
(Declarations
(Acc_Stm
)) then
10503 Insert_Actions
(N
, Declarations
(Acc_Stm
));
10507 Append_To
(Accept_List
,
10508 Make_Aggregate
(Eloc
, Expressions
=> New_List
(Null_Body
, Expr
)));
10510 Num_Accept
:= Num_Accept
+ 1;
10513 ----------------------------
10514 -- Make_And_Declare_Label --
10515 ----------------------------
10517 function Make_And_Declare_Label
(Num
: Int
) return Node_Id
is
10521 Lab_Id
:= Make_Identifier
(Loc
, New_External_Name
('L', Num
));
10523 Make_Label
(Loc
, Lab_Id
);
10526 Make_Implicit_Label_Declaration
(Loc
,
10527 Defining_Identifier
=>
10528 Make_Defining_Identifier
(Loc
, Chars
(Lab_Id
)),
10529 Label_Construct
=> Lab
));
10532 end Make_And_Declare_Label
;
10534 ----------------------
10535 -- Make_Select_Call --
10536 ----------------------
10538 function Make_Select_Call
(Select_Mode
: Entity_Id
) return Node_Id
is
10539 Params
: constant List_Id
:= New_List
;
10543 Make_Attribute_Reference
(Loc
,
10544 Prefix
=> New_Occurrence_Of
(Qnam
, Loc
),
10545 Attribute_Name
=> Name_Unchecked_Access
),
10547 Append
(Select_Mode
, Params
);
10548 Append
(New_Occurrence_Of
(Ann
, Loc
), Params
);
10549 Append
(New_Occurrence_Of
(Xnam
, Loc
), Params
);
10552 Make_Procedure_Call_Statement
(Loc
,
10553 Name
=> New_Occurrence_Of
(RTE
(RE_Selective_Wait
), Loc
),
10554 Parameter_Associations
=> Params
);
10555 end Make_Select_Call
;
10557 --------------------------------
10558 -- Process_Accept_Alternative --
10559 --------------------------------
10561 procedure Process_Accept_Alternative
10566 Astmt
: constant Node_Id
:= Accept_Statement
(Alt
);
10567 Alt_Stats
: List_Id
;
10570 Adjust_Condition
(Condition
(Alt
));
10572 -- Accept with body
10574 if Present
(Handled_Statement_Sequence
(Astmt
)) then
10577 Make_Procedure_Call_Statement
(Sloc
(Proc
),
10580 (Defining_Unit_Name
(Specification
(Proc
)),
10583 -- Accept with no body (followed by trailing statements)
10586 Alt_Stats
:= Empty_List
;
10589 Ensure_Statement_Present
(Sloc
(Astmt
), Alt
);
10591 -- After the call, if any, branch to trailing statements, if any.
10592 -- We create a label for each, as well as the corresponding label
10595 if not Is_Empty_List
(Statements
(Alt
)) then
10596 Lab
:= Make_And_Declare_Label
(Index
);
10597 Append
(Lab
, Trailing_List
);
10598 Append_List
(Statements
(Alt
), Trailing_List
);
10599 Append_To
(Trailing_List
,
10600 Make_Goto_Statement
(Loc
,
10601 Name
=> New_Copy
(Identifier
(End_Lab
))));
10607 Append_To
(Alt_Stats
,
10608 Make_Goto_Statement
(Loc
, Name
=> New_Copy
(Identifier
(Lab
))));
10610 Append_To
(Alt_List
,
10611 Make_Case_Statement_Alternative
(Loc
,
10612 Discrete_Choices
=> New_List
(Make_Integer_Literal
(Loc
, Index
)),
10613 Statements
=> Alt_Stats
));
10614 end Process_Accept_Alternative
;
10616 -------------------------------
10617 -- Process_Delay_Alternative --
10618 -------------------------------
10620 procedure Process_Delay_Alternative
(Alt
: Node_Id
; Index
: Int
) is
10621 Dloc
: constant Source_Ptr
:= Sloc
(Delay_Statement
(Alt
));
10623 Delay_Alt
: List_Id
;
10626 -- Deal with C/Fortran boolean as delay condition
10628 Adjust_Condition
(Condition
(Alt
));
10630 -- Determine the smallest specified delay
10632 -- for each delay alternative generate:
10634 -- if guard-expression then
10635 -- Delay_Val := delay-expression;
10636 -- Guard_Open := True;
10637 -- if Delay_Val < Delay_Min then
10638 -- Delay_Min := Delay_Val;
10639 -- Delay_Index := Index;
10643 -- The enclosing if-statement is omitted if there is no guard
10645 if Delay_Count
= 1 or else First_Delay
then
10646 First_Delay
:= False;
10648 Delay_Alt
:= New_List
(
10649 Make_Assignment_Statement
(Loc
,
10650 Name
=> New_Occurrence_Of
(Delay_Min
, Loc
),
10651 Expression
=> Expression
(Delay_Statement
(Alt
))));
10653 if Delay_Count
> 1 then
10654 Append_To
(Delay_Alt
,
10655 Make_Assignment_Statement
(Loc
,
10656 Name
=> New_Occurrence_Of
(Delay_Index
, Loc
),
10657 Expression
=> Make_Integer_Literal
(Loc
, Index
)));
10661 Delay_Alt
:= New_List
(
10662 Make_Assignment_Statement
(Loc
,
10663 Name
=> New_Occurrence_Of
(Delay_Val
, Loc
),
10664 Expression
=> Expression
(Delay_Statement
(Alt
))));
10666 if Time_Type
= Standard_Duration
then
10669 Left_Opnd
=> New_Occurrence_Of
(Delay_Val
, Loc
),
10670 Right_Opnd
=> New_Occurrence_Of
(Delay_Min
, Loc
));
10673 -- The scope of the time type must define a comparison
10674 -- operator. The scope itself may not be visible, so we
10675 -- construct a node with entity information to insure that
10676 -- semantic analysis can find the proper operator.
10679 Make_Function_Call
(Loc
,
10680 Name
=> Make_Selected_Component
(Loc
,
10682 New_Occurrence_Of
(Scope
(Time_Type
), Loc
),
10684 Make_Operator_Symbol
(Loc
,
10685 Chars
=> Name_Op_Lt
,
10686 Strval
=> No_String
)),
10687 Parameter_Associations
=>
10689 New_Occurrence_Of
(Delay_Val
, Loc
),
10690 New_Occurrence_Of
(Delay_Min
, Loc
)));
10692 Set_Entity
(Prefix
(Name
(Cond
)), Scope
(Time_Type
));
10695 Append_To
(Delay_Alt
,
10696 Make_Implicit_If_Statement
(N
,
10698 Then_Statements
=> New_List
(
10699 Make_Assignment_Statement
(Loc
,
10700 Name
=> New_Occurrence_Of
(Delay_Min
, Loc
),
10701 Expression
=> New_Occurrence_Of
(Delay_Val
, Loc
)),
10703 Make_Assignment_Statement
(Loc
,
10704 Name
=> New_Occurrence_Of
(Delay_Index
, Loc
),
10705 Expression
=> Make_Integer_Literal
(Loc
, Index
)))));
10708 if Check_Guard
then
10709 Append_To
(Delay_Alt
,
10710 Make_Assignment_Statement
(Loc
,
10711 Name
=> New_Occurrence_Of
(Guard_Open
, Loc
),
10712 Expression
=> New_Occurrence_Of
(Standard_True
, Loc
)));
10715 if Present
(Condition
(Alt
)) then
10716 Delay_Alt
:= New_List
(
10717 Make_Implicit_If_Statement
(N
,
10718 Condition
=> Condition
(Alt
),
10719 Then_Statements
=> Delay_Alt
));
10722 Append_List
(Delay_Alt
, Delay_List
);
10724 Ensure_Statement_Present
(Dloc
, Alt
);
10726 -- If the delay alternative has a statement part, add choice to the
10727 -- case statements for delays.
10729 if not Is_Empty_List
(Statements
(Alt
)) then
10731 if Delay_Count
= 1 then
10732 Append_List
(Statements
(Alt
), Delay_Alt_List
);
10735 Append_To
(Delay_Alt_List
,
10736 Make_Case_Statement_Alternative
(Loc
,
10737 Discrete_Choices
=> New_List
(
10738 Make_Integer_Literal
(Loc
, Index
)),
10739 Statements
=> Statements
(Alt
)));
10742 elsif Delay_Count
= 1 then
10744 -- If the single delay has no trailing statements, add a branch
10745 -- to the exit label to the selective wait.
10747 Delay_Alt_List
:= New_List
(
10748 Make_Goto_Statement
(Loc
,
10749 Name
=> New_Copy
(Identifier
(End_Lab
))));
10752 end Process_Delay_Alternative
;
10754 -- Start of processing for Expand_N_Selective_Accept
10757 Process_Statements_For_Controlled_Objects
(N
);
10759 -- First insert some declarations before the select. The first is:
10763 -- This variable holds the parameters passed to the accept body. This
10764 -- declaration has already been inserted by the time we get here by
10765 -- a call to Expand_Accept_Declarations made from the semantics when
10766 -- processing the first accept statement contained in the select. We
10767 -- can find this entity as Accept_Address (E), where E is any of the
10768 -- entries references by contained accept statements.
10770 -- The first step is to scan the list of Selective_Accept_Statements
10771 -- to find this entity, and also count the number of accepts, and
10772 -- determine if terminated, delay or else is present:
10776 Alt
:= First
(Alts
);
10777 while Present
(Alt
) loop
10778 Process_Statements_For_Controlled_Objects
(Alt
);
10780 if Nkind
(Alt
) = N_Accept_Alternative
then
10783 elsif Nkind
(Alt
) = N_Delay_Alternative
then
10784 Delay_Count
:= Delay_Count
+ 1;
10786 -- If the delays are relative delays, the delay expressions have
10787 -- type Standard_Duration. Otherwise they must have some time type
10788 -- recognized by GNAT.
10790 if Nkind
(Delay_Statement
(Alt
)) = N_Delay_Relative_Statement
then
10791 Time_Type
:= Standard_Duration
;
10793 Time_Type
:= Etype
(Expression
(Delay_Statement
(Alt
)));
10795 if Is_RTE
(Base_Type
(Etype
(Time_Type
)), RO_CA_Time
)
10796 or else Is_RTE
(Base_Type
(Etype
(Time_Type
)), RO_RT_Time
)
10801 "& is not a time type (RM 9.6(6))",
10802 Expression
(Delay_Statement
(Alt
)), Time_Type
);
10803 Time_Type
:= Standard_Duration
;
10804 Set_Etype
(Expression
(Delay_Statement
(Alt
)), Any_Type
);
10808 if No
(Condition
(Alt
)) then
10810 -- This guard will always be open
10812 Check_Guard
:= False;
10815 elsif Nkind
(Alt
) = N_Terminate_Alternative
then
10816 Adjust_Condition
(Condition
(Alt
));
10817 Terminate_Alt
:= Alt
;
10820 Num_Alts
:= Num_Alts
+ 1;
10824 Else_Present
:= Present
(Else_Statements
(N
));
10826 -- At the same time (see procedure Add_Accept) we build the accept list:
10828 -- Qnn : Accept_List (1 .. num-select) := (
10829 -- (null-body, entry-index),
10830 -- (null-body, entry-index),
10832 -- (null_body, entry-index));
10834 -- In the above declaration, null-body is True if the corresponding
10835 -- accept has no body, and false otherwise. The entry is either the
10836 -- entry index expression if there is no guard, or if a guard is
10837 -- present, then an if expression of the form:
10839 -- (if guard then entry-index else Null_Task_Entry)
10841 -- If a guard is statically known to be false, the entry can simply
10842 -- be omitted from the accept list.
10845 Make_Object_Declaration
(Loc
,
10846 Defining_Identifier
=> Qnam
,
10847 Object_Definition
=> New_Occurrence_Of
(RTE
(RE_Accept_List
), Loc
),
10848 Aliased_Present
=> True,
10850 Make_Qualified_Expression
(Loc
,
10852 New_Occurrence_Of
(RTE
(RE_Accept_List
), Loc
),
10854 Make_Aggregate
(Loc
, Expressions
=> Accept_List
))));
10856 -- Then we declare the variable that holds the index for the accept
10857 -- that will be selected for service:
10859 -- Xnn : Select_Index;
10862 Make_Object_Declaration
(Loc
,
10863 Defining_Identifier
=> Xnam
,
10864 Object_Definition
=>
10865 New_Occurrence_Of
(RTE
(RE_Select_Index
), Loc
),
10867 New_Occurrence_Of
(RTE
(RE_No_Rendezvous
), Loc
)));
10869 -- After this follow procedure declarations for each accept body
10871 -- procedure Pnn is
10876 -- where the ... are statements from the corresponding procedure body.
10877 -- No parameters are involved, since the parameters are passed via Ann
10878 -- and the parameter references have already been expanded to be direct
10879 -- references to Ann (see Exp_Ch2.Expand_Entry_Parameter). Furthermore,
10880 -- any embedded tasking statements (which would normally be illegal in
10881 -- procedures), have been converted to calls to the tasking runtime so
10882 -- there is no problem in putting them into procedures.
10884 -- The original accept statement has been expanded into a block in
10885 -- the same fashion as for simple accepts (see Build_Accept_Body).
10887 -- Note: we don't really need to build these procedures for the case
10888 -- where no delay statement is present, but it is just as easy to
10889 -- build them unconditionally, and not significantly inefficient,
10890 -- since if they are short they will be inlined anyway.
10892 -- The procedure declarations have been assembled in Body_List
10894 -- If delays are present, we must compute the required delay.
10895 -- We first generate the declarations:
10897 -- Delay_Index : Boolean := 0;
10898 -- Delay_Min : Some_Time_Type.Time;
10899 -- Delay_Val : Some_Time_Type.Time;
10901 -- Delay_Index will be set to the index of the minimum delay, i.e. the
10902 -- active delay that is actually chosen as the basis for the possible
10903 -- delay if an immediate rendez-vous is not possible.
10905 -- In the most common case there is a single delay statement, and this
10906 -- is handled specially.
10908 if Delay_Count
> 0 then
10910 -- Generate the required declarations
10913 Make_Defining_Identifier
(Loc
, New_External_Name
('D', 1));
10915 Make_Defining_Identifier
(Loc
, New_External_Name
('D', 2));
10917 Make_Defining_Identifier
(Loc
, New_External_Name
('D', 3));
10920 Make_Object_Declaration
(Loc
,
10921 Defining_Identifier
=> Delay_Val
,
10922 Object_Definition
=> New_Occurrence_Of
(Time_Type
, Loc
)));
10925 Make_Object_Declaration
(Loc
,
10926 Defining_Identifier
=> Delay_Index
,
10927 Object_Definition
=> New_Occurrence_Of
(Standard_Integer
, Loc
),
10928 Expression
=> Make_Integer_Literal
(Loc
, 0)));
10931 Make_Object_Declaration
(Loc
,
10932 Defining_Identifier
=> Delay_Min
,
10933 Object_Definition
=> New_Occurrence_Of
(Time_Type
, Loc
),
10935 Unchecked_Convert_To
(Time_Type
,
10936 Make_Attribute_Reference
(Loc
,
10938 New_Occurrence_Of
(Underlying_Type
(Time_Type
), Loc
),
10939 Attribute_Name
=> Name_Last
))));
10941 -- Create Duration and Delay_Mode objects used for passing a delay
10944 D
:= Make_Temporary
(Loc
, 'D');
10945 M
:= Make_Temporary
(Loc
, 'M');
10951 -- Note that these values are defined in s-osprim.ads and must
10952 -- be kept in sync:
10954 -- Relative : constant := 0;
10955 -- Absolute_Calendar : constant := 1;
10956 -- Absolute_RT : constant := 2;
10958 if Time_Type
= Standard_Duration
then
10959 Discr
:= Make_Integer_Literal
(Loc
, 0);
10961 elsif Is_RTE
(Base_Type
(Etype
(Time_Type
)), RO_CA_Time
) then
10962 Discr
:= Make_Integer_Literal
(Loc
, 1);
10966 (Is_RTE
(Base_Type
(Etype
(Time_Type
)), RO_RT_Time
));
10967 Discr
:= Make_Integer_Literal
(Loc
, 2);
10971 Make_Object_Declaration
(Loc
,
10972 Defining_Identifier
=> D
,
10973 Object_Definition
=>
10974 New_Occurrence_Of
(Standard_Duration
, Loc
)));
10977 Make_Object_Declaration
(Loc
,
10978 Defining_Identifier
=> M
,
10979 Object_Definition
=>
10980 New_Occurrence_Of
(Standard_Integer
, Loc
),
10981 Expression
=> Discr
));
10984 if Check_Guard
then
10986 Make_Defining_Identifier
(Loc
, New_External_Name
('G', 1));
10989 Make_Object_Declaration
(Loc
,
10990 Defining_Identifier
=> Guard_Open
,
10991 Object_Definition
=>
10992 New_Occurrence_Of
(Standard_Boolean
, Loc
),
10994 New_Occurrence_Of
(Standard_False
, Loc
)));
10997 -- Delay_Count is zero, don't need M and D set (suppress warning)
11004 if Present
(Terminate_Alt
) then
11006 -- If the terminate alternative guard is False, use
11007 -- Simple_Mode; otherwise use Terminate_Mode.
11009 if Present
(Condition
(Terminate_Alt
)) then
11010 Select_Mode
:= Make_If_Expression
(Loc
,
11011 New_List
(Condition
(Terminate_Alt
),
11012 New_Occurrence_Of
(RTE
(RE_Terminate_Mode
), Loc
),
11013 New_Occurrence_Of
(RTE
(RE_Simple_Mode
), Loc
)));
11015 Select_Mode
:= New_Occurrence_Of
(RTE
(RE_Terminate_Mode
), Loc
);
11018 elsif Else_Present
or Delay_Count
> 0 then
11019 Select_Mode
:= New_Occurrence_Of
(RTE
(RE_Else_Mode
), Loc
);
11022 Select_Mode
:= New_Occurrence_Of
(RTE
(RE_Simple_Mode
), Loc
);
11025 Select_Call
:= Make_Select_Call
(Select_Mode
);
11026 Append
(Select_Call
, Stats
);
11028 -- Now generate code to act on the result. There is an entry
11029 -- in this case for each accept statement with a non-null body,
11030 -- followed by a branch to the statements that follow the Accept.
11031 -- In the absence of delay alternatives, we generate:
11034 -- when No_Rendezvous => -- omitted if simple mode
11049 -- Lab0: Else_Statements;
11052 -- Lab1: Trailing_Statements1;
11055 -- Lab2: Trailing_Statements2;
11060 -- Generate label for common exit
11062 End_Lab
:= Make_And_Declare_Label
(Num_Alts
+ 1);
11064 -- First entry is the default case, when no rendezvous is possible
11066 Choices
:= New_List
(New_Occurrence_Of
(RTE
(RE_No_Rendezvous
), Loc
));
11068 if Else_Present
then
11070 -- If no rendezvous is possible, the else part is executed
11072 Lab
:= Make_And_Declare_Label
(0);
11073 Alt_Stats
:= New_List
(
11074 Make_Goto_Statement
(Loc
,
11075 Name
=> New_Copy
(Identifier
(Lab
))));
11077 Append
(Lab
, Trailing_List
);
11078 Append_List
(Else_Statements
(N
), Trailing_List
);
11079 Append_To
(Trailing_List
,
11080 Make_Goto_Statement
(Loc
,
11081 Name
=> New_Copy
(Identifier
(End_Lab
))));
11083 Alt_Stats
:= New_List
(
11084 Make_Goto_Statement
(Loc
,
11085 Name
=> New_Copy
(Identifier
(End_Lab
))));
11088 Append_To
(Alt_List
,
11089 Make_Case_Statement_Alternative
(Loc
,
11090 Discrete_Choices
=> Choices
,
11091 Statements
=> Alt_Stats
));
11093 -- We make use of the fact that Accept_Index is an integer type, and
11094 -- generate successive literals for entries for each accept. Only those
11095 -- for which there is a body or trailing statements get a case entry.
11097 Alt
:= First
(Select_Alternatives
(N
));
11098 Proc
:= First
(Body_List
);
11099 while Present
(Alt
) loop
11101 if Nkind
(Alt
) = N_Accept_Alternative
then
11102 Process_Accept_Alternative
(Alt
, Index
, Proc
);
11103 Index
:= Index
+ 1;
11106 (Handled_Statement_Sequence
(Accept_Statement
(Alt
)))
11111 elsif Nkind
(Alt
) = N_Delay_Alternative
then
11112 Process_Delay_Alternative
(Alt
, Delay_Num
);
11113 Delay_Num
:= Delay_Num
+ 1;
11119 -- An others choice is always added to the main case, as well
11120 -- as the delay case (to satisfy the compiler).
11122 Append_To
(Alt_List
,
11123 Make_Case_Statement_Alternative
(Loc
,
11124 Discrete_Choices
=>
11125 New_List
(Make_Others_Choice
(Loc
)),
11127 New_List
(Make_Goto_Statement
(Loc
,
11128 Name
=> New_Copy
(Identifier
(End_Lab
))))));
11130 Accept_Case
:= New_List
(
11131 Make_Case_Statement
(Loc
,
11132 Expression
=> New_Occurrence_Of
(Xnam
, Loc
),
11133 Alternatives
=> Alt_List
));
11135 Append_List
(Trailing_List
, Accept_Case
);
11136 Append_List
(Body_List
, Decls
);
11138 -- Construct case statement for trailing statements of delay
11139 -- alternatives, if there are several of them.
11141 if Delay_Count
> 1 then
11142 Append_To
(Delay_Alt_List
,
11143 Make_Case_Statement_Alternative
(Loc
,
11144 Discrete_Choices
=>
11145 New_List
(Make_Others_Choice
(Loc
)),
11147 New_List
(Make_Null_Statement
(Loc
))));
11149 Delay_Case
:= New_List
(
11150 Make_Case_Statement
(Loc
,
11151 Expression
=> New_Occurrence_Of
(Delay_Index
, Loc
),
11152 Alternatives
=> Delay_Alt_List
));
11154 Delay_Case
:= Delay_Alt_List
;
11157 -- If there are no delay alternatives, we append the case statement
11158 -- to the statement list.
11160 if Delay_Count
= 0 then
11161 Append_List
(Accept_Case
, Stats
);
11163 -- Delay alternatives present
11166 -- If delay alternatives are present we generate:
11168 -- find minimum delay.
11169 -- DX := minimum delay;
11170 -- M := <delay mode>;
11171 -- Timed_Selective_Wait (Q'Unchecked_Access, Delay_Mode, P,
11174 -- if X = No_Rendezvous then
11175 -- case statement for delay statements.
11177 -- case statement for accept alternatives.
11188 -- The type of the delay expression is known to be legal
11190 if Time_Type
= Standard_Duration
then
11191 Conv
:= New_Occurrence_Of
(Delay_Min
, Loc
);
11193 elsif Is_RTE
(Base_Type
(Etype
(Time_Type
)), RO_CA_Time
) then
11194 Conv
:= Make_Function_Call
(Loc
,
11195 New_Occurrence_Of
(RTE
(RO_CA_To_Duration
), Loc
),
11196 New_List
(New_Occurrence_Of
(Delay_Min
, Loc
)));
11200 (Is_RTE
(Base_Type
(Etype
(Time_Type
)), RO_RT_Time
));
11202 Conv
:= Make_Function_Call
(Loc
,
11203 New_Occurrence_Of
(RTE
(RO_RT_To_Duration
), Loc
),
11204 New_List
(New_Occurrence_Of
(Delay_Min
, Loc
)));
11207 Stmt
:= Make_Assignment_Statement
(Loc
,
11208 Name
=> New_Occurrence_Of
(D
, Loc
),
11209 Expression
=> Conv
);
11211 -- Change the value for Accept_Modes. (Else_Mode -> Delay_Mode)
11213 Parms
:= Parameter_Associations
(Select_Call
);
11214 Parm
:= First
(Parms
);
11216 while Present
(Parm
) and then Parm
/= Select_Mode
loop
11220 pragma Assert
(Present
(Parm
));
11221 Rewrite
(Parm
, New_Occurrence_Of
(RTE
(RE_Delay_Mode
), Loc
));
11224 -- Prepare two new parameters of Duration and Delay_Mode type
11225 -- which represent the value and the mode of the minimum delay.
11228 Insert_After
(Parm
, New_Occurrence_Of
(M
, Loc
));
11229 Insert_After
(Parm
, New_Occurrence_Of
(D
, Loc
));
11231 -- Create a call to RTS
11233 Rewrite
(Select_Call
,
11234 Make_Procedure_Call_Statement
(Loc
,
11235 Name
=> New_Occurrence_Of
(RTE
(RE_Timed_Selective_Wait
), Loc
),
11236 Parameter_Associations
=> Parms
));
11238 -- This new call should follow the calculation of the minimum
11241 Insert_List_Before
(Select_Call
, Delay_List
);
11243 if Check_Guard
then
11245 Make_Implicit_If_Statement
(N
,
11246 Condition
=> New_Occurrence_Of
(Guard_Open
, Loc
),
11247 Then_Statements
=> New_List
(
11248 New_Copy_Tree
(Stmt
),
11249 New_Copy_Tree
(Select_Call
)),
11250 Else_Statements
=> Accept_Or_Raise
);
11251 Rewrite
(Select_Call
, Stmt
);
11253 Insert_Before
(Select_Call
, Stmt
);
11257 Make_Implicit_If_Statement
(N
,
11258 Condition
=> Make_Op_Eq
(Loc
,
11259 Left_Opnd
=> New_Occurrence_Of
(Xnam
, Loc
),
11261 New_Occurrence_Of
(RTE
(RE_No_Rendezvous
), Loc
)),
11263 Then_Statements
=> Delay_Case
,
11264 Else_Statements
=> Accept_Case
);
11266 Append
(Cases
, Stats
);
11269 Append
(End_Lab
, Stats
);
11271 -- Replace accept statement with appropriate block
11274 Make_Block_Statement
(Loc
,
11275 Declarations
=> Decls
,
11276 Handled_Statement_Sequence
=>
11277 Make_Handled_Sequence_Of_Statements
(Loc
, Statements
=> Stats
)));
11280 -- Note: have to worry more about abort deferral in above code ???
11282 -- Final step is to unstack the Accept_Address entries for all accept
11283 -- statements appearing in accept alternatives in the select statement
11285 Alt
:= First
(Alts
);
11286 while Present
(Alt
) loop
11287 if Nkind
(Alt
) = N_Accept_Alternative
then
11288 Remove_Last_Elmt
(Accept_Address
11289 (Entity
(Entry_Direct_Name
(Accept_Statement
(Alt
)))));
11294 end Expand_N_Selective_Accept
;
11296 --------------------------------------
11297 -- Expand_N_Single_Task_Declaration --
11298 --------------------------------------
11300 -- Single task declarations should never be present after semantic
11301 -- analysis, since we expect them to be replaced by a declaration of an
11302 -- anonymous task type, followed by a declaration of the task object. We
11303 -- include this routine to make sure that is happening.
11305 procedure Expand_N_Single_Task_Declaration
(N
: Node_Id
) is
11307 raise Program_Error
;
11308 end Expand_N_Single_Task_Declaration
;
11310 ------------------------
11311 -- Expand_N_Task_Body --
11312 ------------------------
11314 -- Given a task body
11316 -- task body tname is
11322 -- This expansion routine converts it into a procedure and sets the
11323 -- elaboration flag for the procedure to true, to represent the fact
11324 -- that the task body is now elaborated:
11326 -- procedure tnameB (_Task : access tnameV) is
11327 -- discriminal : dtype renames _Task.discriminant;
11329 -- procedure _clean is
11331 -- Abort_Defer.all;
11333 -- Abort_Undefer.all;
11338 -- Abort_Undefer.all;
11340 -- System.Task_Stages.Complete_Activation;
11348 -- In addition, if the task body is an activator, then a call to activate
11349 -- tasks is added at the start of the statements, before the call to
11350 -- Complete_Activation, and if in addition the task is a master then it
11351 -- must be established as a master. These calls are inserted and analyzed
11352 -- in Expand_Cleanup_Actions, when the Handled_Sequence_Of_Statements is
11355 -- There is one discriminal declaration line generated for each
11356 -- discriminant that is present to provide an easy reference point for
11357 -- discriminant references inside the body (see Exp_Ch2.Expand_Name).
11359 -- Note on relationship to GNARLI definition. In the GNARLI definition,
11360 -- task body procedures have a profile (Arg : System.Address). That is
11361 -- needed because GNARLI has to use the same access-to-subprogram type
11362 -- for all task types. We depend here on knowing that in GNAT, passing
11363 -- an address argument by value is identical to passing a record value
11364 -- by access (in either case a single pointer is passed), so even though
11365 -- this procedure has the wrong profile. In fact it's all OK, since the
11366 -- callings sequence is identical.
11368 procedure Expand_N_Task_Body
(N
: Node_Id
) is
11369 Loc
: constant Source_Ptr
:= Sloc
(N
);
11370 Ttyp
: constant Entity_Id
:= Corresponding_Spec
(N
);
11374 Insert_Nod
: Node_Id
;
11375 -- Used to determine the proper location of wrapper body insertions
11378 -- Add renaming declarations for discriminals and a declaration for the
11379 -- entry family index (if applicable).
11381 Install_Private_Data_Declarations
11382 (Loc
, Task_Body_Procedure
(Ttyp
), Ttyp
, N
, Declarations
(N
));
11384 -- Add a call to Abort_Undefer at the very beginning of the task
11385 -- body since this body is called with abort still deferred.
11387 if Abort_Allowed
then
11388 Call
:= Build_Runtime_Call
(Loc
, RE_Abort_Undefer
);
11390 (First
(Statements
(Handled_Statement_Sequence
(N
))), Call
);
11394 -- The statement part has already been protected with an at_end and
11395 -- cleanup actions. The call to Complete_Activation must be placed
11396 -- at the head of the sequence of statements of that block. The
11397 -- declarations have been merged in this sequence of statements but
11398 -- the first real statement is accessible from the First_Real_Statement
11399 -- field (which was set for exactly this purpose).
11401 if Restricted_Profile
then
11402 Call
:= Build_Runtime_Call
(Loc
, RE_Complete_Restricted_Activation
);
11404 Call
:= Build_Runtime_Call
(Loc
, RE_Complete_Activation
);
11408 (First_Real_Statement
(Handled_Statement_Sequence
(N
)), Call
);
11412 Make_Subprogram_Body
(Loc
,
11413 Specification
=> Build_Task_Proc_Specification
(Ttyp
),
11414 Declarations
=> Declarations
(N
),
11415 Handled_Statement_Sequence
=> Handled_Statement_Sequence
(N
));
11417 -- If the task contains generic instantiations, cleanup actions are
11418 -- delayed until after instantiation. Transfer the activation chain to
11419 -- the subprogram, to insure that the activation call is properly
11420 -- generated. It the task body contains inner tasks, indicate that the
11421 -- subprogram is a task master.
11423 if Delay_Cleanups
(Ttyp
) then
11424 Set_Activation_Chain_Entity
(New_N
, Activation_Chain_Entity
(N
));
11425 Set_Is_Task_Master
(New_N
, Is_Task_Master
(N
));
11428 Rewrite
(N
, New_N
);
11431 -- Set elaboration flag immediately after task body. If the body is a
11432 -- subunit, the flag is set in the declarative part containing the stub.
11434 if Nkind
(Parent
(N
)) /= N_Subunit
then
11436 Make_Assignment_Statement
(Loc
,
11438 Make_Identifier
(Loc
, New_External_Name
(Chars
(Ttyp
), 'E')),
11439 Expression
=> New_Occurrence_Of
(Standard_True
, Loc
)));
11442 -- Ada 2005 (AI-345): Construct the primitive entry wrapper bodies after
11443 -- the task body. At this point all wrapper specs have been created,
11444 -- frozen and included in the dispatch table for the task type.
11446 if Ada_Version
>= Ada_2005
then
11447 if Nkind
(Parent
(N
)) = N_Subunit
then
11448 Insert_Nod
:= Corresponding_Stub
(Parent
(N
));
11453 Build_Wrapper_Bodies
(Loc
, Ttyp
, Insert_Nod
);
11455 end Expand_N_Task_Body
;
11457 ------------------------------------
11458 -- Expand_N_Task_Type_Declaration --
11459 ------------------------------------
11461 -- We have several things to do. First we must create a Boolean flag used
11462 -- to mark if the body is elaborated yet. This variable gets set to True
11463 -- when the body of the task is elaborated (we can't rely on the normal
11464 -- ABE mechanism for the task body, since we need to pass an access to
11465 -- this elaboration boolean to the runtime routines).
11467 -- taskE : aliased Boolean := False;
11469 -- Next a variable is declared to hold the task stack size (either the
11470 -- default : Unspecified_Size, or a value that is set by a pragma
11471 -- Storage_Size). If the value of the pragma Storage_Size is static, then
11472 -- the variable is initialized with this value:
11474 -- taskZ : Size_Type := Unspecified_Size;
11476 -- taskZ : Size_Type := Size_Type (size_expression);
11478 -- Note: No variable is needed to hold the task relative deadline since
11479 -- its value would never be static because the parameter is of a private
11480 -- type (Ada.Real_Time.Time_Span).
11482 -- Next we create a corresponding record type declaration used to represent
11483 -- values of this task. The general form of this type declaration is
11485 -- type taskV (discriminants) is record
11486 -- _Task_Id : Task_Id;
11487 -- entry_family : array (bounds) of Void;
11488 -- _Priority : Integer := priority_expression;
11489 -- _Size : Size_Type := size_expression;
11490 -- _Task_Info : Task_Info_Type := task_info_expression;
11491 -- _CPU : Integer := cpu_range_expression;
11492 -- _Relative_Deadline : Time_Span := time_span_expression;
11493 -- _Domain : Dispatching_Domain := dd_expression;
11496 -- The discriminants are present only if the corresponding task type has
11497 -- discriminants, and they exactly mirror the task type discriminants.
11499 -- The Id field is always present. It contains the Task_Id value, as set by
11500 -- the call to Create_Task. Note that although the task is limited, the
11501 -- task value record type is not limited, so there is no problem in passing
11502 -- this field as an out parameter to Create_Task.
11504 -- One entry_family component is present for each entry family in the task
11505 -- definition. The bounds correspond to the bounds of the entry family
11506 -- (which may depend on discriminants). The element type is void, since we
11507 -- only need the bounds information for determining the entry index. Note
11508 -- that the use of an anonymous array would normally be illegal in this
11509 -- context, but this is a parser check, and the semantics is quite prepared
11510 -- to handle such a case.
11512 -- The _Size field is present only if a Storage_Size pragma appears in the
11513 -- task definition. The expression captures the argument that was present
11514 -- in the pragma, and is used to override the task stack size otherwise
11515 -- associated with the task type.
11517 -- The _Priority field is present only if the task entity has a Priority or
11518 -- Interrupt_Priority rep item (pragma, aspect specification or attribute
11519 -- definition clause). It will be filled at the freeze point, when the
11520 -- record init proc is built, to capture the expression of the rep item
11521 -- (see Build_Record_Init_Proc in Exp_Ch3). Note that it cannot be filled
11522 -- here since aspect evaluations are delayed till the freeze point.
11524 -- The _Task_Info field is present only if a Task_Info pragma appears in
11525 -- the task definition. The expression captures the argument that was
11526 -- present in the pragma, and is used to provide the Task_Image parameter
11527 -- to the call to Create_Task.
11529 -- The _CPU field is present only if the task entity has a CPU rep item
11530 -- (pragma, aspect specification or attribute definition clause). It will
11531 -- be filled at the freeze point, when the record init proc is built, to
11532 -- capture the expression of the rep item (see Build_Record_Init_Proc in
11533 -- Exp_Ch3). Note that it cannot be filled here since aspect evaluations
11534 -- are delayed till the freeze point.
11536 -- The _Relative_Deadline field is present only if a Relative_Deadline
11537 -- pragma appears in the task definition. The expression captures the
11538 -- argument that was present in the pragma, and is used to provide the
11539 -- Relative_Deadline parameter to the call to Create_Task.
11541 -- The _Domain field is present only if the task entity has a
11542 -- Dispatching_Domain rep item (pragma, aspect specification or attribute
11543 -- definition clause). It will be filled at the freeze point, when the
11544 -- record init proc is built, to capture the expression of the rep item
11545 -- (see Build_Record_Init_Proc in Exp_Ch3). Note that it cannot be filled
11546 -- here since aspect evaluations are delayed till the freeze point.
11548 -- When a task is declared, an instance of the task value record is
11549 -- created. The elaboration of this declaration creates the correct bounds
11550 -- for the entry families, and also evaluates the size, priority, and
11551 -- task_Info expressions if needed. The initialization routine for the task
11552 -- type itself then calls Create_Task with appropriate parameters to
11553 -- initialize the value of the Task_Id field.
11555 -- Note: the address of this record is passed as the "Discriminants"
11556 -- parameter for Create_Task. Since Create_Task merely passes this onto the
11557 -- body procedure, it does not matter that it does not quite match the
11558 -- GNARLI model of what is being passed (the record contains more than just
11559 -- the discriminants, but the discriminants can be found from the record
11562 -- The Entity_Id for this created record type is placed in the
11563 -- Corresponding_Record_Type field of the associated task type entity.
11565 -- Next we create a procedure specification for the task body procedure:
11567 -- procedure taskB (_Task : access taskV);
11569 -- Note that this must come after the record type declaration, since
11570 -- the spec refers to this type. It turns out that the initialization
11571 -- procedure for the value type references the task body spec, but that's
11572 -- fine, since it won't be generated till the freeze point for the type,
11573 -- which is certainly after the task body spec declaration.
11575 -- Finally, we set the task index value field of the entry attribute in
11576 -- the case of a simple entry.
11578 procedure Expand_N_Task_Type_Declaration
(N
: Node_Id
) is
11579 Loc
: constant Source_Ptr
:= Sloc
(N
);
11580 TaskId
: constant Entity_Id
:= Defining_Identifier
(N
);
11581 Tasktyp
: constant Entity_Id
:= Etype
(Defining_Identifier
(N
));
11582 Tasknm
: constant Name_Id
:= Chars
(Tasktyp
);
11583 Taskdef
: constant Node_Id
:= Task_Definition
(N
);
11585 Body_Decl
: Node_Id
;
11587 Decl_Stack
: Node_Id
;
11588 Elab_Decl
: Node_Id
;
11589 Ent_Stack
: Entity_Id
;
11590 Proc_Spec
: Node_Id
;
11591 Rec_Decl
: Node_Id
;
11592 Rec_Ent
: Entity_Id
;
11593 Size_Decl
: Entity_Id
;
11594 Task_Size
: Node_Id
;
11596 function Get_Relative_Deadline_Pragma
(T
: Node_Id
) return Node_Id
;
11597 -- Searches the task definition T for the first occurrence of the pragma
11598 -- Relative Deadline. The caller has ensured that the pragma is present
11599 -- in the task definition. Note that this routine cannot be implemented
11600 -- with the Rep Item chain mechanism since Relative_Deadline pragmas are
11601 -- not chained because their expansion into a procedure call statement
11602 -- would cause a break in the chain.
11604 ----------------------------------
11605 -- Get_Relative_Deadline_Pragma --
11606 ----------------------------------
11608 function Get_Relative_Deadline_Pragma
(T
: Node_Id
) return Node_Id
is
11612 N
:= First
(Visible_Declarations
(T
));
11613 while Present
(N
) loop
11614 if Nkind
(N
) = N_Pragma
11615 and then Pragma_Name
(N
) = Name_Relative_Deadline
11623 N
:= First
(Private_Declarations
(T
));
11624 while Present
(N
) loop
11625 if Nkind
(N
) = N_Pragma
11626 and then Pragma_Name
(N
) = Name_Relative_Deadline
11634 raise Program_Error
;
11635 end Get_Relative_Deadline_Pragma
;
11637 -- Start of processing for Expand_N_Task_Type_Declaration
11640 -- If already expanded, nothing to do
11642 if Present
(Corresponding_Record_Type
(Tasktyp
)) then
11646 -- Here we will do the expansion
11648 Rec_Decl
:= Build_Corresponding_Record
(N
, Tasktyp
, Loc
);
11650 Rec_Ent
:= Defining_Identifier
(Rec_Decl
);
11651 Cdecls
:= Component_Items
(Component_List
11652 (Type_Definition
(Rec_Decl
)));
11654 Qualify_Entity_Names
(N
);
11656 -- First create the elaboration variable
11659 Make_Object_Declaration
(Loc
,
11660 Defining_Identifier
=>
11661 Make_Defining_Identifier
(Sloc
(Tasktyp
),
11662 Chars
=> New_External_Name
(Tasknm
, 'E')),
11663 Aliased_Present
=> True,
11664 Object_Definition
=> New_Occurrence_Of
(Standard_Boolean
, Loc
),
11665 Expression
=> New_Occurrence_Of
(Standard_False
, Loc
));
11667 Insert_After
(N
, Elab_Decl
);
11669 -- Next create the declaration of the size variable (tasknmZ)
11671 Set_Storage_Size_Variable
(Tasktyp
,
11672 Make_Defining_Identifier
(Sloc
(Tasktyp
),
11673 Chars
=> New_External_Name
(Tasknm
, 'Z')));
11675 if Present
(Taskdef
)
11676 and then Has_Storage_Size_Pragma
(Taskdef
)
11678 Is_Static_Expression
11680 (First
(Pragma_Argument_Associations
11681 (Get_Rep_Pragma
(TaskId
, Name_Storage_Size
)))))
11684 Make_Object_Declaration
(Loc
,
11685 Defining_Identifier
=> Storage_Size_Variable
(Tasktyp
),
11686 Object_Definition
=>
11687 New_Occurrence_Of
(RTE
(RE_Size_Type
), Loc
),
11689 Convert_To
(RTE
(RE_Size_Type
),
11691 (Expression
(First
(Pragma_Argument_Associations
11693 (TaskId
, Name_Storage_Size
)))))));
11697 Make_Object_Declaration
(Loc
,
11698 Defining_Identifier
=> Storage_Size_Variable
(Tasktyp
),
11699 Object_Definition
=>
11700 New_Occurrence_Of
(RTE
(RE_Size_Type
), Loc
),
11702 New_Occurrence_Of
(RTE
(RE_Unspecified_Size
), Loc
));
11705 Insert_After
(Elab_Decl
, Size_Decl
);
11707 -- Next build the rest of the corresponding record declaration. This is
11708 -- done last, since the corresponding record initialization procedure
11709 -- will reference the previously created entities.
11711 -- Fill in the component declarations -- first the _Task_Id field
11714 Make_Component_Declaration
(Loc
,
11715 Defining_Identifier
=>
11716 Make_Defining_Identifier
(Loc
, Name_uTask_Id
),
11717 Component_Definition
=>
11718 Make_Component_Definition
(Loc
,
11719 Aliased_Present
=> False,
11720 Subtype_Indication
=> New_Occurrence_Of
(RTE
(RO_ST_Task_Id
),
11723 -- Declare static ATCB (that is, created by the expander) if we are
11724 -- using the Restricted run time.
11726 if Restricted_Profile
then
11728 Make_Component_Declaration
(Loc
,
11729 Defining_Identifier
=>
11730 Make_Defining_Identifier
(Loc
, Name_uATCB
),
11732 Component_Definition
=>
11733 Make_Component_Definition
(Loc
,
11734 Aliased_Present
=> True,
11735 Subtype_Indication
=> Make_Subtype_Indication
(Loc
,
11737 New_Occurrence_Of
(RTE
(RE_Ada_Task_Control_Block
), Loc
),
11740 Make_Index_Or_Discriminant_Constraint
(Loc
,
11742 New_List
(Make_Integer_Literal
(Loc
, 0)))))));
11746 -- Declare static stack (that is, created by the expander) if we are
11747 -- using the Restricted run time on a bare board configuration.
11749 if Restricted_Profile
11750 and then Preallocated_Stacks_On_Target
11752 -- First we need to extract the appropriate stack size
11754 Ent_Stack
:= Make_Defining_Identifier
(Loc
, Name_uStack
);
11756 if Present
(Taskdef
) and then Has_Storage_Size_Pragma
(Taskdef
) then
11758 Expr_N
: constant Node_Id
:=
11759 Expression
(First
(
11760 Pragma_Argument_Associations
(
11761 Get_Rep_Pragma
(TaskId
, Name_Storage_Size
))));
11762 Etyp
: constant Entity_Id
:= Etype
(Expr_N
);
11763 P
: constant Node_Id
:= Parent
(Expr_N
);
11766 -- The stack is defined inside the corresponding record.
11767 -- Therefore if the size of the stack is set by means of
11768 -- a discriminant, we must reference the discriminant of the
11769 -- corresponding record type.
11771 if Nkind
(Expr_N
) in N_Has_Entity
11772 and then Present
(Discriminal_Link
(Entity
(Expr_N
)))
11776 (CR_Discriminant
(Discriminal_Link
(Entity
(Expr_N
))),
11778 Set_Parent
(Task_Size
, P
);
11779 Set_Etype
(Task_Size
, Etyp
);
11780 Set_Analyzed
(Task_Size
);
11783 Task_Size
:= Relocate_Node
(Expr_N
);
11789 New_Occurrence_Of
(RTE
(RE_Default_Stack_Size
), Loc
);
11792 Decl_Stack
:= Make_Component_Declaration
(Loc
,
11793 Defining_Identifier
=> Ent_Stack
,
11795 Component_Definition
=>
11796 Make_Component_Definition
(Loc
,
11797 Aliased_Present
=> True,
11798 Subtype_Indication
=> Make_Subtype_Indication
(Loc
,
11800 New_Occurrence_Of
(RTE
(RE_Storage_Array
), Loc
),
11803 Make_Index_Or_Discriminant_Constraint
(Loc
,
11804 Constraints
=> New_List
(Make_Range
(Loc
,
11805 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
11806 High_Bound
=> Convert_To
(RTE
(RE_Storage_Offset
),
11809 Append_To
(Cdecls
, Decl_Stack
);
11811 -- The appropriate alignment for the stack is ensured by the run-time
11812 -- code in charge of task creation.
11816 -- Add components for entry families
11818 Collect_Entry_Families
(Loc
, Cdecls
, Size_Decl
, Tasktyp
);
11820 -- Add the _Priority component if a Interrupt_Priority or Priority rep
11821 -- item is present.
11823 if Has_Rep_Item
(TaskId
, Name_Priority
, Check_Parents
=> False) then
11825 Make_Component_Declaration
(Loc
,
11826 Defining_Identifier
=>
11827 Make_Defining_Identifier
(Loc
, Name_uPriority
),
11828 Component_Definition
=>
11829 Make_Component_Definition
(Loc
,
11830 Aliased_Present
=> False,
11831 Subtype_Indication
=>
11832 New_Occurrence_Of
(Standard_Integer
, Loc
))));
11835 -- Add the _Size component if a Storage_Size pragma is present
11837 if Present
(Taskdef
)
11838 and then Has_Storage_Size_Pragma
(Taskdef
)
11841 Make_Component_Declaration
(Loc
,
11842 Defining_Identifier
=>
11843 Make_Defining_Identifier
(Loc
, Name_uSize
),
11845 Component_Definition
=>
11846 Make_Component_Definition
(Loc
,
11847 Aliased_Present
=> False,
11848 Subtype_Indication
=>
11849 New_Occurrence_Of
(RTE
(RE_Size_Type
), Loc
)),
11852 Convert_To
(RTE
(RE_Size_Type
),
11854 Expression
(First
(
11855 Pragma_Argument_Associations
(
11856 Get_Rep_Pragma
(TaskId
, Name_Storage_Size
))))))));
11859 -- Add the _Task_Info component if a Task_Info pragma is present
11861 if Has_Rep_Pragma
(TaskId
, Name_Task_Info
, Check_Parents
=> False) then
11863 Make_Component_Declaration
(Loc
,
11864 Defining_Identifier
=>
11865 Make_Defining_Identifier
(Loc
, Name_uTask_Info
),
11867 Component_Definition
=>
11868 Make_Component_Definition
(Loc
,
11869 Aliased_Present
=> False,
11870 Subtype_Indication
=>
11871 New_Occurrence_Of
(RTE
(RE_Task_Info_Type
), Loc
)),
11873 Expression
=> New_Copy
(
11874 Expression
(First
(
11875 Pragma_Argument_Associations
(
11877 (TaskId
, Name_Task_Info
, Check_Parents
=> False)))))));
11880 -- Add the _CPU component if a CPU rep item is present
11882 if Has_Rep_Item
(TaskId
, Name_CPU
, Check_Parents
=> False) then
11884 Make_Component_Declaration
(Loc
,
11885 Defining_Identifier
=>
11886 Make_Defining_Identifier
(Loc
, Name_uCPU
),
11888 Component_Definition
=>
11889 Make_Component_Definition
(Loc
,
11890 Aliased_Present
=> False,
11891 Subtype_Indication
=>
11892 New_Occurrence_Of
(RTE
(RE_CPU_Range
), Loc
))));
11895 -- Add the _Relative_Deadline component if a Relative_Deadline pragma is
11896 -- present. If we are using a restricted run time this component will
11897 -- not be added (deadlines are not allowed by the Ravenscar profile).
11899 if not Restricted_Profile
11900 and then Present
(Taskdef
)
11901 and then Has_Relative_Deadline_Pragma
(Taskdef
)
11904 Make_Component_Declaration
(Loc
,
11905 Defining_Identifier
=>
11906 Make_Defining_Identifier
(Loc
, Name_uRelative_Deadline
),
11908 Component_Definition
=>
11909 Make_Component_Definition
(Loc
,
11910 Aliased_Present
=> False,
11911 Subtype_Indication
=>
11912 New_Occurrence_Of
(RTE
(RE_Time_Span
), Loc
)),
11915 Convert_To
(RTE
(RE_Time_Span
),
11917 Expression
(First
(
11918 Pragma_Argument_Associations
(
11919 Get_Relative_Deadline_Pragma
(Taskdef
))))))));
11922 -- Add the _Dispatching_Domain component if a Dispatching_Domain rep
11923 -- item is present. If we are using a restricted run time this component
11924 -- will not be added (dispatching domains are not allowed by the
11925 -- Ravenscar profile).
11927 if not Restricted_Profile
11930 (TaskId
, Name_Dispatching_Domain
, Check_Parents
=> False)
11933 Make_Component_Declaration
(Loc
,
11934 Defining_Identifier
=>
11935 Make_Defining_Identifier
(Loc
, Name_uDispatching_Domain
),
11937 Component_Definition
=>
11938 Make_Component_Definition
(Loc
,
11939 Aliased_Present
=> False,
11940 Subtype_Indication
=>
11942 (RTE
(RE_Dispatching_Domain_Access
), Loc
))));
11945 Insert_After
(Size_Decl
, Rec_Decl
);
11947 -- Analyze the record declaration immediately after construction,
11948 -- because the initialization procedure is needed for single task
11949 -- declarations before the next entity is analyzed.
11951 Analyze
(Rec_Decl
);
11953 -- Create the declaration of the task body procedure
11955 Proc_Spec
:= Build_Task_Proc_Specification
(Tasktyp
);
11957 Make_Subprogram_Declaration
(Loc
,
11958 Specification
=> Proc_Spec
);
11960 Insert_After
(Rec_Decl
, Body_Decl
);
11962 -- The subprogram does not comes from source, so we have to indicate the
11963 -- need for debugging information explicitly.
11965 if Comes_From_Source
(Original_Node
(N
)) then
11966 Set_Debug_Info_Needed
(Defining_Entity
(Proc_Spec
));
11969 -- Ada 2005 (AI-345): Construct the primitive entry wrapper specs before
11970 -- the corresponding record has been frozen.
11972 if Ada_Version
>= Ada_2005
then
11973 Build_Wrapper_Specs
(Loc
, Tasktyp
, Rec_Decl
);
11976 -- Ada 2005 (AI-345): We must defer freezing to allow further
11977 -- declaration of primitive subprograms covering task interfaces
11979 if Ada_Version
<= Ada_95
then
11981 -- Now we can freeze the corresponding record. This needs manually
11982 -- freezing, since it is really part of the task type, and the task
11983 -- type is frozen at this stage. We of course need the initialization
11984 -- procedure for this corresponding record type and we won't get it
11985 -- in time if we don't freeze now.
11988 L
: constant List_Id
:= Freeze_Entity
(Rec_Ent
, N
);
11990 if Is_Non_Empty_List
(L
) then
11991 Insert_List_After
(Body_Decl
, L
);
11996 -- Complete the expansion of access types to the current task type, if
11997 -- any were declared.
11999 Expand_Previous_Access_Type
(Tasktyp
);
12001 -- Create wrappers for entries that have pre/postconditions
12007 Ent
:= First_Entity
(Tasktyp
);
12008 while Present
(Ent
) loop
12009 if Ekind_In
(Ent
, E_Entry
, E_Entry_Family
)
12010 and then Present
(Pre_Post_Conditions
(Contract
(Ent
)))
12012 Build_PPC_Wrapper
(Ent
, N
);
12018 end Expand_N_Task_Type_Declaration
;
12020 -------------------------------
12021 -- Expand_N_Timed_Entry_Call --
12022 -------------------------------
12024 -- A timed entry call in normal case is not implemented using ATC mechanism
12025 -- anymore for efficiency reason.
12035 -- is expanded as follows:
12037 -- 1) When T.E is a task entry_call;
12041 -- X : Task_Entry_Index := <entry index>;
12042 -- DX : Duration := To_Duration (D);
12043 -- M : Delay_Mode := <discriminant>;
12044 -- P : parms := (parm, parm, parm);
12047 -- Timed_Protected_Entry_Call
12048 -- (<acceptor-task>, X, P'Address, DX, M, B);
12056 -- 2) When T.E is a protected entry_call;
12060 -- X : Protected_Entry_Index := <entry index>;
12061 -- DX : Duration := To_Duration (D);
12062 -- M : Delay_Mode := <discriminant>;
12063 -- P : parms := (parm, parm, parm);
12066 -- Timed_Protected_Entry_Call
12067 -- (<object>'unchecked_access, X, P'Address, DX, M, B);
12075 -- 3) Ada 2005 (AI-345): When T.E is a dispatching procedure call, there
12076 -- is no delay and the triggering statements are executed. We first
12077 -- determine the kind of of the triggering call and then execute a
12078 -- synchronized operation or a direct call.
12081 -- B : Boolean := False;
12082 -- C : Ada.Tags.Prim_Op_Kind;
12083 -- DX : Duration := To_Duration (D)
12084 -- K : Ada.Tags.Tagged_Kind :=
12085 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
12086 -- M : Integer :=...;
12087 -- P : Parameters := (Param1 .. ParamN);
12091 -- if K = Ada.Tags.TK_Limited_Tagged
12092 -- or else K = Ada.Tags.TK_Tagged
12094 -- <dispatching-call>;
12099 -- Ada.Tags.Get_Offset_Index
12100 -- (Ada.Tags.Tag (<object>), DT_Position (<dispatching-call>));
12102 -- _Disp_Timed_Select (<object>, S, P'Address, DX, M, C, B);
12104 -- if C = POK_Protected_Entry
12105 -- or else C = POK_Task_Entry
12107 -- Param1 := P.Param1;
12109 -- ParamN := P.ParamN;
12113 -- if C = POK_Procedure
12114 -- or else C = POK_Protected_Procedure
12115 -- or else C = POK_Task_Procedure
12117 -- <dispatching-call>;
12123 -- <triggering-statements>
12125 -- <timed-statements>
12129 -- The triggering statement and the sequence of timed statements have not
12130 -- been analyzed yet (see Analyzed_Timed_Entry_Call), but they may contain
12131 -- global references if within an instantiation.
12133 procedure Expand_N_Timed_Entry_Call
(N
: Node_Id
) is
12134 Loc
: constant Source_Ptr
:= Sloc
(N
);
12137 Blk_Typ
: Entity_Id
;
12139 Call_Ent
: Entity_Id
;
12140 Conc_Typ_Stmts
: List_Id
;
12142 D_Alt
: constant Node_Id
:= Delay_Alternative
(N
);
12145 D_Stat
: Node_Id
:= Delay_Statement
(D_Alt
);
12147 D_Type
: Entity_Id
;
12150 E_Alt
: constant Node_Id
:= Entry_Call_Alternative
(N
);
12151 E_Call
: Node_Id
:= Entry_Call_Statement
(E_Alt
);
12156 Is_Disp_Select
: Boolean;
12157 Lim_Typ_Stmts
: List_Id
;
12166 B
: Entity_Id
; -- Call status flag
12167 C
: Entity_Id
; -- Call kind
12168 D
: Entity_Id
; -- Delay
12169 K
: Entity_Id
; -- Tagged kind
12170 M
: Entity_Id
; -- Delay mode
12171 P
: Entity_Id
; -- Parameter block
12172 S
: Entity_Id
; -- Primitive operation slot
12174 -- Start of processing for Expand_N_Timed_Entry_Call
12177 -- Under the Ravenscar profile, timed entry calls are excluded. An error
12178 -- was already reported on spec, so do not attempt to expand the call.
12180 if Restriction_Active
(No_Select_Statements
) then
12184 Process_Statements_For_Controlled_Objects
(E_Alt
);
12185 Process_Statements_For_Controlled_Objects
(D_Alt
);
12187 Ensure_Statement_Present
(Sloc
(D_Stat
), D_Alt
);
12189 -- Retrieve E_Stats and D_Stats now because the finalization machinery
12190 -- may wrap them in blocks.
12192 E_Stats
:= Statements
(E_Alt
);
12193 D_Stats
:= Statements
(D_Alt
);
12195 -- The arguments in the call may require dynamic allocation, and the
12196 -- call statement may have been transformed into a block. The block
12197 -- may contain additional declarations for internal entities, and the
12198 -- original call is found by sequential search.
12200 if Nkind
(E_Call
) = N_Block_Statement
then
12201 E_Call
:= First
(Statements
(Handled_Statement_Sequence
(E_Call
)));
12202 while not Nkind_In
(E_Call
, N_Procedure_Call_Statement
,
12203 N_Entry_Call_Statement
)
12210 Ada_Version
>= Ada_2005
12211 and then Nkind
(E_Call
) = N_Procedure_Call_Statement
;
12213 if Is_Disp_Select
then
12214 Extract_Dispatching_Call
(E_Call
, Call_Ent
, Obj
, Actuals
, Formals
);
12220 -- B : Boolean := False;
12222 B
:= Build_B
(Loc
, Decls
);
12225 -- C : Ada.Tags.Prim_Op_Kind;
12227 C
:= Build_C
(Loc
, Decls
);
12229 -- Because the analysis of all statements was disabled, manually
12230 -- analyze the delay statement.
12233 D_Stat
:= Original_Node
(D_Stat
);
12236 -- Build an entry call using Simple_Entry_Call
12238 Extract_Entry
(E_Call
, Concval
, Ename
, Index
);
12239 Build_Simple_Entry_Call
(E_Call
, Concval
, Ename
, Index
);
12241 Decls
:= Declarations
(E_Call
);
12242 Stmts
:= Statements
(Handled_Statement_Sequence
(E_Call
));
12251 B
:= Make_Defining_Identifier
(Loc
, Name_uB
);
12254 Make_Object_Declaration
(Loc
,
12255 Defining_Identifier
=> B
,
12256 Object_Definition
=>
12257 New_Occurrence_Of
(Standard_Boolean
, Loc
)));
12260 -- Duration and mode processing
12262 D_Type
:= Base_Type
(Etype
(Expression
(D_Stat
)));
12264 -- Use the type of the delay expression (Calendar or Real_Time) to
12265 -- generate the appropriate conversion.
12267 if Nkind
(D_Stat
) = N_Delay_Relative_Statement
then
12268 D_Disc
:= Make_Integer_Literal
(Loc
, 0);
12269 D_Conv
:= Relocate_Node
(Expression
(D_Stat
));
12271 elsif Is_RTE
(D_Type
, RO_CA_Time
) then
12272 D_Disc
:= Make_Integer_Literal
(Loc
, 1);
12274 Make_Function_Call
(Loc
,
12275 Name
=> New_Occurrence_Of
(RTE
(RO_CA_To_Duration
), Loc
),
12276 Parameter_Associations
=>
12277 New_List
(New_Copy
(Expression
(D_Stat
))));
12279 else pragma Assert
(Is_RTE
(D_Type
, RO_RT_Time
));
12280 D_Disc
:= Make_Integer_Literal
(Loc
, 2);
12282 Make_Function_Call
(Loc
,
12283 Name
=> New_Occurrence_Of
(RTE
(RO_RT_To_Duration
), Loc
),
12284 Parameter_Associations
=>
12285 New_List
(New_Copy
(Expression
(D_Stat
))));
12288 D
:= Make_Temporary
(Loc
, 'D');
12294 Make_Object_Declaration
(Loc
,
12295 Defining_Identifier
=> D
,
12296 Object_Definition
=> New_Occurrence_Of
(Standard_Duration
, Loc
)));
12298 M
:= Make_Temporary
(Loc
, 'M');
12301 -- M : Integer := (0 | 1 | 2);
12304 Make_Object_Declaration
(Loc
,
12305 Defining_Identifier
=> M
,
12306 Object_Definition
=> New_Occurrence_Of
(Standard_Integer
, Loc
),
12307 Expression
=> D_Disc
));
12309 -- Do the assignment at this stage only because the evaluation of the
12310 -- expression must not occur before (see ACVC C97302A).
12313 Make_Assignment_Statement
(Loc
,
12314 Name
=> New_Occurrence_Of
(D
, Loc
),
12315 Expression
=> D_Conv
));
12317 -- Parameter block processing
12319 -- Manually create the parameter block for dispatching calls. In the
12320 -- case of entries, the block has already been created during the call
12321 -- to Build_Simple_Entry_Call.
12323 if Is_Disp_Select
then
12325 -- Tagged kind processing, generate:
12326 -- K : Ada.Tags.Tagged_Kind :=
12327 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag <object>));
12329 K
:= Build_K
(Loc
, Decls
, Obj
);
12331 Blk_Typ
:= Build_Parameter_Block
(Loc
, Actuals
, Formals
, Decls
);
12333 Parameter_Block_Pack
(Loc
, Blk_Typ
, Actuals
, Formals
, Decls
, Stmts
);
12335 -- Dispatch table slot processing, generate:
12338 S
:= Build_S
(Loc
, Decls
);
12341 -- S := Ada.Tags.Get_Offset_Index
12342 -- (Ada.Tags.Tag (<object>), DT_Position (Call_Ent));
12345 New_List
(Build_S_Assignment
(Loc
, S
, Obj
, Call_Ent
));
12348 -- _Disp_Timed_Select (<object>, S, P'Address, D, M, C, B);
12350 -- where Obj is the controlling formal parameter, S is the dispatch
12351 -- table slot number of the dispatching operation, P is the wrapped
12352 -- parameter block, D is the duration, M is the duration mode, C is
12353 -- the call kind and B is the call status.
12355 Params
:= New_List
;
12357 Append_To
(Params
, New_Copy_Tree
(Obj
));
12358 Append_To
(Params
, New_Occurrence_Of
(S
, Loc
));
12360 Make_Attribute_Reference
(Loc
,
12361 Prefix
=> New_Occurrence_Of
(P
, Loc
),
12362 Attribute_Name
=> Name_Address
));
12363 Append_To
(Params
, New_Occurrence_Of
(D
, Loc
));
12364 Append_To
(Params
, New_Occurrence_Of
(M
, Loc
));
12365 Append_To
(Params
, New_Occurrence_Of
(C
, Loc
));
12366 Append_To
(Params
, New_Occurrence_Of
(B
, Loc
));
12368 Append_To
(Conc_Typ_Stmts
,
12369 Make_Procedure_Call_Statement
(Loc
,
12373 (Etype
(Etype
(Obj
)), Name_uDisp_Timed_Select
), Loc
),
12374 Parameter_Associations
=> Params
));
12377 -- if C = POK_Protected_Entry
12378 -- or else C = POK_Task_Entry
12380 -- Param1 := P.Param1;
12382 -- ParamN := P.ParamN;
12385 Unpack
:= Parameter_Block_Unpack
(Loc
, P
, Actuals
, Formals
);
12387 -- Generate the if statement only when the packed parameters need
12388 -- explicit assignments to their corresponding actuals.
12390 if Present
(Unpack
) then
12391 Append_To
(Conc_Typ_Stmts
,
12392 Make_Implicit_If_Statement
(N
,
12398 Left_Opnd
=> New_Occurrence_Of
(C
, Loc
),
12401 (RTE
(RE_POK_Protected_Entry
), Loc
)),
12405 Left_Opnd
=> New_Occurrence_Of
(C
, Loc
),
12407 New_Occurrence_Of
(RTE
(RE_POK_Task_Entry
), Loc
))),
12409 Then_Statements
=> Unpack
));
12415 -- if C = POK_Procedure
12416 -- or else C = POK_Protected_Procedure
12417 -- or else C = POK_Task_Procedure
12419 -- <dispatching-call>
12423 N_Stats
:= New_List
(
12424 Make_Implicit_If_Statement
(N
,
12429 Left_Opnd
=> New_Occurrence_Of
(C
, Loc
),
12431 New_Occurrence_Of
(RTE
(RE_POK_Procedure
), Loc
)),
12437 Left_Opnd
=> New_Occurrence_Of
(C
, Loc
),
12439 New_Occurrence_Of
(RTE
(
12440 RE_POK_Protected_Procedure
), Loc
)),
12443 Left_Opnd
=> New_Occurrence_Of
(C
, Loc
),
12446 (RTE
(RE_POK_Task_Procedure
), Loc
)))),
12448 Then_Statements
=> New_List
(E_Call
)));
12450 Append_To
(Conc_Typ_Stmts
,
12451 Make_Implicit_If_Statement
(N
,
12452 Condition
=> New_Occurrence_Of
(B
, Loc
),
12453 Then_Statements
=> N_Stats
));
12456 -- <dispatching-call>;
12460 New_List
(New_Copy_Tree
(E_Call
),
12461 Make_Assignment_Statement
(Loc
,
12462 Name
=> New_Occurrence_Of
(B
, Loc
),
12463 Expression
=> New_Occurrence_Of
(Standard_True
, Loc
)));
12466 -- if K = Ada.Tags.TK_Limited_Tagged
12467 -- or else K = Ada.Tags.TK_Tagged
12475 Make_Implicit_If_Statement
(N
,
12476 Condition
=> Build_Dispatching_Tag_Check
(K
, N
),
12477 Then_Statements
=> Lim_Typ_Stmts
,
12478 Else_Statements
=> Conc_Typ_Stmts
));
12483 -- <triggering-statements>
12485 -- <timed-statements>
12489 Make_Implicit_If_Statement
(N
,
12490 Condition
=> New_Occurrence_Of
(B
, Loc
),
12491 Then_Statements
=> E_Stats
,
12492 Else_Statements
=> D_Stats
));
12495 -- Simple case of a non-dispatching trigger. Skip assignments to
12496 -- temporaries created for in-out parameters.
12498 -- This makes unwarranted assumptions about the shape of the expanded
12499 -- tree for the call, and should be cleaned up ???
12501 Stmt
:= First
(Stmts
);
12502 while Nkind
(Stmt
) /= N_Procedure_Call_Statement
loop
12506 -- Do the assignment at this stage only because the evaluation
12507 -- of the expression must not occur before (see ACVC C97302A).
12509 Insert_Before
(Stmt
,
12510 Make_Assignment_Statement
(Loc
,
12511 Name
=> New_Occurrence_Of
(D
, Loc
),
12512 Expression
=> D_Conv
));
12515 Params
:= Parameter_Associations
(Call
);
12517 -- For a protected type, we build a Timed_Protected_Entry_Call
12519 if Is_Protected_Type
(Etype
(Concval
)) then
12521 -- Create a new call statement
12523 Param
:= First
(Params
);
12524 while Present
(Param
)
12525 and then not Is_RTE
(Etype
(Param
), RE_Call_Modes
)
12530 Dummy
:= Remove_Next
(Next
(Param
));
12532 -- Remove garbage is following the Cancel_Param if present
12534 Dummy
:= Next
(Param
);
12536 -- Remove the mode of the Protected_Entry_Call call, then remove
12537 -- the Communication_Block of the Protected_Entry_Call call, and
12538 -- finally add Duration and a Delay_Mode parameter
12540 pragma Assert
(Present
(Param
));
12541 Rewrite
(Param
, New_Occurrence_Of
(D
, Loc
));
12543 Rewrite
(Dummy
, New_Occurrence_Of
(M
, Loc
));
12545 -- Add a Boolean flag for successful entry call
12547 Append_To
(Params
, New_Occurrence_Of
(B
, Loc
));
12549 case Corresponding_Runtime_Package
(Etype
(Concval
)) is
12550 when System_Tasking_Protected_Objects_Entries
=>
12552 Make_Procedure_Call_Statement
(Loc
,
12555 (RTE
(RE_Timed_Protected_Entry_Call
), Loc
),
12556 Parameter_Associations
=> Params
));
12559 raise Program_Error
;
12562 -- For the task case, build a Timed_Task_Entry_Call
12565 -- Create a new call statement
12567 Append_To
(Params
, New_Occurrence_Of
(D
, Loc
));
12568 Append_To
(Params
, New_Occurrence_Of
(M
, Loc
));
12569 Append_To
(Params
, New_Occurrence_Of
(B
, Loc
));
12572 Make_Procedure_Call_Statement
(Loc
,
12574 New_Occurrence_Of
(RTE
(RE_Timed_Task_Entry_Call
), Loc
),
12575 Parameter_Associations
=> Params
));
12579 Make_Implicit_If_Statement
(N
,
12580 Condition
=> New_Occurrence_Of
(B
, Loc
),
12581 Then_Statements
=> E_Stats
,
12582 Else_Statements
=> D_Stats
));
12586 Make_Block_Statement
(Loc
,
12587 Declarations
=> Decls
,
12588 Handled_Statement_Sequence
=>
12589 Make_Handled_Sequence_Of_Statements
(Loc
, Stmts
)));
12592 end Expand_N_Timed_Entry_Call
;
12594 ----------------------------------------
12595 -- Expand_Protected_Body_Declarations --
12596 ----------------------------------------
12598 procedure Expand_Protected_Body_Declarations
12600 Spec_Id
: Entity_Id
)
12603 if No_Run_Time_Mode
then
12604 Error_Msg_CRT
("protected body", N
);
12607 elsif Expander_Active
then
12609 -- Associate discriminals with the first subprogram or entry body to
12612 if Present
(First_Protected_Operation
(Declarations
(N
))) then
12613 Set_Discriminals
(Parent
(Spec_Id
));
12616 end Expand_Protected_Body_Declarations
;
12618 -------------------------
12619 -- External_Subprogram --
12620 -------------------------
12622 function External_Subprogram
(E
: Entity_Id
) return Entity_Id
is
12623 Subp
: constant Entity_Id
:= Protected_Body_Subprogram
(E
);
12626 -- The internal and external subprograms follow each other on the entity
12627 -- chain. Note that previously private operations had no separate
12628 -- external subprogram. We now create one in all cases, because a
12629 -- private operation may actually appear in an external call, through
12630 -- a 'Access reference used for a callback.
12632 -- If the operation is a function that returns an anonymous access type,
12633 -- the corresponding itype appears before the operation, and must be
12636 -- This mechanism is fragile, there should be a real link between the
12637 -- two versions of the operation, but there is no place to put it ???
12639 if Is_Access_Type
(Next_Entity
(Subp
)) then
12640 return Next_Entity
(Next_Entity
(Subp
));
12642 return Next_Entity
(Subp
);
12644 end External_Subprogram
;
12646 ------------------------------
12647 -- Extract_Dispatching_Call --
12648 ------------------------------
12650 procedure Extract_Dispatching_Call
12652 Call_Ent
: out Entity_Id
;
12653 Object
: out Entity_Id
;
12654 Actuals
: out List_Id
;
12655 Formals
: out List_Id
)
12657 Call_Nam
: Node_Id
;
12660 pragma Assert
(Nkind
(N
) = N_Procedure_Call_Statement
);
12662 if Present
(Original_Node
(N
)) then
12663 Call_Nam
:= Name
(Original_Node
(N
));
12665 Call_Nam
:= Name
(N
);
12668 -- Retrieve the name of the dispatching procedure. It contains the
12669 -- dispatch table slot number.
12672 case Nkind
(Call_Nam
) is
12673 when N_Identifier
=>
12676 when N_Selected_Component
=>
12677 Call_Nam
:= Selector_Name
(Call_Nam
);
12680 raise Program_Error
;
12685 Actuals
:= Parameter_Associations
(N
);
12686 Call_Ent
:= Entity
(Call_Nam
);
12687 Formals
:= Parameter_Specifications
(Parent
(Call_Ent
));
12688 Object
:= First
(Actuals
);
12690 if Present
(Original_Node
(Object
)) then
12691 Object
:= Original_Node
(Object
);
12694 -- If the type of the dispatching object is an access type then return
12695 -- an explicit dereference.
12697 if Is_Access_Type
(Etype
(Object
)) then
12698 Object
:= Make_Explicit_Dereference
(Sloc
(N
), Object
);
12701 end Extract_Dispatching_Call
;
12703 -------------------
12704 -- Extract_Entry --
12705 -------------------
12707 procedure Extract_Entry
12709 Concval
: out Node_Id
;
12710 Ename
: out Node_Id
;
12711 Index
: out Node_Id
)
12713 Nam
: constant Node_Id
:= Name
(N
);
12716 -- For a simple entry, the name is a selected component, with the
12717 -- prefix being the task value, and the selector being the entry.
12719 if Nkind
(Nam
) = N_Selected_Component
then
12720 Concval
:= Prefix
(Nam
);
12721 Ename
:= Selector_Name
(Nam
);
12724 -- For a member of an entry family, the name is an indexed component
12725 -- where the prefix is a selected component, whose prefix in turn is
12726 -- the task value, and whose selector is the entry family. The single
12727 -- expression in the expressions list of the indexed component is the
12728 -- subscript for the family.
12730 else pragma Assert
(Nkind
(Nam
) = N_Indexed_Component
);
12731 Concval
:= Prefix
(Prefix
(Nam
));
12732 Ename
:= Selector_Name
(Prefix
(Nam
));
12733 Index
:= First
(Expressions
(Nam
));
12737 -------------------
12738 -- Family_Offset --
12739 -------------------
12741 function Family_Offset
12746 Cap
: Boolean) return Node_Id
12752 function Convert_Discriminant_Ref
(Bound
: Node_Id
) return Node_Id
;
12753 -- If one of the bounds is a reference to a discriminant, replace with
12754 -- corresponding discriminal of type. Within the body of a task retrieve
12755 -- the renamed discriminant by simple visibility, using its generated
12756 -- name. Within a protected object, find the original discriminant and
12757 -- replace it with the discriminal of the current protected operation.
12759 ------------------------------
12760 -- Convert_Discriminant_Ref --
12761 ------------------------------
12763 function Convert_Discriminant_Ref
(Bound
: Node_Id
) return Node_Id
is
12764 Loc
: constant Source_Ptr
:= Sloc
(Bound
);
12769 if Is_Entity_Name
(Bound
)
12770 and then Ekind
(Entity
(Bound
)) = E_Discriminant
12772 if Is_Task_Type
(Ttyp
)
12773 and then Has_Completion
(Ttyp
)
12775 B
:= Make_Identifier
(Loc
, Chars
(Entity
(Bound
)));
12776 Find_Direct_Name
(B
);
12778 elsif Is_Protected_Type
(Ttyp
) then
12779 D
:= First_Discriminant
(Ttyp
);
12780 while Chars
(D
) /= Chars
(Entity
(Bound
)) loop
12781 Next_Discriminant
(D
);
12784 B
:= New_Occurrence_Of
(Discriminal
(D
), Loc
);
12787 B
:= New_Occurrence_Of
(Discriminal
(Entity
(Bound
)), Loc
);
12790 elsif Nkind
(Bound
) = N_Attribute_Reference
then
12794 B
:= New_Copy_Tree
(Bound
);
12798 Make_Attribute_Reference
(Loc
,
12799 Attribute_Name
=> Name_Pos
,
12800 Prefix
=> New_Occurrence_Of
(Etype
(Bound
), Loc
),
12801 Expressions
=> New_List
(B
));
12802 end Convert_Discriminant_Ref
;
12804 -- Start of processing for Family_Offset
12807 Real_Hi
:= Convert_Discriminant_Ref
(Hi
);
12808 Real_Lo
:= Convert_Discriminant_Ref
(Lo
);
12811 if Is_Task_Type
(Ttyp
) then
12812 Ityp
:= RTE
(RE_Task_Entry_Index
);
12814 Ityp
:= RTE
(RE_Protected_Entry_Index
);
12818 Make_Attribute_Reference
(Loc
,
12819 Prefix
=> New_Occurrence_Of
(Ityp
, Loc
),
12820 Attribute_Name
=> Name_Min
,
12821 Expressions
=> New_List
(
12823 Make_Integer_Literal
(Loc
, Entry_Family_Bound
- 1)));
12826 Make_Attribute_Reference
(Loc
,
12827 Prefix
=> New_Occurrence_Of
(Ityp
, Loc
),
12828 Attribute_Name
=> Name_Max
,
12829 Expressions
=> New_List
(
12831 Make_Integer_Literal
(Loc
, -Entry_Family_Bound
)));
12834 return Make_Op_Subtract
(Loc
, Real_Hi
, Real_Lo
);
12841 function Family_Size
12846 Cap
: Boolean) return Node_Id
12851 if Is_Task_Type
(Ttyp
) then
12852 Ityp
:= RTE
(RE_Task_Entry_Index
);
12854 Ityp
:= RTE
(RE_Protected_Entry_Index
);
12858 Make_Attribute_Reference
(Loc
,
12859 Prefix
=> New_Occurrence_Of
(Ityp
, Loc
),
12860 Attribute_Name
=> Name_Max
,
12861 Expressions
=> New_List
(
12864 Family_Offset
(Loc
, Hi
, Lo
, Ttyp
, Cap
),
12866 Make_Integer_Literal
(Loc
, 1)),
12867 Make_Integer_Literal
(Loc
, 0)));
12870 ----------------------------
12871 -- Find_Enclosing_Context --
12872 ----------------------------
12874 procedure Find_Enclosing_Context
12876 Context
: out Node_Id
;
12877 Context_Id
: out Entity_Id
;
12878 Context_Decls
: out List_Id
)
12881 -- Traverse the parent chain looking for an enclosing body, block,
12882 -- package or return statement.
12884 Context
:= Parent
(N
);
12885 while not Nkind_In
(Context
, N_Block_Statement
,
12887 N_Extended_Return_Statement
,
12889 N_Package_Declaration
,
12893 Context
:= Parent
(Context
);
12896 -- Extract the constituents of the context
12898 if Nkind
(Context
) = N_Extended_Return_Statement
then
12899 Context_Decls
:= Return_Object_Declarations
(Context
);
12900 Context_Id
:= Return_Statement_Entity
(Context
);
12902 -- Package declarations and bodies use a common library-level activation
12903 -- chain or task master, therefore return the package declaration as the
12904 -- proper carrier for the appropriate flag.
12906 elsif Nkind
(Context
) = N_Package_Body
then
12907 Context_Decls
:= Declarations
(Context
);
12908 Context_Id
:= Corresponding_Spec
(Context
);
12909 Context
:= Parent
(Context_Id
);
12911 if Nkind
(Context
) = N_Defining_Program_Unit_Name
then
12912 Context
:= Parent
(Parent
(Context
));
12914 Context
:= Parent
(Context
);
12917 elsif Nkind
(Context
) = N_Package_Declaration
then
12918 Context_Decls
:= Visible_Declarations
(Specification
(Context
));
12919 Context_Id
:= Defining_Unit_Name
(Specification
(Context
));
12921 if Nkind
(Context_Id
) = N_Defining_Program_Unit_Name
then
12922 Context_Id
:= Defining_Identifier
(Context_Id
);
12926 Context_Decls
:= Declarations
(Context
);
12928 if Nkind
(Context
) = N_Block_Statement
then
12929 Context_Id
:= Entity
(Identifier
(Context
));
12931 elsif Nkind
(Context
) = N_Entry_Body
then
12932 Context_Id
:= Defining_Identifier
(Context
);
12934 elsif Nkind
(Context
) = N_Subprogram_Body
then
12935 if Present
(Corresponding_Spec
(Context
)) then
12936 Context_Id
:= Corresponding_Spec
(Context
);
12938 Context_Id
:= Defining_Unit_Name
(Specification
(Context
));
12940 if Nkind
(Context_Id
) = N_Defining_Program_Unit_Name
then
12941 Context_Id
:= Defining_Identifier
(Context_Id
);
12945 elsif Nkind
(Context
) = N_Task_Body
then
12946 Context_Id
:= Corresponding_Spec
(Context
);
12949 raise Program_Error
;
12953 pragma Assert
(Present
(Context
));
12954 pragma Assert
(Present
(Context_Id
));
12955 pragma Assert
(Present
(Context_Decls
));
12956 end Find_Enclosing_Context
;
12958 -----------------------
12959 -- Find_Master_Scope --
12960 -----------------------
12962 function Find_Master_Scope
(E
: Entity_Id
) return Entity_Id
is
12966 -- In Ada 2005, the master is the innermost enclosing scope that is not
12967 -- transient. If the enclosing block is the rewriting of a call or the
12968 -- scope is an extended return statement this is valid master. The
12969 -- master in an extended return is only used within the return, and is
12970 -- subsequently overwritten in Move_Activation_Chain, but it must exist
12971 -- now before that overwriting occurs.
12975 if Ada_Version
>= Ada_2005
then
12976 while Is_Internal
(S
) loop
12977 if Nkind
(Parent
(S
)) = N_Block_Statement
12979 Nkind
(Original_Node
(Parent
(S
))) = N_Procedure_Call_Statement
12983 elsif Ekind
(S
) = E_Return_Statement
then
12993 end Find_Master_Scope
;
12995 -------------------------------
12996 -- First_Protected_Operation --
12997 -------------------------------
12999 function First_Protected_Operation
(D
: List_Id
) return Node_Id
is
13000 First_Op
: Node_Id
;
13003 First_Op
:= First
(D
);
13004 while Present
(First_Op
)
13005 and then not Nkind_In
(First_Op
, N_Subprogram_Body
, N_Entry_Body
)
13011 end First_Protected_Operation
;
13013 ---------------------------------------
13014 -- Install_Private_Data_Declarations --
13015 ---------------------------------------
13017 procedure Install_Private_Data_Declarations
13019 Spec_Id
: Entity_Id
;
13020 Conc_Typ
: Entity_Id
;
13021 Body_Nod
: Node_Id
;
13023 Barrier
: Boolean := False;
13024 Family
: Boolean := False)
13026 Is_Protected
: constant Boolean := Is_Protected_Type
(Conc_Typ
);
13029 Insert_Node
: Node_Id
:= Empty
;
13030 Obj_Ent
: Entity_Id
;
13032 procedure Add
(Decl
: Node_Id
);
13033 -- Add a single declaration after Insert_Node. If this is the first
13034 -- addition, Decl is added to the front of Decls and it becomes the
13037 function Replace_Bound
(Bound
: Node_Id
) return Node_Id
;
13038 -- The bounds of an entry index may depend on discriminants, create a
13039 -- reference to the corresponding prival. Otherwise return a duplicate
13040 -- of the original bound.
13046 procedure Add
(Decl
: Node_Id
) is
13048 if No
(Insert_Node
) then
13049 Prepend_To
(Decls
, Decl
);
13051 Insert_After
(Insert_Node
, Decl
);
13054 Insert_Node
:= Decl
;
13057 --------------------------
13058 -- Replace_Discriminant --
13059 --------------------------
13061 function Replace_Bound
(Bound
: Node_Id
) return Node_Id
is
13063 if Nkind
(Bound
) = N_Identifier
13064 and then Is_Discriminal
(Entity
(Bound
))
13066 return Make_Identifier
(Loc
, Chars
(Entity
(Bound
)));
13068 return Duplicate_Subexpr
(Bound
);
13072 -- Start of processing for Install_Private_Data_Declarations
13075 -- Step 1: Retrieve the concurrent object entity. Obj_Ent can denote
13076 -- formal parameter _O, _object or _task depending on the context.
13078 Obj_Ent
:= Concurrent_Object
(Spec_Id
, Conc_Typ
);
13080 -- Special processing of _O for barrier functions, protected entries
13087 (Ekind
(Spec_Id
) = E_Entry
13088 or else Ekind
(Spec_Id
) = E_Entry_Family
))
13091 Conc_Rec
: constant Entity_Id
:=
13092 Corresponding_Record_Type
(Conc_Typ
);
13093 Typ_Id
: constant Entity_Id
:=
13094 Make_Defining_Identifier
(Loc
,
13095 New_External_Name
(Chars
(Conc_Rec
), 'P'));
13098 -- type prot_typVP is access prot_typV;
13101 Make_Full_Type_Declaration
(Loc
,
13102 Defining_Identifier
=> Typ_Id
,
13104 Make_Access_To_Object_Definition
(Loc
,
13105 Subtype_Indication
=>
13106 New_Occurrence_Of
(Conc_Rec
, Loc
)));
13110 -- _object : prot_typVP := prot_typV (_O);
13113 Make_Object_Declaration
(Loc
,
13114 Defining_Identifier
=>
13115 Make_Defining_Identifier
(Loc
, Name_uObject
),
13116 Object_Definition
=> New_Occurrence_Of
(Typ_Id
, Loc
),
13118 Unchecked_Convert_To
(Typ_Id
,
13119 New_Occurrence_Of
(Obj_Ent
, Loc
)));
13122 -- Set the reference to the concurrent object
13124 Obj_Ent
:= Defining_Identifier
(Decl
);
13128 -- Step 2: Create the Protection object and build its declaration for
13129 -- any protected entry (family) of subprogram. Note for the lock-free
13130 -- implementation, the Protection object is not needed anymore.
13132 if Is_Protected
and then not Uses_Lock_Free
(Conc_Typ
) then
13134 Prot_Ent
: constant Entity_Id
:= Make_Temporary
(Loc
, 'R');
13138 Set_Protection_Object
(Spec_Id
, Prot_Ent
);
13140 -- Determine the proper protection type
13142 if Has_Attach_Handler
(Conc_Typ
)
13143 and then not Restricted_Profile
13145 Prot_Typ
:= RE_Static_Interrupt_Protection
;
13147 elsif Has_Interrupt_Handler
(Conc_Typ
)
13148 and then not Restriction_Active
(No_Dynamic_Attachment
)
13150 Prot_Typ
:= RE_Dynamic_Interrupt_Protection
;
13153 case Corresponding_Runtime_Package
(Conc_Typ
) is
13154 when System_Tasking_Protected_Objects_Entries
=>
13155 Prot_Typ
:= RE_Protection_Entries
;
13157 when System_Tasking_Protected_Objects_Single_Entry
=>
13158 Prot_Typ
:= RE_Protection_Entry
;
13160 when System_Tasking_Protected_Objects
=>
13161 Prot_Typ
:= RE_Protection
;
13164 raise Program_Error
;
13169 -- conc_typR : protection_typ renames _object._object;
13172 Make_Object_Renaming_Declaration
(Loc
,
13173 Defining_Identifier
=> Prot_Ent
,
13175 New_Occurrence_Of
(RTE
(Prot_Typ
), Loc
),
13177 Make_Selected_Component
(Loc
,
13178 Prefix
=> New_Occurrence_Of
(Obj_Ent
, Loc
),
13179 Selector_Name
=> Make_Identifier
(Loc
, Name_uObject
)));
13184 -- Step 3: Add discriminant renamings (if any)
13186 if Has_Discriminants
(Conc_Typ
) then
13191 D
:= First_Discriminant
(Conc_Typ
);
13192 while Present
(D
) loop
13194 -- Adjust the source location
13196 Set_Sloc
(Discriminal
(D
), Loc
);
13199 -- discr_name : discr_typ renames _object.discr_name;
13201 -- discr_name : discr_typ renames _task.discr_name;
13204 Make_Object_Renaming_Declaration
(Loc
,
13205 Defining_Identifier
=> Discriminal
(D
),
13206 Subtype_Mark
=> New_Occurrence_Of
(Etype
(D
), Loc
),
13208 Make_Selected_Component
(Loc
,
13209 Prefix
=> New_Occurrence_Of
(Obj_Ent
, Loc
),
13210 Selector_Name
=> Make_Identifier
(Loc
, Chars
(D
))));
13213 Next_Discriminant
(D
);
13218 -- Step 4: Add private component renamings (if any)
13220 if Is_Protected
then
13221 Def
:= Protected_Definition
(Parent
(Conc_Typ
));
13223 if Present
(Private_Declarations
(Def
)) then
13226 Comp_Id
: Entity_Id
;
13227 Decl_Id
: Entity_Id
;
13230 Comp
:= First
(Private_Declarations
(Def
));
13231 while Present
(Comp
) loop
13232 if Nkind
(Comp
) = N_Component_Declaration
then
13233 Comp_Id
:= Defining_Identifier
(Comp
);
13235 Make_Defining_Identifier
(Loc
, Chars
(Comp_Id
));
13237 -- Minimal decoration
13239 if Ekind
(Spec_Id
) = E_Function
then
13240 Set_Ekind
(Decl_Id
, E_Constant
);
13242 Set_Ekind
(Decl_Id
, E_Variable
);
13245 Set_Prival
(Comp_Id
, Decl_Id
);
13246 Set_Prival_Link
(Decl_Id
, Comp_Id
);
13247 Set_Is_Aliased
(Decl_Id
, Is_Aliased
(Comp_Id
));
13250 -- comp_name : comp_typ renames _object.comp_name;
13253 Make_Object_Renaming_Declaration
(Loc
,
13254 Defining_Identifier
=> Decl_Id
,
13256 New_Occurrence_Of
(Etype
(Comp_Id
), Loc
),
13258 Make_Selected_Component
(Loc
,
13260 New_Occurrence_Of
(Obj_Ent
, Loc
),
13262 Make_Identifier
(Loc
, Chars
(Comp_Id
))));
13272 -- Step 5: Add the declaration of the entry index and the associated
13273 -- type for barrier functions and entry families.
13275 if (Barrier
and then Family
)
13276 or else Ekind
(Spec_Id
) = E_Entry_Family
13279 E
: constant Entity_Id
:= Index_Object
(Spec_Id
);
13280 Index
: constant Entity_Id
:=
13281 Defining_Identifier
(
13282 Entry_Index_Specification
(
13283 Entry_Body_Formal_Part
(Body_Nod
)));
13284 Index_Con
: constant Entity_Id
:=
13285 Make_Defining_Identifier
(Loc
, Chars
(Index
));
13287 Index_Typ
: Entity_Id
;
13291 -- Minimal decoration
13293 Set_Ekind
(Index_Con
, E_Constant
);
13294 Set_Entry_Index_Constant
(Index
, Index_Con
);
13295 Set_Discriminal_Link
(Index_Con
, Index
);
13297 -- Retrieve the bounds of the entry family
13299 High
:= Type_High_Bound
(Etype
(Index
));
13300 Low
:= Type_Low_Bound
(Etype
(Index
));
13302 -- In the simple case the entry family is given by a subtype
13303 -- mark and the index constant has the same type.
13305 if Is_Entity_Name
(Original_Node
(
13306 Discrete_Subtype_Definition
(Parent
(Index
))))
13308 Index_Typ
:= Etype
(Index
);
13310 -- Otherwise a new subtype declaration is required
13313 High
:= Replace_Bound
(High
);
13314 Low
:= Replace_Bound
(Low
);
13316 Index_Typ
:= Make_Temporary
(Loc
, 'J');
13319 -- subtype Jnn is <Etype of Index> range Low .. High;
13322 Make_Subtype_Declaration
(Loc
,
13323 Defining_Identifier
=> Index_Typ
,
13324 Subtype_Indication
=>
13325 Make_Subtype_Indication
(Loc
,
13327 New_Occurrence_Of
(Base_Type
(Etype
(Index
)), Loc
),
13329 Make_Range_Constraint
(Loc
,
13330 Range_Expression
=>
13331 Make_Range
(Loc
, Low
, High
))));
13335 Set_Etype
(Index_Con
, Index_Typ
);
13337 -- Create the object which designates the index:
13338 -- J : constant Jnn :=
13339 -- Jnn'Val (_E - <index expr> + Jnn'Pos (Jnn'First));
13341 -- where Jnn is the subtype created above or the original type of
13342 -- the index, _E is a formal of the protected body subprogram and
13343 -- <index expr> is the index of the first family member.
13346 Make_Object_Declaration
(Loc
,
13347 Defining_Identifier
=> Index_Con
,
13348 Constant_Present
=> True,
13349 Object_Definition
=>
13350 New_Occurrence_Of
(Index_Typ
, Loc
),
13353 Make_Attribute_Reference
(Loc
,
13355 New_Occurrence_Of
(Index_Typ
, Loc
),
13356 Attribute_Name
=> Name_Val
,
13358 Expressions
=> New_List
(
13362 Make_Op_Subtract
(Loc
,
13364 New_Occurrence_Of
(E
, Loc
),
13366 Entry_Index_Expression
(Loc
,
13367 Defining_Identifier
(Body_Nod
),
13371 Make_Attribute_Reference
(Loc
,
13373 New_Occurrence_Of
(Index_Typ
, Loc
),
13374 Attribute_Name
=> Name_Pos
,
13375 Expressions
=> New_List
(
13376 Make_Attribute_Reference
(Loc
,
13378 New_Occurrence_Of
(Index_Typ
, Loc
),
13379 Attribute_Name
=> Name_First
)))))));
13383 end Install_Private_Data_Declarations
;
13385 -----------------------
13386 -- Is_Exception_Safe --
13387 -----------------------
13389 function Is_Exception_Safe
(Subprogram
: Node_Id
) return Boolean is
13391 function Has_Side_Effect
(N
: Node_Id
) return Boolean;
13392 -- Return True whenever encountering a subprogram call or raise
13393 -- statement of any kind in the sequence of statements
13395 ---------------------
13396 -- Has_Side_Effect --
13397 ---------------------
13399 -- What is this doing buried two levels down in exp_ch9. It seems like a
13400 -- generally useful function, and indeed there may be code duplication
13401 -- going on here ???
13403 function Has_Side_Effect
(N
: Node_Id
) return Boolean is
13407 function Is_Call_Or_Raise
(N
: Node_Id
) return Boolean;
13408 -- Indicate whether N is a subprogram call or a raise statement
13410 ----------------------
13411 -- Is_Call_Or_Raise --
13412 ----------------------
13414 function Is_Call_Or_Raise
(N
: Node_Id
) return Boolean is
13416 return Nkind_In
(N
, N_Procedure_Call_Statement
,
13419 N_Raise_Constraint_Error
,
13420 N_Raise_Program_Error
,
13421 N_Raise_Storage_Error
);
13422 end Is_Call_Or_Raise
;
13424 -- Start of processing for Has_Side_Effect
13428 while Present
(Stmt
) loop
13429 if Is_Call_Or_Raise
(Stmt
) then
13433 -- An object declaration can also contain a function call or a
13434 -- raise statement.
13436 if Nkind
(Stmt
) = N_Object_Declaration
then
13437 Expr
:= Expression
(Stmt
);
13439 if Present
(Expr
) and then Is_Call_Or_Raise
(Expr
) then
13448 end Has_Side_Effect
;
13450 -- Start of processing for Is_Exception_Safe
13453 -- When exceptions can't be propagated, the subprogram returns normally
13455 if No_Exception_Handlers_Set
then
13459 -- If the checks handled by the back end are not disabled, we cannot
13460 -- ensure that no exception will be raised.
13462 if not Access_Checks_Suppressed
(Empty
)
13463 or else not Discriminant_Checks_Suppressed
(Empty
)
13464 or else not Range_Checks_Suppressed
(Empty
)
13465 or else not Index_Checks_Suppressed
(Empty
)
13466 or else Opt
.Stack_Checking_Enabled
13471 if Has_Side_Effect
(First
(Declarations
(Subprogram
)))
13474 (First
(Statements
(Handled_Statement_Sequence
(Subprogram
))))
13480 end Is_Exception_Safe
;
13482 ---------------------------------
13483 -- Is_Potentially_Large_Family --
13484 ---------------------------------
13486 function Is_Potentially_Large_Family
13487 (Base_Index
: Entity_Id
;
13488 Conctyp
: Entity_Id
;
13490 Hi
: Node_Id
) return Boolean
13493 return Scope
(Base_Index
) = Standard_Standard
13494 and then Base_Index
= Base_Type
(Standard_Integer
)
13495 and then Has_Discriminants
(Conctyp
)
13497 Present
(Discriminant_Default_Value
(First_Discriminant
(Conctyp
)))
13499 (Denotes_Discriminant
(Lo
, True)
13501 Denotes_Discriminant
(Hi
, True));
13502 end Is_Potentially_Large_Family
;
13504 -------------------------------------
13505 -- Is_Private_Primitive_Subprogram --
13506 -------------------------------------
13508 function Is_Private_Primitive_Subprogram
(Id
: Entity_Id
) return Boolean is
13511 (Ekind
(Id
) = E_Function
or else Ekind
(Id
) = E_Procedure
)
13512 and then Is_Private_Primitive
(Id
);
13513 end Is_Private_Primitive_Subprogram
;
13519 function Index_Object
(Spec_Id
: Entity_Id
) return Entity_Id
is
13520 Bod_Subp
: constant Entity_Id
:= Protected_Body_Subprogram
(Spec_Id
);
13521 Formal
: Entity_Id
;
13524 Formal
:= First_Formal
(Bod_Subp
);
13525 while Present
(Formal
) loop
13527 -- Look for formal parameter _E
13529 if Chars
(Formal
) = Name_uE
then
13533 Next_Formal
(Formal
);
13536 -- A protected body subprogram should always have the parameter in
13539 raise Program_Error
;
13542 --------------------------------
13543 -- Make_Initialize_Protection --
13544 --------------------------------
13546 function Make_Initialize_Protection
13547 (Protect_Rec
: Entity_Id
) return List_Id
13549 Loc
: constant Source_Ptr
:= Sloc
(Protect_Rec
);
13552 Ptyp
: constant Node_Id
:=
13553 Corresponding_Concurrent_Type
(Protect_Rec
);
13555 L
: constant List_Id
:= New_List
;
13556 Has_Entry
: constant Boolean := Has_Entries
(Ptyp
);
13557 Prio_Type
: Entity_Id
;
13558 Prio_Var
: Entity_Id
:= Empty
;
13559 Restricted
: constant Boolean := Restricted_Profile
;
13562 -- We may need two calls to properly initialize the object, one to
13563 -- Initialize_Protection, and possibly one to Install_Handlers if we
13564 -- have a pragma Attach_Handler.
13566 -- Get protected declaration. In the case of a task type declaration,
13567 -- this is simply the parent of the protected type entity. In the single
13568 -- protected object declaration, this parent will be the implicit type,
13569 -- and we can find the corresponding single protected object declaration
13570 -- by searching forward in the declaration list in the tree.
13572 -- Is the test for N_Single_Protected_Declaration needed here??? Nodes
13573 -- of this type should have been removed during semantic analysis.
13575 Pdec
:= Parent
(Ptyp
);
13576 while not Nkind_In
(Pdec
, N_Protected_Type_Declaration
,
13577 N_Single_Protected_Declaration
)
13582 -- Build the parameter list for the call. Note that _Init is the name
13583 -- of the formal for the object to be initialized, which is the task
13584 -- value record itself.
13588 -- For lock-free implementation, skip initializations of the Protection
13591 if not Uses_Lock_Free
(Defining_Identifier
(Pdec
)) then
13592 -- Object parameter. This is a pointer to the object of type
13593 -- Protection used by the GNARL to control the protected object.
13596 Make_Attribute_Reference
(Loc
,
13598 Make_Selected_Component
(Loc
,
13599 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
13600 Selector_Name
=> Make_Identifier
(Loc
, Name_uObject
)),
13601 Attribute_Name
=> Name_Unchecked_Access
));
13603 -- Priority parameter. Set to Unspecified_Priority unless there is a
13604 -- Priority rep item, in which case we take the value from the pragma
13605 -- or attribute definition clause, or there is an Interrupt_Priority
13606 -- rep item and no Priority rep item, and we set the ceiling to
13607 -- Interrupt_Priority'Last, an implementation-defined value, see
13610 if Has_Rep_Item
(Ptyp
, Name_Priority
, Check_Parents
=> False) then
13612 Prio_Clause
: constant Node_Id
:=
13614 (Ptyp
, Name_Priority
, Check_Parents
=> False);
13621 if Nkind
(Prio_Clause
) = N_Pragma
then
13624 (First
(Pragma_Argument_Associations
(Prio_Clause
)));
13626 -- Get_Rep_Item returns either priority pragma.
13628 if Pragma_Name
(Prio_Clause
) = Name_Priority
then
13629 Prio_Type
:= RTE
(RE_Any_Priority
);
13631 Prio_Type
:= RTE
(RE_Interrupt_Priority
);
13634 -- Attribute definition clause Priority
13637 if Chars
(Prio_Clause
) = Name_Priority
then
13638 Prio_Type
:= RTE
(RE_Any_Priority
);
13640 Prio_Type
:= RTE
(RE_Interrupt_Priority
);
13643 Prio
:= Expression
(Prio_Clause
);
13646 -- Always create a locale variable to capture the priority.
13647 -- The priority is also passed to Install_Restriced_Handlers.
13648 -- Note that it is really necessary to create this variable
13649 -- explicitly. It might be thought that removing side effects
13650 -- would the appropriate approach, but that could generate
13651 -- declarations improperly placed in the enclosing scope.
13653 Prio_Var
:= Make_Temporary
(Loc
, 'R', Prio
);
13655 Make_Object_Declaration
(Loc
,
13656 Defining_Identifier
=> Prio_Var
,
13657 Object_Definition
=> New_Occurrence_Of
(Prio_Type
, Loc
),
13658 Expression
=> Relocate_Node
(Prio
)));
13660 Append_To
(Args
, New_Occurrence_Of
(Prio_Var
, Loc
));
13663 -- When no priority is specified but an xx_Handler pragma is, we
13664 -- default to System.Interrupts.Default_Interrupt_Priority, see
13667 elsif Has_Attach_Handler
(Ptyp
)
13668 or else Has_Interrupt_Handler
(Ptyp
)
13671 New_Occurrence_Of
(RTE
(RE_Default_Interrupt_Priority
), Loc
));
13673 -- Normal case, no priority or xx_Handler specified, default priority
13677 New_Occurrence_Of
(RTE
(RE_Unspecified_Priority
), Loc
));
13680 -- Test for Compiler_Info parameter. This parameter allows entry body
13681 -- procedures and barrier functions to be called from the runtime. It
13682 -- is a pointer to the record generated by the compiler to represent
13683 -- the protected object.
13685 -- A protected type without entries that covers an interface and
13686 -- overrides the abstract routines with protected procedures is
13687 -- considered equivalent to a protected type with entries in the
13688 -- context of dispatching select statements.
13690 -- Protected types with interrupt handlers (when not using a
13691 -- restricted profile) are also considered equivalent to protected
13692 -- types with entries.
13694 -- The types which are used (Static_Interrupt_Protection and
13695 -- Dynamic_Interrupt_Protection) are derived from Protection_Entries.
13698 Pkg_Id
: constant RTU_Id
:= Corresponding_Runtime_Package
(Ptyp
);
13700 Called_Subp
: RE_Id
;
13704 when System_Tasking_Protected_Objects_Entries
=>
13705 Called_Subp
:= RE_Initialize_Protection_Entries
;
13707 -- Argument Compiler_Info
13710 Make_Attribute_Reference
(Loc
,
13711 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
13712 Attribute_Name
=> Name_Address
));
13714 when System_Tasking_Protected_Objects_Single_Entry
=>
13715 Called_Subp
:= RE_Initialize_Protection_Entry
;
13717 -- Argument Compiler_Info
13720 Make_Attribute_Reference
(Loc
,
13721 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
13722 Attribute_Name
=> Name_Address
));
13724 when System_Tasking_Protected_Objects
=>
13725 Called_Subp
:= RE_Initialize_Protection
;
13728 raise Program_Error
;
13731 -- Entry_Bodies parameter. This is a pointer to an array of
13732 -- pointers to the entry body procedures and barrier functions of
13733 -- the object. If the protected type has no entries this object
13734 -- will not exist, in this case, pass a null (it can happen when
13735 -- there are protected interrupt handlers or interfaces).
13738 P_Arr
:= Entry_Bodies_Array
(Ptyp
);
13740 -- Argument Entry_Body (for single entry) or Entry_Bodies (for
13741 -- multiple entries).
13744 Make_Attribute_Reference
(Loc
,
13745 Prefix
=> New_Occurrence_Of
(P_Arr
, Loc
),
13746 Attribute_Name
=> Name_Unrestricted_Access
));
13748 if Pkg_Id
= System_Tasking_Protected_Objects_Entries
then
13750 -- Find index mapping function (clumsy but ok for now)
13752 while Ekind
(P_Arr
) /= E_Function
loop
13753 Next_Entity
(P_Arr
);
13757 Make_Attribute_Reference
(Loc
,
13758 Prefix
=> New_Occurrence_Of
(P_Arr
, Loc
),
13759 Attribute_Name
=> Name_Unrestricted_Access
));
13762 elsif Pkg_Id
= System_Tasking_Protected_Objects_Single_Entry
then
13764 -- This is the case where we have a protected object with
13765 -- interfaces and no entries, and the single entry restriction
13766 -- is in effect. We pass a null pointer for the entry
13767 -- parameter because there is no actual entry.
13769 Append_To
(Args
, Make_Null
(Loc
));
13771 elsif Pkg_Id
= System_Tasking_Protected_Objects_Entries
then
13773 -- This is the case where we have a protected object with no
13775 -- - either interrupt handlers with non restricted profile,
13777 -- Note that the types which are used for interrupt handlers
13778 -- (Static/Dynamic_Interrupt_Protection) are derived from
13779 -- Protection_Entries. We pass two null pointers because there
13780 -- is no actual entry, and the initialization procedure needs
13781 -- both Entry_Bodies and Find_Body_Index.
13783 Append_To
(Args
, Make_Null
(Loc
));
13784 Append_To
(Args
, Make_Null
(Loc
));
13788 Make_Procedure_Call_Statement
(Loc
,
13789 Name
=> New_Occurrence_Of
(RTE
(Called_Subp
), Loc
),
13790 Parameter_Associations
=> Args
));
13794 if Has_Attach_Handler
(Ptyp
) then
13796 -- We have a list of N Attach_Handler (ProcI, ExprI), and we have to
13797 -- make the following call:
13799 -- Install_Handlers (_object,
13800 -- ((Expr1, Proc1'access), ...., (ExprN, ProcN'access));
13802 -- or, in the case of Ravenscar:
13804 -- Install_Restricted_Handlers
13805 -- (Prio, (Expr1, Proc1'access), ...., (ExprN, ProcN'access));
13808 Args
: constant List_Id
:= New_List
;
13809 Table
: constant List_Id
:= New_List
;
13810 Ritem
: Node_Id
:= First_Rep_Item
(Ptyp
);
13813 -- Build the Priority parameter (only for ravenscar)
13817 -- Priority comes from a pragma
13819 if Present
(Prio_Var
) then
13820 Append_To
(Args
, New_Occurrence_Of
(Prio_Var
, Loc
));
13822 -- Priority is the default one
13827 (RTE
(RE_Default_Interrupt_Priority
), Loc
));
13831 -- Build the Attach_Handler table argument
13833 while Present
(Ritem
) loop
13834 if Nkind
(Ritem
) = N_Pragma
13835 and then Pragma_Name
(Ritem
) = Name_Attach_Handler
13838 Handler
: constant Node_Id
:=
13839 First
(Pragma_Argument_Associations
(Ritem
));
13841 Interrupt
: constant Node_Id
:= Next
(Handler
);
13842 Expr
: constant Node_Id
:= Expression
(Interrupt
);
13846 Make_Aggregate
(Loc
, Expressions
=> New_List
(
13847 Unchecked_Convert_To
13848 (RTE
(RE_System_Interrupt_Id
), Expr
),
13849 Make_Attribute_Reference
(Loc
,
13850 Prefix
=> Make_Selected_Component
(Loc
,
13851 Make_Identifier
(Loc
, Name_uInit
),
13852 Duplicate_Subexpr_No_Checks
13853 (Expression
(Handler
))),
13854 Attribute_Name
=> Name_Access
))));
13858 Next_Rep_Item
(Ritem
);
13861 -- Append the table argument we just built
13863 Append_To
(Args
, Make_Aggregate
(Loc
, Table
));
13865 -- Append the Install_Handlers (or Install_Restricted_Handlers)
13866 -- call to the statements.
13869 -- Call a simplified version of Install_Handlers to be used
13870 -- when the Ravenscar restrictions are in effect
13871 -- (Install_Restricted_Handlers).
13874 Make_Procedure_Call_Statement
(Loc
,
13877 (RTE
(RE_Install_Restricted_Handlers
), Loc
),
13878 Parameter_Associations
=> Args
));
13881 if not Uses_Lock_Free
(Defining_Identifier
(Pdec
)) then
13882 -- First, prepends the _object argument
13885 Make_Attribute_Reference
(Loc
,
13887 Make_Selected_Component
(Loc
,
13888 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
13890 Make_Identifier
(Loc
, Name_uObject
)),
13891 Attribute_Name
=> Name_Unchecked_Access
));
13894 -- Then, insert call to Install_Handlers
13897 Make_Procedure_Call_Statement
(Loc
,
13898 Name
=> New_Occurrence_Of
(RTE
(RE_Install_Handlers
), Loc
),
13899 Parameter_Associations
=> Args
));
13905 end Make_Initialize_Protection
;
13907 ---------------------------
13908 -- Make_Task_Create_Call --
13909 ---------------------------
13911 function Make_Task_Create_Call
(Task_Rec
: Entity_Id
) return Node_Id
is
13912 Loc
: constant Source_Ptr
:= Sloc
(Task_Rec
);
13922 Ttyp
:= Corresponding_Concurrent_Type
(Task_Rec
);
13923 Tnam
:= Chars
(Ttyp
);
13925 -- Get task declaration. In the case of a task type declaration, this is
13926 -- simply the parent of the task type entity. In the single task
13927 -- declaration, this parent will be the implicit type, and we can find
13928 -- the corresponding single task declaration by searching forward in the
13929 -- declaration list in the tree.
13931 -- Is the test for N_Single_Task_Declaration needed here??? Nodes of
13932 -- this type should have been removed during semantic analysis.
13934 Tdec
:= Parent
(Ttyp
);
13935 while not Nkind_In
(Tdec
, N_Task_Type_Declaration
,
13936 N_Single_Task_Declaration
)
13941 -- Now we can find the task definition from this declaration
13943 Tdef
:= Task_Definition
(Tdec
);
13945 -- Build the parameter list for the call. Note that _Init is the name
13946 -- of the formal for the object to be initialized, which is the task
13947 -- value record itself.
13951 -- Priority parameter. Set to Unspecified_Priority unless there is a
13952 -- Priority rep item, in which case we take the value from the rep item.
13954 if Has_Rep_Item
(Ttyp
, Name_Priority
, Check_Parents
=> False) then
13956 Make_Selected_Component
(Loc
,
13957 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
13958 Selector_Name
=> Make_Identifier
(Loc
, Name_uPriority
)));
13961 New_Occurrence_Of
(RTE
(RE_Unspecified_Priority
), Loc
));
13964 -- Optional Stack parameter
13966 if Restricted_Profile
then
13968 -- If the stack has been preallocated by the expander then
13969 -- pass its address. Otherwise, pass a null address.
13971 if Preallocated_Stacks_On_Target
then
13973 Make_Attribute_Reference
(Loc
,
13975 Make_Selected_Component
(Loc
,
13976 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
13977 Selector_Name
=> Make_Identifier
(Loc
, Name_uStack
)),
13978 Attribute_Name
=> Name_Address
));
13982 New_Occurrence_Of
(RTE
(RE_Null_Address
), Loc
));
13986 -- Size parameter. If no Storage_Size pragma is present, then
13987 -- the size is taken from the taskZ variable for the type, which
13988 -- is either Unspecified_Size, or has been reset by the use of
13989 -- a Storage_Size attribute definition clause. If a pragma is
13990 -- present, then the size is taken from the _Size field of the
13991 -- task value record, which was set from the pragma value.
13994 and then Has_Storage_Size_Pragma
(Tdef
)
13997 Make_Selected_Component
(Loc
,
13998 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
13999 Selector_Name
=> Make_Identifier
(Loc
, Name_uSize
)));
14003 New_Occurrence_Of
(Storage_Size_Variable
(Ttyp
), Loc
));
14006 -- Task_Info parameter. Set to Unspecified_Task_Info unless there is a
14007 -- Task_Info pragma, in which case we take the value from the pragma.
14009 if Has_Rep_Pragma
(Ttyp
, Name_Task_Info
, Check_Parents
=> False) then
14011 Make_Selected_Component
(Loc
,
14012 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
14013 Selector_Name
=> Make_Identifier
(Loc
, Name_uTask_Info
)));
14017 New_Occurrence_Of
(RTE
(RE_Unspecified_Task_Info
), Loc
));
14020 -- CPU parameter. Set to Unspecified_CPU unless there is a CPU rep item,
14021 -- in which case we take the value from the rep item. The parameter is
14022 -- passed as an Integer because in the case of unspecified CPU the
14023 -- value is not in the range of CPU_Range.
14025 if Has_Rep_Item
(Ttyp
, Name_CPU
, Check_Parents
=> False) then
14027 Convert_To
(Standard_Integer
,
14028 Make_Selected_Component
(Loc
,
14029 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
14030 Selector_Name
=> Make_Identifier
(Loc
, Name_uCPU
))));
14033 New_Occurrence_Of
(RTE
(RE_Unspecified_CPU
), Loc
));
14036 if not Restricted_Profile
then
14038 -- Deadline parameter. If no Relative_Deadline pragma is present,
14039 -- then the deadline is Time_Span_Zero. If a pragma is present, then
14040 -- the deadline is taken from the _Relative_Deadline field of the
14041 -- task value record, which was set from the pragma value. Note that
14042 -- this parameter must not be generated for the restricted profiles
14043 -- since Ravenscar does not allow deadlines.
14045 -- Case where pragma Relative_Deadline applies: use given value
14048 and then Has_Relative_Deadline_Pragma
(Tdef
)
14051 Make_Selected_Component
(Loc
,
14053 Make_Identifier
(Loc
, Name_uInit
),
14055 Make_Identifier
(Loc
, Name_uRelative_Deadline
)));
14057 -- No pragma Relative_Deadline apply to the task
14061 New_Occurrence_Of
(RTE
(RE_Time_Span_Zero
), Loc
));
14064 -- Dispatching_Domain parameter. If no Dispatching_Domain rep item is
14065 -- present, then the dispatching domain is null. If a rep item is
14066 -- present, then the dispatching domain is taken from the
14067 -- _Dispatching_Domain field of the task value record, which was set
14068 -- from the rep item value. Note that this parameter must not be
14069 -- generated for the restricted profiles since Ravenscar does not
14070 -- allow dispatching domains.
14072 -- Case where Dispatching_Domain rep item applies: use given value
14075 (Ttyp
, Name_Dispatching_Domain
, Check_Parents
=> False)
14078 Make_Selected_Component
(Loc
,
14080 Make_Identifier
(Loc
, Name_uInit
),
14082 Make_Identifier
(Loc
, Name_uDispatching_Domain
)));
14084 -- No pragma or aspect Dispatching_Domain apply to the task
14087 Append_To
(Args
, Make_Null
(Loc
));
14090 -- Number of entries. This is an expression of the form:
14092 -- n + _Init.a'Length + _Init.a'B'Length + ...
14094 -- where a,b... are the entry family names for the task definition
14097 Build_Entry_Count_Expression
14102 (Parent
(Corresponding_Record_Type
(Ttyp
))))),
14104 Append_To
(Args
, Ecount
);
14106 -- Master parameter. This is a reference to the _Master parameter of
14107 -- the initialization procedure, except in the case of the pragma
14108 -- Restrictions (No_Task_Hierarchy) where the value is fixed to
14109 -- System.Tasking.Library_Task_Level.
14111 if Restriction_Active
(No_Task_Hierarchy
) = False then
14112 Append_To
(Args
, Make_Identifier
(Loc
, Name_uMaster
));
14115 New_Occurrence_Of
(RTE
(RE_Library_Task_Level
), Loc
));
14119 -- State parameter. This is a pointer to the task body procedure. The
14120 -- required value is obtained by taking 'Unrestricted_Access of the task
14121 -- body procedure and converting it (with an unchecked conversion) to
14122 -- the type required by the task kernel. For further details, see the
14123 -- description of Expand_N_Task_Body. We use 'Unrestricted_Access rather
14124 -- than 'Address in order to avoid creating trampolines.
14127 Body_Proc
: constant Node_Id
:= Get_Task_Body_Procedure
(Ttyp
);
14128 Subp_Ptr_Typ
: constant Node_Id
:=
14129 Create_Itype
(E_Access_Subprogram_Type
, Tdec
);
14130 Ref
: constant Node_Id
:= Make_Itype_Reference
(Loc
);
14133 Set_Directly_Designated_Type
(Subp_Ptr_Typ
, Body_Proc
);
14134 Set_Etype
(Subp_Ptr_Typ
, Subp_Ptr_Typ
);
14136 -- Be sure to freeze a reference to the access-to-subprogram type,
14137 -- otherwise gigi will complain that it's in the wrong scope, because
14138 -- it's actually inside the init procedure for the record type that
14139 -- corresponds to the task type.
14141 -- This processing is causing a crash in the .NET/JVM back ends that
14142 -- is not yet understood, so skip it in these cases ???
14144 if VM_Target
= No_VM
then
14145 Set_Itype
(Ref
, Subp_Ptr_Typ
);
14146 Append_Freeze_Action
(Task_Rec
, Ref
);
14149 Unchecked_Convert_To
(RTE
(RE_Task_Procedure_Access
),
14150 Make_Qualified_Expression
(Loc
,
14151 Subtype_Mark
=> New_Occurrence_Of
(Subp_Ptr_Typ
, Loc
),
14153 Make_Attribute_Reference
(Loc
,
14155 New_Occurrence_Of
(Body_Proc
, Loc
),
14156 Attribute_Name
=> Name_Unrestricted_Access
))));
14158 -- For the .NET/JVM cases revert to the original code below ???
14162 Unchecked_Convert_To
(RTE
(RE_Task_Procedure_Access
),
14163 Make_Attribute_Reference
(Loc
,
14165 New_Occurrence_Of
(Body_Proc
, Loc
),
14166 Attribute_Name
=> Name_Address
)));
14170 -- Discriminants parameter. This is just the address of the task
14171 -- value record itself (which contains the discriminant values
14174 Make_Attribute_Reference
(Loc
,
14175 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
14176 Attribute_Name
=> Name_Address
));
14178 -- Elaborated parameter. This is an access to the elaboration Boolean
14181 Make_Attribute_Reference
(Loc
,
14182 Prefix
=> Make_Identifier
(Loc
, New_External_Name
(Tnam
, 'E')),
14183 Attribute_Name
=> Name_Unchecked_Access
));
14185 -- Add Chain parameter (not done for sequential elaboration policy, see
14186 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
14188 if Partition_Elaboration_Policy
/= 'S' then
14189 Append_To
(Args
, Make_Identifier
(Loc
, Name_uChain
));
14192 -- Task name parameter. Take this from the _Task_Id parameter to the
14193 -- init call unless there is a Task_Name pragma, in which case we take
14194 -- the value from the pragma.
14196 if Has_Rep_Pragma
(Ttyp
, Name_Task_Name
, Check_Parents
=> False) then
14197 -- Copy expression in full, because it may be dynamic and have
14204 (Pragma_Argument_Associations
14206 (Ttyp
, Name_Task_Name
, Check_Parents
=> False))))));
14209 Append_To
(Args
, Make_Identifier
(Loc
, Name_uTask_Name
));
14212 -- Created_Task parameter. This is the _Task_Id field of the task
14216 Make_Selected_Component
(Loc
,
14217 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
14218 Selector_Name
=> Make_Identifier
(Loc
, Name_uTask_Id
)));
14224 if Restricted_Profile
then
14225 if Partition_Elaboration_Policy
= 'S' then
14226 Create_RE
:= RE_Create_Restricted_Task_Sequential
;
14228 Create_RE
:= RE_Create_Restricted_Task
;
14231 Create_RE
:= RE_Create_Task
;
14234 Name
:= New_Occurrence_Of
(RTE
(Create_RE
), Loc
);
14238 Make_Procedure_Call_Statement
(Loc
,
14240 Parameter_Associations
=> Args
);
14241 end Make_Task_Create_Call
;
14243 ------------------------------
14244 -- Next_Protected_Operation --
14245 ------------------------------
14247 function Next_Protected_Operation
(N
: Node_Id
) return Node_Id
is
14251 Next_Op
:= Next
(N
);
14252 while Present
(Next_Op
)
14253 and then not Nkind_In
(Next_Op
, N_Subprogram_Body
, N_Entry_Body
)
14259 end Next_Protected_Operation
;
14261 ---------------------
14262 -- Null_Statements --
14263 ---------------------
14265 function Null_Statements
(Stats
: List_Id
) return Boolean is
14269 Stmt
:= First
(Stats
);
14270 while Nkind
(Stmt
) /= N_Empty
14271 and then (Nkind_In
(Stmt
, N_Null_Statement
, N_Label
)
14273 (Nkind
(Stmt
) = N_Pragma
14275 Nam_In
(Pragma_Name
(Stmt
), Name_Unreferenced
,
14282 return Nkind
(Stmt
) = N_Empty
;
14283 end Null_Statements
;
14285 --------------------------
14286 -- Parameter_Block_Pack --
14287 --------------------------
14289 function Parameter_Block_Pack
14291 Blk_Typ
: Entity_Id
;
14295 Stmts
: List_Id
) return Node_Id
14297 Actual
: Entity_Id
;
14298 Expr
: Node_Id
:= Empty
;
14299 Formal
: Entity_Id
;
14300 Has_Param
: Boolean := False;
14303 Temp_Asn
: Node_Id
;
14304 Temp_Nam
: Node_Id
;
14307 Actual
:= First
(Actuals
);
14308 Formal
:= Defining_Identifier
(First
(Formals
));
14309 Params
:= New_List
;
14311 while Present
(Actual
) loop
14312 if Is_By_Copy_Type
(Etype
(Actual
)) then
14314 -- Jnn : aliased <formal-type>
14316 Temp_Nam
:= Make_Temporary
(Loc
, 'J');
14319 Make_Object_Declaration
(Loc
,
14322 Defining_Identifier
=>
14324 Object_Definition
=>
14325 New_Occurrence_Of
(Etype
(Formal
), Loc
)));
14327 if Ekind
(Formal
) /= E_Out_Parameter
then
14333 New_Occurrence_Of
(Temp_Nam
, Loc
);
14335 Set_Assignment_OK
(Temp_Asn
);
14338 Make_Assignment_Statement
(Loc
,
14342 New_Copy_Tree
(Actual
)));
14346 -- Jnn'unchecked_access
14349 Make_Attribute_Reference
(Loc
,
14351 Name_Unchecked_Access
,
14353 New_Occurrence_Of
(Temp_Nam
, Loc
)));
14357 -- The controlling parameter is omitted
14360 if not Is_Controlling_Actual
(Actual
) then
14362 Make_Reference
(Loc
, New_Copy_Tree
(Actual
)));
14368 Next_Actual
(Actual
);
14369 Next_Formal_With_Extras
(Formal
);
14373 Expr
:= Make_Aggregate
(Loc
, Params
);
14378 -- J1'unchecked_access;
14379 -- <actual2>'reference;
14382 P
:= Make_Temporary
(Loc
, 'P');
14385 Make_Object_Declaration
(Loc
,
14386 Defining_Identifier
=>
14388 Object_Definition
=>
14389 New_Occurrence_Of
(Blk_Typ
, Loc
),
14394 end Parameter_Block_Pack
;
14396 ----------------------------
14397 -- Parameter_Block_Unpack --
14398 ----------------------------
14400 function Parameter_Block_Unpack
14404 Formals
: List_Id
) return List_Id
14406 Actual
: Entity_Id
;
14408 Formal
: Entity_Id
;
14409 Has_Asnmt
: Boolean := False;
14410 Result
: constant List_Id
:= New_List
;
14413 Actual
:= First
(Actuals
);
14414 Formal
:= Defining_Identifier
(First
(Formals
));
14415 while Present
(Actual
) loop
14416 if Is_By_Copy_Type
(Etype
(Actual
))
14417 and then Ekind
(Formal
) /= E_In_Parameter
14420 -- <actual> := P.<formal>;
14423 Make_Assignment_Statement
(Loc
,
14427 Make_Explicit_Dereference
(Loc
,
14428 Make_Selected_Component
(Loc
,
14430 New_Occurrence_Of
(P
, Loc
),
14432 Make_Identifier
(Loc
, Chars
(Formal
)))));
14434 Set_Assignment_OK
(Name
(Asnmt
));
14435 Append_To
(Result
, Asnmt
);
14440 Next_Actual
(Actual
);
14441 Next_Formal_With_Extras
(Formal
);
14447 return New_List
(Make_Null_Statement
(Loc
));
14449 end Parameter_Block_Unpack
;
14451 ----------------------
14452 -- Set_Discriminals --
14453 ----------------------
14455 procedure Set_Discriminals
(Dec
: Node_Id
) is
14458 D_Minal
: Entity_Id
;
14461 pragma Assert
(Nkind
(Dec
) = N_Protected_Type_Declaration
);
14462 Pdef
:= Defining_Identifier
(Dec
);
14464 if Has_Discriminants
(Pdef
) then
14465 D
:= First_Discriminant
(Pdef
);
14466 while Present
(D
) loop
14468 Make_Defining_Identifier
(Sloc
(D
),
14469 Chars
=> New_External_Name
(Chars
(D
), 'D'));
14471 Set_Ekind
(D_Minal
, E_Constant
);
14472 Set_Etype
(D_Minal
, Etype
(D
));
14473 Set_Scope
(D_Minal
, Pdef
);
14474 Set_Discriminal
(D
, D_Minal
);
14475 Set_Discriminal_Link
(D_Minal
, D
);
14477 Next_Discriminant
(D
);
14480 end Set_Discriminals
;
14482 -----------------------
14483 -- Trivial_Accept_OK --
14484 -----------------------
14486 function Trivial_Accept_OK
return Boolean is
14488 case Opt
.Task_Dispatching_Policy
is
14490 -- If we have the default task dispatching policy in effect, we can
14491 -- definitely do the optimization (one way of looking at this is to
14492 -- think of the formal definition of the default policy being allowed
14493 -- to run any task it likes after a rendezvous, so even if notionally
14494 -- a full rescheduling occurs, we can say that our dispatching policy
14495 -- (i.e. the default dispatching policy) reorders the queue to be the
14496 -- same as just before the call.
14501 -- FIFO_Within_Priorities certainly does not permit this
14502 -- optimization since the Rendezvous is a scheduling action that may
14503 -- require some other task to be run.
14508 -- For now, disallow the optimization for all other policies. This
14509 -- may be over-conservative, but it is certainly not incorrect.
14515 end Trivial_Accept_OK
;