1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2009, Free Software Foundation, Inc. --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 ------------------------------------------------------------------------------
26 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_Ch11
; use Exp_Ch11
;
33 with Exp_Ch6
; use Exp_Ch6
;
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_Ch11
; use Sem_Ch11
;
55 with Sem_Elab
; use Sem_Elab
;
56 with Sem_Eval
; use Sem_Eval
;
57 with Sem_Res
; use Sem_Res
;
58 with Sem_Util
; use Sem_Util
;
59 with Sinfo
; use Sinfo
;
60 with Snames
; use Snames
;
61 with Stand
; use Stand
;
62 with Stringt
; use Stringt
;
63 with Targparm
; use Targparm
;
64 with Tbuild
; use Tbuild
;
65 with Uintp
; use Uintp
;
67 package body Exp_Ch9
is
69 -- The following constant establishes the upper bound for the index of
70 -- an entry family. It is used to limit the allocated size of protected
71 -- types with defaulted discriminant of an integer type, when the bound
72 -- of some entry family depends on a discriminant. The limitation to
73 -- entry families of 128K should be reasonable in all cases, and is a
74 -- documented implementation restriction. It will be lifted when protected
75 -- entry families are re-implemented as a single ordered queue.
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_Entry_Count_Expression
132 (Concurrent_Type
: Node_Id
;
133 Component_List
: List_Id
;
134 Loc
: Source_Ptr
) return Node_Id
;
135 -- Compute number of entries for concurrent object. This is a count of
136 -- simple entries, followed by an expression that computes the length
137 -- of the range of each entry family. A single array with that size is
138 -- allocated for each concurrent object of the type.
140 function Build_Parameter_Block
144 Decls
: List_Id
) return Entity_Id
;
145 -- Generate an access type for each actual parameter in the list Actuals.
146 -- Create an encapsulating record that contains all the actuals and return
147 -- its type. Generate:
148 -- type Ann1 is access all <actual1-type>
150 -- type AnnN is access all <actualN-type>
151 -- type Pnn is record
157 procedure Build_Wrapper_Bodies
161 -- Ada 2005 (AI-345): Typ is either a concurrent type or the corresponding
162 -- record of a concurrent type. N is the insertion node where all bodies
163 -- will be placed. This routine builds the bodies of the subprograms which
164 -- serve as an indirection mechanism to overriding primitives of concurrent
165 -- types, entries and protected procedures. Any new body is analyzed.
167 procedure Build_Wrapper_Specs
171 -- Ada 2005 (AI-345): Typ is either a concurrent type or the corresponding
172 -- record of a concurrent type. N is the insertion node where all specs
173 -- will be placed. This routine builds the specs of the subprograms which
174 -- serve as an indirection mechanism to overriding primitives of concurrent
175 -- types, entries and protected procedures. Any new spec is analyzed.
177 function Build_Find_Body_Index
(Typ
: Entity_Id
) return Node_Id
;
178 -- Build the function that translates the entry index in the call
179 -- (which depends on the size of entry families) into an index into the
180 -- Entry_Bodies_Array, to determine the body and barrier function used
181 -- in a protected entry call. A pointer to this function appears in every
184 function Build_Find_Body_Index_Spec
(Typ
: Entity_Id
) return Node_Id
;
185 -- Build subprogram declaration for previous one
187 function Build_Protected_Entry
190 Pid
: Node_Id
) return Node_Id
;
191 -- Build the procedure implementing the statement sequence of the specified
194 function Build_Protected_Entry_Specification
197 Ent_Id
: Entity_Id
) return Node_Id
;
198 -- Build a specification for the procedure implementing the statements of
199 -- the specified entry body. Add attributes associating it with the entry
200 -- defining identifier Ent_Id.
202 function Build_Protected_Spec
204 Obj_Type
: Entity_Id
;
206 Unprotected
: Boolean := False) return List_Id
;
207 -- Utility shared by Build_Protected_Sub_Spec and Expand_Access_Protected_
208 -- Subprogram_Type. Builds signature of protected subprogram, adding the
209 -- formal that corresponds to the object itself. For an access to protected
210 -- subprogram, there is no object type to specify, so the parameter has
211 -- type Address and mode In. An indirect call through such a pointer will
212 -- convert the address to a reference to the actual object. The object is
213 -- a limited record and therefore a by_reference type.
215 function Build_Protected_Subprogram_Body
218 N_Op_Spec
: Node_Id
) return Node_Id
;
219 -- This function is used to construct the protected version of a protected
220 -- subprogram. Its statement sequence first defers abort, then locks
221 -- the associated protected object, and then enters a block that contains
222 -- a call to the unprotected version of the subprogram (for details, see
223 -- Build_Unprotected_Subprogram_Body). This block statement requires
224 -- a cleanup handler that unlocks the object in all cases.
225 -- (see Exp_Ch7.Expand_Cleanup_Actions).
227 function Build_Selected_Name
229 Selector
: Entity_Id
;
230 Append_Char
: Character := ' ') return Name_Id
;
231 -- Build a name in the form of Prefix__Selector, with an optional
232 -- character appended. This is used for internal subprograms generated
233 -- for operations of protected types, including barrier functions.
234 -- For the subprograms generated for entry bodies and entry barriers,
235 -- the generated name includes a sequence number that makes names
236 -- unique in the presence of entry overloading. This is necessary
237 -- because entry body procedures and barrier functions all have the
240 procedure Build_Simple_Entry_Call
245 -- Some comments here would be useful ???
247 function Build_Task_Proc_Specification
(T
: Entity_Id
) return Node_Id
;
248 -- This routine constructs a specification for the procedure that we will
249 -- build for the task body for task type T. The spec has the form:
251 -- procedure tnameB (_Task : access tnameV);
253 -- where name is the character name taken from the task type entity that
254 -- is passed as the argument to the procedure, and tnameV is the task
255 -- value type that is associated with the task type.
257 function Build_Unprotected_Subprogram_Body
259 Pid
: Node_Id
) return Node_Id
;
260 -- This routine constructs the unprotected version of a protected
261 -- subprogram body, which is contains all of the code in the
262 -- original, unexpanded body. This is the version of the protected
263 -- subprogram that is called from all protected operations on the same
264 -- object, including the protected version of the same subprogram.
266 procedure Collect_Entry_Families
269 Current_Node
: in out Node_Id
;
270 Conctyp
: Entity_Id
);
271 -- For each entry family in a concurrent type, create an anonymous array
272 -- type of the right size, and add a component to the corresponding_record.
274 function Concurrent_Object
275 (Spec_Id
: Entity_Id
;
276 Conc_Typ
: Entity_Id
) return Entity_Id
;
277 -- Given a subprogram entity Spec_Id and concurrent type Conc_Typ, return
278 -- the entity associated with the concurrent object in the Protected_Body_
279 -- Subprogram or the Task_Body_Procedure of Spec_Id. The returned entity
280 -- denotes formal parameter _O, _object or _task.
282 function Copy_Result_Type
(Res
: Node_Id
) return Node_Id
;
283 -- Copy the result type of a function specification, when building the
284 -- internal operation corresponding to a protected function, or when
285 -- expanding an access to protected function. If the result is an anonymous
286 -- access to subprogram itself, we need to create a new signature with the
287 -- same parameter names and the same resolved types, but with new entities
290 procedure Debug_Private_Data_Declarations
(Decls
: List_Id
);
291 -- Decls is a list which may contain the declarations created by Install_
292 -- Private_Data_Declarations. All generated entities are marked as needing
293 -- debug info and debug nodes are manually generation where necessary. This
294 -- step of the expansion must to be done after private data has been moved
295 -- to its final resting scope to ensure proper visibility of debug objects.
297 function Family_Offset
302 Cap
: Boolean) return Node_Id
;
303 -- Compute (Hi - Lo) for two entry family indices. Hi is the index in
304 -- an accept statement, or the upper bound in the discrete subtype of
305 -- an entry declaration. Lo is the corresponding lower bound. Ttyp is
306 -- the concurrent type of the entry. If Cap is true, the result is
307 -- capped according to Entry_Family_Bound.
314 Cap
: Boolean) return Node_Id
;
315 -- Compute (Hi - Lo) + 1 Max 0, to determine the number of entries in
316 -- a family, and handle properly the superflat case. This is equivalent
317 -- to the use of 'Length on the index type, but must use Family_Offset
318 -- to handle properly the case of bounds that depend on discriminants.
319 -- If Cap is true, the result is capped according to Entry_Family_Bound.
321 procedure Extract_Dispatching_Call
323 Call_Ent
: out Entity_Id
;
324 Object
: out Entity_Id
;
325 Actuals
: out List_Id
;
326 Formals
: out List_Id
);
327 -- Given a dispatching call, extract the entity of the name of the call,
328 -- its object parameter, its actual parameters and the formal parameters
329 -- of the overridden interface-level version.
331 procedure Extract_Entry
333 Concval
: out Node_Id
;
335 Index
: out Node_Id
);
336 -- Given an entry call, returns the associated concurrent object,
337 -- the entry name, and the entry family index.
339 function Find_Task_Or_Protected_Pragma
341 P
: Name_Id
) return Node_Id
;
342 -- Searches the task or protected definition T for the first occurrence
343 -- of the pragma whose name is given by P. The caller has ensured that
344 -- the pragma is present in the task definition. A special case is that
345 -- when P is Name_uPriority, the call will also find Interrupt_Priority.
346 -- ??? Should be implemented with the rep item chain mechanism.
348 function Index_Object
(Spec_Id
: Entity_Id
) return Entity_Id
;
349 -- Given a subprogram identifier, return the entity which is associated
350 -- with the protection entry index in the Protected_Body_Subprogram or the
351 -- Task_Body_Procedure of Spec_Id. The returned entity denotes formal
354 function Is_Potentially_Large_Family
355 (Base_Index
: Entity_Id
;
358 Hi
: Node_Id
) return Boolean;
360 function Is_Private_Primitive_Subprogram
(Id
: Entity_Id
) return Boolean;
361 -- Determine whether Id is a function or a procedure and is marked as a
362 -- private primitive.
364 function Null_Statements
(Stats
: List_Id
) return Boolean;
365 -- Used to check DO-END sequence. Checks for equivalent of DO NULL; END.
366 -- Allows labels, and pragma Warnings/Unreferenced in the sequence as
367 -- well to still count as null. Returns True for a null sequence. The
368 -- argument is the list of statements from the DO-END sequence.
370 function Parameter_Block_Pack
376 Stmts
: List_Id
) return Entity_Id
;
377 -- Set the components of the generated parameter block with the values of
378 -- the actual parameters. Generate aliased temporaries to capture the
379 -- values for types that are passed by copy. Otherwise generate a reference
380 -- to the actual's value. Return the address of the aggregate block.
382 -- Jnn1 : alias <formal-type1>;
383 -- Jnn1 := <actual1>;
386 -- Jnn1'unchecked_access;
387 -- <actual2>'reference;
390 function Parameter_Block_Unpack
394 Formals
: List_Id
) return List_Id
;
395 -- Retrieve the values of the components from the parameter block and
396 -- assign then to the original actual parameters. Generate:
397 -- <actual1> := P.<formal1>;
399 -- <actualN> := P.<formalN>;
401 function Trivial_Accept_OK
return Boolean;
402 -- If there is no DO-END block for an accept, or if the DO-END block has
403 -- only null statements, then it is possible to do the Rendezvous with much
404 -- less overhead using the Accept_Trivial routine in the run-time library.
405 -- However, this is not always a valid optimization. Whether it is valid or
406 -- not depends on the Task_Dispatching_Policy. The issue is whether a full
407 -- rescheduling action is required or not. In FIFO_Within_Priorities, such
408 -- a rescheduling is required, so this optimization is not allowed. This
409 -- function returns True if the optimization is permitted.
411 -----------------------------
412 -- Actual_Index_Expression --
413 -----------------------------
415 function Actual_Index_Expression
419 Tsk
: Entity_Id
) return Node_Id
421 Ttyp
: constant Entity_Id
:= Etype
(Tsk
);
429 function Actual_Family_Offset
(Hi
, Lo
: Node_Id
) return Node_Id
;
430 -- Compute difference between bounds of entry family
432 --------------------------
433 -- Actual_Family_Offset --
434 --------------------------
436 function Actual_Family_Offset
(Hi
, Lo
: Node_Id
) return Node_Id
is
438 function Actual_Discriminant_Ref
(Bound
: Node_Id
) return Node_Id
;
439 -- Replace a reference to a discriminant with a selected component
440 -- denoting the discriminant of the target task.
442 -----------------------------
443 -- Actual_Discriminant_Ref --
444 -----------------------------
446 function Actual_Discriminant_Ref
(Bound
: Node_Id
) return Node_Id
is
447 Typ
: constant Entity_Id
:= Etype
(Bound
);
451 if not Is_Entity_Name
(Bound
)
452 or else Ekind
(Entity
(Bound
)) /= E_Discriminant
454 if Nkind
(Bound
) = N_Attribute_Reference
then
457 B
:= New_Copy_Tree
(Bound
);
462 Make_Selected_Component
(Sloc
,
463 Prefix
=> New_Copy_Tree
(Tsk
),
464 Selector_Name
=> New_Occurrence_Of
(Entity
(Bound
), Sloc
));
466 Analyze_And_Resolve
(B
, Typ
);
470 Make_Attribute_Reference
(Sloc
,
471 Attribute_Name
=> Name_Pos
,
472 Prefix
=> New_Occurrence_Of
(Etype
(Bound
), Sloc
),
473 Expressions
=> New_List
(B
));
474 end Actual_Discriminant_Ref
;
476 -- Start of processing for Actual_Family_Offset
480 Make_Op_Subtract
(Sloc
,
481 Left_Opnd
=> Actual_Discriminant_Ref
(Hi
),
482 Right_Opnd
=> Actual_Discriminant_Ref
(Lo
));
483 end Actual_Family_Offset
;
485 -- Start of processing for Actual_Index_Expression
488 -- The queues of entries and entry families appear in textual order in
489 -- the associated record. The entry index is computed as the sum of the
490 -- number of queues for all entries that precede the designated one, to
491 -- which is added the index expression, if this expression denotes a
492 -- member of a family.
494 -- The following is a place holder for the count of simple entries
496 Num
:= Make_Integer_Literal
(Sloc
, 1);
498 -- We construct an expression which is a series of addition operations.
499 -- See comments in Entry_Index_Expression, which is identical in
502 if Present
(Index
) then
503 S
:= Etype
(Discrete_Subtype_Definition
(Declaration_Node
(Ent
)));
510 Actual_Family_Offset
(
511 Make_Attribute_Reference
(Sloc
,
512 Attribute_Name
=> Name_Pos
,
513 Prefix
=> New_Reference_To
(Base_Type
(S
), Sloc
),
514 Expressions
=> New_List
(Relocate_Node
(Index
))),
515 Type_Low_Bound
(S
)));
520 -- Now add lengths of preceding entries and entry families
522 Prev
:= First_Entity
(Ttyp
);
524 while Chars
(Prev
) /= Chars
(Ent
)
525 or else (Ekind
(Prev
) /= Ekind
(Ent
))
526 or else not Sem_Ch6
.Type_Conformant
(Ent
, Prev
)
528 if Ekind
(Prev
) = E_Entry
then
529 Set_Intval
(Num
, Intval
(Num
) + 1);
531 elsif Ekind
(Prev
) = E_Entry_Family
then
533 Etype
(Discrete_Subtype_Definition
(Declaration_Node
(Prev
)));
535 -- The need for the following full view retrieval stems from
536 -- this complex case of nested generics and tasking:
539 -- type Formal_Index is range <>;
542 -- type Index is private;
549 -- type Index is new Formal_Index range 1 .. 10;
552 -- package body Outer is
554 -- entry Fam (Index); -- (2)
557 -- package body Inner is -- (3)
565 -- We are currently building the index expression for the entry
566 -- call "T.E" (1). Part of the expansion must mention the range
567 -- of the discrete type "Index" (2) of entry family "Fam".
568 -- However only the private view of type "Index" is available to
569 -- the inner generic (3) because there was no prior mention of
570 -- the type inside "Inner". This visibility requirement is
571 -- implicit and cannot be detected during the construction of
572 -- the generic trees and needs special handling.
575 and then Is_Private_Type
(S
)
576 and then Present
(Full_View
(S
))
581 Lo
:= Type_Low_Bound
(S
);
582 Hi
:= Type_High_Bound
(S
);
590 Actual_Family_Offset
(Hi
, Lo
),
592 Make_Integer_Literal
(Sloc
, 1)));
594 -- Other components are anonymous types to be ignored
604 end Actual_Index_Expression
;
606 --------------------------
607 -- Add_Formal_Renamings --
608 --------------------------
610 procedure Add_Formal_Renamings
616 Ptr
: constant Entity_Id
:=
618 (Next
(First
(Parameter_Specifications
(Spec
))));
619 -- The name of the formal that holds the address of the parameter block
628 Formal
:= First_Formal
(Ent
);
629 while Present
(Formal
) loop
630 Comp
:= Entry_Component
(Formal
);
632 Make_Defining_Identifier
(Sloc
(Formal
),
633 Chars
=> Chars
(Formal
));
634 Set_Etype
(New_F
, Etype
(Formal
));
635 Set_Scope
(New_F
, Ent
);
637 -- Now we set debug info needed on New_F even though it does not
638 -- come from source, so that the debugger will get the right
639 -- information for these generated names.
641 Set_Debug_Info_Needed
(New_F
);
643 if Ekind
(Formal
) = E_In_Parameter
then
644 Set_Ekind
(New_F
, E_Constant
);
646 Set_Ekind
(New_F
, E_Variable
);
647 Set_Extra_Constrained
(New_F
, Extra_Constrained
(Formal
));
650 Set_Actual_Subtype
(New_F
, Actual_Subtype
(Formal
));
653 Make_Object_Renaming_Declaration
(Loc
,
654 Defining_Identifier
=> New_F
,
656 New_Reference_To
(Etype
(Formal
), Loc
),
658 Make_Explicit_Dereference
(Loc
,
659 Make_Selected_Component
(Loc
,
661 Unchecked_Convert_To
(Entry_Parameters_Type
(Ent
),
662 Make_Identifier
(Loc
, Chars
(Ptr
))),
664 New_Reference_To
(Comp
, Loc
))));
666 Append
(Decl
, Decls
);
667 Set_Renamed_Object
(Formal
, New_F
);
668 Next_Formal
(Formal
);
670 end Add_Formal_Renamings
;
672 ------------------------
673 -- Add_Object_Pointer --
674 ------------------------
676 procedure Add_Object_Pointer
678 Conc_Typ
: Entity_Id
;
681 Rec_Typ
: constant Entity_Id
:= Corresponding_Record_Type
(Conc_Typ
);
686 -- Create the renaming declaration for the Protection object of a
687 -- protected type. _Object is used by Complete_Entry_Body.
688 -- ??? An attempt to make this a renaming was unsuccessful.
690 -- Build the entity for the access type
693 Make_Defining_Identifier
(Loc
,
694 New_External_Name
(Chars
(Rec_Typ
), 'P'));
697 -- _object : poVP := poVP!O;
700 Make_Object_Declaration
(Loc
,
701 Defining_Identifier
=>
702 Make_Defining_Identifier
(Loc
, Name_uObject
),
704 New_Reference_To
(Obj_Ptr
, Loc
),
706 Unchecked_Convert_To
(Obj_Ptr
,
707 Make_Identifier
(Loc
, Name_uO
)));
708 Set_Debug_Info_Needed
(Defining_Identifier
(Decl
));
709 Prepend_To
(Decls
, Decl
);
712 -- type poVP is access poV;
715 Make_Full_Type_Declaration
(Loc
,
716 Defining_Identifier
=>
719 Make_Access_To_Object_Definition
(Loc
,
720 Subtype_Indication
=>
721 New_Reference_To
(Rec_Typ
, Loc
)));
722 Set_Debug_Info_Needed
(Defining_Identifier
(Decl
));
723 Prepend_To
(Decls
, Decl
);
724 end Add_Object_Pointer
;
726 -----------------------
727 -- Build_Accept_Body --
728 -----------------------
730 function Build_Accept_Body
(Astat
: Node_Id
) return Node_Id
is
731 Loc
: constant Source_Ptr
:= Sloc
(Astat
);
732 Stats
: constant Node_Id
:= Handled_Statement_Sequence
(Astat
);
739 -- At the end of the statement sequence, Complete_Rendezvous is called.
740 -- A label skipping the Complete_Rendezvous, and all other accept
741 -- processing, has already been added for the expansion of requeue
742 -- statements. The Sloc is copied from the last statement since it
743 -- is really part of this last statement.
747 (Sloc
(Last
(Statements
(Stats
))), RE_Complete_Rendezvous
);
748 Insert_Before
(Last
(Statements
(Stats
)), Call
);
751 -- If exception handlers are present, then append Complete_Rendezvous
752 -- calls to the handlers, and construct the required outer block. As
753 -- above, the Sloc is copied from the last statement in the sequence.
755 if Present
(Exception_Handlers
(Stats
)) then
756 Hand
:= First
(Exception_Handlers
(Stats
));
757 while Present
(Hand
) loop
760 (Sloc
(Last
(Statements
(Hand
))), RE_Complete_Rendezvous
);
761 Append
(Call
, Statements
(Hand
));
767 Make_Handled_Sequence_Of_Statements
(Loc
,
768 Statements
=> New_List
(
769 Make_Block_Statement
(Loc
,
770 Handled_Statement_Sequence
=> Stats
)));
776 -- At this stage we know that the new statement sequence does not
777 -- have an exception handler part, so we supply one to call
778 -- Exceptional_Complete_Rendezvous. This handler is
780 -- when all others =>
781 -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
783 -- We handle Abort_Signal to make sure that we properly catch the abort
784 -- case and wake up the caller.
786 Ohandle
:= Make_Others_Choice
(Loc
);
787 Set_All_Others
(Ohandle
);
789 Set_Exception_Handlers
(New_S
,
791 Make_Implicit_Exception_Handler
(Loc
,
792 Exception_Choices
=> New_List
(Ohandle
),
794 Statements
=> New_List
(
795 Make_Procedure_Call_Statement
(Sloc
(Stats
),
796 Name
=> New_Reference_To
(
797 RTE
(RE_Exceptional_Complete_Rendezvous
), Sloc
(Stats
)),
798 Parameter_Associations
=> New_List
(
799 Make_Function_Call
(Sloc
(Stats
),
800 Name
=> New_Reference_To
(
801 RTE
(RE_Get_GNAT_Exception
), Sloc
(Stats
)))))))));
803 Set_Parent
(New_S
, Astat
); -- temp parent for Analyze call
804 Analyze_Exception_Handlers
(Exception_Handlers
(New_S
));
805 Expand_Exception_Handlers
(New_S
);
807 -- Exceptional_Complete_Rendezvous must be called with abort
808 -- still deferred, which is the case for a "when all others" handler.
811 end Build_Accept_Body
;
813 -----------------------------------
814 -- Build_Activation_Chain_Entity --
815 -----------------------------------
817 procedure Build_Activation_Chain_Entity
(N
: Node_Id
) is
823 -- Loop to find enclosing construct containing activation chain variable
827 while not Nkind_In
(P
, N_Subprogram_Body
,
828 N_Package_Declaration
,
832 N_Extended_Return_Statement
)
837 -- If we are in a package body, the activation chain variable is
838 -- declared in the body, but the Activation_Chain_Entity is attached
841 if Nkind
(P
) = N_Package_Body
then
842 Decls
:= Declarations
(P
);
843 P
:= Unit_Declaration_Node
(Corresponding_Spec
(P
));
845 elsif Nkind
(P
) = N_Package_Declaration
then
846 Decls
:= Visible_Declarations
(Specification
(P
));
848 elsif Nkind
(P
) = N_Extended_Return_Statement
then
849 Decls
:= Return_Object_Declarations
(P
);
852 Decls
:= Declarations
(P
);
855 -- If activation chain entity not already declared, declare it
857 if Nkind
(P
) = N_Extended_Return_Statement
858 or else No
(Activation_Chain_Entity
(P
))
860 Chain
:= Make_Defining_Identifier
(Sloc
(N
), Name_uChain
);
862 -- Note: An extended return statement is not really a task activator,
863 -- but it does have an activation chain on which to store the tasks
864 -- temporarily. On successful return, the tasks on this chain are
865 -- moved to the chain passed in by the caller. We do not build an
866 -- Activation_Chain_Entity for an N_Extended_Return_Statement,
867 -- because we do not want to build a call to Activate_Tasks. Task
868 -- activation is the responsibility of the caller.
870 if Nkind
(P
) /= N_Extended_Return_Statement
then
871 Set_Activation_Chain_Entity
(P
, Chain
);
875 Make_Object_Declaration
(Sloc
(P
),
876 Defining_Identifier
=> Chain
,
877 Aliased_Present
=> True,
879 New_Reference_To
(RTE
(RE_Activation_Chain
), Sloc
(P
))));
881 Analyze
(First
(Decls
));
883 end Build_Activation_Chain_Entity
;
885 ----------------------------
886 -- Build_Barrier_Function --
887 ----------------------------
889 function Build_Barrier_Function
892 Pid
: Node_Id
) return Node_Id
894 Loc
: constant Source_Ptr
:= Sloc
(N
);
895 Func_Id
: constant Entity_Id
:= Barrier_Function
(Ent
);
896 Ent_Formals
: constant Node_Id
:= Entry_Body_Formal_Part
(N
);
897 Op_Decls
: constant List_Id
:= New_List
;
901 -- Add a declaration for the Protection object, renaming declarations
902 -- for the discriminals and privals and finally a declaration for the
903 -- entry family index (if applicable).
905 Install_Private_Data_Declarations
906 (Loc
, Func_Id
, Pid
, N
, Op_Decls
, True, Ekind
(Ent
) = E_Entry_Family
);
908 -- Note: the condition in the barrier function needs to be properly
909 -- processed for the C/Fortran boolean possibility, but this happens
910 -- automatically since the return statement does this normalization.
913 Make_Subprogram_Body
(Loc
,
915 Build_Barrier_Function_Specification
(Loc
,
916 Make_Defining_Identifier
(Loc
, Chars
(Func_Id
))),
917 Declarations
=> Op_Decls
,
918 Handled_Statement_Sequence
=>
919 Make_Handled_Sequence_Of_Statements
(Loc
,
920 Statements
=> New_List
(
921 Make_Simple_Return_Statement
(Loc
,
922 Expression
=> Condition
(Ent_Formals
)))));
923 Set_Is_Entry_Barrier_Function
(Func_Body
);
926 end Build_Barrier_Function
;
928 ------------------------------------------
929 -- Build_Barrier_Function_Specification --
930 ------------------------------------------
932 function Build_Barrier_Function_Specification
934 Def_Id
: Entity_Id
) return Node_Id
937 Set_Debug_Info_Needed
(Def_Id
);
939 return Make_Function_Specification
(Loc
,
940 Defining_Unit_Name
=> Def_Id
,
941 Parameter_Specifications
=> New_List
(
942 Make_Parameter_Specification
(Loc
,
943 Defining_Identifier
=>
944 Make_Defining_Identifier
(Loc
, Name_uO
),
946 New_Reference_To
(RTE
(RE_Address
), Loc
)),
948 Make_Parameter_Specification
(Loc
,
949 Defining_Identifier
=>
950 Make_Defining_Identifier
(Loc
, Name_uE
),
952 New_Reference_To
(RTE
(RE_Protected_Entry_Index
), Loc
))),
955 New_Reference_To
(Standard_Boolean
, Loc
));
956 end Build_Barrier_Function_Specification
;
958 --------------------------
959 -- Build_Call_With_Task --
960 --------------------------
962 function Build_Call_With_Task
964 E
: Entity_Id
) return Node_Id
966 Loc
: constant Source_Ptr
:= Sloc
(N
);
969 Make_Function_Call
(Loc
,
970 Name
=> New_Reference_To
(E
, Loc
),
971 Parameter_Associations
=> New_List
(Concurrent_Ref
(N
)));
972 end Build_Call_With_Task
;
974 --------------------------------
975 -- Build_Corresponding_Record --
976 --------------------------------
978 function Build_Corresponding_Record
981 Loc
: Source_Ptr
) return Node_Id
983 Rec_Ent
: constant Entity_Id
:=
984 Make_Defining_Identifier
985 (Loc
, New_External_Name
(Chars
(Ctyp
), 'V'));
988 New_Disc
: Entity_Id
;
992 Set_Corresponding_Record_Type
(Ctyp
, Rec_Ent
);
993 Set_Ekind
(Rec_Ent
, E_Record_Type
);
994 Set_Has_Delayed_Freeze
(Rec_Ent
, Has_Delayed_Freeze
(Ctyp
));
995 Set_Is_Concurrent_Record_Type
(Rec_Ent
, True);
996 Set_Corresponding_Concurrent_Type
(Rec_Ent
, Ctyp
);
997 Set_Stored_Constraint
(Rec_Ent
, No_Elist
);
1000 -- Use discriminals to create list of discriminants for record, and
1001 -- create new discriminals for use in default expressions, etc. It is
1002 -- worth noting that a task discriminant gives rise to 5 entities;
1004 -- a) The original discriminant.
1005 -- b) The discriminal for use in the task.
1006 -- c) The discriminant of the corresponding record.
1007 -- d) The discriminal for the init proc of the corresponding record.
1008 -- e) The local variable that renames the discriminant in the procedure
1009 -- for the task body.
1011 -- In fact the discriminals b) are used in the renaming declarations
1012 -- for e). See details in einfo (Handling of Discriminants).
1014 if Present
(Discriminant_Specifications
(N
)) then
1016 Disc
:= First_Discriminant
(Ctyp
);
1018 while Present
(Disc
) loop
1019 New_Disc
:= CR_Discriminant
(Disc
);
1022 Make_Discriminant_Specification
(Loc
,
1023 Defining_Identifier
=> New_Disc
,
1024 Discriminant_Type
=>
1025 New_Occurrence_Of
(Etype
(Disc
), Loc
),
1027 New_Copy
(Discriminant_Default_Value
(Disc
))));
1029 Next_Discriminant
(Disc
);
1036 -- Now we can construct the record type declaration. Note that this
1037 -- record is "limited tagged". It is "limited" to reflect the underlying
1038 -- limitedness of the task or protected object that it represents, and
1039 -- ensuring for example that it is properly passed by reference. It is
1040 -- "tagged" to give support to dispatching calls through interfaces (Ada
1044 Make_Full_Type_Declaration
(Loc
,
1045 Defining_Identifier
=> Rec_Ent
,
1046 Discriminant_Specifications
=> Dlist
,
1048 Make_Record_Definition
(Loc
,
1050 Make_Component_List
(Loc
,
1051 Component_Items
=> Cdecls
),
1053 Ada_Version
>= Ada_05
and then Is_Tagged_Type
(Ctyp
),
1054 Limited_Present
=> True));
1055 end Build_Corresponding_Record
;
1057 ----------------------------------
1058 -- Build_Entry_Count_Expression --
1059 ----------------------------------
1061 function Build_Entry_Count_Expression
1062 (Concurrent_Type
: Node_Id
;
1063 Component_List
: List_Id
;
1064 Loc
: Source_Ptr
) return Node_Id
1076 -- Count number of non-family entries
1079 Ent
:= First_Entity
(Concurrent_Type
);
1080 while Present
(Ent
) loop
1081 if Ekind
(Ent
) = E_Entry
then
1088 Ecount
:= Make_Integer_Literal
(Loc
, Eindx
);
1090 -- Loop through entry families building the addition nodes
1092 Ent
:= First_Entity
(Concurrent_Type
);
1093 Comp
:= First
(Component_List
);
1094 while Present
(Ent
) loop
1095 if Ekind
(Ent
) = E_Entry_Family
then
1096 while Chars
(Ent
) /= Chars
(Defining_Identifier
(Comp
)) loop
1100 Typ
:= Etype
(Discrete_Subtype_Definition
(Parent
(Ent
)));
1101 Hi
:= Type_High_Bound
(Typ
);
1102 Lo
:= Type_Low_Bound
(Typ
);
1103 Large
:= Is_Potentially_Large_Family
1104 (Base_Type
(Typ
), Concurrent_Type
, Lo
, Hi
);
1107 Left_Opnd
=> Ecount
,
1108 Right_Opnd
=> Family_Size
1109 (Loc
, Hi
, Lo
, Concurrent_Type
, Large
));
1116 end Build_Entry_Count_Expression
;
1118 -----------------------
1119 -- Build_Entry_Names --
1120 -----------------------
1122 function Build_Entry_Names
(Conc_Typ
: Entity_Id
) return Node_Id
is
1123 Loc
: constant Source_Ptr
:= Sloc
(Conc_Typ
);
1129 Typ
: Entity_Id
:= Conc_Typ
;
1131 procedure Build_Entry_Family_Name
(Id
: Entity_Id
);
1133 -- for Lnn in Family_Low .. Family_High loop
1136 -- (_init._object <or> _init._task_id,
1138 -- new String ("<Entry name>(" & Lnn'Img & ")"));
1140 -- Note that the bounds of the range may reference discriminants. The
1141 -- above construct is added directly to the statements of the block.
1143 procedure Build_Entry_Name
(Id
: Entity_Id
);
1147 -- (_init._object <or>_init._task_id,
1149 -- new String ("<Entry name>");
1150 -- The above construct is added directly to the statements of the block.
1152 function Build_Set_Entry_Name_Call
(Arg3
: Node_Id
) return Node_Id
;
1153 -- Generate the call to the runtime routine Set_Entry_Name with actuals
1154 -- _init._task_id or _init._object, Inn and Arg3.
1156 function Find_Protection_Type
(Conc_Typ
: Entity_Id
) return Entity_Id
;
1157 -- Given a protected type or its corresponding record, find the type of
1160 procedure Increment_Index
(Stmts
: List_Id
);
1161 -- Generate the following and add it to Stmts
1164 -----------------------------
1165 -- Build_Entry_Family_Name --
1166 -----------------------------
1168 procedure Build_Entry_Family_Name
(Id
: Entity_Id
) is
1169 Def
: constant Node_Id
:=
1170 Discrete_Subtype_Definition
(Parent
(Id
));
1171 L_Id
: constant Entity_Id
:=
1172 Make_Defining_Identifier
(Loc
, New_Internal_Name
('L'));
1173 L_Stmts
: constant List_Id
:= New_List
;
1176 function Build_Range
(Def
: Node_Id
) return Node_Id
;
1177 -- Given a discrete subtype definition of an entry family, generate a
1178 -- range node which covers the range of Def's type.
1184 function Build_Range
(Def
: Node_Id
) return Node_Id
is
1185 High
: Node_Id
:= Type_High_Bound
(Etype
(Def
));
1186 Low
: Node_Id
:= Type_Low_Bound
(Etype
(Def
));
1189 -- If a bound references a discriminant, generate an identifier
1190 -- with the same name. Resolution will map it to the formals of
1193 if Is_Entity_Name
(Low
)
1194 and then Ekind
(Entity
(Low
)) = E_Discriminant
1196 Low
:= Make_Identifier
(Loc
, Chars
(Low
));
1198 Low
:= New_Copy_Tree
(Low
);
1201 if Is_Entity_Name
(High
)
1202 and then Ekind
(Entity
(High
)) = E_Discriminant
1204 High
:= Make_Identifier
(Loc
, Chars
(High
));
1206 High
:= New_Copy_Tree
(High
);
1212 High_Bound
=> High
);
1215 -- Start of processing for Build_Entry_Family_Name
1218 Get_Name_String
(Chars
(Id
));
1220 -- Add a leading '('
1222 Add_Char_To_Name_Buffer
('(');
1225 -- new String'("<Entry name>(" & Lnn'Img & ")");
1227 -- This is an implicit heap allocation, and Comes_From_Source is
1228 -- False, which ensures that it will get flagged as a violation of
1229 -- No_Implicit_Heap_Allocations when that restriction applies.
1232 Make_Allocator
(Loc
,
1233 Make_Qualified_Expression
(Loc
,
1235 New_Reference_To
(Standard_String
, Loc
),
1237 Make_Op_Concat
(Loc
,
1239 Make_Op_Concat
(Loc
,
1241 Make_String_Literal
(Loc
,
1242 Strval
=> String_From_Name_Buffer
),
1244 Make_Attribute_Reference
(Loc
,
1246 New_Reference_To
(L_Id
, Loc
),
1247 Attribute_Name
=> Name_Img
)),
1249 Make_String_Literal
(Loc
,
1252 Increment_Index
(L_Stmts
);
1253 Append_To
(L_Stmts
, Build_Set_Entry_Name_Call
(Val
));
1256 -- for Lnn in Family_Low .. Family_High loop
1259 -- (_init._object <or> _init._task_id, Inn, <Val>);
1263 Make_Loop_Statement
(Loc
,
1265 Make_Iteration_Scheme
(Loc
,
1266 Loop_Parameter_Specification
=>
1267 Make_Loop_Parameter_Specification
(Loc
,
1268 Defining_Identifier
=> L_Id
,
1269 Discrete_Subtype_Definition
=>
1270 Build_Range
(Def
))),
1271 Statements
=> L_Stmts
,
1272 End_Label
=> Empty
));
1273 end Build_Entry_Family_Name
;
1275 ----------------------
1276 -- Build_Entry_Name --
1277 ----------------------
1279 procedure Build_Entry_Name
(Id
: Entity_Id
) is
1283 Get_Name_String
(Chars
(Id
));
1285 -- This is an implicit heap allocation, and Comes_From_Source is
1286 -- False, which ensures that it will get flagged as a violation of
1287 -- No_Implicit_Heap_Allocations when that restriction applies.
1290 Make_Allocator
(Loc
,
1291 Make_Qualified_Expression
(Loc
,
1293 New_Reference_To
(Standard_String
, Loc
),
1295 Make_String_Literal
(Loc
,
1296 String_From_Name_Buffer
)));
1298 Increment_Index
(B_Stmts
);
1299 Append_To
(B_Stmts
, Build_Set_Entry_Name_Call
(Val
));
1300 end Build_Entry_Name
;
1302 -------------------------------
1303 -- Build_Set_Entry_Name_Call --
1304 -------------------------------
1306 function Build_Set_Entry_Name_Call
(Arg3
: Node_Id
) return Node_Id
is
1311 -- Determine the proper name for the first argument and the RTS
1314 if Is_Protected_Type
(Typ
) then
1315 Arg1
:= Name_uObject
;
1316 Proc
:= RO_PE_Set_Entry_Name
;
1318 else pragma Assert
(Is_Task_Type
(Typ
));
1319 Arg1
:= Name_uTask_Id
;
1320 Proc
:= RO_TS_Set_Entry_Name
;
1324 -- Set_Entry_Name (_init.Arg1, Inn, Arg3);
1327 Make_Procedure_Call_Statement
(Loc
,
1329 New_Reference_To
(RTE
(Proc
), Loc
),
1330 Parameter_Associations
=> New_List
(
1331 Make_Selected_Component
(Loc
, -- _init._object
1332 Prefix
=> -- _init._task_id
1333 Make_Identifier
(Loc
, Name_uInit
),
1335 Make_Identifier
(Loc
, Arg1
)),
1336 New_Reference_To
(Index
, Loc
), -- Inn
1338 end Build_Set_Entry_Name_Call
;
1340 --------------------------
1341 -- Find_Protection_Type --
1342 --------------------------
1344 function Find_Protection_Type
(Conc_Typ
: Entity_Id
) return Entity_Id
is
1346 Typ
: Entity_Id
:= Conc_Typ
;
1349 if Is_Concurrent_Type
(Typ
) then
1350 Typ
:= Corresponding_Record_Type
(Typ
);
1353 Comp
:= First_Component
(Typ
);
1354 while Present
(Comp
) loop
1355 if Chars
(Comp
) = Name_uObject
then
1356 return Base_Type
(Etype
(Comp
));
1359 Next_Component
(Comp
);
1362 -- The corresponding record of a protected type should always have an
1365 raise Program_Error
;
1366 end Find_Protection_Type
;
1368 ---------------------
1369 -- Increment_Index --
1370 ---------------------
1372 procedure Increment_Index
(Stmts
: List_Id
) is
1378 Make_Assignment_Statement
(Loc
,
1380 New_Reference_To
(Index
, Loc
),
1384 New_Reference_To
(Index
, Loc
),
1386 Make_Integer_Literal
(Loc
, 1))));
1387 end Increment_Index
;
1389 -- Start of processing for Build_Entry_Names
1392 -- Retrieve the original concurrent type
1394 if Is_Concurrent_Record_Type
(Typ
) then
1395 Typ
:= Corresponding_Concurrent_Type
(Typ
);
1398 pragma Assert
(Is_Protected_Type
(Typ
) or else Is_Task_Type
(Typ
));
1400 -- Nothing to do if the type has no entries
1402 if not Has_Entries
(Typ
) then
1406 -- Avoid generating entry names for a protected type with only one entry
1408 if Is_Protected_Type
(Typ
)
1409 and then Find_Protection_Type
(Typ
) /= RTE
(RE_Protection_Entries
)
1414 Index
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('I'));
1416 -- Step 1: Generate the declaration of the index variable:
1417 -- Inn : Protected_Entry_Index := 0;
1419 -- Inn : Task_Entry_Index := 0;
1421 if Is_Protected_Type
(Typ
) then
1422 Index_Typ
:= RE_Protected_Entry_Index
;
1424 Index_Typ
:= RE_Task_Entry_Index
;
1427 B_Decls
:= New_List
;
1429 Make_Object_Declaration
(Loc
,
1430 Defining_Identifier
=> Index
,
1431 Object_Definition
=>
1432 New_Reference_To
(RTE
(Index_Typ
), Loc
),
1434 Make_Integer_Literal
(Loc
, 0)));
1436 B_Stmts
:= New_List
;
1438 -- Step 2: Generate a call to Set_Entry_Name for each entry and entry
1441 Comp
:= First_Entity
(Typ
);
1442 while Present
(Comp
) loop
1443 if Ekind
(Comp
) = E_Entry
then
1444 Build_Entry_Name
(Comp
);
1446 elsif Ekind
(Comp
) = E_Entry_Family
then
1447 Build_Entry_Family_Name
(Comp
);
1453 -- Step 3: Wrap the statements in a block
1456 Make_Block_Statement
(Loc
,
1457 Declarations
=> B_Decls
,
1458 Handled_Statement_Sequence
=>
1459 Make_Handled_Sequence_Of_Statements
(Loc
,
1460 Statements
=> B_Stmts
));
1461 end Build_Entry_Names
;
1463 ---------------------------
1464 -- Build_Parameter_Block --
1465 ---------------------------
1467 function Build_Parameter_Block
1471 Decls
: List_Id
) return Entity_Id
1477 Has_Comp
: Boolean := False;
1481 Actual
:= First
(Actuals
);
1483 Formal
:= Defining_Identifier
(First
(Formals
));
1485 while Present
(Actual
) loop
1486 if not Is_Controlling_Actual
(Actual
) then
1489 -- type Ann is access all <actual-type>
1492 Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
1495 Make_Full_Type_Declaration
(Loc
,
1496 Defining_Identifier
=>
1499 Make_Access_To_Object_Definition
(Loc
,
1503 Ekind
(Formal
) = E_In_Parameter
,
1504 Subtype_Indication
=>
1505 New_Reference_To
(Etype
(Actual
), Loc
))));
1511 Make_Component_Declaration
(Loc
,
1512 Defining_Identifier
=>
1513 Make_Defining_Identifier
(Loc
, Chars
(Formal
)),
1514 Component_Definition
=>
1515 Make_Component_Definition
(Loc
,
1518 Subtype_Indication
=>
1519 New_Reference_To
(Comp_Nam
, Loc
))));
1524 Next_Actual
(Actual
);
1525 Next_Formal_With_Extras
(Formal
);
1529 Make_Defining_Identifier
(Loc
, New_Internal_Name
('P'));
1534 -- type Pnn is record
1539 -- where Pnn is a parameter wrapping record, Param1 .. ParamN are
1540 -- the original parameter names and Ann1 .. AnnN are the access to
1544 Make_Full_Type_Declaration
(Loc
,
1545 Defining_Identifier
=>
1548 Make_Record_Definition
(Loc
,
1550 Make_Component_List
(Loc
, Comps
))));
1553 -- type Pnn is null record;
1556 Make_Full_Type_Declaration
(Loc
,
1557 Defining_Identifier
=>
1560 Make_Record_Definition
(Loc
,
1561 Null_Present
=> True,
1562 Component_List
=> Empty
)));
1566 end Build_Parameter_Block
;
1568 --------------------------
1569 -- Build_Wrapper_Bodies --
1570 --------------------------
1572 procedure Build_Wrapper_Bodies
1577 Rec_Typ
: Entity_Id
;
1579 function Build_Wrapper_Body
1581 Subp_Id
: Entity_Id
;
1582 Obj_Typ
: Entity_Id
;
1583 Formals
: List_Id
) return Node_Id
;
1584 -- Ada 2005 (AI-345): Build the body that wraps a primitive operation
1585 -- associated with a protected or task type. Subp_Id is the subprogram
1586 -- name which will be wrapped. Obj_Typ is the type of the new formal
1587 -- parameter which handles dispatching and object notation. Formals are
1588 -- the original formals of Subp_Id which will be explicitly replicated.
1590 ------------------------
1591 -- Build_Wrapper_Body --
1592 ------------------------
1594 function Build_Wrapper_Body
1596 Subp_Id
: Entity_Id
;
1597 Obj_Typ
: Entity_Id
;
1598 Formals
: List_Id
) return Node_Id
1600 Body_Spec
: Node_Id
;
1603 Body_Spec
:= Build_Wrapper_Spec
(Subp_Id
, Obj_Typ
, Formals
);
1605 -- The subprogram is not overriding or is not a primitive declared
1606 -- between two views.
1608 if No
(Body_Spec
) then
1613 Actuals
: List_Id
:= No_List
;
1615 First_Form
: Node_Id
;
1620 -- Map formals to actuals. Use the list built for the wrapper
1621 -- spec, skipping the object notation parameter.
1623 First_Form
:= First
(Parameter_Specifications
(Body_Spec
));
1625 Formal
:= First_Form
;
1628 if Present
(Formal
) then
1629 Actuals
:= New_List
;
1631 while Present
(Formal
) loop
1633 Make_Identifier
(Loc
, Chars
=>
1634 Chars
(Defining_Identifier
(Formal
))));
1640 -- Special processing for primitives declared between a private
1641 -- type and its completion: the wrapper needs a properly typed
1642 -- parameter if the wrapped operation has a controlling first
1643 -- parameter. Note that this might not be the case for a function
1644 -- with a controlling result.
1646 if Is_Private_Primitive_Subprogram
(Subp_Id
) then
1647 if No
(Actuals
) then
1648 Actuals
:= New_List
;
1651 if Is_Controlling_Formal
(First_Formal
(Subp_Id
)) then
1652 Prepend_To
(Actuals
,
1653 Unchecked_Convert_To
(
1654 Corresponding_Concurrent_Type
(Obj_Typ
),
1655 Make_Identifier
(Loc
, Name_uO
)));
1658 Prepend_To
(Actuals
,
1659 Make_Identifier
(Loc
, Chars
=>
1660 Chars
(Defining_Identifier
(First_Form
))));
1663 Nam
:= New_Reference_To
(Subp_Id
, Loc
);
1665 -- An access-to-variable object parameter requires an explicit
1666 -- dereference in the unchecked conversion. This case occurs
1667 -- when a protected entry wrapper must override an interface
1668 -- level procedure with interface access as first parameter.
1670 -- O.all.Subp_Id (Formal_1, ..., Formal_N)
1672 if Nkind
(Parameter_Type
(First_Form
)) =
1676 Make_Explicit_Dereference
(Loc
,
1677 Prefix
=> Make_Identifier
(Loc
, Name_uO
));
1679 Conv_Id
:= Make_Identifier
(Loc
, Name_uO
);
1683 Make_Selected_Component
(Loc
,
1685 Unchecked_Convert_To
(
1686 Corresponding_Concurrent_Type
(Obj_Typ
),
1689 New_Reference_To
(Subp_Id
, Loc
));
1692 -- Create the subprogram body. For a function, the call to the
1693 -- actual subprogram has to be converted to the corresponding
1694 -- record if it is a controlling result.
1696 if Ekind
(Subp_Id
) = E_Function
then
1702 Make_Function_Call
(Loc
,
1704 Parameter_Associations
=> Actuals
);
1706 if Has_Controlling_Result
(Subp_Id
) then
1708 Unchecked_Convert_To
1709 (Corresponding_Record_Type
(Etype
(Subp_Id
)), Res
);
1713 Make_Subprogram_Body
(Loc
,
1714 Specification
=> Body_Spec
,
1715 Declarations
=> Empty_List
,
1716 Handled_Statement_Sequence
=>
1717 Make_Handled_Sequence_Of_Statements
(Loc
,
1718 Statements
=> New_List
(
1719 Make_Simple_Return_Statement
(Loc
, Res
))));
1724 Make_Subprogram_Body
(Loc
,
1725 Specification
=> Body_Spec
,
1726 Declarations
=> Empty_List
,
1727 Handled_Statement_Sequence
=>
1728 Make_Handled_Sequence_Of_Statements
(Loc
,
1729 Statements
=> New_List
(
1730 Make_Procedure_Call_Statement
(Loc
,
1732 Parameter_Associations
=> Actuals
))));
1735 end Build_Wrapper_Body
;
1737 -- Start of processing for Build_Wrapper_Bodies
1740 if Is_Concurrent_Type
(Typ
) then
1741 Rec_Typ
:= Corresponding_Record_Type
(Typ
);
1746 -- Generate wrapper bodies for a concurrent type which implements an
1749 if Present
(Interfaces
(Rec_Typ
)) then
1751 Insert_Nod
: Node_Id
;
1753 Prim_Elmt
: Elmt_Id
;
1754 Prim_Decl
: Node_Id
;
1756 Wrap_Body
: Node_Id
;
1757 Wrap_Id
: Entity_Id
;
1762 -- Examine all primitive operations of the corresponding record
1763 -- type, looking for wrapper specs. Generate bodies in order to
1766 Prim_Elmt
:= First_Elmt
(Primitive_Operations
(Rec_Typ
));
1767 while Present
(Prim_Elmt
) loop
1768 Prim
:= Node
(Prim_Elmt
);
1770 if (Ekind
(Prim
) = E_Function
1771 or else Ekind
(Prim
) = E_Procedure
)
1772 and then Is_Primitive_Wrapper
(Prim
)
1774 Subp
:= Wrapped_Entity
(Prim
);
1775 Prim_Decl
:= Parent
(Parent
(Prim
));
1778 Build_Wrapper_Body
(Loc
,
1781 Formals
=> Parameter_Specifications
(Parent
(Subp
)));
1782 Wrap_Id
:= Defining_Unit_Name
(Specification
(Wrap_Body
));
1784 Set_Corresponding_Spec
(Wrap_Body
, Prim
);
1785 Set_Corresponding_Body
(Prim_Decl
, Wrap_Id
);
1787 Insert_After
(Insert_Nod
, Wrap_Body
);
1788 Insert_Nod
:= Wrap_Body
;
1790 Analyze
(Wrap_Body
);
1793 Next_Elmt
(Prim_Elmt
);
1797 end Build_Wrapper_Bodies
;
1799 ------------------------
1800 -- Build_Wrapper_Spec --
1801 ------------------------
1803 function Build_Wrapper_Spec
1804 (Subp_Id
: Entity_Id
;
1805 Obj_Typ
: Entity_Id
;
1806 Formals
: List_Id
) return Node_Id
1808 Loc
: constant Source_Ptr
:= Sloc
(Subp_Id
);
1809 First_Param
: Node_Id
;
1811 Iface_Elmt
: Elmt_Id
;
1812 Iface_Op
: Entity_Id
;
1813 Iface_Op_Elmt
: Elmt_Id
;
1815 function Overriding_Possible
1816 (Iface_Op
: Entity_Id
;
1817 Wrapper
: Entity_Id
) return Boolean;
1818 -- Determine whether a primitive operation can be overridden by Wrapper.
1819 -- Iface_Op is the candidate primitive operation of an interface type,
1820 -- Wrapper is the generated entry wrapper.
1822 function Replicate_Formals
1824 Formals
: List_Id
) return List_Id
;
1825 -- An explicit parameter replication is required due to the Is_Entry_
1826 -- Formal flag being set for all the formals of an entry. The explicit
1827 -- replication removes the flag that would otherwise cause a different
1828 -- path of analysis.
1830 -------------------------
1831 -- Overriding_Possible --
1832 -------------------------
1834 function Overriding_Possible
1835 (Iface_Op
: Entity_Id
;
1836 Wrapper
: Entity_Id
) return Boolean
1838 Iface_Op_Spec
: constant Node_Id
:= Parent
(Iface_Op
);
1839 Wrapper_Spec
: constant Node_Id
:= Parent
(Wrapper
);
1841 function Type_Conformant_Parameters
1842 (Iface_Op_Params
: List_Id
;
1843 Wrapper_Params
: List_Id
) return Boolean;
1844 -- Determine whether the parameters of the generated entry wrapper
1845 -- and those of a primitive operation are type conformant. During
1846 -- this check, the first parameter of the primitive operation is
1847 -- skipped if it is a controlling argument: protected functions
1848 -- may have a controlling result.
1850 --------------------------------
1851 -- Type_Conformant_Parameters --
1852 --------------------------------
1854 function Type_Conformant_Parameters
1855 (Iface_Op_Params
: List_Id
;
1856 Wrapper_Params
: List_Id
) return Boolean
1858 Iface_Op_Param
: Node_Id
;
1859 Iface_Op_Typ
: Entity_Id
;
1860 Wrapper_Param
: Node_Id
;
1861 Wrapper_Typ
: Entity_Id
;
1864 -- Skip the first (controlling) parameter of primitive operation
1866 Iface_Op_Param
:= First
(Iface_Op_Params
);
1868 if Present
(First_Formal
(Iface_Op
))
1869 and then Is_Controlling_Formal
(First_Formal
(Iface_Op
))
1871 Iface_Op_Param
:= Next
(Iface_Op_Param
);
1874 Wrapper_Param
:= First
(Wrapper_Params
);
1875 while Present
(Iface_Op_Param
)
1876 and then Present
(Wrapper_Param
)
1878 Iface_Op_Typ
:= Find_Parameter_Type
(Iface_Op_Param
);
1879 Wrapper_Typ
:= Find_Parameter_Type
(Wrapper_Param
);
1881 -- The two parameters must be mode conformant
1883 if not Conforming_Types
1884 (Iface_Op_Typ
, Wrapper_Typ
, Mode_Conformant
)
1889 Next
(Iface_Op_Param
);
1890 Next
(Wrapper_Param
);
1893 -- One of the lists is longer than the other
1895 if Present
(Iface_Op_Param
) or else Present
(Wrapper_Param
) then
1900 end Type_Conformant_Parameters
;
1902 -- Start of processing for Overriding_Possible
1905 if Chars
(Iface_Op
) /= Chars
(Wrapper
) then
1909 -- If an inherited subprogram is implemented by a protected procedure
1910 -- or an entry, then the first parameter of the inherited subprogram
1911 -- shall be of mode OUT or IN OUT, or access-to-variable parameter.
1913 if Ekind
(Iface_Op
) = E_Procedure
1914 and then Present
(Parameter_Specifications
(Iface_Op_Spec
))
1917 Obj_Param
: constant Node_Id
:=
1918 First
(Parameter_Specifications
(Iface_Op_Spec
));
1920 if not Out_Present
(Obj_Param
)
1921 and then Nkind
(Parameter_Type
(Obj_Param
)) /=
1930 Type_Conformant_Parameters
(
1931 Parameter_Specifications
(Iface_Op_Spec
),
1932 Parameter_Specifications
(Wrapper_Spec
));
1933 end Overriding_Possible
;
1935 -----------------------
1936 -- Replicate_Formals --
1937 -----------------------
1939 function Replicate_Formals
1941 Formals
: List_Id
) return List_Id
1943 New_Formals
: constant List_Id
:= New_List
;
1945 Param_Type
: Node_Id
;
1948 Formal
:= First
(Formals
);
1950 -- Skip the object parameter when dealing with primitives declared
1951 -- between two views.
1953 if Is_Private_Primitive_Subprogram
(Subp_Id
)
1954 and then not Has_Controlling_Result
(Subp_Id
)
1956 Formal
:= Next
(Formal
);
1959 while Present
(Formal
) loop
1961 -- Create an explicit copy of the entry parameter
1963 -- When creating the wrapper subprogram for a primitive operation
1964 -- of a protected interface we must construct an equivalent
1965 -- signature to that of the overriding operation. For regular
1966 -- parameters we can just use the type of the formal, but for
1967 -- access to subprogram parameters we need to reanalyze the
1968 -- parameter type to create local entities for the signature of
1969 -- the subprogram type. Using the entities of the overriding
1970 -- subprogram will result in out-of-scope errors in the back-end.
1972 if Nkind
(Parameter_Type
(Formal
)) = N_Access_Definition
then
1973 Param_Type
:= Copy_Separate_Tree
(Parameter_Type
(Formal
));
1976 New_Reference_To
(Etype
(Parameter_Type
(Formal
)), Loc
);
1979 Append_To
(New_Formals
,
1980 Make_Parameter_Specification
(Loc
,
1981 Defining_Identifier
=>
1982 Make_Defining_Identifier
(Loc
,
1983 Chars
=> Chars
(Defining_Identifier
(Formal
))),
1984 In_Present
=> In_Present
(Formal
),
1985 Out_Present
=> Out_Present
(Formal
),
1986 Parameter_Type
=> Param_Type
));
1992 end Replicate_Formals
;
1994 -- Start of processing for Build_Wrapper_Spec
1997 -- There is no point in building wrappers for non-tagged concurrent
2000 pragma Assert
(Is_Tagged_Type
(Obj_Typ
));
2002 -- An entry or a protected procedure can override a routine where the
2003 -- controlling formal is either IN OUT, OUT or is of access-to-variable
2004 -- type. Since the wrapper must have the exact same signature as that of
2005 -- the overridden subprogram, we try to find the overriding candidate
2006 -- and use its controlling formal.
2008 First_Param
:= Empty
;
2010 -- Check every implemented interface
2012 if Present
(Interfaces
(Obj_Typ
)) then
2013 Iface_Elmt
:= First_Elmt
(Interfaces
(Obj_Typ
));
2014 Search
: while Present
(Iface_Elmt
) loop
2015 Iface
:= Node
(Iface_Elmt
);
2017 -- Check every interface primitive
2019 if Present
(Primitive_Operations
(Iface
)) then
2020 Iface_Op_Elmt
:= First_Elmt
(Primitive_Operations
(Iface
));
2021 while Present
(Iface_Op_Elmt
) loop
2022 Iface_Op
:= Node
(Iface_Op_Elmt
);
2024 -- Ignore predefined primitives
2026 if not Is_Predefined_Dispatching_Operation
(Iface_Op
) then
2027 Iface_Op
:= Ultimate_Alias
(Iface_Op
);
2029 -- The current primitive operation can be overridden by
2030 -- the generated entry wrapper.
2032 if Overriding_Possible
(Iface_Op
, Subp_Id
) then
2034 First
(Parameter_Specifications
(Parent
(Iface_Op
)));
2040 Next_Elmt
(Iface_Op_Elmt
);
2044 Next_Elmt
(Iface_Elmt
);
2048 -- If the subprogram to be wrapped is not overriding anything or is not
2049 -- a primitive declared between two views, do not produce anything. This
2050 -- avoids spurious errors involving overriding.
2053 and then not Is_Private_Primitive_Subprogram
(Subp_Id
)
2059 Wrapper_Id
: constant Entity_Id
:=
2060 Make_Defining_Identifier
(Loc
, Chars
(Subp_Id
));
2061 New_Formals
: List_Id
;
2062 Obj_Param
: Node_Id
;
2063 Obj_Param_Typ
: Entity_Id
;
2066 -- Minimum decoration is needed to catch the entity in
2067 -- Sem_Ch6.Override_Dispatching_Operation.
2069 if Ekind
(Subp_Id
) = E_Function
then
2070 Set_Ekind
(Wrapper_Id
, E_Function
);
2072 Set_Ekind
(Wrapper_Id
, E_Procedure
);
2075 Set_Is_Primitive_Wrapper
(Wrapper_Id
);
2076 Set_Wrapped_Entity
(Wrapper_Id
, Subp_Id
);
2077 Set_Is_Private_Primitive
(Wrapper_Id
,
2078 Is_Private_Primitive_Subprogram
(Subp_Id
));
2080 -- Process the formals
2082 New_Formals
:= Replicate_Formals
(Loc
, Formals
);
2084 -- A function with a controlling result and no first controlling
2085 -- formal needs no additional parameter.
2087 if Has_Controlling_Result
(Subp_Id
)
2089 (No
(First_Formal
(Subp_Id
))
2090 or else not Is_Controlling_Formal
(First_Formal
(Subp_Id
)))
2094 -- Routine Subp_Id has been found to override an interface primitive.
2095 -- If the interface operation has an access parameter, create a copy
2096 -- of it, with the same null exclusion indicator if present.
2098 elsif Present
(First_Param
) then
2099 if Nkind
(Parameter_Type
(First_Param
)) = N_Access_Definition
then
2101 Make_Access_Definition
(Loc
,
2103 New_Reference_To
(Obj_Typ
, Loc
));
2104 Set_Null_Exclusion_Present
(Obj_Param_Typ
,
2105 Null_Exclusion_Present
(Parameter_Type
(First_Param
)));
2108 Obj_Param_Typ
:= New_Reference_To
(Obj_Typ
, Loc
);
2112 Make_Parameter_Specification
(Loc
,
2113 Defining_Identifier
=>
2114 Make_Defining_Identifier
(Loc
,
2116 In_Present
=> In_Present
(First_Param
),
2117 Out_Present
=> Out_Present
(First_Param
),
2118 Parameter_Type
=> Obj_Param_Typ
);
2120 Prepend_To
(New_Formals
, Obj_Param
);
2122 -- If we are dealing with a primitive declared between two views,
2123 -- implemented by a synchronized operation, we need to create
2124 -- a default parameter. The mode of the parameter must match that
2125 -- of the primitive operation.
2128 pragma Assert
(Is_Private_Primitive_Subprogram
(Subp_Id
));
2130 Make_Parameter_Specification
(Loc
,
2131 Defining_Identifier
=>
2132 Make_Defining_Identifier
(Loc
, Name_uO
),
2133 In_Present
=> In_Present
(Parent
(First_Entity
(Subp_Id
))),
2134 Out_Present
=> Ekind
(Subp_Id
) /= E_Function
,
2135 Parameter_Type
=> New_Reference_To
(Obj_Typ
, Loc
));
2136 Prepend_To
(New_Formals
, Obj_Param
);
2139 -- Build the final spec. If it is a function with a controlling
2140 -- result, it is a primitive operation of the corresponding
2141 -- record type, so mark the spec accordingly.
2143 if Ekind
(Subp_Id
) = E_Function
then
2149 if Has_Controlling_Result
(Subp_Id
) then
2152 (Corresponding_Record_Type
(Etype
(Subp_Id
)), Loc
);
2154 Res_Def
:= New_Copy
(Result_Definition
(Parent
(Subp_Id
)));
2158 Make_Function_Specification
(Loc
,
2159 Defining_Unit_Name
=> Wrapper_Id
,
2160 Parameter_Specifications
=> New_Formals
,
2161 Result_Definition
=> Res_Def
);
2165 Make_Procedure_Specification
(Loc
,
2166 Defining_Unit_Name
=> Wrapper_Id
,
2167 Parameter_Specifications
=> New_Formals
);
2170 end Build_Wrapper_Spec
;
2172 -------------------------
2173 -- Build_Wrapper_Specs --
2174 -------------------------
2176 procedure Build_Wrapper_Specs
2182 Rec_Typ
: Entity_Id
;
2185 if Is_Protected_Type
(Typ
) then
2186 Def
:= Protected_Definition
(Parent
(Typ
));
2187 else pragma Assert
(Is_Task_Type
(Typ
));
2188 Def
:= Task_Definition
(Parent
(Typ
));
2191 Rec_Typ
:= Corresponding_Record_Type
(Typ
);
2193 -- Generate wrapper specs for a concurrent type which implements an
2194 -- interface and has visible entries and/or protected procedures.
2196 if Present
(Interfaces
(Rec_Typ
))
2197 and then Present
(Def
)
2198 and then Present
(Visible_Declarations
(Def
))
2202 Wrap_Decl
: Node_Id
;
2203 Wrap_Spec
: Node_Id
;
2206 Decl
:= First
(Visible_Declarations
(Def
));
2207 while Present
(Decl
) loop
2210 if Nkind
(Decl
) = N_Entry_Declaration
2211 and then Ekind
(Defining_Identifier
(Decl
)) = E_Entry
2215 (Subp_Id
=> Defining_Identifier
(Decl
),
2217 Formals
=> Parameter_Specifications
(Decl
));
2219 elsif Nkind
(Decl
) = N_Subprogram_Declaration
then
2222 (Subp_Id
=> Defining_Unit_Name
(Specification
(Decl
)),
2225 Parameter_Specifications
(Specification
(Decl
)));
2228 if Present
(Wrap_Spec
) then
2230 Make_Subprogram_Declaration
(Loc
,
2231 Specification
=> Wrap_Spec
);
2233 Insert_After
(N
, Wrap_Decl
);
2236 Analyze
(Wrap_Decl
);
2243 end Build_Wrapper_Specs
;
2245 ---------------------------
2246 -- Build_Find_Body_Index --
2247 ---------------------------
2249 function Build_Find_Body_Index
(Typ
: Entity_Id
) return Node_Id
is
2250 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
2253 Has_F
: Boolean := False;
2255 If_St
: Node_Id
:= Empty
;
2258 Decls
: List_Id
:= New_List
;
2261 Siz
: Node_Id
:= Empty
;
2263 procedure Add_If_Clause
(Expr
: Node_Id
);
2264 -- Add test for range of current entry
2266 function Convert_Discriminant_Ref
(Bound
: Node_Id
) return Node_Id
;
2267 -- If a bound of an entry is given by a discriminant, retrieve the
2268 -- actual value of the discriminant from the enclosing object.
2274 procedure Add_If_Clause
(Expr
: Node_Id
) is
2276 Stats
: constant List_Id
:=
2278 Make_Simple_Return_Statement
(Loc
,
2279 Expression
=> Make_Integer_Literal
(Loc
, Index
+ 1)));
2282 -- Index for current entry body
2286 -- Compute total length of entry queues so far
2294 Right_Opnd
=> Expr
);
2299 Left_Opnd
=> Make_Identifier
(Loc
, Name_uE
),
2302 -- Map entry queue indices in the range of the current family
2303 -- into the current index, that designates the entry body.
2307 Make_Implicit_If_Statement
(Typ
,
2309 Then_Statements
=> Stats
,
2310 Elsif_Parts
=> New_List
);
2316 Make_Elsif_Part
(Loc
,
2318 Then_Statements
=> Stats
),
2319 Elsif_Parts
(If_St
));
2323 ------------------------------
2324 -- Convert_Discriminant_Ref --
2325 ------------------------------
2327 function Convert_Discriminant_Ref
(Bound
: Node_Id
) return Node_Id
is
2331 if Is_Entity_Name
(Bound
)
2332 and then Ekind
(Entity
(Bound
)) = E_Discriminant
2335 Make_Selected_Component
(Loc
,
2337 Unchecked_Convert_To
(Corresponding_Record_Type
(Typ
),
2338 Make_Explicit_Dereference
(Loc
,
2339 Make_Identifier
(Loc
, Name_uObject
))),
2340 Selector_Name
=> Make_Identifier
(Loc
, Chars
(Bound
)));
2341 Set_Etype
(B
, Etype
(Entity
(Bound
)));
2343 B
:= New_Copy_Tree
(Bound
);
2347 end Convert_Discriminant_Ref
;
2349 -- Start of processing for Build_Find_Body_Index
2352 Spec
:= Build_Find_Body_Index_Spec
(Typ
);
2354 Ent
:= First_Entity
(Typ
);
2355 while Present
(Ent
) loop
2356 if Ekind
(Ent
) = E_Entry_Family
then
2366 -- If the protected type has no entry families, there is a one-one
2367 -- correspondence between entry queue and entry body.
2370 Make_Simple_Return_Statement
(Loc
,
2371 Expression
=> Make_Identifier
(Loc
, Name_uE
));
2374 -- Suppose entries e1, e2, ... have size l1, l2, ... we generate
2377 -- if E <= l1 then return 1;
2378 -- elsif E <= l1 + l2 then return 2;
2383 Ent
:= First_Entity
(Typ
);
2385 Add_Object_Pointer
(Loc
, Typ
, Decls
);
2387 while Present
(Ent
) loop
2389 if Ekind
(Ent
) = E_Entry
then
2390 Add_If_Clause
(Make_Integer_Literal
(Loc
, 1));
2392 elsif Ekind
(Ent
) = E_Entry_Family
then
2394 E_Typ
:= Etype
(Discrete_Subtype_Definition
(Parent
(Ent
)));
2395 Hi
:= Convert_Discriminant_Ref
(Type_High_Bound
(E_Typ
));
2396 Lo
:= Convert_Discriminant_Ref
(Type_Low_Bound
(E_Typ
));
2397 Add_If_Clause
(Family_Size
(Loc
, Hi
, Lo
, Typ
, False));
2406 Make_Simple_Return_Statement
(Loc
,
2407 Expression
=> Make_Integer_Literal
(Loc
, 1));
2409 elsif Nkind
(Ret
) = N_If_Statement
then
2411 -- Ranges are in increasing order, so last one doesn't need guard
2414 Nod
: constant Node_Id
:= Last
(Elsif_Parts
(Ret
));
2417 Set_Else_Statements
(Ret
, Then_Statements
(Nod
));
2423 Make_Subprogram_Body
(Loc
,
2424 Specification
=> Spec
,
2425 Declarations
=> Decls
,
2426 Handled_Statement_Sequence
=>
2427 Make_Handled_Sequence_Of_Statements
(Loc
,
2428 Statements
=> New_List
(Ret
)));
2429 end Build_Find_Body_Index
;
2431 --------------------------------
2432 -- Build_Find_Body_Index_Spec --
2433 --------------------------------
2435 function Build_Find_Body_Index_Spec
(Typ
: Entity_Id
) return Node_Id
is
2436 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
2437 Id
: constant Entity_Id
:=
2438 Make_Defining_Identifier
(Loc
,
2439 Chars
=> New_External_Name
(Chars
(Typ
), 'F'));
2440 Parm1
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uO
);
2441 Parm2
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uE
);
2445 Make_Function_Specification
(Loc
,
2446 Defining_Unit_Name
=> Id
,
2447 Parameter_Specifications
=> New_List
(
2448 Make_Parameter_Specification
(Loc
,
2449 Defining_Identifier
=> Parm1
,
2451 New_Reference_To
(RTE
(RE_Address
), Loc
)),
2453 Make_Parameter_Specification
(Loc
,
2454 Defining_Identifier
=> Parm2
,
2456 New_Reference_To
(RTE
(RE_Protected_Entry_Index
), Loc
))),
2457 Result_Definition
=> New_Occurrence_Of
(
2458 RTE
(RE_Protected_Entry_Index
), Loc
));
2459 end Build_Find_Body_Index_Spec
;
2461 -------------------------
2462 -- Build_Master_Entity --
2463 -------------------------
2465 procedure Build_Master_Entity
(E
: Entity_Id
) is
2466 Loc
: constant Source_Ptr
:= Sloc
(E
);
2474 -- Ada 2005 (AI-287): Do not set/get the has_master_entity reminder
2475 -- in internal scopes, unless present already.. Required for nested
2476 -- limited aggregates, where the expansion of task components may
2477 -- generate inner blocks. If the block is the rewriting of a call
2478 -- or the scope is an extended return statement this is valid master.
2479 -- The master in an extended return is only used within the return,
2480 -- and is subsequently overwritten in Move_Activation_Chain, but it
2483 if Ada_Version
>= Ada_05
then
2484 while Is_Internal
(S
) loop
2485 if Nkind
(Parent
(S
)) = N_Block_Statement
2487 Nkind
(Original_Node
(Parent
(S
))) = N_Procedure_Call_Statement
2490 elsif Ekind
(S
) = E_Return_Statement
then
2498 -- Nothing to do if we already built a master entity for this scope
2499 -- or if there is no task hierarchy.
2501 if Has_Master_Entity
(S
)
2502 or else Restriction_Active
(No_Task_Hierarchy
)
2507 -- Otherwise first build the master entity
2508 -- _Master : constant Master_Id := Current_Master.all;
2509 -- and insert it just before the current declaration
2512 Make_Object_Declaration
(Loc
,
2513 Defining_Identifier
=>
2514 Make_Defining_Identifier
(Loc
, Name_uMaster
),
2515 Constant_Present
=> True,
2516 Object_Definition
=> New_Reference_To
(RTE
(RE_Master_Id
), Loc
),
2518 Make_Explicit_Dereference
(Loc
,
2519 New_Reference_To
(RTE
(RE_Current_Master
), Loc
)));
2522 Insert_Before
(P
, Decl
);
2525 -- Ada 2005 (AI-287): Set the has_master_entity reminder in the
2526 -- non-internal scope selected above.
2528 if Ada_Version
>= Ada_05
then
2529 Set_Has_Master_Entity
(S
);
2531 Set_Has_Master_Entity
(Scope
(E
));
2534 -- Now mark the containing scope as a task master
2536 while Nkind
(P
) /= N_Compilation_Unit
loop
2539 -- If we fall off the top, we are at the outer level, and the
2540 -- environment task is our effective master, so nothing to mark.
2543 (P
, N_Task_Body
, N_Block_Statement
, N_Subprogram_Body
)
2545 Set_Is_Task_Master
(P
, True);
2548 elsif Nkind
(Parent
(P
)) = N_Subunit
then
2549 P
:= Corresponding_Stub
(Parent
(P
));
2552 end Build_Master_Entity
;
2554 ---------------------------
2555 -- Build_Protected_Entry --
2556 ---------------------------
2558 function Build_Protected_Entry
2561 Pid
: Node_Id
) return Node_Id
2563 Loc
: constant Source_Ptr
:= Sloc
(N
);
2565 Decls
: constant List_Id
:= Declarations
(N
);
2566 End_Lab
: constant Node_Id
:=
2567 End_Label
(Handled_Statement_Sequence
(N
));
2568 End_Loc
: constant Source_Ptr
:=
2569 Sloc
(Last
(Statements
(Handled_Statement_Sequence
(N
))));
2570 -- Used for the generated call to Complete_Entry_Body
2572 Han_Loc
: Source_Ptr
;
2573 -- Used for the exception handler, inserted at end of the body
2575 Op_Decls
: constant List_Id
:= New_List
;
2583 -- Set the source location on the exception handler only when debugging
2584 -- the expanded code (see Make_Implicit_Exception_Handler).
2586 if Debug_Generated_Code
then
2589 -- Otherwise the inserted code should not be visible to the debugger
2592 Han_Loc
:= No_Location
;
2596 Make_Defining_Identifier
(Loc
,
2597 Chars
=> Chars
(Protected_Body_Subprogram
(Ent
)));
2599 Build_Protected_Entry_Specification
(Loc
, Edef
, Empty
);
2601 -- Add the following declarations:
2602 -- type poVP is access poV;
2603 -- _object : poVP := poVP (_O);
2605 -- where _O is the formal parameter associated with the concurrent
2606 -- object. These declarations are needed for Complete_Entry_Body.
2608 Add_Object_Pointer
(Loc
, Pid
, Op_Decls
);
2610 -- Add renamings for all formals, the Protection object, discriminals,
2611 -- privals and the entry index constant for use by debugger.
2613 Add_Formal_Renamings
(Espec
, Op_Decls
, Ent
, Loc
);
2614 Debug_Private_Data_Declarations
(Decls
);
2616 case Corresponding_Runtime_Package
(Pid
) is
2617 when System_Tasking_Protected_Objects_Entries
=>
2619 New_Reference_To
(RTE
(RE_Complete_Entry_Body
), Loc
);
2621 when System_Tasking_Protected_Objects_Single_Entry
=>
2623 New_Reference_To
(RTE
(RE_Complete_Single_Entry_Body
), Loc
);
2626 raise Program_Error
;
2629 Op_Stats
:= New_List
(
2630 Make_Block_Statement
(Loc
,
2631 Declarations
=> Decls
,
2632 Handled_Statement_Sequence
=>
2633 Handled_Statement_Sequence
(N
)),
2635 Make_Procedure_Call_Statement
(End_Loc
,
2637 Parameter_Associations
=> New_List
(
2638 Make_Attribute_Reference
(End_Loc
,
2640 Make_Selected_Component
(End_Loc
,
2642 Make_Identifier
(End_Loc
, Name_uObject
),
2644 Make_Identifier
(End_Loc
, Name_uObject
)),
2645 Attribute_Name
=> Name_Unchecked_Access
))));
2647 -- When exceptions can not be propagated, we never need to call
2648 -- Exception_Complete_Entry_Body
2650 if No_Exception_Handlers_Set
then
2652 Make_Subprogram_Body
(Loc
,
2653 Specification
=> Espec
,
2654 Declarations
=> Op_Decls
,
2655 Handled_Statement_Sequence
=>
2656 Make_Handled_Sequence_Of_Statements
(Loc
,
2657 Statements
=> Op_Stats
,
2658 End_Label
=> End_Lab
));
2661 Ohandle
:= Make_Others_Choice
(Loc
);
2662 Set_All_Others
(Ohandle
);
2664 case Corresponding_Runtime_Package
(Pid
) is
2665 when System_Tasking_Protected_Objects_Entries
=>
2668 (RTE
(RE_Exceptional_Complete_Entry_Body
), Loc
);
2670 when System_Tasking_Protected_Objects_Single_Entry
=>
2673 (RTE
(RE_Exceptional_Complete_Single_Entry_Body
), Loc
);
2676 raise Program_Error
;
2679 -- Create body of entry procedure. The renaming declarations are
2680 -- placed ahead of the block that contains the actual entry body.
2683 Make_Subprogram_Body
(Loc
,
2684 Specification
=> Espec
,
2685 Declarations
=> Op_Decls
,
2686 Handled_Statement_Sequence
=>
2687 Make_Handled_Sequence_Of_Statements
(Loc
,
2688 Statements
=> Op_Stats
,
2689 End_Label
=> End_Lab
,
2690 Exception_Handlers
=> New_List
(
2691 Make_Implicit_Exception_Handler
(Han_Loc
,
2692 Exception_Choices
=> New_List
(Ohandle
),
2694 Statements
=> New_List
(
2695 Make_Procedure_Call_Statement
(Han_Loc
,
2697 Parameter_Associations
=> New_List
(
2698 Make_Attribute_Reference
(Han_Loc
,
2700 Make_Selected_Component
(Han_Loc
,
2702 Make_Identifier
(Han_Loc
, Name_uObject
),
2704 Make_Identifier
(Han_Loc
, Name_uObject
)),
2705 Attribute_Name
=> Name_Unchecked_Access
),
2707 Make_Function_Call
(Han_Loc
,
2708 Name
=> New_Reference_To
(
2709 RTE
(RE_Get_GNAT_Exception
), Loc
)))))))));
2711 end Build_Protected_Entry
;
2713 -----------------------------------------
2714 -- Build_Protected_Entry_Specification --
2715 -----------------------------------------
2717 function Build_Protected_Entry_Specification
2720 Ent_Id
: Entity_Id
) return Node_Id
2722 P
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uP
);
2725 Set_Debug_Info_Needed
(Def_Id
);
2727 if Present
(Ent_Id
) then
2728 Append_Elmt
(P
, Accept_Address
(Ent_Id
));
2732 Make_Procedure_Specification
(Loc
,
2733 Defining_Unit_Name
=> Def_Id
,
2734 Parameter_Specifications
=> New_List
(
2735 Make_Parameter_Specification
(Loc
,
2736 Defining_Identifier
=>
2737 Make_Defining_Identifier
(Loc
, Name_uO
),
2739 New_Reference_To
(RTE
(RE_Address
), Loc
)),
2741 Make_Parameter_Specification
(Loc
,
2742 Defining_Identifier
=> P
,
2744 New_Reference_To
(RTE
(RE_Address
), Loc
)),
2746 Make_Parameter_Specification
(Loc
,
2747 Defining_Identifier
=>
2748 Make_Defining_Identifier
(Loc
, Name_uE
),
2750 New_Reference_To
(RTE
(RE_Protected_Entry_Index
), Loc
))));
2751 end Build_Protected_Entry_Specification
;
2753 --------------------------
2754 -- Build_Protected_Spec --
2755 --------------------------
2757 function Build_Protected_Spec
2759 Obj_Type
: Entity_Id
;
2761 Unprotected
: Boolean := False) return List_Id
2763 Loc
: constant Source_Ptr
:= Sloc
(N
);
2766 New_Plist
: List_Id
;
2767 New_Param
: Node_Id
;
2770 New_Plist
:= New_List
;
2772 Formal
:= First_Formal
(Ident
);
2773 while Present
(Formal
) loop
2775 Make_Parameter_Specification
(Loc
,
2776 Defining_Identifier
=>
2777 Make_Defining_Identifier
(Sloc
(Formal
), Chars
(Formal
)),
2778 In_Present
=> In_Present
(Parent
(Formal
)),
2779 Out_Present
=> Out_Present
(Parent
(Formal
)),
2780 Parameter_Type
=> New_Reference_To
(Etype
(Formal
), Loc
));
2783 Set_Protected_Formal
(Formal
, Defining_Identifier
(New_Param
));
2786 Append
(New_Param
, New_Plist
);
2787 Next_Formal
(Formal
);
2790 -- If the subprogram is a procedure and the context is not an access
2791 -- to protected subprogram, the parameter is in-out. Otherwise it is
2795 Make_Parameter_Specification
(Loc
,
2796 Defining_Identifier
=>
2797 Make_Defining_Identifier
(Loc
, Name_uObject
),
2800 (Etype
(Ident
) = Standard_Void_Type
2801 and then not Is_RTE
(Obj_Type
, RE_Address
)),
2803 New_Reference_To
(Obj_Type
, Loc
));
2804 Set_Debug_Info_Needed
(Defining_Identifier
(Decl
));
2805 Prepend_To
(New_Plist
, Decl
);
2808 end Build_Protected_Spec
;
2810 ---------------------------------------
2811 -- Build_Protected_Sub_Specification --
2812 ---------------------------------------
2814 function Build_Protected_Sub_Specification
2816 Prot_Typ
: Entity_Id
;
2817 Mode
: Subprogram_Protection_Mode
) return Node_Id
2819 Loc
: constant Source_Ptr
:= Sloc
(N
);
2823 New_Plist
: List_Id
;
2826 Append_Chr
: constant array (Subprogram_Protection_Mode
) of Character :=
2827 (Dispatching_Mode
=> ' ',
2828 Protected_Mode
=> 'P',
2829 Unprotected_Mode
=> 'N');
2832 if Ekind
(Defining_Unit_Name
(Specification
(N
))) =
2835 Decl
:= Unit_Declaration_Node
(Corresponding_Spec
(N
));
2840 Def_Id
:= Defining_Unit_Name
(Specification
(Decl
));
2843 Build_Protected_Spec
2844 (Decl
, Corresponding_Record_Type
(Prot_Typ
), Def_Id
,
2845 Mode
= Unprotected_Mode
);
2847 Make_Defining_Identifier
(Loc
,
2848 Chars
=> Build_Selected_Name
(Prot_Typ
, Def_Id
, Append_Chr
(Mode
)));
2850 -- The unprotected operation carries the user code, and debugging
2851 -- information must be generated for it, even though this spec does
2852 -- not come from source. It is also convenient to allow gdb to step
2853 -- into the protected operation, even though it only contains lock/
2856 Set_Debug_Info_Needed
(New_Id
);
2858 -- If a pragma Eliminate applies to the source entity, the internal
2859 -- subprograms will be eliminated as well.
2861 Set_Is_Eliminated
(New_Id
, Is_Eliminated
(Def_Id
));
2863 if Nkind
(Specification
(Decl
)) = N_Procedure_Specification
then
2865 Make_Procedure_Specification
(Loc
,
2866 Defining_Unit_Name
=> New_Id
,
2867 Parameter_Specifications
=> New_Plist
);
2869 -- Create a new specification for the anonymous subprogram type
2873 Make_Function_Specification
(Loc
,
2874 Defining_Unit_Name
=> New_Id
,
2875 Parameter_Specifications
=> New_Plist
,
2876 Result_Definition
=>
2877 Copy_Result_Type
(Result_Definition
(Specification
(Decl
))));
2879 Set_Return_Present
(Defining_Unit_Name
(New_Spec
));
2883 end Build_Protected_Sub_Specification
;
2885 -------------------------------------
2886 -- Build_Protected_Subprogram_Body --
2887 -------------------------------------
2889 function Build_Protected_Subprogram_Body
2892 N_Op_Spec
: Node_Id
) return Node_Id
2894 Loc
: constant Source_Ptr
:= Sloc
(N
);
2896 P_Op_Spec
: Node_Id
;
2899 Unprot_Call
: Node_Id
;
2901 Lock_Name
: Node_Id
;
2902 Lock_Stmt
: Node_Id
;
2903 Service_Name
: Node_Id
;
2905 Return_Stmt
: Node_Id
:= Empty
; -- init to avoid gcc 3 warning
2906 Pre_Stmts
: List_Id
:= No_List
; -- init to avoid gcc 3 warning
2908 Object_Parm
: Node_Id
;
2911 function Is_Exception_Safe
(Subprogram
: Node_Id
) return Boolean;
2912 -- Tell whether a given subprogram cannot raise an exception
2914 -----------------------
2915 -- Is_Exception_Safe --
2916 -----------------------
2918 function Is_Exception_Safe
(Subprogram
: Node_Id
) return Boolean is
2920 function Has_Side_Effect
(N
: Node_Id
) return Boolean;
2921 -- Return True whenever encountering a subprogram call or raise
2922 -- statement of any kind in the sequence of statements
2924 ---------------------
2925 -- Has_Side_Effect --
2926 ---------------------
2928 -- What is this doing buried two levels down in exp_ch9. It seems
2929 -- like a generally useful function, and indeed there may be code
2930 -- duplication going on here ???
2932 function Has_Side_Effect
(N
: Node_Id
) return Boolean is
2936 function Is_Call_Or_Raise
(N
: Node_Id
) return Boolean;
2937 -- Indicate whether N is a subprogram call or a raise statement
2939 ----------------------
2940 -- Is_Call_Or_Raise --
2941 ----------------------
2943 function Is_Call_Or_Raise
(N
: Node_Id
) return Boolean is
2945 return Nkind_In
(N
, N_Procedure_Call_Statement
,
2948 N_Raise_Constraint_Error
,
2949 N_Raise_Program_Error
,
2950 N_Raise_Storage_Error
);
2951 end Is_Call_Or_Raise
;
2953 -- Start of processing for Has_Side_Effect
2957 while Present
(Stmt
) loop
2958 if Is_Call_Or_Raise
(Stmt
) then
2962 -- An object declaration can also contain a function call
2963 -- or a raise statement
2965 if Nkind
(Stmt
) = N_Object_Declaration
then
2966 Expr
:= Expression
(Stmt
);
2968 if Present
(Expr
) and then Is_Call_Or_Raise
(Expr
) then
2977 end Has_Side_Effect
;
2979 -- Start of processing for Is_Exception_Safe
2982 -- If the checks handled by the back end are not disabled, we cannot
2983 -- ensure that no exception will be raised.
2985 if not Access_Checks_Suppressed
(Empty
)
2986 or else not Discriminant_Checks_Suppressed
(Empty
)
2987 or else not Range_Checks_Suppressed
(Empty
)
2988 or else not Index_Checks_Suppressed
(Empty
)
2989 or else Opt
.Stack_Checking_Enabled
2994 if Has_Side_Effect
(First
(Declarations
(Subprogram
)))
2997 First
(Statements
(Handled_Statement_Sequence
(Subprogram
))))
3003 end Is_Exception_Safe
;
3005 -- Start of processing for Build_Protected_Subprogram_Body
3008 Op_Spec
:= Specification
(N
);
3009 Exc_Safe
:= Is_Exception_Safe
(N
);
3012 Build_Protected_Sub_Specification
(N
, Pid
, Protected_Mode
);
3014 -- Build a list of the formal parameters of the protected version of
3015 -- the subprogram to use as the actual parameters of the unprotected
3018 Uactuals
:= New_List
;
3019 Pformal
:= First
(Parameter_Specifications
(P_Op_Spec
));
3020 while Present
(Pformal
) loop
3022 Make_Identifier
(Loc
, Chars
(Defining_Identifier
(Pformal
))),
3027 -- Make a call to the unprotected version of the subprogram built above
3028 -- for use by the protected version built below.
3030 if Nkind
(Op_Spec
) = N_Function_Specification
then
3032 R
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('R'));
3034 Make_Object_Declaration
(Loc
,
3035 Defining_Identifier
=> R
,
3036 Constant_Present
=> True,
3037 Object_Definition
=> New_Copy
(Result_Definition
(N_Op_Spec
)),
3039 Make_Function_Call
(Loc
,
3040 Name
=> Make_Identifier
(Loc
,
3041 Chars
(Defining_Unit_Name
(N_Op_Spec
))),
3042 Parameter_Associations
=> Uactuals
));
3043 Return_Stmt
:= Make_Simple_Return_Statement
(Loc
,
3044 Expression
=> New_Reference_To
(R
, Loc
));
3047 Unprot_Call
:= Make_Simple_Return_Statement
(Loc
,
3048 Expression
=> Make_Function_Call
(Loc
,
3050 Make_Identifier
(Loc
,
3051 Chars
(Defining_Unit_Name
(N_Op_Spec
))),
3052 Parameter_Associations
=> Uactuals
));
3057 Make_Procedure_Call_Statement
(Loc
,
3059 Make_Identifier
(Loc
,
3060 Chars
(Defining_Unit_Name
(N_Op_Spec
))),
3061 Parameter_Associations
=> Uactuals
);
3064 -- Wrap call in block that will be covered by an at_end handler
3066 if not Exc_Safe
then
3067 Unprot_Call
:= Make_Block_Statement
(Loc
,
3068 Handled_Statement_Sequence
=>
3069 Make_Handled_Sequence_Of_Statements
(Loc
,
3070 Statements
=> New_List
(Unprot_Call
)));
3073 -- Make the protected subprogram body. This locks the protected
3074 -- object and calls the unprotected version of the subprogram.
3076 case Corresponding_Runtime_Package
(Pid
) is
3077 when System_Tasking_Protected_Objects_Entries
=>
3078 Lock_Name
:= New_Reference_To
(RTE
(RE_Lock_Entries
), Loc
);
3079 Service_Name
:= New_Reference_To
(RTE
(RE_Service_Entries
), Loc
);
3081 when System_Tasking_Protected_Objects_Single_Entry
=>
3082 Lock_Name
:= New_Reference_To
(RTE
(RE_Lock_Entry
), Loc
);
3083 Service_Name
:= New_Reference_To
(RTE
(RE_Service_Entry
), Loc
);
3085 when System_Tasking_Protected_Objects
=>
3086 Lock_Name
:= New_Reference_To
(RTE
(RE_Lock
), Loc
);
3087 Service_Name
:= New_Reference_To
(RTE
(RE_Unlock
), Loc
);
3090 raise Program_Error
;
3094 Make_Attribute_Reference
(Loc
,
3096 Make_Selected_Component
(Loc
,
3098 Make_Identifier
(Loc
, Name_uObject
),
3100 Make_Identifier
(Loc
, Name_uObject
)),
3101 Attribute_Name
=> Name_Unchecked_Access
);
3103 Lock_Stmt
:= Make_Procedure_Call_Statement
(Loc
,
3105 Parameter_Associations
=> New_List
(Object_Parm
));
3107 if Abort_Allowed
then
3109 Make_Procedure_Call_Statement
(Loc
,
3110 Name
=> New_Reference_To
(RTE
(RE_Abort_Defer
), Loc
),
3111 Parameter_Associations
=> Empty_List
),
3115 Stmts
:= New_List
(Lock_Stmt
);
3118 if not Exc_Safe
then
3119 Append
(Unprot_Call
, Stmts
);
3121 if Nkind
(Op_Spec
) = N_Function_Specification
then
3123 Stmts
:= Empty_List
;
3125 Append
(Unprot_Call
, Stmts
);
3129 Make_Procedure_Call_Statement
(Loc
,
3130 Name
=> Service_Name
,
3131 Parameter_Associations
=>
3132 New_List
(New_Copy_Tree
(Object_Parm
))),
3135 if Abort_Allowed
then
3137 Make_Procedure_Call_Statement
(Loc
,
3138 Name
=> New_Reference_To
(RTE
(RE_Abort_Undefer
), Loc
),
3139 Parameter_Associations
=> Empty_List
),
3143 if Nkind
(Op_Spec
) = N_Function_Specification
then
3144 Append
(Return_Stmt
, Stmts
);
3145 Append
(Make_Block_Statement
(Loc
,
3146 Declarations
=> New_List
(Unprot_Call
),
3147 Handled_Statement_Sequence
=>
3148 Make_Handled_Sequence_Of_Statements
(Loc
,
3149 Statements
=> Stmts
)), Pre_Stmts
);
3155 Make_Subprogram_Body
(Loc
,
3156 Declarations
=> Empty_List
,
3157 Specification
=> P_Op_Spec
,
3158 Handled_Statement_Sequence
=>
3159 Make_Handled_Sequence_Of_Statements
(Loc
, Statements
=> Stmts
));
3161 if not Exc_Safe
then
3162 Set_Is_Protected_Subprogram_Body
(Sub_Body
);
3166 end Build_Protected_Subprogram_Body
;
3168 -------------------------------------
3169 -- Build_Protected_Subprogram_Call --
3170 -------------------------------------
3172 procedure Build_Protected_Subprogram_Call
3176 External
: Boolean := True)
3178 Loc
: constant Source_Ptr
:= Sloc
(N
);
3179 Sub
: constant Entity_Id
:= Entity
(Name
);
3185 New_Sub
:= New_Occurrence_Of
(External_Subprogram
(Sub
), Loc
);
3188 New_Occurrence_Of
(Protected_Body_Subprogram
(Sub
), Loc
);
3191 if Present
(Parameter_Associations
(N
)) then
3192 Params
:= New_Copy_List_Tree
(Parameter_Associations
(N
));
3197 -- If the type is an untagged derived type, convert to the root type,
3198 -- which is the one on which the operations are defined.
3200 if Nkind
(Rec
) = N_Unchecked_Type_Conversion
3201 and then not Is_Tagged_Type
(Etype
(Rec
))
3202 and then Is_Derived_Type
(Etype
(Rec
))
3204 Set_Etype
(Rec
, Root_Type
(Etype
(Rec
)));
3205 Set_Subtype_Mark
(Rec
,
3206 New_Occurrence_Of
(Root_Type
(Etype
(Rec
)), Sloc
(N
)));
3209 Prepend
(Rec
, Params
);
3211 if Ekind
(Sub
) = E_Procedure
then
3213 Make_Procedure_Call_Statement
(Loc
,
3215 Parameter_Associations
=> Params
));
3218 pragma Assert
(Ekind
(Sub
) = E_Function
);
3220 Make_Function_Call
(Loc
,
3222 Parameter_Associations
=> Params
));
3226 and then Nkind
(Rec
) = N_Unchecked_Type_Conversion
3227 and then Is_Entity_Name
(Expression
(Rec
))
3228 and then Is_Shared_Passive
(Entity
(Expression
(Rec
)))
3230 Add_Shared_Var_Lock_Procs
(N
);
3232 end Build_Protected_Subprogram_Call
;
3234 -------------------------
3235 -- Build_Selected_Name --
3236 -------------------------
3238 function Build_Selected_Name
3239 (Prefix
: Entity_Id
;
3240 Selector
: Entity_Id
;
3241 Append_Char
: Character := ' ') return Name_Id
3243 Select_Buffer
: String (1 .. Hostparm
.Max_Name_Length
);
3244 Select_Len
: Natural;
3247 Get_Name_String
(Chars
(Selector
));
3248 Select_Len
:= Name_Len
;
3249 Select_Buffer
(1 .. Select_Len
) := Name_Buffer
(1 .. Name_Len
);
3250 Get_Name_String
(Chars
(Prefix
));
3252 -- If scope is anonymous type, discard suffix to recover name of
3253 -- single protected object. Otherwise use protected type name.
3255 if Name_Buffer
(Name_Len
) = 'T' then
3256 Name_Len
:= Name_Len
- 1;
3259 Add_Str_To_Name_Buffer
("__");
3260 for J
in 1 .. Select_Len
loop
3261 Add_Char_To_Name_Buffer
(Select_Buffer
(J
));
3264 -- Now add the Append_Char if specified. The encoding to follow
3265 -- depends on the type of entity. If Append_Char is either 'N' or 'P',
3266 -- then the entity is associated to a protected type subprogram.
3267 -- Otherwise, it is a protected type entry. For each case, the
3268 -- encoding to follow for the suffix is documented in exp_dbug.ads.
3270 -- It would be better to encapsulate this as a routine in Exp_Dbug ???
3272 if Append_Char
/= ' ' then
3273 if Append_Char
= 'P' or Append_Char
= 'N' then
3274 Add_Char_To_Name_Buffer
(Append_Char
);
3277 Add_Str_To_Name_Buffer
((1 => '_', 2 => Append_Char
));
3278 return New_External_Name
(Name_Find
, ' ', -1);
3283 end Build_Selected_Name
;
3285 -----------------------------
3286 -- Build_Simple_Entry_Call --
3287 -----------------------------
3289 -- A task entry call is converted to a call to Call_Simple
3292 -- P : parms := (parm, parm, parm);
3294 -- Call_Simple (acceptor-task, entry-index, P'Address);
3300 -- Here Pnn is an aggregate of the type constructed for the entry to hold
3301 -- the parameters, and the constructed aggregate value contains either the
3302 -- parameters or, in the case of non-elementary types, references to these
3303 -- parameters. Then the address of this aggregate is passed to the runtime
3304 -- routine, along with the task id value and the task entry index value.
3305 -- Pnn is only required if parameters are present.
3307 -- The assignments after the call are present only in the case of in-out
3308 -- or out parameters for elementary types, and are used to assign back the
3309 -- resulting values of such parameters.
3311 -- Note: the reason that we insert a block here is that in the context
3312 -- of selects, conditional entry calls etc. the entry call statement
3313 -- appears on its own, not as an element of a list.
3315 -- A protected entry call is converted to a Protected_Entry_Call:
3318 -- P : E1_Params := (param, param, param);
3320 -- Bnn : Communications_Block;
3323 -- P : E1_Params := (param, param, param);
3324 -- Bnn : Communications_Block;
3327 -- Protected_Entry_Call (
3328 -- Object => po._object'Access,
3329 -- E => <entry index>;
3330 -- Uninterpreted_Data => P'Address;
3331 -- Mode => Simple_Call;
3338 procedure Build_Simple_Entry_Call
3347 -- If call has been inlined, nothing left to do
3349 if Nkind
(N
) = N_Block_Statement
then
3353 -- Convert entry call to Call_Simple call
3356 Loc
: constant Source_Ptr
:= Sloc
(N
);
3357 Parms
: constant List_Id
:= Parameter_Associations
(N
);
3358 Stats
: constant List_Id
:= New_List
;
3361 Comm_Name
: Entity_Id
;
3365 Ent_Acc
: Entity_Id
;
3367 Iface_Tag
: Entity_Id
;
3368 Iface_Typ
: Entity_Id
;
3381 -- Simple entry and entry family cases merge here
3383 Ent
:= Entity
(Ename
);
3384 Ent_Acc
:= Entry_Parameters_Type
(Ent
);
3385 Conctyp
:= Etype
(Concval
);
3387 -- If prefix is an access type, dereference to obtain the task type
3389 if Is_Access_Type
(Conctyp
) then
3390 Conctyp
:= Designated_Type
(Conctyp
);
3393 -- Special case for protected subprogram calls
3395 if Is_Protected_Type
(Conctyp
)
3396 and then Is_Subprogram
(Entity
(Ename
))
3398 if not Is_Eliminated
(Entity
(Ename
)) then
3399 Build_Protected_Subprogram_Call
3400 (N
, Ename
, Convert_Concurrent
(Concval
, Conctyp
));
3407 -- First parameter is the Task_Id value from the task value or the
3408 -- Object from the protected object value, obtained by selecting
3409 -- the _Task_Id or _Object from the result of doing an unchecked
3410 -- conversion to convert the value to the corresponding record type.
3412 if Nkind
(Concval
) = N_Function_Call
3413 and then Is_Task_Type
(Conctyp
)
3414 and then Ada_Version
>= Ada_05
3417 Obj
: constant Entity_Id
:=
3418 Make_Defining_Identifier
(Loc
, New_Internal_Name
('F'));
3423 Make_Object_Declaration
(Loc
,
3424 Defining_Identifier
=> Obj
,
3425 Object_Definition
=> New_Occurrence_Of
(Conctyp
, Loc
),
3426 Expression
=> Relocate_Node
(Concval
));
3427 Set_Etype
(Obj
, Conctyp
);
3428 Decls
:= New_List
(Decl
);
3429 Rewrite
(Concval
, New_Occurrence_Of
(Obj
, Loc
));
3436 Parm1
:= Concurrent_Ref
(Concval
);
3438 -- Second parameter is the entry index, computed by the routine
3439 -- provided for this purpose. The value of this expression is
3440 -- assigned to an intermediate variable to assure that any entry
3441 -- family index expressions are evaluated before the entry
3445 or else Restriction_Active
(No_Entry_Queue
) = False
3446 or else not Is_Protected_Type
(Conctyp
)
3447 or else Number_Entries
(Conctyp
) > 1
3448 or else (Has_Attach_Handler
(Conctyp
)
3449 and then not Restricted_Profile
)
3451 X
:= Make_Defining_Identifier
(Loc
, Name_uX
);
3454 Make_Object_Declaration
(Loc
,
3455 Defining_Identifier
=> X
,
3456 Object_Definition
=>
3457 New_Reference_To
(RTE
(RE_Task_Entry_Index
), Loc
),
3458 Expression
=> Actual_Index_Expression
(
3459 Loc
, Entity
(Ename
), Index
, Concval
));
3461 Append_To
(Decls
, Xdecl
);
3462 Parm2
:= New_Reference_To
(X
, Loc
);
3469 -- The third parameter is the packaged parameters. If there are
3470 -- none, then it is just the null address, since nothing is passed.
3473 Parm3
:= New_Reference_To
(RTE
(RE_Null_Address
), Loc
);
3476 -- Case of parameters present, where third argument is the address
3477 -- of a packaged record containing the required parameter values.
3480 -- First build a list of parameter values, which are references to
3481 -- objects of the parameter types.
3485 Actual
:= First_Actual
(N
);
3486 Formal
:= First_Formal
(Ent
);
3488 while Present
(Actual
) loop
3490 -- If it is a by_copy_type, copy it to a new variable. The
3491 -- packaged record has a field that points to this variable.
3493 if Is_By_Copy_Type
(Etype
(Actual
)) then
3495 Make_Object_Declaration
(Loc
,
3496 Defining_Identifier
=>
3497 Make_Defining_Identifier
(Loc
,
3498 Chars
=> New_Internal_Name
('J')),
3499 Aliased_Present
=> True,
3500 Object_Definition
=>
3501 New_Reference_To
(Etype
(Formal
), Loc
));
3503 -- Mark the object as not needing initialization since the
3504 -- initialization is performed separately, avoiding errors
3505 -- on cases such as formals of null-excluding access types.
3507 Set_No_Initialization
(N_Node
);
3509 -- We must make an assignment statement separate for the
3510 -- case of limited type. We cannot assign it unless the
3511 -- Assignment_OK flag is set first. An out formal of an
3512 -- access type must also be initialized from the actual,
3513 -- as stated in RM 6.4.1 (13).
3515 if Ekind
(Formal
) /= E_Out_Parameter
3516 or else Is_Access_Type
(Etype
(Formal
))
3519 New_Reference_To
(Defining_Identifier
(N_Node
), Loc
);
3520 Set_Assignment_OK
(N_Var
);
3522 Make_Assignment_Statement
(Loc
,
3524 Expression
=> Relocate_Node
(Actual
)));
3527 Append
(N_Node
, Decls
);
3530 Make_Attribute_Reference
(Loc
,
3531 Attribute_Name
=> Name_Unchecked_Access
,
3533 New_Reference_To
(Defining_Identifier
(N_Node
), Loc
)));
3535 -- Interface class-wide formal
3537 if Ada_Version
>= Ada_05
3538 and then Ekind
(Etype
(Formal
)) = E_Class_Wide_Type
3539 and then Is_Interface
(Etype
(Formal
))
3541 Iface_Typ
:= Etype
(Etype
(Formal
));
3544 -- formal_iface_type! (actual.iface_tag)'reference
3547 Find_Interface_Tag
(Etype
(Actual
), Iface_Typ
);
3548 pragma Assert
(Present
(Iface_Tag
));
3551 Make_Reference
(Loc
,
3552 Unchecked_Convert_To
(Iface_Typ
,
3553 Make_Selected_Component
(Loc
,
3555 Relocate_Node
(Actual
),
3557 New_Reference_To
(Iface_Tag
, Loc
)))));
3563 Make_Reference
(Loc
, Relocate_Node
(Actual
)));
3567 Next_Actual
(Actual
);
3568 Next_Formal_With_Extras
(Formal
);
3571 -- Now build the declaration of parameters initialized with the
3572 -- aggregate containing this constructed parameter list.
3574 P
:= Make_Defining_Identifier
(Loc
, Name_uP
);
3577 Make_Object_Declaration
(Loc
,
3578 Defining_Identifier
=> P
,
3579 Object_Definition
=>
3580 New_Reference_To
(Designated_Type
(Ent_Acc
), Loc
),
3582 Make_Aggregate
(Loc
, Expressions
=> Plist
));
3585 Make_Attribute_Reference
(Loc
,
3586 Prefix
=> New_Reference_To
(P
, Loc
),
3587 Attribute_Name
=> Name_Address
);
3589 Append
(Pdecl
, Decls
);
3592 -- Now we can create the call, case of protected type
3594 if Is_Protected_Type
(Conctyp
) then
3595 case Corresponding_Runtime_Package
(Conctyp
) is
3596 when System_Tasking_Protected_Objects_Entries
=>
3598 -- Change the type of the index declaration
3600 Set_Object_Definition
(Xdecl
,
3601 New_Reference_To
(RTE
(RE_Protected_Entry_Index
), Loc
));
3603 -- Some additional declarations for protected entry calls
3609 -- Bnn : Communications_Block;
3612 Make_Defining_Identifier
(Loc
, New_Internal_Name
('B'));
3615 Make_Object_Declaration
(Loc
,
3616 Defining_Identifier
=> Comm_Name
,
3617 Object_Definition
=>
3618 New_Reference_To
(RTE
(RE_Communication_Block
), Loc
)));
3620 -- Some additional statements for protected entry calls
3622 -- Protected_Entry_Call (
3623 -- Object => po._object'Access,
3624 -- E => <entry index>;
3625 -- Uninterpreted_Data => P'Address;
3626 -- Mode => Simple_Call;
3630 Make_Procedure_Call_Statement
(Loc
,
3632 New_Reference_To
(RTE
(RE_Protected_Entry_Call
), Loc
),
3634 Parameter_Associations
=> New_List
(
3635 Make_Attribute_Reference
(Loc
,
3636 Attribute_Name
=> Name_Unchecked_Access
,
3640 New_Reference_To
(RTE
(RE_Simple_Call
), Loc
),
3641 New_Occurrence_Of
(Comm_Name
, Loc
)));
3643 when System_Tasking_Protected_Objects_Single_Entry
=>
3644 -- Protected_Single_Entry_Call (
3645 -- Object => po._object'Access,
3646 -- Uninterpreted_Data => P'Address;
3647 -- Mode => Simple_Call);
3650 Make_Procedure_Call_Statement
(Loc
,
3651 Name
=> New_Reference_To
(
3652 RTE
(RE_Protected_Single_Entry_Call
), Loc
),
3654 Parameter_Associations
=> New_List
(
3655 Make_Attribute_Reference
(Loc
,
3656 Attribute_Name
=> Name_Unchecked_Access
,
3659 New_Reference_To
(RTE
(RE_Simple_Call
), Loc
)));
3662 raise Program_Error
;
3665 -- Case of task type
3669 Make_Procedure_Call_Statement
(Loc
,
3670 Name
=> New_Reference_To
(RTE
(RE_Call_Simple
), Loc
),
3671 Parameter_Associations
=> New_List
(Parm1
, Parm2
, Parm3
));
3675 Append_To
(Stats
, Call
);
3677 -- If there are out or in/out parameters by copy add assignment
3678 -- statements for the result values.
3680 if Present
(Parms
) then
3681 Actual
:= First_Actual
(N
);
3682 Formal
:= First_Formal
(Ent
);
3684 Set_Assignment_OK
(Actual
);
3685 while Present
(Actual
) loop
3686 if Is_By_Copy_Type
(Etype
(Actual
))
3687 and then Ekind
(Formal
) /= E_In_Parameter
3690 Make_Assignment_Statement
(Loc
,
3691 Name
=> New_Copy
(Actual
),
3693 Make_Explicit_Dereference
(Loc
,
3694 Make_Selected_Component
(Loc
,
3695 Prefix
=> New_Reference_To
(P
, Loc
),
3697 Make_Identifier
(Loc
, Chars
(Formal
)))));
3699 -- In all cases (including limited private types) we want
3700 -- the assignment to be valid.
3702 Set_Assignment_OK
(Name
(N_Node
));
3704 -- If the call is the triggering alternative in an
3705 -- asynchronous select, or the entry_call alternative of a
3706 -- conditional entry call, the assignments for in-out
3707 -- parameters are incorporated into the statement list that
3708 -- follows, so that there are executed only if the entry
3711 if (Nkind
(Parent
(N
)) = N_Triggering_Alternative
3712 and then N
= Triggering_Statement
(Parent
(N
)))
3714 (Nkind
(Parent
(N
)) = N_Entry_Call_Alternative
3715 and then N
= Entry_Call_Statement
(Parent
(N
)))
3717 if No
(Statements
(Parent
(N
))) then
3718 Set_Statements
(Parent
(N
), New_List
);
3721 Prepend
(N_Node
, Statements
(Parent
(N
)));
3724 Insert_After
(Call
, N_Node
);
3728 Next_Actual
(Actual
);
3729 Next_Formal_With_Extras
(Formal
);
3733 -- Finally, create block and analyze it
3736 Make_Block_Statement
(Loc
,
3737 Declarations
=> Decls
,
3738 Handled_Statement_Sequence
=>
3739 Make_Handled_Sequence_Of_Statements
(Loc
,
3740 Statements
=> Stats
)));
3744 end Build_Simple_Entry_Call
;
3746 --------------------------------
3747 -- Build_Task_Activation_Call --
3748 --------------------------------
3750 procedure Build_Task_Activation_Call
(N
: Node_Id
) is
3751 Loc
: constant Source_Ptr
:= Sloc
(N
);
3758 -- Get the activation chain entity. Except in the case of a package
3759 -- body, this is in the node that was passed. For a package body, we
3760 -- have to find the corresponding package declaration node.
3762 if Nkind
(N
) = N_Package_Body
then
3763 P
:= Corresponding_Spec
(N
);
3766 exit when Nkind
(P
) = N_Package_Declaration
;
3769 Chain
:= Activation_Chain_Entity
(P
);
3772 Chain
:= Activation_Chain_Entity
(N
);
3775 if Present
(Chain
) then
3776 if Restricted_Profile
then
3777 Name
:= New_Reference_To
(RTE
(RE_Activate_Restricted_Tasks
), Loc
);
3779 Name
:= New_Reference_To
(RTE
(RE_Activate_Tasks
), Loc
);
3783 Make_Procedure_Call_Statement
(Loc
,
3785 Parameter_Associations
=>
3786 New_List
(Make_Attribute_Reference
(Loc
,
3787 Prefix
=> New_Occurrence_Of
(Chain
, Loc
),
3788 Attribute_Name
=> Name_Unchecked_Access
)));
3790 if Nkind
(N
) = N_Package_Declaration
then
3791 if Present
(Corresponding_Body
(N
)) then
3794 elsif Present
(Private_Declarations
(Specification
(N
))) then
3795 Append
(Call
, Private_Declarations
(Specification
(N
)));
3798 Append
(Call
, Visible_Declarations
(Specification
(N
)));
3802 if Present
(Handled_Statement_Sequence
(N
)) then
3804 -- The call goes at the start of the statement sequence
3805 -- after the start of exception range label if one is present.
3811 Stm
:= First
(Statements
(Handled_Statement_Sequence
(N
)));
3813 -- A special case, skip exception range label if one is
3814 -- present (from front end zcx processing).
3816 if Nkind
(Stm
) = N_Label
and then Exception_Junk
(Stm
) then
3820 -- Another special case, if the first statement is a block
3821 -- from optimization of a local raise to a goto, then the
3822 -- call goes inside this block.
3824 if Nkind
(Stm
) = N_Block_Statement
3825 and then Exception_Junk
(Stm
)
3828 First
(Statements
(Handled_Statement_Sequence
(Stm
)));
3831 -- Insertion point is after any exception label pushes,
3832 -- since we want it covered by any local handlers.
3834 while Nkind
(Stm
) in N_Push_xxx_Label
loop
3838 -- Now we have the proper insertion point
3840 Insert_Before
(Stm
, Call
);
3844 Set_Handled_Statement_Sequence
(N
,
3845 Make_Handled_Sequence_Of_Statements
(Loc
,
3846 Statements
=> New_List
(Call
)));
3851 Check_Task_Activation
(N
);
3853 end Build_Task_Activation_Call
;
3855 -------------------------------
3856 -- Build_Task_Allocate_Block --
3857 -------------------------------
3859 procedure Build_Task_Allocate_Block
3864 T
: constant Entity_Id
:= Entity
(Expression
(N
));
3865 Init
: constant Entity_Id
:= Base_Init_Proc
(T
);
3866 Loc
: constant Source_Ptr
:= Sloc
(N
);
3867 Chain
: constant Entity_Id
:=
3868 Make_Defining_Identifier
(Loc
, Name_uChain
);
3874 Blkent
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
3877 Make_Block_Statement
(Loc
,
3878 Identifier
=> New_Reference_To
(Blkent
, Loc
),
3879 Declarations
=> New_List
(
3881 -- _Chain : Activation_Chain;
3883 Make_Object_Declaration
(Loc
,
3884 Defining_Identifier
=> Chain
,
3885 Aliased_Present
=> True,
3886 Object_Definition
=>
3887 New_Reference_To
(RTE
(RE_Activation_Chain
), Loc
))),
3889 Handled_Statement_Sequence
=>
3890 Make_Handled_Sequence_Of_Statements
(Loc
,
3892 Statements
=> New_List
(
3896 Make_Procedure_Call_Statement
(Loc
,
3897 Name
=> New_Reference_To
(Init
, Loc
),
3898 Parameter_Associations
=> Args
),
3900 -- Activate_Tasks (_Chain);
3902 Make_Procedure_Call_Statement
(Loc
,
3903 Name
=> New_Reference_To
(RTE
(RE_Activate_Tasks
), Loc
),
3904 Parameter_Associations
=> New_List
(
3905 Make_Attribute_Reference
(Loc
,
3906 Prefix
=> New_Reference_To
(Chain
, Loc
),
3907 Attribute_Name
=> Name_Unchecked_Access
))))),
3909 Has_Created_Identifier
=> True,
3910 Is_Task_Allocation_Block
=> True);
3913 Make_Implicit_Label_Declaration
(Loc
,
3914 Defining_Identifier
=> Blkent
,
3915 Label_Construct
=> Block
));
3917 Append_To
(Actions
, Block
);
3919 Set_Activation_Chain_Entity
(Block
, Chain
);
3920 end Build_Task_Allocate_Block
;
3922 -----------------------------------------------
3923 -- Build_Task_Allocate_Block_With_Init_Stmts --
3924 -----------------------------------------------
3926 procedure Build_Task_Allocate_Block_With_Init_Stmts
3929 Init_Stmts
: List_Id
)
3931 Loc
: constant Source_Ptr
:= Sloc
(N
);
3932 Chain
: constant Entity_Id
:=
3933 Make_Defining_Identifier
(Loc
, Name_uChain
);
3938 Blkent
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
3940 Append_To
(Init_Stmts
,
3941 Make_Procedure_Call_Statement
(Loc
,
3942 Name
=> New_Reference_To
(RTE
(RE_Activate_Tasks
), Loc
),
3943 Parameter_Associations
=> New_List
(
3944 Make_Attribute_Reference
(Loc
,
3945 Prefix
=> New_Reference_To
(Chain
, Loc
),
3946 Attribute_Name
=> Name_Unchecked_Access
))));
3949 Make_Block_Statement
(Loc
,
3950 Identifier
=> New_Reference_To
(Blkent
, Loc
),
3951 Declarations
=> New_List
(
3953 -- _Chain : Activation_Chain;
3955 Make_Object_Declaration
(Loc
,
3956 Defining_Identifier
=> Chain
,
3957 Aliased_Present
=> True,
3958 Object_Definition
=>
3959 New_Reference_To
(RTE
(RE_Activation_Chain
), Loc
))),
3961 Handled_Statement_Sequence
=>
3962 Make_Handled_Sequence_Of_Statements
(Loc
, Init_Stmts
),
3964 Has_Created_Identifier
=> True,
3965 Is_Task_Allocation_Block
=> True);
3968 Make_Implicit_Label_Declaration
(Loc
,
3969 Defining_Identifier
=> Blkent
,
3970 Label_Construct
=> Block
));
3972 Append_To
(Actions
, Block
);
3974 Set_Activation_Chain_Entity
(Block
, Chain
);
3975 end Build_Task_Allocate_Block_With_Init_Stmts
;
3977 -----------------------------------
3978 -- Build_Task_Proc_Specification --
3979 -----------------------------------
3981 function Build_Task_Proc_Specification
(T
: Entity_Id
) return Node_Id
is
3982 Loc
: constant Source_Ptr
:= Sloc
(T
);
3983 Spec_Id
: Entity_Id
;
3987 Make_Defining_Identifier
(Loc
,
3988 Chars
=> New_External_Name
(Chars
(T
), 'B'));
3989 Set_Is_Internal
(Spec_Id
);
3991 -- Associate the procedure with the task, if this is the declaration
3992 -- (and not the body) of the procedure.
3994 if No
(Task_Body_Procedure
(T
)) then
3995 Set_Task_Body_Procedure
(T
, Spec_Id
);
3999 Make_Procedure_Specification
(Loc
,
4000 Defining_Unit_Name
=> Spec_Id
,
4001 Parameter_Specifications
=> New_List
(
4002 Make_Parameter_Specification
(Loc
,
4003 Defining_Identifier
=>
4004 Make_Defining_Identifier
(Loc
, Name_uTask
),
4006 Make_Access_Definition
(Loc
,
4008 New_Reference_To
(Corresponding_Record_Type
(T
), Loc
)))));
4009 end Build_Task_Proc_Specification
;
4011 ---------------------------------------
4012 -- Build_Unprotected_Subprogram_Body --
4013 ---------------------------------------
4015 function Build_Unprotected_Subprogram_Body
4017 Pid
: Node_Id
) return Node_Id
4019 Decls
: constant List_Id
:= Declarations
(N
);
4022 -- Add renamings for the Protection object, discriminals, privals and
4023 -- the entry index constant for use by debugger.
4025 Debug_Private_Data_Declarations
(Decls
);
4027 -- Make an unprotected version of the subprogram for use within the same
4028 -- object, with a new name and an additional parameter representing the
4032 Make_Subprogram_Body
(Sloc
(N
),
4034 Build_Protected_Sub_Specification
(N
, Pid
, Unprotected_Mode
),
4035 Declarations
=> Decls
,
4036 Handled_Statement_Sequence
=> Handled_Statement_Sequence
(N
));
4037 end Build_Unprotected_Subprogram_Body
;
4039 ----------------------------
4040 -- Collect_Entry_Families --
4041 ----------------------------
4043 procedure Collect_Entry_Families
4046 Current_Node
: in out Node_Id
;
4047 Conctyp
: Entity_Id
)
4050 Efam_Decl
: Node_Id
;
4051 Efam_Type
: Entity_Id
;
4054 Efam
:= First_Entity
(Conctyp
);
4055 while Present
(Efam
) loop
4056 if Ekind
(Efam
) = E_Entry_Family
then
4058 Make_Defining_Identifier
(Loc
,
4059 Chars
=> New_Internal_Name
('F'));
4064 (Etype
(Discrete_Subtype_Definition
(Parent
(Efam
))));
4066 Bas_Decl
: Node_Id
:= Empty
;
4071 (Discrete_Subtype_Definition
(Parent
(Efam
)), Lo
, Hi
);
4073 if Is_Potentially_Large_Family
(Bas
, Conctyp
, Lo
, Hi
) then
4075 Make_Defining_Identifier
(Loc
,
4076 Chars
=> New_Internal_Name
('B'));
4079 Make_Subtype_Declaration
(Loc
,
4080 Defining_Identifier
=> Bas
,
4081 Subtype_Indication
=>
4082 Make_Subtype_Indication
(Loc
,
4084 New_Occurrence_Of
(Standard_Integer
, Loc
),
4086 Make_Range_Constraint
(Loc
,
4087 Range_Expression
=> Make_Range
(Loc
,
4088 Make_Integer_Literal
4089 (Loc
, -Entry_Family_Bound
),
4090 Make_Integer_Literal
4091 (Loc
, Entry_Family_Bound
- 1)))));
4093 Insert_After
(Current_Node
, Bas_Decl
);
4094 Current_Node
:= Bas_Decl
;
4099 Make_Full_Type_Declaration
(Loc
,
4100 Defining_Identifier
=> Efam_Type
,
4102 Make_Unconstrained_Array_Definition
(Loc
,
4104 (New_List
(New_Occurrence_Of
(Bas
, Loc
))),
4106 Component_Definition
=>
4107 Make_Component_Definition
(Loc
,
4108 Aliased_Present
=> False,
4109 Subtype_Indication
=>
4110 New_Reference_To
(Standard_Character
, Loc
))));
4113 Insert_After
(Current_Node
, Efam_Decl
);
4114 Current_Node
:= Efam_Decl
;
4115 Analyze
(Efam_Decl
);
4118 Make_Component_Declaration
(Loc
,
4119 Defining_Identifier
=>
4120 Make_Defining_Identifier
(Loc
, Chars
(Efam
)),
4122 Component_Definition
=>
4123 Make_Component_Definition
(Loc
,
4124 Aliased_Present
=> False,
4125 Subtype_Indication
=>
4126 Make_Subtype_Indication
(Loc
,
4128 New_Occurrence_Of
(Efam_Type
, Loc
),
4131 Make_Index_Or_Discriminant_Constraint
(Loc
,
4132 Constraints
=> New_List
(
4134 (Etype
(Discrete_Subtype_Definition
4135 (Parent
(Efam
))), Loc
)))))));
4141 end Collect_Entry_Families
;
4143 -----------------------
4144 -- Concurrent_Object --
4145 -----------------------
4147 function Concurrent_Object
4148 (Spec_Id
: Entity_Id
;
4149 Conc_Typ
: Entity_Id
) return Entity_Id
4152 -- Parameter _O or _object
4154 if Is_Protected_Type
(Conc_Typ
) then
4155 return First_Formal
(Protected_Body_Subprogram
(Spec_Id
));
4160 pragma Assert
(Is_Task_Type
(Conc_Typ
));
4161 return First_Formal
(Task_Body_Procedure
(Conc_Typ
));
4163 end Concurrent_Object
;
4165 ----------------------
4166 -- Copy_Result_Type --
4167 ----------------------
4169 function Copy_Result_Type
(Res
: Node_Id
) return Node_Id
is
4170 New_Res
: constant Node_Id
:= New_Copy_Tree
(Res
);
4175 -- If the result type is an access_to_subprogram, we must create
4176 -- new entities for its spec.
4178 if Nkind
(New_Res
) = N_Access_Definition
4179 and then Present
(Access_To_Subprogram_Definition
(New_Res
))
4181 -- Provide new entities for the formals
4183 Par_Spec
:= First
(Parameter_Specifications
4184 (Access_To_Subprogram_Definition
(New_Res
)));
4185 while Present
(Par_Spec
) loop
4186 Formal
:= Defining_Identifier
(Par_Spec
);
4187 Set_Defining_Identifier
(Par_Spec
,
4188 Make_Defining_Identifier
(Sloc
(Formal
), Chars
(Formal
)));
4194 end Copy_Result_Type
;
4196 --------------------
4197 -- Concurrent_Ref --
4198 --------------------
4200 -- The expression returned for a reference to a concurrent object has the
4203 -- taskV!(name)._Task_Id
4207 -- objectV!(name)._Object
4209 -- for a protected object. For the case of an access to a concurrent
4210 -- object, there is an extra explicit dereference:
4212 -- taskV!(name.all)._Task_Id
4213 -- objectV!(name.all)._Object
4215 -- here taskV and objectV are the types for the associated records, which
4216 -- contain the required _Task_Id and _Object fields for tasks and protected
4217 -- objects, respectively.
4219 -- For the case of a task type name, the expression is
4223 -- i.e. a call to the Self function which returns precisely this Task_Id
4225 -- For the case of a protected type name, the expression is
4229 -- which is a renaming of the _object field of the current object
4230 -- record, passed into protected operations as a parameter.
4232 function Concurrent_Ref
(N
: Node_Id
) return Node_Id
is
4233 Loc
: constant Source_Ptr
:= Sloc
(N
);
4234 Ntyp
: constant Entity_Id
:= Etype
(N
);
4238 function Is_Current_Task
(T
: Entity_Id
) return Boolean;
4239 -- Check whether the reference is to the immediately enclosing task
4240 -- type, or to an outer one (rare but legal).
4242 ---------------------
4243 -- Is_Current_Task --
4244 ---------------------
4246 function Is_Current_Task
(T
: Entity_Id
) return Boolean is
4250 Scop
:= Current_Scope
;
4251 while Present
(Scop
)
4252 and then Scop
/= Standard_Standard
4258 elsif Is_Task_Type
(Scop
) then
4261 -- If this is a procedure nested within the task type, we must
4262 -- assume that it can be called from an inner task, and therefore
4263 -- cannot treat it as a local reference.
4265 elsif Is_Overloadable
(Scop
)
4266 and then In_Open_Scopes
(T
)
4271 Scop
:= Scope
(Scop
);
4275 -- We know that we are within the task body, so should have found it
4278 raise Program_Error
;
4279 end Is_Current_Task
;
4281 -- Start of processing for Concurrent_Ref
4284 if Is_Access_Type
(Ntyp
) then
4285 Dtyp
:= Designated_Type
(Ntyp
);
4287 if Is_Protected_Type
(Dtyp
) then
4288 Sel
:= Name_uObject
;
4290 Sel
:= Name_uTask_Id
;
4294 Make_Selected_Component
(Loc
,
4296 Unchecked_Convert_To
(Corresponding_Record_Type
(Dtyp
),
4297 Make_Explicit_Dereference
(Loc
, N
)),
4298 Selector_Name
=> Make_Identifier
(Loc
, Sel
));
4300 elsif Is_Entity_Name
(N
)
4301 and then Is_Concurrent_Type
(Entity
(N
))
4303 if Is_Task_Type
(Entity
(N
)) then
4305 if Is_Current_Task
(Entity
(N
)) then
4307 Make_Function_Call
(Loc
,
4308 Name
=> New_Reference_To
(RTE
(RE_Self
), Loc
));
4313 T_Self
: constant Entity_Id
:=
4314 Make_Defining_Identifier
(Loc
,
4315 Chars
=> New_Internal_Name
('T'));
4316 T_Body
: constant Node_Id
:=
4317 Parent
(Corresponding_Body
(Parent
(Entity
(N
))));
4320 Decl
:= Make_Object_Declaration
(Loc
,
4321 Defining_Identifier
=> T_Self
,
4322 Object_Definition
=>
4323 New_Occurrence_Of
(RTE
(RO_ST_Task_Id
), Loc
),
4325 Make_Function_Call
(Loc
,
4326 Name
=> New_Reference_To
(RTE
(RE_Self
), Loc
)));
4327 Prepend
(Decl
, Declarations
(T_Body
));
4329 Set_Scope
(T_Self
, Entity
(N
));
4330 return New_Occurrence_Of
(T_Self
, Loc
);
4335 pragma Assert
(Is_Protected_Type
(Entity
(N
)));
4338 New_Reference_To
(Find_Protection_Object
(Current_Scope
), Loc
);
4342 if Is_Protected_Type
(Ntyp
) then
4343 Sel
:= Name_uObject
;
4345 elsif Is_Task_Type
(Ntyp
) then
4346 Sel
:= Name_uTask_Id
;
4349 raise Program_Error
;
4353 Make_Selected_Component
(Loc
,
4355 Unchecked_Convert_To
(Corresponding_Record_Type
(Ntyp
),
4357 Selector_Name
=> Make_Identifier
(Loc
, Sel
));
4361 ------------------------
4362 -- Convert_Concurrent --
4363 ------------------------
4365 function Convert_Concurrent
4367 Typ
: Entity_Id
) return Node_Id
4370 if not Is_Concurrent_Type
(Typ
) then
4374 Unchecked_Convert_To
4375 (Corresponding_Record_Type
(Typ
), New_Copy_Tree
(N
));
4377 end Convert_Concurrent
;
4379 -------------------------------------
4380 -- Debug_Private_Data_Declarations --
4381 -------------------------------------
4383 procedure Debug_Private_Data_Declarations
(Decls
: List_Id
) is
4384 Debug_Nod
: Node_Id
;
4388 Decl
:= First
(Decls
);
4389 while Present
(Decl
)
4390 and then not Comes_From_Source
(Decl
)
4392 -- Declaration for concurrent entity _object and its access type,
4393 -- along with the entry index subtype:
4394 -- type prot_typVP is access prot_typV;
4395 -- _object : prot_typVP := prot_typV (_O);
4396 -- subtype Jnn is <Type of Index> range Low .. High;
4398 if Nkind_In
(Decl
, N_Full_Type_Declaration
, N_Object_Declaration
) then
4399 Set_Debug_Info_Needed
(Defining_Identifier
(Decl
));
4401 -- Declaration for the Protection object, discriminals, privals and
4402 -- entry index constant:
4403 -- conc_typR : protection_typ renames _object._object;
4404 -- discr_nameD : discr_typ renames _object.discr_name;
4405 -- discr_nameD : discr_typ renames _task.discr_name;
4406 -- prival_name : comp_typ renames _object.comp_name;
4407 -- J : constant Jnn :=
4408 -- Jnn'Val (_E - <Index expression> + Jnn'Pos (Jnn'First));
4410 elsif Nkind
(Decl
) = N_Object_Renaming_Declaration
then
4411 Set_Debug_Info_Needed
(Defining_Identifier
(Decl
));
4412 Debug_Nod
:= Debug_Renaming_Declaration
(Decl
);
4414 if Present
(Debug_Nod
) then
4415 Insert_After
(Decl
, Debug_Nod
);
4421 end Debug_Private_Data_Declarations
;
4423 ----------------------------
4424 -- Entry_Index_Expression --
4425 ----------------------------
4427 function Entry_Index_Expression
4431 Ttyp
: Entity_Id
) return Node_Id
4441 -- The queues of entries and entry families appear in textual order in
4442 -- the associated record. The entry index is computed as the sum of the
4443 -- number of queues for all entries that precede the designated one, to
4444 -- which is added the index expression, if this expression denotes a
4445 -- member of a family.
4447 -- The following is a place holder for the count of simple entries
4449 Num
:= Make_Integer_Literal
(Sloc
, 1);
4451 -- We construct an expression which is a series of addition operations.
4452 -- The first operand is the number of single entries that precede this
4453 -- one, the second operand is the index value relative to the start of
4454 -- the referenced family, and the remaining operands are the lengths of
4455 -- the entry families that precede this entry, i.e. the constructed
4458 -- number_simple_entries +
4459 -- (s'pos (index-value) - s'pos (family'first)) + 1 +
4460 -- family'length + ...
4462 -- where index-value is the given index value, and s is the index
4463 -- subtype (we have to use pos because the subtype might be an
4464 -- enumeration type preventing direct subtraction). Note that the task
4465 -- entry array is one-indexed.
4467 -- The upper bound of the entry family may be a discriminant, so we
4468 -- retrieve the lower bound explicitly to compute offset, rather than
4469 -- using the index subtype which may mention a discriminant.
4471 if Present
(Index
) then
4472 S
:= Etype
(Discrete_Subtype_Definition
(Declaration_Node
(Ent
)));
4481 Make_Attribute_Reference
(Sloc
,
4482 Attribute_Name
=> Name_Pos
,
4483 Prefix
=> New_Reference_To
(Base_Type
(S
), Sloc
),
4484 Expressions
=> New_List
(Relocate_Node
(Index
))),
4492 -- Now add lengths of preceding entries and entry families
4494 Prev
:= First_Entity
(Ttyp
);
4496 while Chars
(Prev
) /= Chars
(Ent
)
4497 or else (Ekind
(Prev
) /= Ekind
(Ent
))
4498 or else not Sem_Ch6
.Type_Conformant
(Ent
, Prev
)
4500 if Ekind
(Prev
) = E_Entry
then
4501 Set_Intval
(Num
, Intval
(Num
) + 1);
4503 elsif Ekind
(Prev
) = E_Entry_Family
then
4505 Etype
(Discrete_Subtype_Definition
(Declaration_Node
(Prev
)));
4506 Lo
:= Type_Low_Bound
(S
);
4507 Hi
:= Type_High_Bound
(S
);
4512 Right_Opnd
=> Family_Size
(Sloc
, Hi
, Lo
, Ttyp
, False));
4514 -- Other components are anonymous types to be ignored
4524 end Entry_Index_Expression
;
4526 ---------------------------
4527 -- Establish_Task_Master --
4528 ---------------------------
4530 procedure Establish_Task_Master
(N
: Node_Id
) is
4533 if Restriction_Active
(No_Task_Hierarchy
) = False then
4534 Call
:= Build_Runtime_Call
(Sloc
(N
), RE_Enter_Master
);
4535 Prepend_To
(Declarations
(N
), Call
);
4538 end Establish_Task_Master
;
4540 --------------------------------
4541 -- Expand_Accept_Declarations --
4542 --------------------------------
4544 -- Part of the expansion of an accept statement involves the creation of
4545 -- a declaration that can be referenced from the statement sequence of
4550 -- This declaration is inserted immediately before the accept statement
4551 -- and it is important that it be inserted before the statements of the
4552 -- statement sequence are analyzed. Thus it would be too late to create
4553 -- this declaration in the Expand_N_Accept_Statement routine, which is
4554 -- why there is a separate procedure to be called directly from Sem_Ch9.
4556 -- Ann is used to hold the address of the record containing the parameters
4557 -- (see Expand_N_Entry_Call for more details on how this record is built).
4558 -- References to the parameters do an unchecked conversion of this address
4559 -- to a pointer to the required record type, and then access the field that
4560 -- holds the value of the required parameter. The entity for the address
4561 -- variable is held as the top stack element (i.e. the last element) of the
4562 -- Accept_Address stack in the corresponding entry entity, and this element
4563 -- must be set in place before the statements are processed.
4565 -- The above description applies to the case of a stand alone accept
4566 -- statement, i.e. one not appearing as part of a select alternative.
4568 -- For the case of an accept that appears as part of a select alternative
4569 -- of a selective accept, we must still create the declaration right away,
4570 -- since Ann is needed immediately, but there is an important difference:
4572 -- The declaration is inserted before the selective accept, not before
4573 -- the accept statement (which is not part of a list anyway, and so would
4574 -- not accommodate inserted declarations)
4576 -- We only need one address variable for the entire selective accept. So
4577 -- the Ann declaration is created only for the first accept alternative,
4578 -- and subsequent accept alternatives reference the same Ann variable.
4580 -- We can distinguish the two cases by seeing whether the accept statement
4581 -- is part of a list. If not, then it must be in an accept alternative.
4583 -- To expand the requeue statement, a label is provided at the end of the
4584 -- accept statement or alternative of which it is a part, so that the
4585 -- statement can be skipped after the requeue is complete. This label is
4586 -- created here rather than during the expansion of the accept statement,
4587 -- because it will be needed by any requeue statements within the accept,
4588 -- which are expanded before the accept.
4590 procedure Expand_Accept_Declarations
(N
: Node_Id
; Ent
: Entity_Id
) is
4591 Loc
: constant Source_Ptr
:= Sloc
(N
);
4592 Stats
: constant Node_Id
:= Handled_Statement_Sequence
(N
);
4593 Ann
: Entity_Id
:= Empty
;
4601 if Expander_Active
then
4603 -- If we have no handled statement sequence, we may need to build
4604 -- a dummy sequence consisting of a null statement. This can be
4605 -- skipped if the trivial accept optimization is permitted.
4607 if not Trivial_Accept_OK
4609 (No
(Stats
) or else Null_Statements
(Statements
(Stats
)))
4611 Set_Handled_Statement_Sequence
(N
,
4612 Make_Handled_Sequence_Of_Statements
(Loc
,
4613 New_List
(Make_Null_Statement
(Loc
))));
4616 -- Create and declare two labels to be placed at the end of the
4617 -- accept statement. The first label is used to allow requeues to
4618 -- skip the remainder of entry processing. The second label is used
4619 -- to skip the remainder of entry processing if the rendezvous
4620 -- completes in the middle of the accept body.
4622 if Present
(Handled_Statement_Sequence
(N
)) then
4623 Lab_Id
:= Make_Identifier
(Loc
, New_Internal_Name
('L'));
4625 Make_Defining_Identifier
(Loc
, Chars
(Lab_Id
)));
4626 Lab
:= Make_Label
(Loc
, Lab_Id
);
4628 Make_Implicit_Label_Declaration
(Loc
,
4629 Defining_Identifier
=> Entity
(Lab_Id
),
4630 Label_Construct
=> Lab
);
4631 Append
(Lab
, Statements
(Handled_Statement_Sequence
(N
)));
4633 Lab_Id
:= Make_Identifier
(Loc
, New_Internal_Name
('L'));
4635 Make_Defining_Identifier
(Loc
, Chars
(Lab_Id
)));
4636 Lab
:= Make_Label
(Loc
, Lab_Id
);
4638 Make_Implicit_Label_Declaration
(Loc
,
4639 Defining_Identifier
=> Entity
(Lab_Id
),
4640 Label_Construct
=> Lab
);
4641 Append
(Lab
, Statements
(Handled_Statement_Sequence
(N
)));
4648 -- Case of stand alone accept statement
4650 if Is_List_Member
(N
) then
4652 if Present
(Handled_Statement_Sequence
(N
)) then
4654 Make_Defining_Identifier
(Loc
,
4655 Chars
=> New_Internal_Name
('A'));
4658 Make_Object_Declaration
(Loc
,
4659 Defining_Identifier
=> Ann
,
4660 Object_Definition
=>
4661 New_Reference_To
(RTE
(RE_Address
), Loc
));
4663 Insert_Before
(N
, Adecl
);
4666 Insert_Before
(N
, Ldecl
);
4669 Insert_Before
(N
, Ldecl2
);
4673 -- Case of accept statement which is in an accept alternative
4677 Acc_Alt
: constant Node_Id
:= Parent
(N
);
4678 Sel_Acc
: constant Node_Id
:= Parent
(Acc_Alt
);
4682 pragma Assert
(Nkind
(Acc_Alt
) = N_Accept_Alternative
);
4683 pragma Assert
(Nkind
(Sel_Acc
) = N_Selective_Accept
);
4685 -- ??? Consider a single label for select statements
4687 if Present
(Handled_Statement_Sequence
(N
)) then
4689 Statements
(Handled_Statement_Sequence
(N
)));
4693 Statements
(Handled_Statement_Sequence
(N
)));
4697 -- Find first accept alternative of the selective accept. A
4698 -- valid selective accept must have at least one accept in it.
4700 Alt
:= First
(Select_Alternatives
(Sel_Acc
));
4702 while Nkind
(Alt
) /= N_Accept_Alternative
loop
4706 -- If we are the first accept statement, then we have to create
4707 -- the Ann variable, as for the stand alone case, except that
4708 -- it is inserted before the selective accept. Similarly, a
4709 -- label for requeue expansion must be declared.
4711 if N
= Accept_Statement
(Alt
) then
4713 Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
4716 Make_Object_Declaration
(Loc
,
4717 Defining_Identifier
=> Ann
,
4718 Object_Definition
=>
4719 New_Reference_To
(RTE
(RE_Address
), Loc
));
4721 Insert_Before
(Sel_Acc
, Adecl
);
4724 -- If we are not the first accept statement, then find the Ann
4725 -- variable allocated by the first accept and use it.
4729 Node
(Last_Elmt
(Accept_Address
4730 (Entity
(Entry_Direct_Name
(Accept_Statement
(Alt
))))));
4735 -- Merge here with Ann either created or referenced, and Adecl
4736 -- pointing to the corresponding declaration. Remaining processing
4737 -- is the same for the two cases.
4739 if Present
(Ann
) then
4740 Append_Elmt
(Ann
, Accept_Address
(Ent
));
4741 Set_Debug_Info_Needed
(Ann
);
4744 -- Create renaming declarations for the entry formals. Each reference
4745 -- to a formal becomes a dereference of a component of the parameter
4746 -- block, whose address is held in Ann. These declarations are
4747 -- eventually inserted into the accept block, and analyzed there so
4748 -- that they have the proper scope for gdb and do not conflict with
4749 -- other declarations.
4751 if Present
(Parameter_Specifications
(N
))
4752 and then Present
(Handled_Statement_Sequence
(N
))
4762 Formal
:= First_Formal
(Ent
);
4764 while Present
(Formal
) loop
4765 Comp
:= Entry_Component
(Formal
);
4767 Make_Defining_Identifier
(Loc
, Chars
(Formal
));
4769 Set_Etype
(New_F
, Etype
(Formal
));
4770 Set_Scope
(New_F
, Ent
);
4772 -- Now we set debug info needed on New_F even though it does
4773 -- not come from source, so that the debugger will get the
4774 -- right information for these generated names.
4776 Set_Debug_Info_Needed
(New_F
);
4778 if Ekind
(Formal
) = E_In_Parameter
then
4779 Set_Ekind
(New_F
, E_Constant
);
4781 Set_Ekind
(New_F
, E_Variable
);
4782 Set_Extra_Constrained
(New_F
, Extra_Constrained
(Formal
));
4785 Set_Actual_Subtype
(New_F
, Actual_Subtype
(Formal
));
4788 Make_Object_Renaming_Declaration
(Loc
,
4789 Defining_Identifier
=>
4792 New_Reference_To
(Etype
(Formal
), Loc
),
4794 Make_Explicit_Dereference
(Loc
,
4795 Make_Selected_Component
(Loc
,
4797 Unchecked_Convert_To
(
4798 Entry_Parameters_Type
(Ent
),
4799 New_Reference_To
(Ann
, Loc
)),
4801 New_Reference_To
(Comp
, Loc
))));
4803 if No
(Declarations
(N
)) then
4804 Set_Declarations
(N
, New_List
);
4807 Append
(Decl
, Declarations
(N
));
4808 Set_Renamed_Object
(Formal
, New_F
);
4809 Next_Formal
(Formal
);
4816 end Expand_Accept_Declarations
;
4818 ---------------------------------------------
4819 -- Expand_Access_Protected_Subprogram_Type --
4820 ---------------------------------------------
4822 procedure Expand_Access_Protected_Subprogram_Type
(N
: Node_Id
) is
4823 Loc
: constant Source_Ptr
:= Sloc
(N
);
4825 T
: constant Entity_Id
:= Defining_Identifier
(N
);
4826 D_T
: constant Entity_Id
:= Designated_Type
(T
);
4827 D_T2
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
,
4828 Chars
=> New_Internal_Name
('D'));
4829 E_T
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
,
4830 Chars
=> New_Internal_Name
('E'));
4831 P_List
: constant List_Id
:= Build_Protected_Spec
4832 (N
, RTE
(RE_Address
), D_T
, False);
4838 -- Create access to subprogram with full signature
4840 if Etype
(D_T
) /= Standard_Void_Type
then
4842 Make_Access_Function_Definition
(Loc
,
4843 Parameter_Specifications
=> P_List
,
4844 Result_Definition
=>
4845 Copy_Result_Type
(Result_Definition
(Type_Definition
(N
))));
4849 Make_Access_Procedure_Definition
(Loc
,
4850 Parameter_Specifications
=> P_List
);
4854 Make_Full_Type_Declaration
(Loc
,
4855 Defining_Identifier
=> D_T2
,
4856 Type_Definition
=> Def1
);
4858 Insert_After
(N
, Decl1
);
4861 -- Create Equivalent_Type, a record with two components for an access to
4862 -- object and an access to subprogram.
4865 Make_Component_Declaration
(Loc
,
4866 Defining_Identifier
=>
4867 Make_Defining_Identifier
(Loc
, New_Internal_Name
('P')),
4868 Component_Definition
=>
4869 Make_Component_Definition
(Loc
,
4870 Aliased_Present
=> False,
4871 Subtype_Indication
=>
4872 New_Occurrence_Of
(RTE
(RE_Address
), Loc
))),
4874 Make_Component_Declaration
(Loc
,
4875 Defining_Identifier
=>
4876 Make_Defining_Identifier
(Loc
, New_Internal_Name
('S')),
4877 Component_Definition
=>
4878 Make_Component_Definition
(Loc
,
4879 Aliased_Present
=> False,
4880 Subtype_Indication
=> New_Occurrence_Of
(D_T2
, Loc
))));
4883 Make_Full_Type_Declaration
(Loc
,
4884 Defining_Identifier
=> E_T
,
4886 Make_Record_Definition
(Loc
,
4888 Make_Component_List
(Loc
,
4889 Component_Items
=> Comps
)));
4891 Insert_After
(Decl1
, Decl2
);
4893 Set_Equivalent_Type
(T
, E_T
);
4894 end Expand_Access_Protected_Subprogram_Type
;
4896 --------------------------
4897 -- Expand_Entry_Barrier --
4898 --------------------------
4900 procedure Expand_Entry_Barrier
(N
: Node_Id
; Ent
: Entity_Id
) is
4901 Cond
: constant Node_Id
:=
4902 Condition
(Entry_Body_Formal_Part
(N
));
4903 Prot
: constant Entity_Id
:= Scope
(Ent
);
4904 Spec_Decl
: constant Node_Id
:= Parent
(Prot
);
4907 Body_Decl
: Node_Id
;
4910 if No_Run_Time_Mode
then
4911 Error_Msg_CRT
("entry barrier", N
);
4915 -- The body of the entry barrier must be analyzed in the context of the
4916 -- protected object, but its scope is external to it, just as any other
4917 -- unprotected version of a protected operation. The specification has
4918 -- been produced when the protected type declaration was elaborated. We
4919 -- build the body, insert it in the enclosing scope, but analyze it in
4920 -- the current context. A more uniform approach would be to treat the
4921 -- barrier just as a protected function, and discard the protected
4922 -- version of it because it is never called.
4924 if Expander_Active
then
4925 B_F
:= Build_Barrier_Function
(N
, Ent
, Prot
);
4926 Func
:= Barrier_Function
(Ent
);
4927 Set_Corresponding_Spec
(B_F
, Func
);
4929 Body_Decl
:= Parent
(Corresponding_Body
(Spec_Decl
));
4931 if Nkind
(Parent
(Body_Decl
)) = N_Subunit
then
4932 Body_Decl
:= Corresponding_Stub
(Parent
(Body_Decl
));
4935 Insert_Before_And_Analyze
(Body_Decl
, B_F
);
4937 Set_Discriminals
(Spec_Decl
);
4938 Set_Scope
(Func
, Scope
(Prot
));
4941 Analyze_And_Resolve
(Cond
, Any_Boolean
);
4944 -- The Ravenscar profile restricts barriers to simple variables declared
4945 -- within the protected object. We also allow Boolean constants, since
4946 -- these appear in several published examples and are also allowed by
4947 -- the Aonix compiler.
4949 -- Note that after analysis variables in this context will be replaced
4950 -- by the corresponding prival, that is to say a renaming of a selected
4951 -- component of the form _Object.Var. If expansion is disabled, as
4952 -- within a generic, we check that the entity appears in the current
4955 if Is_Entity_Name
(Cond
) then
4957 -- A small optimization of useless renamings. If the scope of the
4958 -- entity of the condition is not the barrier function, then the
4959 -- condition does not reference any of the generated renamings
4960 -- within the function.
4963 and then Scope
(Entity
(Cond
)) /= Func
4965 Set_Declarations
(B_F
, Empty_List
);
4968 if Entity
(Cond
) = Standard_False
4970 Entity
(Cond
) = Standard_True
4974 elsif not Expander_Active
4975 and then Scope
(Entity
(Cond
)) = Current_Scope
4979 -- Check for case of _object.all.field (note that the explicit
4980 -- dereference gets inserted by analyze/expand of _object.field)
4982 elsif Present
(Renamed_Object
(Entity
(Cond
)))
4984 Nkind
(Renamed_Object
(Entity
(Cond
))) = N_Selected_Component
4988 (Prefix
(Renamed_Object
(Entity
(Cond
))))) = Name_uObject
4994 -- It is not a boolean variable or literal, so check the restriction
4996 Check_Restriction
(Simple_Barriers
, Cond
);
4997 end Expand_Entry_Barrier
;
4999 ------------------------------
5000 -- Expand_N_Abort_Statement --
5001 ------------------------------
5003 -- Expand abort T1, T2, .. Tn; into:
5004 -- Abort_Tasks (Task_List'(1 => T1.Task_Id, 2 => T2.Task_Id ...))
5006 procedure Expand_N_Abort_Statement
(N
: Node_Id
) is
5007 Loc
: constant Source_Ptr
:= Sloc
(N
);
5008 Tlist
: constant List_Id
:= Names
(N
);
5014 Aggr
:= Make_Aggregate
(Loc
, Component_Associations
=> New_List
);
5017 Tasknm
:= First
(Tlist
);
5019 while Present
(Tasknm
) loop
5022 -- A task interface class-wide type object is being aborted.
5023 -- Retrieve its _task_id by calling a dispatching routine.
5025 if Ada_Version
>= Ada_05
5026 and then Ekind
(Etype
(Tasknm
)) = E_Class_Wide_Type
5027 and then Is_Interface
(Etype
(Tasknm
))
5028 and then Is_Task_Interface
(Etype
(Tasknm
))
5030 Append_To
(Component_Associations
(Aggr
),
5031 Make_Component_Association
(Loc
,
5032 Choices
=> New_List
(
5033 Make_Integer_Literal
(Loc
, Count
)),
5036 -- Task_Id (Tasknm._disp_get_task_id)
5038 Make_Unchecked_Type_Conversion
(Loc
,
5040 New_Reference_To
(RTE
(RO_ST_Task_Id
), Loc
),
5042 Make_Selected_Component
(Loc
,
5044 New_Copy_Tree
(Tasknm
),
5046 Make_Identifier
(Loc
, Name_uDisp_Get_Task_Id
)))));
5049 Append_To
(Component_Associations
(Aggr
),
5050 Make_Component_Association
(Loc
,
5051 Choices
=> New_List
(
5052 Make_Integer_Literal
(Loc
, Count
)),
5053 Expression
=> Concurrent_Ref
(Tasknm
)));
5060 Make_Procedure_Call_Statement
(Loc
,
5061 Name
=> New_Reference_To
(RTE
(RE_Abort_Tasks
), Loc
),
5062 Parameter_Associations
=> New_List
(
5063 Make_Qualified_Expression
(Loc
,
5064 Subtype_Mark
=> New_Reference_To
(RTE
(RE_Task_List
), Loc
),
5065 Expression
=> Aggr
))));
5068 end Expand_N_Abort_Statement
;
5070 -------------------------------
5071 -- Expand_N_Accept_Statement --
5072 -------------------------------
5074 -- This procedure handles expansion of accept statements that stand
5075 -- alone, i.e. they are not part of an accept alternative. The expansion
5076 -- of accept statement in accept alternatives is handled by the routines
5077 -- Expand_N_Accept_Alternative and Expand_N_Selective_Accept. The
5078 -- following description applies only to stand alone accept statements.
5080 -- If there is no handled statement sequence, or only null statements,
5081 -- then this is called a trivial accept, and the expansion is:
5083 -- Accept_Trivial (entry-index)
5085 -- If there is a handled statement sequence, then the expansion is:
5092 -- Accept_Call (entry-index, Ann);
5093 -- Renaming_Declarations for formals
5094 -- <statement sequence from N_Accept_Statement node>
5095 -- Complete_Rendezvous;
5100 -- <exception handler from N_Accept_Statement node>
5101 -- Complete_Rendezvous;
5103 -- <exception handler from N_Accept_Statement node>
5104 -- Complete_Rendezvous;
5109 -- when all others =>
5110 -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
5113 -- The first three declarations were already inserted ahead of the accept
5114 -- statement by the Expand_Accept_Declarations procedure, which was called
5115 -- directly from the semantics during analysis of the accept statement,
5116 -- before analyzing its contained statements.
5118 -- The declarations from the N_Accept_Statement, as noted in Sinfo, come
5119 -- from possible expansion activity (the original source of course does
5120 -- not have any declarations associated with the accept statement, since
5121 -- an accept statement has no declarative part). In particular, if the
5122 -- expander is active, the first such declaration is the declaration of
5123 -- the Accept_Params_Ptr entity (see Sem_Ch9.Analyze_Accept_Statement).
5125 -- The two blocks are merged into a single block if the inner block has
5126 -- no exception handlers, but otherwise two blocks are required, since
5127 -- exceptions might be raised in the exception handlers of the inner
5128 -- block, and Exceptional_Complete_Rendezvous must be called.
5130 procedure Expand_N_Accept_Statement
(N
: Node_Id
) is
5131 Loc
: constant Source_Ptr
:= Sloc
(N
);
5132 Stats
: constant Node_Id
:= Handled_Statement_Sequence
(N
);
5133 Ename
: constant Node_Id
:= Entry_Direct_Name
(N
);
5134 Eindx
: constant Node_Id
:= Entry_Index
(N
);
5135 Eent
: constant Entity_Id
:= Entity
(Ename
);
5136 Acstack
: constant Elist_Id
:= Accept_Address
(Eent
);
5137 Ann
: constant Entity_Id
:= Node
(Last_Elmt
(Acstack
));
5138 Ttyp
: constant Entity_Id
:= Etype
(Scope
(Eent
));
5143 -- Start of processing for Expand_N_Accept_Statement
5146 -- If accept statement is not part of a list, then its parent must be
5147 -- an accept alternative, and, as described above, we do not do any
5148 -- expansion for such accept statements at this level.
5150 if not Is_List_Member
(N
) then
5151 pragma Assert
(Nkind
(Parent
(N
)) = N_Accept_Alternative
);
5154 -- Trivial accept case (no statement sequence, or null statements).
5155 -- If the accept statement has declarations, then just insert them
5156 -- before the procedure call.
5158 elsif Trivial_Accept_OK
5159 and then (No
(Stats
) or else Null_Statements
(Statements
(Stats
)))
5161 -- Remove declarations for renamings, because the parameter block
5162 -- will not be assigned.
5169 D
:= First
(Declarations
(N
));
5171 while Present
(D
) loop
5173 if Nkind
(D
) = N_Object_Renaming_Declaration
then
5181 if Present
(Declarations
(N
)) then
5182 Insert_Actions
(N
, Declarations
(N
));
5186 Make_Procedure_Call_Statement
(Loc
,
5187 Name
=> New_Reference_To
(RTE
(RE_Accept_Trivial
), Loc
),
5188 Parameter_Associations
=> New_List
(
5189 Entry_Index_Expression
(Loc
, Entity
(Ename
), Eindx
, Ttyp
))));
5193 -- Discard Entry_Address that was created for it, so it will not be
5194 -- emitted if this accept statement is in the statement part of a
5195 -- delay alternative.
5197 if Present
(Stats
) then
5198 Remove_Last_Elmt
(Acstack
);
5201 -- Case of statement sequence present
5204 -- Construct the block, using the declarations from the accept
5205 -- statement if any to initialize the declarations of the block.
5207 Blkent
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
5208 Set_Ekind
(Blkent
, E_Block
);
5209 Set_Etype
(Blkent
, Standard_Void_Type
);
5210 Set_Scope
(Blkent
, Current_Scope
);
5213 Make_Block_Statement
(Loc
,
5214 Identifier
=> New_Reference_To
(Blkent
, Loc
),
5215 Declarations
=> Declarations
(N
),
5216 Handled_Statement_Sequence
=> Build_Accept_Body
(N
));
5218 -- Prepend call to Accept_Call to main statement sequence If the
5219 -- accept has exception handlers, the statement sequence is wrapped
5220 -- in a block. Insert call and renaming declarations in the
5221 -- declarations of the block, so they are elaborated before the
5225 Make_Procedure_Call_Statement
(Loc
,
5226 Name
=> New_Reference_To
(RTE
(RE_Accept_Call
), Loc
),
5227 Parameter_Associations
=> New_List
(
5228 Entry_Index_Expression
(Loc
, Entity
(Ename
), Eindx
, Ttyp
),
5229 New_Reference_To
(Ann
, Loc
)));
5231 if Parent
(Stats
) = N
then
5232 Prepend
(Call
, Statements
(Stats
));
5241 Push_Scope
(Blkent
);
5249 D
:= First
(Declarations
(N
));
5250 while Present
(D
) loop
5253 if Nkind
(D
) = N_Object_Renaming_Declaration
then
5255 -- The renaming declarations for the formals were created
5256 -- during analysis of the accept statement, and attached to
5257 -- the list of declarations. Place them now in the context
5258 -- of the accept block or subprogram.
5261 Typ
:= Entity
(Subtype_Mark
(D
));
5262 Insert_After
(Call
, D
);
5265 -- If the formal is class_wide, it does not have an actual
5266 -- subtype. The analysis of the renaming declaration creates
5267 -- one, but we need to retain the class-wide nature of the
5270 if Is_Class_Wide_Type
(Typ
) then
5271 Set_Etype
(Defining_Identifier
(D
), Typ
);
5282 -- Replace the accept statement by the new block
5287 -- Last step is to unstack the Accept_Address value
5289 Remove_Last_Elmt
(Acstack
);
5291 end Expand_N_Accept_Statement
;
5293 ----------------------------------
5294 -- Expand_N_Asynchronous_Select --
5295 ----------------------------------
5297 -- This procedure assumes that the trigger statement is an entry call or
5298 -- a dispatching procedure call. A delay alternative should already have
5299 -- been expanded into an entry call to the appropriate delay object Wait
5302 -- If the trigger is a task entry call, the select is implemented with
5303 -- a Task_Entry_Call:
5308 -- P : parms := (parm, parm, parm);
5310 -- -- Clean is added by Exp_Ch7.Expand_Cleanup_Actions
5312 -- procedure _clean is
5315 -- Cancel_Task_Entry_Call (C);
5322 -- (<acceptor-task>, -- Acceptor
5323 -- <entry-index>, -- E
5324 -- P'Address, -- Uninterpreted_Data
5325 -- Asynchronous_Call, -- Mode
5326 -- B); -- Rendezvous_Successful
5333 -- _clean; -- Added by Exp_Ch7.Expand_Cleanup_Actions
5336 -- when Abort_Signal => Abort_Undefer;
5343 -- <triggered-statements>
5347 -- Note that Build_Simple_Entry_Call is used to expand the entry of the
5348 -- asynchronous entry call (by Expand_N_Entry_Call_Statement procedure)
5352 -- P : parms := (parm, parm, parm);
5354 -- Call_Simple (acceptor-task, entry-index, P'Address);
5360 -- so the task at hand is to convert the latter expansion into the former
5362 -- If the trigger is a protected entry call, the select is implemented
5363 -- with Protected_Entry_Call:
5366 -- P : E1_Params := (param, param, param);
5367 -- Bnn : Communications_Block;
5372 -- -- Clean is added by Exp_Ch7.Expand_Cleanup_Actions
5374 -- procedure _clean is
5377 -- if Enqueued (Bnn) then
5378 -- Cancel_Protected_Entry_Call (Bnn);
5385 -- Protected_Entry_Call
5386 -- (po._object'Access, -- Object
5387 -- <entry index>, -- E
5388 -- P'Address, -- Uninterpreted_Data
5389 -- Asynchronous_Call, -- Mode
5392 -- if Enqueued (Bnn) then
5396 -- _clean; -- Added by Exp_Ch7.Expand_Cleanup_Actions
5399 -- when Abort_Signal => Abort_Undefer;
5402 -- if not Cancelled (Bnn) then
5403 -- <triggered-statements>
5407 -- Build_Simple_Entry_Call is used to expand the all to a simple protected
5411 -- P : E1_Params := (param, param, param);
5412 -- Bnn : Communications_Block;
5415 -- Protected_Entry_Call
5416 -- (po._object'Access, -- Object
5417 -- <entry index>, -- E
5418 -- P'Address, -- Uninterpreted_Data
5419 -- Simple_Call, -- Mode
5426 -- Ada 2005 (AI-345): If the trigger is a dispatching call, the select is
5430 -- B : Boolean := False;
5431 -- Bnn : Communication_Block;
5432 -- C : Ada.Tags.Prim_Op_Kind;
5433 -- D : System.Storage_Elements.Dummy_Communication_Block;
5434 -- K : Ada.Tags.Tagged_Kind :=
5435 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
5436 -- P : Parameters := (Param1 .. ParamN);
5441 -- if K = Ada.Tags.TK_Limited_Tagged then
5442 -- <dispatching-call>;
5443 -- <triggering-statements>;
5447 -- Ada.Tags.Get_Offset_Index
5448 -- (Ada.Tags.Tag (<object>), DT_Position (<dispatching-call>));
5450 -- _Disp_Get_Prim_Op_Kind (<object>, S, C);
5452 -- if C = POK_Protected_Entry then
5454 -- procedure _clean is
5456 -- if Enqueued (Bnn) then
5457 -- Cancel_Protected_Entry_Call (Bnn);
5463 -- _Disp_Asynchronous_Select
5464 -- (<object>, S, P'Address, D, B);
5465 -- Bnn := Communication_Block (D);
5467 -- Param1 := P.Param1;
5469 -- ParamN := P.ParamN;
5471 -- if Enqueued (Bnn) then
5472 -- <abortable-statements>
5475 -- _clean; -- Added by Exp_Ch7.Expand_Cleanup_Actions
5478 -- when Abort_Signal => Abort_Undefer;
5481 -- if not Cancelled (Bnn) then
5482 -- <triggering-statements>
5485 -- elsif C = POK_Task_Entry then
5487 -- procedure _clean is
5489 -- Cancel_Task_Entry_Call (U);
5495 -- _Disp_Asynchronous_Select
5496 -- (<object>, S, P'Address, D, B);
5497 -- Bnn := Communication_Bloc (D);
5499 -- Param1 := P.Param1;
5501 -- ParamN := P.ParamN;
5506 -- <abortable-statements>
5508 -- _clean; -- Added by Exp_Ch7.Expand_Cleanup_Actions
5511 -- when Abort_Signal => Abort_Undefer;
5515 -- <triggering-statements>
5520 -- <dispatching-call>;
5521 -- <triggering-statements>
5526 -- The job is to convert this to the asynchronous form
5528 -- If the trigger is a delay statement, it will have been expanded into a
5529 -- call to one of the GNARL delay procedures. This routine will convert
5530 -- this into a protected entry call on a delay object and then continue
5531 -- processing as for a protected entry call trigger. This requires
5532 -- declaring a Delay_Block object and adding a pointer to this object to
5533 -- the parameter list of the delay procedure to form the parameter list of
5534 -- the entry call. This object is used by the runtime to queue the delay
5537 -- For a description of the use of P and the assignments after the call,
5538 -- see Expand_N_Entry_Call_Statement.
5540 procedure Expand_N_Asynchronous_Select
(N
: Node_Id
) is
5541 Loc
: constant Source_Ptr
:= Sloc
(N
);
5542 Abrt
: constant Node_Id
:= Abortable_Part
(N
);
5543 Astats
: constant List_Id
:= Statements
(Abrt
);
5544 Trig
: constant Node_Id
:= Triggering_Alternative
(N
);
5545 Tstats
: constant List_Id
:= Statements
(Trig
);
5547 Abort_Block_Ent
: Entity_Id
;
5548 Abortable_Block
: Node_Id
;
5550 Blk_Ent
: Entity_Id
;
5551 Blk_Typ
: Entity_Id
;
5553 Call_Ent
: Entity_Id
;
5554 Cancel_Param
: Entity_Id
;
5555 Cleanup_Block
: Node_Id
;
5556 Cleanup_Block_Ent
: Entity_Id
;
5557 Cleanup_Stmts
: List_Id
;
5558 Conc_Typ_Stmts
: List_Id
;
5560 Dblock_Ent
: Entity_Id
;
5565 Enqueue_Call
: Node_Id
;
5569 Lim_Typ_Stmts
: List_Id
;
5575 ProtE_Stmts
: List_Id
;
5576 ProtP_Stmts
: List_Id
;
5579 Target_Undefer
: RE_Id
;
5580 TaskE_Stmts
: List_Id
;
5581 Undefer_Args
: List_Id
:= No_List
;
5583 B
: Entity_Id
; -- Call status flag
5584 Bnn
: Entity_Id
; -- Communication block
5585 C
: Entity_Id
; -- Call kind
5586 K
: Entity_Id
; -- Tagged kind
5587 P
: Entity_Id
; -- Parameter block
5588 S
: Entity_Id
; -- Primitive operation slot
5589 T
: Entity_Id
; -- Additional status flag
5592 Blk_Ent
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
5593 Ecall
:= Triggering_Statement
(Trig
);
5595 -- The arguments in the call may require dynamic allocation, and the
5596 -- call statement may have been transformed into a block. The block
5597 -- may contain additional declarations for internal entities, and the
5598 -- original call is found by sequential search.
5600 if Nkind
(Ecall
) = N_Block_Statement
then
5601 Ecall
:= First
(Statements
(Handled_Statement_Sequence
(Ecall
)));
5602 while not Nkind_In
(Ecall
, N_Procedure_Call_Statement
,
5603 N_Entry_Call_Statement
)
5609 -- This is either a dispatching call or a delay statement used as a
5610 -- trigger which was expanded into a procedure call.
5612 if Nkind
(Ecall
) = N_Procedure_Call_Statement
then
5613 if Ada_Version
>= Ada_05
5615 (No
(Original_Node
(Ecall
))
5616 or else not Nkind_In
(Original_Node
(Ecall
),
5617 N_Delay_Relative_Statement
,
5618 N_Delay_Until_Statement
))
5620 Extract_Dispatching_Call
(Ecall
, Call_Ent
, Obj
, Actuals
, Formals
);
5625 -- Call status flag processing, generate:
5626 -- B : Boolean := False;
5628 B
:= Build_B
(Loc
, Decls
);
5630 -- Communication block processing, generate:
5631 -- Bnn : Communication_Block;
5633 Bnn
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('B'));
5636 Make_Object_Declaration
(Loc
,
5637 Defining_Identifier
=>
5639 Object_Definition
=>
5640 New_Reference_To
(RTE
(RE_Communication_Block
), Loc
)));
5642 -- Call kind processing, generate:
5643 -- C : Ada.Tags.Prim_Op_Kind;
5645 C
:= Build_C
(Loc
, Decls
);
5647 -- Tagged kind processing, generate:
5648 -- K : Ada.Tags.Tagged_Kind :=
5649 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
5651 -- Dummy communication block, generate:
5652 -- D : Dummy_Communication_Block;
5655 Make_Object_Declaration
(Loc
,
5656 Defining_Identifier
=>
5657 Make_Defining_Identifier
(Loc
, Name_uD
),
5658 Object_Definition
=>
5660 RTE
(RE_Dummy_Communication_Block
), Loc
)));
5662 K
:= Build_K
(Loc
, Decls
, Obj
);
5664 -- Parameter block processing
5666 Blk_Typ
:= Build_Parameter_Block
5667 (Loc
, Actuals
, Formals
, Decls
);
5668 P
:= Parameter_Block_Pack
5669 (Loc
, Blk_Typ
, Actuals
, Formals
, Decls
, Stmts
);
5671 -- Dispatch table slot processing, generate:
5674 S
:= Build_S
(Loc
, Decls
);
5676 -- Additional status flag processing, generate:
5678 T
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('T'));
5681 Make_Object_Declaration
(Loc
,
5682 Defining_Identifier
=>
5684 Object_Definition
=>
5685 New_Reference_To
(Standard_Boolean
, Loc
)));
5687 ------------------------------
5688 -- Protected entry handling --
5689 ------------------------------
5692 -- Param1 := P.Param1;
5694 -- ParamN := P.ParamN;
5696 Cleanup_Stmts
:= Parameter_Block_Unpack
(Loc
, P
, Actuals
, Formals
);
5699 -- Bnn := Communication_Block (D);
5701 Prepend_To
(Cleanup_Stmts
,
5702 Make_Assignment_Statement
(Loc
,
5704 New_Reference_To
(Bnn
, Loc
),
5706 Make_Unchecked_Type_Conversion
(Loc
,
5708 New_Reference_To
(RTE
(RE_Communication_Block
), Loc
),
5710 Make_Identifier
(Loc
, Name_uD
))));
5713 -- _Disp_Asynchronous_Select (<object>, S, P'Address, D, B);
5715 Prepend_To
(Cleanup_Stmts
,
5716 Make_Procedure_Call_Statement
(Loc
,
5719 Find_Prim_Op
(Etype
(Etype
(Obj
)),
5720 Name_uDisp_Asynchronous_Select
),
5722 Parameter_Associations
=>
5724 New_Copy_Tree
(Obj
), -- <object>
5725 New_Reference_To
(S
, Loc
), -- S
5726 Make_Attribute_Reference
(Loc
, -- P'Address
5728 New_Reference_To
(P
, Loc
),
5731 Make_Identifier
(Loc
, Name_uD
), -- D
5732 New_Reference_To
(B
, Loc
)))); -- B
5735 -- if Enqueued (Bnn) then
5736 -- <abortable-statements>
5739 Append_To
(Cleanup_Stmts
,
5740 Make_If_Statement
(Loc
,
5742 Make_Function_Call
(Loc
,
5744 New_Reference_To
(RTE
(RE_Enqueued
), Loc
),
5745 Parameter_Associations
=>
5747 New_Reference_To
(Bnn
, Loc
))),
5750 New_Copy_List_Tree
(Astats
)));
5752 -- Wrap the statements in a block. Exp_Ch7.Expand_Cleanup_Actions
5753 -- will then generate a _clean for the communication block Bnn.
5757 -- procedure _clean is
5759 -- if Enqueued (Bnn) then
5760 -- Cancel_Protected_Entry_Call (Bnn);
5769 Cleanup_Block_Ent
:=
5770 Make_Defining_Identifier
(Loc
, New_Internal_Name
('C'));
5773 Build_Cleanup_Block
(Loc
, Cleanup_Block_Ent
, Cleanup_Stmts
, Bnn
);
5775 -- Wrap the cleanup block in an exception handling block
5781 -- when Abort_Signal => Abort_Undefer;
5785 Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
5789 Make_Implicit_Label_Declaration
(Loc
,
5790 Defining_Identifier
=>
5794 (Loc
, Abort_Block_Ent
, Cleanup_Block_Ent
, Cleanup_Block
));
5797 -- if not Cancelled (Bnn) then
5798 -- <triggering-statements>
5801 Append_To
(ProtE_Stmts
,
5802 Make_If_Statement
(Loc
,
5806 Make_Function_Call
(Loc
,
5808 New_Reference_To
(RTE
(RE_Cancelled
), Loc
),
5809 Parameter_Associations
=>
5811 New_Reference_To
(Bnn
, Loc
)))),
5814 New_Copy_List_Tree
(Tstats
)));
5816 -------------------------
5817 -- Task entry handling --
5818 -------------------------
5821 -- Param1 := P.Param1;
5823 -- ParamN := P.ParamN;
5825 TaskE_Stmts
:= Parameter_Block_Unpack
(Loc
, P
, Actuals
, Formals
);
5828 -- Bnn := Communication_Block (D);
5830 Append_To
(TaskE_Stmts
,
5831 Make_Assignment_Statement
(Loc
,
5833 New_Reference_To
(Bnn
, Loc
),
5835 Make_Unchecked_Type_Conversion
(Loc
,
5837 New_Reference_To
(RTE
(RE_Communication_Block
), Loc
),
5839 Make_Identifier
(Loc
, Name_uD
))));
5842 -- _Disp_Asynchronous_Select (<object>, S, P'Address, D, B);
5844 Prepend_To
(TaskE_Stmts
,
5845 Make_Procedure_Call_Statement
(Loc
,
5848 Find_Prim_Op
(Etype
(Etype
(Obj
)),
5849 Name_uDisp_Asynchronous_Select
),
5851 Parameter_Associations
=>
5853 New_Copy_Tree
(Obj
), -- <object>
5854 New_Reference_To
(S
, Loc
), -- S
5855 Make_Attribute_Reference
(Loc
, -- P'Address
5857 New_Reference_To
(P
, Loc
),
5860 Make_Identifier
(Loc
, Name_uD
), -- D
5861 New_Reference_To
(B
, Loc
)))); -- B
5866 Prepend_To
(TaskE_Stmts
,
5867 Make_Procedure_Call_Statement
(Loc
,
5869 New_Reference_To
(RTE
(RE_Abort_Defer
), Loc
),
5870 Parameter_Associations
=>
5875 -- <abortable-statements>
5877 Cleanup_Stmts
:= New_Copy_List_Tree
(Astats
);
5879 Prepend_To
(Cleanup_Stmts
,
5880 Make_Procedure_Call_Statement
(Loc
,
5882 New_Reference_To
(RTE
(RE_Abort_Undefer
), Loc
),
5883 Parameter_Associations
=>
5886 -- Wrap the statements in a block. Exp_Ch7.Expand_Cleanup_Actions
5887 -- will generate a _clean for the additional status flag.
5891 -- procedure _clean is
5893 -- Cancel_Task_Entry_Call (U);
5901 Cleanup_Block_Ent
:=
5902 Make_Defining_Identifier
(Loc
, New_Internal_Name
('C'));
5905 Build_Cleanup_Block
(Loc
, Cleanup_Block_Ent
, Cleanup_Stmts
, T
);
5907 -- Wrap the cleanup block in an exception handling block
5913 -- when Abort_Signal => Abort_Undefer;
5917 Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
5919 Append_To
(TaskE_Stmts
,
5920 Make_Implicit_Label_Declaration
(Loc
,
5921 Defining_Identifier
=>
5924 Append_To
(TaskE_Stmts
,
5926 (Loc
, Abort_Block_Ent
, Cleanup_Block_Ent
, Cleanup_Block
));
5930 -- <triggering-statements>
5933 Append_To
(TaskE_Stmts
,
5934 Make_If_Statement
(Loc
,
5938 New_Reference_To
(T
, Loc
)),
5941 New_Copy_List_Tree
(Tstats
)));
5943 ----------------------------------
5944 -- Protected procedure handling --
5945 ----------------------------------
5948 -- <dispatching-call>;
5949 -- <triggering-statements>
5951 ProtP_Stmts
:= New_Copy_List_Tree
(Tstats
);
5952 Prepend_To
(ProtP_Stmts
, New_Copy_Tree
(Ecall
));
5955 -- S := Ada.Tags.Get_Offset_Index
5956 -- (Ada.Tags.Tag (<object>), DT_Position (Call_Ent));
5959 New_List
(Build_S_Assignment
(Loc
, S
, Obj
, Call_Ent
));
5962 -- _Disp_Get_Prim_Op_Kind (<object>, S, C);
5964 Append_To
(Conc_Typ_Stmts
,
5965 Make_Procedure_Call_Statement
(Loc
,
5968 Find_Prim_Op
(Etype
(Etype
(Obj
)),
5969 Name_uDisp_Get_Prim_Op_Kind
),
5971 Parameter_Associations
=>
5973 New_Copy_Tree
(Obj
),
5974 New_Reference_To
(S
, Loc
),
5975 New_Reference_To
(C
, Loc
))));
5978 -- if C = POK_Procedure_Entry then
5980 -- elsif C = POK_Task_Entry then
5986 Append_To
(Conc_Typ_Stmts
,
5987 Make_If_Statement
(Loc
,
5991 New_Reference_To
(C
, Loc
),
5993 New_Reference_To
(RTE
(RE_POK_Protected_Entry
), Loc
)),
6000 Make_Elsif_Part
(Loc
,
6004 New_Reference_To
(C
, Loc
),
6006 New_Reference_To
(RTE
(RE_POK_Task_Entry
), Loc
)),
6015 -- <dispatching-call>;
6016 -- <triggering-statements>
6018 Lim_Typ_Stmts
:= New_Copy_List_Tree
(Tstats
);
6019 Prepend_To
(Lim_Typ_Stmts
, New_Copy_Tree
(Ecall
));
6022 -- if K = Ada.Tags.TK_Limited_Tagged then
6029 Make_If_Statement
(Loc
,
6033 New_Reference_To
(K
, Loc
),
6035 New_Reference_To
(RTE
(RE_TK_Limited_Tagged
), Loc
)),
6044 Make_Block_Statement
(Loc
,
6047 Handled_Statement_Sequence
=>
6048 Make_Handled_Sequence_Of_Statements
(Loc
, Stmts
)));
6053 -- Delay triggering statement processing
6056 -- Add a Delay_Block object to the parameter list of the delay
6057 -- procedure to form the parameter list of the Wait entry call.
6060 Make_Defining_Identifier
(Loc
, New_Internal_Name
('D'));
6062 Pdef
:= Entity
(Name
(Ecall
));
6064 if Is_RTE
(Pdef
, RO_CA_Delay_For
) then
6066 New_Reference_To
(RTE
(RE_Enqueue_Duration
), Loc
);
6068 elsif Is_RTE
(Pdef
, RO_CA_Delay_Until
) then
6070 New_Reference_To
(RTE
(RE_Enqueue_Calendar
), Loc
);
6072 else pragma Assert
(Is_RTE
(Pdef
, RO_RT_Delay_Until
));
6073 Enqueue_Call
:= New_Reference_To
(RTE
(RE_Enqueue_RT
), Loc
);
6076 Append_To
(Parameter_Associations
(Ecall
),
6077 Make_Attribute_Reference
(Loc
,
6078 Prefix
=> New_Reference_To
(Dblock_Ent
, Loc
),
6079 Attribute_Name
=> Name_Unchecked_Access
));
6081 -- Create the inner block to protect the abortable part
6084 Make_Implicit_Exception_Handler
(Loc
,
6085 Exception_Choices
=>
6086 New_List
(New_Reference_To
(Stand
.Abort_Signal
, Loc
)),
6087 Statements
=> New_List
(
6088 Make_Procedure_Call_Statement
(Loc
,
6089 Name
=> New_Reference_To
(RTE
(RE_Abort_Undefer
), Loc
)))));
6092 Make_Procedure_Call_Statement
(Loc
,
6093 Name
=> New_Reference_To
(RTE
(RE_Abort_Undefer
), Loc
)));
6096 Make_Block_Statement
(Loc
,
6097 Identifier
=> New_Reference_To
(Blk_Ent
, Loc
),
6098 Handled_Statement_Sequence
=>
6099 Make_Handled_Sequence_Of_Statements
(Loc
,
6100 Statements
=> Astats
),
6101 Has_Created_Identifier
=> True,
6102 Is_Asynchronous_Call_Block
=> True);
6104 -- Append call to if Enqueue (When, DB'Unchecked_Access) then
6107 Make_Implicit_If_Statement
(N
,
6108 Condition
=> Make_Function_Call
(Loc
,
6109 Name
=> Enqueue_Call
,
6110 Parameter_Associations
=> Parameter_Associations
(Ecall
)),
6112 New_List
(Make_Block_Statement
(Loc
,
6113 Handled_Statement_Sequence
=>
6114 Make_Handled_Sequence_Of_Statements
(Loc
,
6115 Statements
=> New_List
(
6116 Make_Implicit_Label_Declaration
(Loc
,
6117 Defining_Identifier
=> Blk_Ent
,
6118 Label_Construct
=> Abortable_Block
),
6120 Exception_Handlers
=> Hdle
)))));
6122 Stmts
:= New_List
(Ecall
);
6124 -- Construct statement sequence for new block
6127 Make_Implicit_If_Statement
(N
,
6128 Condition
=> Make_Function_Call
(Loc
,
6129 Name
=> New_Reference_To
(
6130 RTE
(RE_Timed_Out
), Loc
),
6131 Parameter_Associations
=> New_List
(
6132 Make_Attribute_Reference
(Loc
,
6133 Prefix
=> New_Reference_To
(Dblock_Ent
, Loc
),
6134 Attribute_Name
=> Name_Unchecked_Access
))),
6135 Then_Statements
=> Tstats
));
6137 -- The result is the new block
6139 Set_Entry_Cancel_Parameter
(Blk_Ent
, Dblock_Ent
);
6142 Make_Block_Statement
(Loc
,
6143 Declarations
=> New_List
(
6144 Make_Object_Declaration
(Loc
,
6145 Defining_Identifier
=> Dblock_Ent
,
6146 Aliased_Present
=> True,
6147 Object_Definition
=> New_Reference_To
(
6148 RTE
(RE_Delay_Block
), Loc
))),
6150 Handled_Statement_Sequence
=>
6151 Make_Handled_Sequence_Of_Statements
(Loc
, Stmts
)));
6161 Extract_Entry
(Ecall
, Concval
, Ename
, Index
);
6162 Build_Simple_Entry_Call
(Ecall
, Concval
, Ename
, Index
);
6164 Stmts
:= Statements
(Handled_Statement_Sequence
(Ecall
));
6165 Decls
:= Declarations
(Ecall
);
6167 if Is_Protected_Type
(Etype
(Concval
)) then
6169 -- Get the declarations of the block expanded from the entry call
6171 Decl
:= First
(Decls
);
6172 while Present
(Decl
)
6174 (Nkind
(Decl
) /= N_Object_Declaration
6175 or else not Is_RTE
(Etype
(Object_Definition
(Decl
)),
6176 RE_Communication_Block
))
6181 pragma Assert
(Present
(Decl
));
6182 Cancel_Param
:= Defining_Identifier
(Decl
);
6184 -- Change the mode of the Protected_Entry_Call call
6186 -- Protected_Entry_Call (
6187 -- Object => po._object'Access,
6188 -- E => <entry index>;
6189 -- Uninterpreted_Data => P'Address;
6190 -- Mode => Asynchronous_Call;
6193 Stmt
:= First
(Stmts
);
6195 -- Skip assignments to temporaries created for in-out parameters
6197 -- This makes unwarranted assumptions about the shape of the expanded
6198 -- tree for the call, and should be cleaned up ???
6200 while Nkind
(Stmt
) /= N_Procedure_Call_Statement
loop
6206 Param
:= First
(Parameter_Associations
(Call
));
6207 while Present
(Param
)
6208 and then not Is_RTE
(Etype
(Param
), RE_Call_Modes
)
6213 pragma Assert
(Present
(Param
));
6214 Rewrite
(Param
, New_Reference_To
(RTE
(RE_Asynchronous_Call
), Loc
));
6217 -- Append an if statement to execute the abortable part
6220 -- if Enqueued (Bnn) then
6223 Make_Implicit_If_Statement
(N
,
6224 Condition
=> Make_Function_Call
(Loc
,
6225 Name
=> New_Reference_To
(
6226 RTE
(RE_Enqueued
), Loc
),
6227 Parameter_Associations
=> New_List
(
6228 New_Reference_To
(Cancel_Param
, Loc
))),
6229 Then_Statements
=> Astats
));
6232 Make_Block_Statement
(Loc
,
6233 Identifier
=> New_Reference_To
(Blk_Ent
, Loc
),
6234 Handled_Statement_Sequence
=>
6235 Make_Handled_Sequence_Of_Statements
(Loc
,
6236 Statements
=> Stmts
),
6237 Has_Created_Identifier
=> True,
6238 Is_Asynchronous_Call_Block
=> True);
6240 -- For the VM call Update_Exception instead of Abort_Undefer.
6241 -- See 4jexcept.ads for an explanation.
6243 if VM_Target
= No_VM
then
6244 Target_Undefer
:= RE_Abort_Undefer
;
6246 Target_Undefer
:= RE_Update_Exception
;
6248 New_List
(Make_Function_Call
(Loc
,
6249 Name
=> New_Occurrence_Of
6250 (RTE
(RE_Current_Target_Exception
), Loc
)));
6254 Make_Block_Statement
(Loc
,
6255 Handled_Statement_Sequence
=>
6256 Make_Handled_Sequence_Of_Statements
(Loc
,
6257 Statements
=> New_List
(
6258 Make_Implicit_Label_Declaration
(Loc
,
6259 Defining_Identifier
=> Blk_Ent
,
6260 Label_Construct
=> Abortable_Block
),
6265 Exception_Handlers
=> New_List
(
6266 Make_Implicit_Exception_Handler
(Loc
,
6268 -- when Abort_Signal =>
6269 -- Abort_Undefer.all;
6271 Exception_Choices
=>
6272 New_List
(New_Reference_To
(Stand
.Abort_Signal
, Loc
)),
6273 Statements
=> New_List
(
6274 Make_Procedure_Call_Statement
(Loc
,
6275 Name
=> New_Reference_To
(
6276 RTE
(Target_Undefer
), Loc
),
6277 Parameter_Associations
=> Undefer_Args
)))))),
6279 -- if not Cancelled (Bnn) then
6280 -- triggered statements
6283 Make_Implicit_If_Statement
(N
,
6284 Condition
=> Make_Op_Not
(Loc
,
6286 Make_Function_Call
(Loc
,
6287 Name
=> New_Occurrence_Of
(RTE
(RE_Cancelled
), Loc
),
6288 Parameter_Associations
=> New_List
(
6289 New_Occurrence_Of
(Cancel_Param
, Loc
)))),
6290 Then_Statements
=> Tstats
));
6292 -- Asynchronous task entry call
6299 B
:= Make_Defining_Identifier
(Loc
, Name_uB
);
6301 -- Insert declaration of B in declarations of existing block
6304 Make_Object_Declaration
(Loc
,
6305 Defining_Identifier
=> B
,
6306 Object_Definition
=> New_Reference_To
(Standard_Boolean
, Loc
)));
6308 Cancel_Param
:= Make_Defining_Identifier
(Loc
, Name_uC
);
6310 -- Insert declaration of C in declarations of existing block
6313 Make_Object_Declaration
(Loc
,
6314 Defining_Identifier
=> Cancel_Param
,
6315 Object_Definition
=> New_Reference_To
(Standard_Boolean
, Loc
)));
6317 -- Remove and save the call to Call_Simple
6319 Stmt
:= First
(Stmts
);
6321 -- Skip assignments to temporaries created for in-out parameters.
6322 -- This makes unwarranted assumptions about the shape of the expanded
6323 -- tree for the call, and should be cleaned up ???
6325 while Nkind
(Stmt
) /= N_Procedure_Call_Statement
loop
6331 -- Create the inner block to protect the abortable part
6334 Make_Implicit_Exception_Handler
(Loc
,
6335 Exception_Choices
=>
6336 New_List
(New_Reference_To
(Stand
.Abort_Signal
, Loc
)),
6339 Make_Procedure_Call_Statement
(Loc
,
6340 Name
=> New_Reference_To
(RTE
(RE_Abort_Undefer
), Loc
)))));
6343 Make_Procedure_Call_Statement
(Loc
,
6344 Name
=> New_Reference_To
(RTE
(RE_Abort_Undefer
), Loc
)));
6347 Make_Block_Statement
(Loc
,
6348 Identifier
=> New_Reference_To
(Blk_Ent
, Loc
),
6349 Handled_Statement_Sequence
=>
6350 Make_Handled_Sequence_Of_Statements
(Loc
,
6351 Statements
=> Astats
),
6352 Has_Created_Identifier
=> True,
6353 Is_Asynchronous_Call_Block
=> True);
6356 Make_Block_Statement
(Loc
,
6357 Handled_Statement_Sequence
=>
6358 Make_Handled_Sequence_Of_Statements
(Loc
,
6359 Statements
=> New_List
(
6360 Make_Implicit_Label_Declaration
(Loc
,
6361 Defining_Identifier
=>
6366 Exception_Handlers
=> Hdle
)));
6368 -- Create new call statement
6370 Params
:= Parameter_Associations
(Call
);
6373 New_Reference_To
(RTE
(RE_Asynchronous_Call
), Loc
));
6375 New_Reference_To
(B
, Loc
));
6378 Make_Procedure_Call_Statement
(Loc
,
6380 New_Reference_To
(RTE
(RE_Task_Entry_Call
), Loc
),
6381 Parameter_Associations
=> Params
));
6383 -- Construct statement sequence for new block
6386 Make_Implicit_If_Statement
(N
,
6389 New_Reference_To
(Cancel_Param
, Loc
)),
6390 Then_Statements
=> Tstats
));
6392 -- Protected the call against abort
6395 Make_Procedure_Call_Statement
(Loc
,
6396 Name
=> New_Reference_To
(RTE
(RE_Abort_Defer
), Loc
),
6397 Parameter_Associations
=> Empty_List
));
6400 Set_Entry_Cancel_Parameter
(Blk_Ent
, Cancel_Param
);
6402 -- The result is the new block
6405 Make_Block_Statement
(Loc
,
6406 Declarations
=> Decls
,
6407 Handled_Statement_Sequence
=>
6408 Make_Handled_Sequence_Of_Statements
(Loc
, Stmts
)));
6411 end Expand_N_Asynchronous_Select
;
6413 -------------------------------------
6414 -- Expand_N_Conditional_Entry_Call --
6415 -------------------------------------
6417 -- The conditional task entry call is converted to a call to
6422 -- P : parms := (parm, parm, parm);
6426 -- (<acceptor-task>, -- Acceptor
6427 -- <entry-index>, -- E
6428 -- P'Address, -- Uninterpreted_Data
6429 -- Conditional_Call, -- Mode
6430 -- B); -- Rendezvous_Successful
6435 -- normal-statements
6441 -- For a description of the use of P and the assignments after the call,
6442 -- see Expand_N_Entry_Call_Statement. Note that the entry call of the
6443 -- conditional entry call has already been expanded (by the Expand_N_Entry
6444 -- _Call_Statement procedure) as follows:
6447 -- P : parms := (parm, parm, parm);
6449 -- ... info for in-out parameters
6450 -- Call_Simple (acceptor-task, entry-index, P'Address);
6456 -- so the task at hand is to convert the latter expansion into the former
6458 -- The conditional protected entry call is converted to a call to
6459 -- Protected_Entry_Call:
6462 -- P : parms := (parm, parm, parm);
6463 -- Bnn : Communications_Block;
6466 -- Protected_Entry_Call
6467 -- (po._object'Access, -- Object
6468 -- <entry index>, -- E
6469 -- P'Address, -- Uninterpreted_Data
6470 -- Conditional_Call, -- Mode
6475 -- if Cancelled (Bnn) then
6478 -- normal-statements
6482 -- Ada 2005 (AI-345): A dispatching conditional entry call is converted
6486 -- B : Boolean := False;
6487 -- C : Ada.Tags.Prim_Op_Kind;
6488 -- K : Ada.Tags.Tagged_Kind :=
6489 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
6490 -- P : Parameters := (Param1 .. ParamN);
6494 -- if K = Ada.Tags.TK_Limited_Tagged then
6495 -- <dispatching-call>;
6496 -- <triggering-statements>
6500 -- Ada.Tags.Get_Offset_Index
6501 -- (Ada.Tags.Tag (<object>), DT_Position (<dispatching-call>));
6503 -- _Disp_Conditional_Select (<object>, S, P'Address, C, B);
6505 -- if C = POK_Protected_Entry
6506 -- or else C = POK_Task_Entry
6508 -- Param1 := P.Param1;
6510 -- ParamN := P.ParamN;
6514 -- if C = POK_Procedure
6515 -- or else C = POK_Protected_Procedure
6516 -- or else C = POK_Task_Procedure
6518 -- <dispatching-call>;
6521 -- <triggering-statements>
6523 -- <else-statements>
6528 procedure Expand_N_Conditional_Entry_Call
(N
: Node_Id
) is
6529 Loc
: constant Source_Ptr
:= Sloc
(N
);
6530 Alt
: constant Node_Id
:= Entry_Call_Alternative
(N
);
6531 Blk
: Node_Id
:= Entry_Call_Statement
(Alt
);
6534 Blk_Typ
: Entity_Id
;
6536 Call_Ent
: Entity_Id
;
6537 Conc_Typ_Stmts
: List_Id
;
6541 Lim_Typ_Stmts
: List_Id
;
6548 Transient_Blk
: Node_Id
;
6551 B
: Entity_Id
; -- Call status flag
6552 C
: Entity_Id
; -- Call kind
6553 K
: Entity_Id
; -- Tagged kind
6554 P
: Entity_Id
; -- Parameter block
6555 S
: Entity_Id
; -- Primitive operation slot
6558 if Ada_Version
>= Ada_05
6559 and then Nkind
(Blk
) = N_Procedure_Call_Statement
6561 Extract_Dispatching_Call
(Blk
, Call_Ent
, Obj
, Actuals
, Formals
);
6566 -- Call status flag processing, generate:
6567 -- B : Boolean := False;
6569 B
:= Build_B
(Loc
, Decls
);
6571 -- Call kind processing, generate:
6572 -- C : Ada.Tags.Prim_Op_Kind;
6574 C
:= Build_C
(Loc
, Decls
);
6576 -- Tagged kind processing, generate:
6577 -- K : Ada.Tags.Tagged_Kind :=
6578 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
6580 K
:= Build_K
(Loc
, Decls
, Obj
);
6582 -- Parameter block processing
6584 Blk_Typ
:= Build_Parameter_Block
(Loc
, Actuals
, Formals
, Decls
);
6585 P
:= Parameter_Block_Pack
6586 (Loc
, Blk_Typ
, Actuals
, Formals
, Decls
, Stmts
);
6588 -- Dispatch table slot processing, generate:
6591 S
:= Build_S
(Loc
, Decls
);
6594 -- S := Ada.Tags.Get_Offset_Index
6595 -- (Ada.Tags.Tag (<object>), DT_Position (Call_Ent));
6598 New_List
(Build_S_Assignment
(Loc
, S
, Obj
, Call_Ent
));
6601 -- _Disp_Conditional_Select (<object>, S, P'Address, C, B);
6603 Append_To
(Conc_Typ_Stmts
,
6604 Make_Procedure_Call_Statement
(Loc
,
6607 Find_Prim_Op
(Etype
(Etype
(Obj
)),
6608 Name_uDisp_Conditional_Select
),
6610 Parameter_Associations
=>
6612 New_Copy_Tree
(Obj
), -- <object>
6613 New_Reference_To
(S
, Loc
), -- S
6614 Make_Attribute_Reference
(Loc
, -- P'Address
6616 New_Reference_To
(P
, Loc
),
6619 New_Reference_To
(C
, Loc
), -- C
6620 New_Reference_To
(B
, Loc
)))); -- B
6623 -- if C = POK_Protected_Entry
6624 -- or else C = POK_Task_Entry
6626 -- Param1 := P.Param1;
6628 -- ParamN := P.ParamN;
6631 Unpack
:= Parameter_Block_Unpack
(Loc
, P
, Actuals
, Formals
);
6633 -- Generate the if statement only when the packed parameters need
6634 -- explicit assignments to their corresponding actuals.
6636 if Present
(Unpack
) then
6637 Append_To
(Conc_Typ_Stmts
,
6638 Make_If_Statement
(Loc
,
6645 New_Reference_To
(C
, Loc
),
6647 New_Reference_To
(RTE
(
6648 RE_POK_Protected_Entry
), Loc
)),
6652 New_Reference_To
(C
, Loc
),
6654 New_Reference_To
(RTE
(RE_POK_Task_Entry
), Loc
))),
6662 -- if C = POK_Procedure
6663 -- or else C = POK_Protected_Procedure
6664 -- or else C = POK_Task_Procedure
6666 -- <dispatching-call>
6668 -- <normal-statements>
6670 -- <else-statements>
6673 N_Stats
:= New_Copy_List_Tree
(Statements
(Alt
));
6675 Prepend_To
(N_Stats
,
6676 Make_If_Statement
(Loc
,
6682 New_Reference_To
(C
, Loc
),
6684 New_Reference_To
(RTE
(RE_POK_Procedure
), Loc
)),
6691 New_Reference_To
(C
, Loc
),
6693 New_Reference_To
(RTE
(
6694 RE_POK_Protected_Procedure
), Loc
)),
6699 New_Reference_To
(C
, Loc
),
6701 New_Reference_To
(RTE
(
6702 RE_POK_Task_Procedure
), Loc
)))),
6707 Append_To
(Conc_Typ_Stmts
,
6708 Make_If_Statement
(Loc
,
6709 Condition
=> New_Reference_To
(B
, Loc
),
6710 Then_Statements
=> N_Stats
,
6711 Else_Statements
=> Else_Statements
(N
)));
6714 -- <dispatching-call>;
6715 -- <triggering-statements>
6717 Lim_Typ_Stmts
:= New_Copy_List_Tree
(Statements
(Alt
));
6718 Prepend_To
(Lim_Typ_Stmts
, New_Copy_Tree
(Blk
));
6721 -- if K = Ada.Tags.TK_Limited_Tagged then
6728 Make_If_Statement
(Loc
,
6732 New_Reference_To
(K
, Loc
),
6734 New_Reference_To
(RTE
(RE_TK_Limited_Tagged
), Loc
)),
6743 Make_Block_Statement
(Loc
,
6746 Handled_Statement_Sequence
=>
6747 Make_Handled_Sequence_Of_Statements
(Loc
, Stmts
)));
6749 -- As described above, The entry alternative is transformed into a
6750 -- block that contains the gnulli call, and possibly assignment
6751 -- statements for in-out parameters. The gnulli call may itself be
6752 -- rewritten into a transient block if some unconstrained parameters
6753 -- require it. We need to retrieve the call to complete its parameter
6758 First_Real_Statement
(Handled_Statement_Sequence
(Blk
));
6760 if Present
(Transient_Blk
)
6761 and then Nkind
(Transient_Blk
) = N_Block_Statement
6763 Blk
:= Transient_Blk
;
6766 Stmts
:= Statements
(Handled_Statement_Sequence
(Blk
));
6767 Stmt
:= First
(Stmts
);
6768 while Nkind
(Stmt
) /= N_Procedure_Call_Statement
loop
6773 Params
:= Parameter_Associations
(Call
);
6775 if Is_RTE
(Entity
(Name
(Call
)), RE_Protected_Entry_Call
) then
6777 -- Substitute Conditional_Entry_Call for Simple_Call parameter
6779 Param
:= First
(Params
);
6780 while Present
(Param
)
6781 and then not Is_RTE
(Etype
(Param
), RE_Call_Modes
)
6786 pragma Assert
(Present
(Param
));
6787 Rewrite
(Param
, New_Reference_To
(RTE
(RE_Conditional_Call
), Loc
));
6791 -- Find the Communication_Block parameter for the call to the
6792 -- Cancelled function.
6794 Decl
:= First
(Declarations
(Blk
));
6795 while Present
(Decl
)
6796 and then not Is_RTE
(Etype
(Object_Definition
(Decl
)),
6797 RE_Communication_Block
)
6802 -- Add an if statement to execute the else part if the call
6803 -- does not succeed (as indicated by the Cancelled predicate).
6806 Make_Implicit_If_Statement
(N
,
6807 Condition
=> Make_Function_Call
(Loc
,
6808 Name
=> New_Reference_To
(RTE
(RE_Cancelled
), Loc
),
6809 Parameter_Associations
=> New_List
(
6810 New_Reference_To
(Defining_Identifier
(Decl
), Loc
))),
6811 Then_Statements
=> Else_Statements
(N
),
6812 Else_Statements
=> Statements
(Alt
)));
6815 B
:= Make_Defining_Identifier
(Loc
, Name_uB
);
6817 -- Insert declaration of B in declarations of existing block
6819 if No
(Declarations
(Blk
)) then
6820 Set_Declarations
(Blk
, New_List
);
6823 Prepend_To
(Declarations
(Blk
),
6824 Make_Object_Declaration
(Loc
,
6825 Defining_Identifier
=> B
,
6826 Object_Definition
=>
6827 New_Reference_To
(Standard_Boolean
, Loc
)));
6829 -- Create new call statement
6832 New_Reference_To
(RTE
(RE_Conditional_Call
), Loc
));
6833 Append_To
(Params
, New_Reference_To
(B
, Loc
));
6836 Make_Procedure_Call_Statement
(Loc
,
6837 Name
=> New_Reference_To
(RTE
(RE_Task_Entry_Call
), Loc
),
6838 Parameter_Associations
=> Params
));
6840 -- Construct statement sequence for new block
6843 Make_Implicit_If_Statement
(N
,
6844 Condition
=> New_Reference_To
(B
, Loc
),
6845 Then_Statements
=> Statements
(Alt
),
6846 Else_Statements
=> Else_Statements
(N
)));
6849 -- The result is the new block
6852 Make_Block_Statement
(Loc
,
6853 Declarations
=> Declarations
(Blk
),
6854 Handled_Statement_Sequence
=>
6855 Make_Handled_Sequence_Of_Statements
(Loc
, Stmts
)));
6859 end Expand_N_Conditional_Entry_Call
;
6861 ---------------------------------------
6862 -- Expand_N_Delay_Relative_Statement --
6863 ---------------------------------------
6865 -- Delay statement is implemented as a procedure call to Delay_For
6866 -- defined in Ada.Calendar.Delays in order to reduce the overhead of
6867 -- simple delays imposed by the use of Protected Objects.
6869 procedure Expand_N_Delay_Relative_Statement
(N
: Node_Id
) is
6870 Loc
: constant Source_Ptr
:= Sloc
(N
);
6873 Make_Procedure_Call_Statement
(Loc
,
6874 Name
=> New_Reference_To
(RTE
(RO_CA_Delay_For
), Loc
),
6875 Parameter_Associations
=> New_List
(Expression
(N
))));
6877 end Expand_N_Delay_Relative_Statement
;
6879 ------------------------------------
6880 -- Expand_N_Delay_Until_Statement --
6881 ------------------------------------
6883 -- Delay Until statement is implemented as a procedure call to
6884 -- Delay_Until defined in Ada.Calendar.Delays and Ada.Real_Time.Delays.
6886 procedure Expand_N_Delay_Until_Statement
(N
: Node_Id
) is
6887 Loc
: constant Source_Ptr
:= Sloc
(N
);
6891 if Is_RTE
(Base_Type
(Etype
(Expression
(N
))), RO_CA_Time
) then
6892 Typ
:= RTE
(RO_CA_Delay_Until
);
6894 Typ
:= RTE
(RO_RT_Delay_Until
);
6898 Make_Procedure_Call_Statement
(Loc
,
6899 Name
=> New_Reference_To
(Typ
, Loc
),
6900 Parameter_Associations
=> New_List
(Expression
(N
))));
6903 end Expand_N_Delay_Until_Statement
;
6905 -------------------------
6906 -- Expand_N_Entry_Body --
6907 -------------------------
6909 procedure Expand_N_Entry_Body
(N
: Node_Id
) is
6911 -- Associate discriminals with the next protected operation body to be
6914 if Present
(Next_Protected_Operation
(N
)) then
6915 Set_Discriminals
(Parent
(Current_Scope
));
6917 end Expand_N_Entry_Body
;
6919 -----------------------------------
6920 -- Expand_N_Entry_Call_Statement --
6921 -----------------------------------
6923 -- An entry call is expanded into GNARLI calls to implement a simple entry
6924 -- call (see Build_Simple_Entry_Call).
6926 procedure Expand_N_Entry_Call_Statement
(N
: Node_Id
) is
6932 if No_Run_Time_Mode
then
6933 Error_Msg_CRT
("entry call", N
);
6937 -- If this entry call is part of an asynchronous select, don't expand it
6938 -- here; it will be expanded with the select statement. Don't expand
6939 -- timed entry calls either, as they are translated into asynchronous
6942 -- ??? This whole approach is questionable; it may be better to go back
6943 -- to allowing the expansion to take place and then attempting to fix it
6944 -- up in Expand_N_Asynchronous_Select. The tricky part is figuring out
6945 -- whether the expanded call is on a task or protected entry.
6947 if (Nkind
(Parent
(N
)) /= N_Triggering_Alternative
6948 or else N
/= Triggering_Statement
(Parent
(N
)))
6949 and then (Nkind
(Parent
(N
)) /= N_Entry_Call_Alternative
6950 or else N
/= Entry_Call_Statement
(Parent
(N
))
6951 or else Nkind
(Parent
(Parent
(N
))) /= N_Timed_Entry_Call
)
6953 Extract_Entry
(N
, Concval
, Ename
, Index
);
6954 Build_Simple_Entry_Call
(N
, Concval
, Ename
, Index
);
6956 end Expand_N_Entry_Call_Statement
;
6958 --------------------------------
6959 -- Expand_N_Entry_Declaration --
6960 --------------------------------
6962 -- If there are parameters, then first, each of the formals is marked by
6963 -- setting Is_Entry_Formal. Next a record type is built which is used to
6964 -- hold the parameter values. The name of this record type is entryP where
6965 -- entry is the name of the entry, with an additional corresponding access
6966 -- type called entryPA. The record type has matching components for each
6967 -- formal (the component names are the same as the formal names). For
6968 -- elementary types, the component type matches the formal type. For
6969 -- composite types, an access type is declared (with the name formalA)
6970 -- which designates the formal type, and the type of the component is this
6971 -- access type. Finally the Entry_Component of each formal is set to
6972 -- reference the corresponding record component.
6974 procedure Expand_N_Entry_Declaration
(N
: Node_Id
) is
6975 Loc
: constant Source_Ptr
:= Sloc
(N
);
6976 Entry_Ent
: constant Entity_Id
:= Defining_Identifier
(N
);
6977 Components
: List_Id
;
6980 Last_Decl
: Node_Id
;
6981 Component
: Entity_Id
;
6984 Rec_Ent
: Entity_Id
;
6985 Acc_Ent
: Entity_Id
;
6988 Formal
:= First_Formal
(Entry_Ent
);
6991 -- Most processing is done only if parameters are present
6993 if Present
(Formal
) then
6994 Components
:= New_List
;
6996 -- Loop through formals
6998 while Present
(Formal
) loop
6999 Set_Is_Entry_Formal
(Formal
);
7001 Make_Defining_Identifier
(Sloc
(Formal
), Chars
(Formal
));
7002 Set_Entry_Component
(Formal
, Component
);
7003 Set_Entry_Formal
(Component
, Formal
);
7004 Ftype
:= Etype
(Formal
);
7006 -- Declare new access type and then append
7009 Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
7012 Make_Full_Type_Declaration
(Loc
,
7013 Defining_Identifier
=> Ctype
,
7015 Make_Access_To_Object_Definition
(Loc
,
7016 All_Present
=> True,
7017 Constant_Present
=> Ekind
(Formal
) = E_In_Parameter
,
7018 Subtype_Indication
=> New_Reference_To
(Ftype
, Loc
)));
7020 Insert_After
(Last_Decl
, Decl
);
7023 Append_To
(Components
,
7024 Make_Component_Declaration
(Loc
,
7025 Defining_Identifier
=> Component
,
7026 Component_Definition
=>
7027 Make_Component_Definition
(Loc
,
7028 Aliased_Present
=> False,
7029 Subtype_Indication
=> New_Reference_To
(Ctype
, Loc
))));
7031 Next_Formal_With_Extras
(Formal
);
7034 -- Create the Entry_Parameter_Record declaration
7037 Make_Defining_Identifier
(Loc
, New_Internal_Name
('P'));
7040 Make_Full_Type_Declaration
(Loc
,
7041 Defining_Identifier
=> Rec_Ent
,
7043 Make_Record_Definition
(Loc
,
7045 Make_Component_List
(Loc
,
7046 Component_Items
=> Components
)));
7048 Insert_After
(Last_Decl
, Decl
);
7051 -- Construct and link in the corresponding access type
7054 Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
7056 Set_Entry_Parameters_Type
(Entry_Ent
, Acc_Ent
);
7059 Make_Full_Type_Declaration
(Loc
,
7060 Defining_Identifier
=> Acc_Ent
,
7062 Make_Access_To_Object_Definition
(Loc
,
7063 All_Present
=> True,
7064 Subtype_Indication
=> New_Reference_To
(Rec_Ent
, Loc
)));
7066 Insert_After
(Last_Decl
, Decl
);
7069 end Expand_N_Entry_Declaration
;
7071 -----------------------------
7072 -- Expand_N_Protected_Body --
7073 -----------------------------
7075 -- Protected bodies are expanded to the completion of the subprograms
7076 -- created for the corresponding protected type. These are a protected and
7077 -- unprotected version of each protected subprogram in the object, a
7078 -- function to calculate each entry barrier, and a procedure to execute the
7079 -- sequence of statements of each protected entry body. For example, for
7080 -- protected type ptype:
7083 -- (O : System.Address;
7084 -- E : Protected_Entry_Index)
7087 -- <discriminant renamings>
7088 -- <private object renamings>
7090 -- return <barrier expression>;
7093 -- procedure pprocN (_object : in out poV;...) is
7094 -- <discriminant renamings>
7095 -- <private object renamings>
7097 -- <sequence of statements>
7100 -- procedure pprocP (_object : in out poV;...) is
7101 -- procedure _clean is
7104 -- ptypeS (_object, Pn);
7105 -- Unlock (_object._object'Access);
7106 -- Abort_Undefer.all;
7111 -- Lock (_object._object'Access);
7112 -- pprocN (_object;...);
7117 -- function pfuncN (_object : poV;...) return Return_Type is
7118 -- <discriminant renamings>
7119 -- <private object renamings>
7121 -- <sequence of statements>
7124 -- function pfuncP (_object : poV) return Return_Type is
7125 -- procedure _clean is
7127 -- Unlock (_object._object'Access);
7128 -- Abort_Undefer.all;
7133 -- Lock (_object._object'Access);
7134 -- return pfuncN (_object);
7141 -- (O : System.Address;
7142 -- P : System.Address;
7143 -- E : Protected_Entry_Index)
7145 -- <discriminant renamings>
7146 -- <private object renamings>
7147 -- type poVP is access poV;
7148 -- _Object : ptVP := ptVP!(O);
7152 -- <statement sequence>
7153 -- Complete_Entry_Body (_Object._Object);
7155 -- when all others =>
7156 -- Exceptional_Complete_Entry_Body (
7157 -- _Object._Object, Get_GNAT_Exception);
7161 -- The type poV is the record created for the protected type to hold
7162 -- the state of the protected object.
7164 procedure Expand_N_Protected_Body
(N
: Node_Id
) is
7165 Loc
: constant Source_Ptr
:= Sloc
(N
);
7166 Pid
: constant Entity_Id
:= Corresponding_Spec
(N
);
7168 Current_Node
: Node_Id
;
7169 Disp_Op_Body
: Node_Id
;
7170 New_Op_Body
: Node_Id
;
7171 Num_Entries
: Natural := 0;
7176 Chain
: Entity_Id
:= Empty
;
7177 -- Finalization chain that may be attached to new body
7179 function Build_Dispatching_Subprogram_Body
7182 Prot_Bod
: Node_Id
) return Node_Id
;
7183 -- Build a dispatching version of the protected subprogram body. The
7184 -- newly generated subprogram contains a call to the original protected
7185 -- body. The following code is generated:
7187 -- function <protected-function-name> (Param1 .. ParamN) return
7190 -- return <protected-function-name>P (Param1 .. ParamN);
7191 -- end <protected-function-name>;
7195 -- procedure <protected-procedure-name> (Param1 .. ParamN) is
7197 -- <protected-procedure-name>P (Param1 .. ParamN);
7198 -- end <protected-procedure-name>
7200 ---------------------------------------
7201 -- Build_Dispatching_Subprogram_Body --
7202 ---------------------------------------
7204 function Build_Dispatching_Subprogram_Body
7207 Prot_Bod
: Node_Id
) return Node_Id
7209 Loc
: constant Source_Ptr
:= Sloc
(N
);
7216 -- Generate a specification without a letter suffix in order to
7217 -- override an interface function or procedure.
7220 Build_Protected_Sub_Specification
(N
, Pid
, Dispatching_Mode
);
7222 -- The formal parameters become the actuals of the protected
7223 -- function or procedure call.
7225 Actuals
:= New_List
;
7226 Formal
:= First
(Parameter_Specifications
(Spec
));
7227 while Present
(Formal
) loop
7229 Make_Identifier
(Loc
, Chars
(Defining_Identifier
(Formal
))));
7234 if Nkind
(Spec
) = N_Procedure_Specification
then
7237 Make_Procedure_Call_Statement
(Loc
,
7239 New_Reference_To
(Corresponding_Spec
(Prot_Bod
), Loc
),
7240 Parameter_Associations
=> Actuals
));
7242 pragma Assert
(Nkind
(Spec
) = N_Function_Specification
);
7246 Make_Simple_Return_Statement
(Loc
,
7248 Make_Function_Call
(Loc
,
7250 New_Reference_To
(Corresponding_Spec
(Prot_Bod
), Loc
),
7251 Parameter_Associations
=> Actuals
)));
7255 Make_Subprogram_Body
(Loc
,
7256 Declarations
=> Empty_List
,
7257 Specification
=> Spec
,
7258 Handled_Statement_Sequence
=>
7259 Make_Handled_Sequence_Of_Statements
(Loc
, Stmts
));
7260 end Build_Dispatching_Subprogram_Body
;
7262 -- Start of processing for Expand_N_Protected_Body
7265 if No_Run_Time_Mode
then
7266 Error_Msg_CRT
("protected body", N
);
7270 -- This is the proper body corresponding to a stub. The declarations
7271 -- must be inserted at the point of the stub, which in turn is in the
7272 -- declarative part of the parent unit.
7274 if Nkind
(Parent
(N
)) = N_Subunit
then
7275 Current_Node
:= Corresponding_Stub
(Parent
(N
));
7280 Op_Body
:= First
(Declarations
(N
));
7282 -- The protected body is replaced with the bodies of its
7283 -- protected operations, and the declarations for internal objects
7284 -- that may have been created for entry family bounds.
7286 Rewrite
(N
, Make_Null_Statement
(Sloc
(N
)));
7289 while Present
(Op_Body
) loop
7290 case Nkind
(Op_Body
) is
7291 when N_Subprogram_Declaration
=>
7294 when N_Subprogram_Body
=>
7296 -- Do not create bodies for eliminated operations
7298 if not Is_Eliminated
(Defining_Entity
(Op_Body
))
7299 and then not Is_Eliminated
(Corresponding_Spec
(Op_Body
))
7302 Build_Unprotected_Subprogram_Body
(Op_Body
, Pid
);
7304 -- Propagate the finalization chain to the new body. In the
7305 -- unlikely event that the subprogram contains a declaration
7306 -- or allocator for an object that requires finalization,
7307 -- the corresponding chain is created when analyzing the
7308 -- body, and attached to its entity. This entity is not
7309 -- further elaborated, and so the chain properly belongs to
7310 -- the newly created subprogram body.
7313 Finalization_Chain_Entity
(Defining_Entity
(Op_Body
));
7315 if Present
(Chain
) then
7316 Set_Finalization_Chain_Entity
7317 (Protected_Body_Subprogram
7318 (Corresponding_Spec
(Op_Body
)), Chain
);
7320 (Handled_Statement_Sequence
(New_Op_Body
), False);
7323 Insert_After
(Current_Node
, New_Op_Body
);
7324 Current_Node
:= New_Op_Body
;
7325 Analyze
(New_Op_Body
);
7327 -- Build the corresponding protected operation. It may
7328 -- appear that this is needed only if this is a visible
7329 -- operation of the type, or if it is an interrupt handler,
7330 -- and this was the strategy used previously in GNAT.
7331 -- However, the operation may be exported through a 'Access
7332 -- to an external caller. This is the common idiom in code
7333 -- that uses the Ada 2005 Timing_Events package. As a result
7334 -- we need to produce the protected body for both visible
7335 -- and private operations.
7337 if Present
(Corresponding_Spec
(Op_Body
)) then
7339 Unit_Declaration_Node
(Corresponding_Spec
(Op_Body
));
7341 if Nkind
(Parent
(Op_Decl
)) =
7342 N_Protected_Definition
7345 Build_Protected_Subprogram_Body
(
7346 Op_Body
, Pid
, Specification
(New_Op_Body
));
7348 Insert_After
(Current_Node
, New_Op_Body
);
7349 Analyze
(New_Op_Body
);
7351 Current_Node
:= New_Op_Body
;
7353 -- Generate an overriding primitive operation body for
7354 -- this subprogram if the protected type implements
7357 if Ada_Version
>= Ada_05
7358 and then Present
(Interfaces
(
7359 Corresponding_Record_Type
(Pid
)))
7362 Build_Dispatching_Subprogram_Body
(
7363 Op_Body
, Pid
, New_Op_Body
);
7365 Insert_After
(Current_Node
, Disp_Op_Body
);
7366 Analyze
(Disp_Op_Body
);
7368 Current_Node
:= Disp_Op_Body
;
7374 when N_Entry_Body
=>
7375 Op_Id
:= Defining_Identifier
(Op_Body
);
7376 Num_Entries
:= Num_Entries
+ 1;
7378 New_Op_Body
:= Build_Protected_Entry
(Op_Body
, Op_Id
, Pid
);
7380 Insert_After
(Current_Node
, New_Op_Body
);
7381 Current_Node
:= New_Op_Body
;
7382 Analyze
(New_Op_Body
);
7384 when N_Implicit_Label_Declaration
=>
7387 when N_Itype_Reference
=>
7388 Insert_After
(Current_Node
, New_Copy
(Op_Body
));
7390 when N_Freeze_Entity
=>
7391 New_Op_Body
:= New_Copy
(Op_Body
);
7393 if Present
(Entity
(Op_Body
))
7394 and then Freeze_Node
(Entity
(Op_Body
)) = Op_Body
7396 Set_Freeze_Node
(Entity
(Op_Body
), New_Op_Body
);
7399 Insert_After
(Current_Node
, New_Op_Body
);
7400 Current_Node
:= New_Op_Body
;
7401 Analyze
(New_Op_Body
);
7404 New_Op_Body
:= New_Copy
(Op_Body
);
7405 Insert_After
(Current_Node
, New_Op_Body
);
7406 Current_Node
:= New_Op_Body
;
7407 Analyze
(New_Op_Body
);
7409 when N_Object_Declaration
=>
7410 pragma Assert
(not Comes_From_Source
(Op_Body
));
7411 New_Op_Body
:= New_Copy
(Op_Body
);
7412 Insert_After
(Current_Node
, New_Op_Body
);
7413 Current_Node
:= New_Op_Body
;
7414 Analyze
(New_Op_Body
);
7417 raise Program_Error
;
7424 -- Finally, create the body of the function that maps an entry index
7425 -- into the corresponding body index, except when there is no entry,
7426 -- or in a ravenscar-like profile.
7428 if Corresponding_Runtime_Package
(Pid
) =
7429 System_Tasking_Protected_Objects_Entries
7431 New_Op_Body
:= Build_Find_Body_Index
(Pid
);
7432 Insert_After
(Current_Node
, New_Op_Body
);
7433 Current_Node
:= New_Op_Body
;
7434 Analyze
(New_Op_Body
);
7437 -- Ada 2005 (AI-345): Construct the primitive wrapper bodies after the
7438 -- protected body. At this point all wrapper specs have been created,
7439 -- frozen and included in the dispatch table for the protected type.
7441 if Ada_Version
>= Ada_05
then
7442 Build_Wrapper_Bodies
(Loc
, Pid
, Current_Node
);
7444 end Expand_N_Protected_Body
;
7446 -----------------------------------------
7447 -- Expand_N_Protected_Type_Declaration --
7448 -----------------------------------------
7450 -- First we create a corresponding record type declaration used to
7451 -- represent values of this protected type.
7452 -- The general form of this type declaration is
7454 -- type poV (discriminants) is record
7455 -- _Object : aliased <kind>Protection
7456 -- [(<entry count> [, <handler count>])];
7457 -- [entry_family : array (bounds) of Void;]
7458 -- <private data fields>
7461 -- The discriminants are present only if the corresponding protected type
7462 -- has discriminants, and they exactly mirror the protected type
7463 -- discriminants. The private data fields similarly mirror the private
7464 -- declarations of the protected type.
7466 -- The Object field is always present. It contains RTS specific data used
7467 -- to control the protected object. It is declared as Aliased so that it
7468 -- can be passed as a pointer to the RTS. This allows the protected record
7469 -- to be referenced within RTS data structures. An appropriate Protection
7470 -- type and discriminant are generated.
7472 -- The Service field is present for protected objects with entries. It
7473 -- contains sufficient information to allow the entry service procedure for
7474 -- this object to be called when the object is not known till runtime.
7476 -- One entry_family component is present for each entry family in the
7477 -- task definition (see Expand_N_Task_Type_Declaration).
7479 -- When a protected object is declared, an instance of the protected type
7480 -- value record is created. The elaboration of this declaration creates the
7481 -- correct bounds for the entry families, and also evaluates the priority
7482 -- expression if needed. The initialization routine for the protected type
7483 -- itself then calls Initialize_Protection with appropriate parameters to
7484 -- initialize the value of the Task_Id field. Install_Handlers may be also
7485 -- called if a pragma Attach_Handler applies.
7487 -- Note: this record is passed to the subprograms created by the expansion
7488 -- of protected subprograms and entries. It is an in parameter to protected
7489 -- functions and an in out parameter to procedures and entry bodies. The
7490 -- Entity_Id for this created record type is placed in the
7491 -- Corresponding_Record_Type field of the associated protected type entity.
7493 -- Next we create a procedure specifications for protected subprograms and
7494 -- entry bodies. For each protected subprograms two subprograms are
7495 -- created, an unprotected and a protected version. The unprotected version
7496 -- is called from within other operations of the same protected object.
7498 -- We also build the call to register the procedure if a pragma
7499 -- Interrupt_Handler applies.
7501 -- A single subprogram is created to service all entry bodies; it has an
7502 -- additional boolean out parameter indicating that the previous entry call
7503 -- made by the current task was serviced immediately, i.e. not by proxy.
7504 -- The O parameter contains a pointer to a record object of the type
7505 -- described above. An untyped interface is used here to allow this
7506 -- procedure to be called in places where the type of the object to be
7507 -- serviced is not known. This must be done, for example, when a call that
7508 -- may have been requeued is cancelled; the corresponding object must be
7509 -- serviced, but which object that is not known till runtime.
7512 -- (O : System.Address; P : out Boolean);
7513 -- procedure pprocN (_object : in out poV);
7514 -- procedure pproc (_object : in out poV);
7515 -- function pfuncN (_object : poV);
7516 -- function pfunc (_object : poV);
7519 -- Note that this must come after the record type declaration, since
7520 -- the specs refer to this type.
7522 procedure Expand_N_Protected_Type_Declaration
(N
: Node_Id
) is
7523 Loc
: constant Source_Ptr
:= Sloc
(N
);
7524 Prot_Typ
: constant Entity_Id
:= Defining_Identifier
(N
);
7526 Pdef
: constant Node_Id
:= Protected_Definition
(N
);
7527 -- This contains two lists; one for visible and one for private decls
7531 Discr_Map
: constant Elist_Id
:= New_Elmt_List
;
7535 Comp_Id
: Entity_Id
;
7537 Current_Node
: Node_Id
:= N
;
7538 Bdef
: Entity_Id
:= Empty
; -- avoid uninit warning
7539 Edef
: Entity_Id
:= Empty
; -- avoid uninit warning
7540 Entries_Aggr
: Node_Id
;
7541 Body_Id
: Entity_Id
;
7544 Object_Comp
: Node_Id
;
7546 procedure Check_Inlining
(Subp
: Entity_Id
);
7547 -- If the original operation has a pragma Inline, propagate the flag
7548 -- to the internal body, for possible inlining later on. The source
7549 -- operation is invisible to the back-end and is never actually called.
7551 function Static_Component_Size
(Comp
: Entity_Id
) return Boolean;
7552 -- When compiling under the Ravenscar profile, private components must
7553 -- have a static size, or else a protected object will require heap
7554 -- allocation, violating the corresponding restriction. It is preferable
7555 -- to make this check here, because it provides a better error message
7556 -- than the back-end, which refers to the object as a whole.
7558 procedure Register_Handler
;
7559 -- For a protected operation that is an interrupt handler, add the
7560 -- freeze action that will register it as such.
7562 --------------------
7563 -- Check_Inlining --
7564 --------------------
7566 procedure Check_Inlining
(Subp
: Entity_Id
) is
7568 if Is_Inlined
(Subp
) then
7569 Set_Is_Inlined
(Protected_Body_Subprogram
(Subp
));
7570 Set_Is_Inlined
(Subp
, False);
7574 ---------------------------------
7575 -- Check_Static_Component_Size --
7576 ---------------------------------
7578 function Static_Component_Size
(Comp
: Entity_Id
) return Boolean is
7579 Typ
: constant Entity_Id
:= Etype
(Comp
);
7583 if Is_Scalar_Type
(Typ
) then
7586 elsif Is_Array_Type
(Typ
) then
7587 return Compile_Time_Known_Bounds
(Typ
);
7589 elsif Is_Record_Type
(Typ
) then
7590 C
:= First_Component
(Typ
);
7591 while Present
(C
) loop
7592 if not Static_Component_Size
(C
) then
7601 -- Any other types will be checked by the back-end
7606 end Static_Component_Size
;
7608 ----------------------
7609 -- Register_Handler --
7610 ----------------------
7612 procedure Register_Handler
is
7614 -- All semantic checks already done in Sem_Prag
7616 Prot_Proc
: constant Entity_Id
:=
7618 (Specification
(Current_Node
));
7620 Proc_Address
: constant Node_Id
:=
7621 Make_Attribute_Reference
(Loc
,
7622 Prefix
=> New_Reference_To
(Prot_Proc
, Loc
),
7623 Attribute_Name
=> Name_Address
);
7625 RTS_Call
: constant Entity_Id
:=
7626 Make_Procedure_Call_Statement
(Loc
,
7629 RTE
(RE_Register_Interrupt_Handler
), Loc
),
7630 Parameter_Associations
=>
7631 New_List
(Proc_Address
));
7633 Append_Freeze_Action
(Prot_Proc
, RTS_Call
);
7634 end Register_Handler
;
7636 -- Start of processing for Expand_N_Protected_Type_Declaration
7639 if Present
(Corresponding_Record_Type
(Prot_Typ
)) then
7642 Rec_Decl
:= Build_Corresponding_Record
(N
, Prot_Typ
, Loc
);
7645 Cdecls
:= Component_Items
(Component_List
(Type_Definition
(Rec_Decl
)));
7647 -- Ada 2005 (AI-345): Propagate the attribute that contains the list
7648 -- of implemented interfaces.
7650 Set_Interface_List
(Type_Definition
(Rec_Decl
), Interface_List
(N
));
7652 Qualify_Entity_Names
(N
);
7654 -- If the type has discriminants, their occurrences in the declaration
7655 -- have been replaced by the corresponding discriminals. For components
7656 -- that are constrained by discriminants, their homologues in the
7657 -- corresponding record type must refer to the discriminants of that
7658 -- record, so we must apply a new renaming to subtypes_indications:
7660 -- protected discriminant => discriminal => record discriminant
7662 -- This replacement is not applied to default expressions, for which
7663 -- the discriminal is correct.
7665 if Has_Discriminants
(Prot_Typ
) then
7671 Disc
:= First_Discriminant
(Prot_Typ
);
7672 Decl
:= First
(Discriminant_Specifications
(Rec_Decl
));
7673 while Present
(Disc
) loop
7674 Append_Elmt
(Discriminal
(Disc
), Discr_Map
);
7675 Append_Elmt
(Defining_Identifier
(Decl
), Discr_Map
);
7676 Next_Discriminant
(Disc
);
7682 -- Fill in the component declarations
7684 -- Add components for entry families. For each entry family, create an
7685 -- anonymous type declaration with the same size, and analyze the type.
7687 Collect_Entry_Families
(Loc
, Cdecls
, Current_Node
, Prot_Typ
);
7689 -- Prepend the _Object field with the right type to the component list.
7690 -- We need to compute the number of entries, and in some cases the
7691 -- number of Attach_Handler pragmas.
7695 Num_Attach_Handler
: Int
:= 0;
7696 Protection_Subtype
: Node_Id
;
7697 Entry_Count_Expr
: constant Node_Id
:=
7698 Build_Entry_Count_Expression
7699 (Prot_Typ
, Cdecls
, Loc
);
7702 -- Could this be simplified using Corresponding_Runtime_Package???
7704 if Has_Attach_Handler
(Prot_Typ
) then
7705 Ritem
:= First_Rep_Item
(Prot_Typ
);
7706 while Present
(Ritem
) loop
7707 if Nkind
(Ritem
) = N_Pragma
7708 and then Pragma_Name
(Ritem
) = Name_Attach_Handler
7710 Num_Attach_Handler
:= Num_Attach_Handler
+ 1;
7713 Next_Rep_Item
(Ritem
);
7716 if Restricted_Profile
then
7717 if Has_Entries
(Prot_Typ
) then
7718 Protection_Subtype
:=
7719 New_Reference_To
(RTE
(RE_Protection_Entry
), Loc
);
7721 Protection_Subtype
:=
7722 New_Reference_To
(RTE
(RE_Protection
), Loc
);
7725 Protection_Subtype
:=
7726 Make_Subtype_Indication
7730 (RTE
(RE_Static_Interrupt_Protection
), Loc
),
7732 Make_Index_Or_Discriminant_Constraint
(
7734 Constraints
=> New_List
(
7736 Make_Integer_Literal
(Loc
, Num_Attach_Handler
))));
7739 elsif Has_Interrupt_Handler
(Prot_Typ
) then
7740 Protection_Subtype
:=
7741 Make_Subtype_Indication
(
7743 Subtype_Mark
=> New_Reference_To
7744 (RTE
(RE_Dynamic_Interrupt_Protection
), Loc
),
7746 Make_Index_Or_Discriminant_Constraint
(
7748 Constraints
=> New_List
(Entry_Count_Expr
)));
7750 -- Type has explicit entries or generated primitive entry wrappers
7752 elsif Has_Entries
(Prot_Typ
)
7753 or else (Ada_Version
>= Ada_05
7754 and then Present
(Interface_List
(N
)))
7756 case Corresponding_Runtime_Package
(Prot_Typ
) is
7757 when System_Tasking_Protected_Objects_Entries
=>
7758 Protection_Subtype
:=
7759 Make_Subtype_Indication
(Loc
,
7761 New_Reference_To
(RTE
(RE_Protection_Entries
), Loc
),
7763 Make_Index_Or_Discriminant_Constraint
(
7765 Constraints
=> New_List
(Entry_Count_Expr
)));
7767 when System_Tasking_Protected_Objects_Single_Entry
=>
7768 Protection_Subtype
:=
7769 New_Reference_To
(RTE
(RE_Protection_Entry
), Loc
);
7772 raise Program_Error
;
7776 Protection_Subtype
:= New_Reference_To
(RTE
(RE_Protection
), Loc
);
7780 Make_Component_Declaration
(Loc
,
7781 Defining_Identifier
=>
7782 Make_Defining_Identifier
(Loc
, Name_uObject
),
7783 Component_Definition
=>
7784 Make_Component_Definition
(Loc
,
7785 Aliased_Present
=> True,
7786 Subtype_Indication
=> Protection_Subtype
));
7789 pragma Assert
(Present
(Pdef
));
7791 -- Add private field components
7793 if Present
(Private_Declarations
(Pdef
)) then
7794 Priv
:= First
(Private_Declarations
(Pdef
));
7796 while Present
(Priv
) loop
7798 if Nkind
(Priv
) = N_Component_Declaration
then
7799 if not Static_Component_Size
(Defining_Identifier
(Priv
)) then
7801 -- When compiling for a restricted profile, the private
7802 -- components must have a static size. If not, this is an
7803 -- error for a single protected declaration, and rates a
7804 -- warning on a protected type declaration.
7806 if not Comes_From_Source
(Prot_Typ
) then
7807 Check_Restriction
(No_Implicit_Heap_Allocations
, Priv
);
7809 elsif Restriction_Active
(No_Implicit_Heap_Allocations
) then
7810 Error_Msg_N
("component has non-static size?", Priv
);
7812 ("\creation of protected object of type& will violate"
7813 & " restriction No_Implicit_Heap_Allocations?",
7818 -- The component definition consists of a subtype indication,
7819 -- or (in Ada 2005) an access definition. Make a copy of the
7820 -- proper definition.
7823 Old_Comp
: constant Node_Id
:= Component_Definition
(Priv
);
7824 Pent
: constant Entity_Id
:= Defining_Identifier
(Priv
);
7828 if Present
(Subtype_Indication
(Old_Comp
)) then
7830 Make_Component_Definition
(Sloc
(Pent
),
7831 Aliased_Present
=> False,
7832 Subtype_Indication
=>
7833 New_Copy_Tree
(Subtype_Indication
(Old_Comp
),
7837 Make_Component_Definition
(Sloc
(Pent
),
7838 Aliased_Present
=> False,
7839 Access_Definition
=>
7840 New_Copy_Tree
(Access_Definition
(Old_Comp
),
7845 Make_Component_Declaration
(Loc
,
7846 Defining_Identifier
=>
7847 Make_Defining_Identifier
(Sloc
(Pent
), Chars
(Pent
)),
7848 Component_Definition
=> New_Comp
,
7849 Expression
=> Expression
(Priv
));
7851 Append_To
(Cdecls
, New_Priv
);
7854 elsif Nkind
(Priv
) = N_Subprogram_Declaration
then
7856 -- Make the unprotected version of the subprogram available
7857 -- for expansion of intra object calls. There is need for
7858 -- a protected version only if the subprogram is an interrupt
7859 -- handler, otherwise this operation can only be called from
7863 Make_Subprogram_Declaration
(Loc
,
7865 Build_Protected_Sub_Specification
7866 (Priv
, Prot_Typ
, Unprotected_Mode
));
7868 Insert_After
(Current_Node
, Sub
);
7871 Set_Protected_Body_Subprogram
7872 (Defining_Unit_Name
(Specification
(Priv
)),
7873 Defining_Unit_Name
(Specification
(Sub
)));
7874 Check_Inlining
(Defining_Unit_Name
(Specification
(Priv
)));
7875 Current_Node
:= Sub
;
7878 Make_Subprogram_Declaration
(Loc
,
7880 Build_Protected_Sub_Specification
7881 (Priv
, Prot_Typ
, Protected_Mode
));
7883 Insert_After
(Current_Node
, Sub
);
7885 Current_Node
:= Sub
;
7887 if Is_Interrupt_Handler
7888 (Defining_Unit_Name
(Specification
(Priv
)))
7890 if not Restricted_Profile
then
7900 -- Put the _Object component after the private component so that it
7901 -- be finalized early as required by 9.4 (20)
7903 Append_To
(Cdecls
, Object_Comp
);
7905 Insert_After
(Current_Node
, Rec_Decl
);
7906 Current_Node
:= Rec_Decl
;
7908 -- Analyze the record declaration immediately after construction,
7909 -- because the initialization procedure is needed for single object
7910 -- declarations before the next entity is analyzed (the freeze call
7911 -- that generates this initialization procedure is found below).
7913 Analyze
(Rec_Decl
, Suppress
=> All_Checks
);
7915 -- Ada 2005 (AI-345): Construct the primitive entry wrappers before
7916 -- the corresponding record is frozen. If any wrappers are generated,
7917 -- Current_Node is updated accordingly.
7919 if Ada_Version
>= Ada_05
then
7920 Build_Wrapper_Specs
(Loc
, Prot_Typ
, Current_Node
);
7923 -- Collect pointers to entry bodies and their barriers, to be placed
7924 -- in the Entry_Bodies_Array for the type. For each entry/family we
7925 -- add an expression to the aggregate which is the initial value of
7926 -- this array. The array is declared after all protected subprograms.
7928 if Has_Entries
(Prot_Typ
) then
7929 Entries_Aggr
:= Make_Aggregate
(Loc
, Expressions
=> New_List
);
7931 Entries_Aggr
:= Empty
;
7934 -- Build two new procedure specifications for each protected subprogram;
7935 -- one to call from outside the object and one to call from inside.
7936 -- Build a barrier function and an entry body action procedure
7937 -- specification for each protected entry. Initialize the entry body
7938 -- array. If subprogram is flagged as eliminated, do not generate any
7939 -- internal operations.
7943 Comp
:= First
(Visible_Declarations
(Pdef
));
7945 while Present
(Comp
) loop
7946 if Nkind
(Comp
) = N_Subprogram_Declaration
then
7948 Make_Subprogram_Declaration
(Loc
,
7950 Build_Protected_Sub_Specification
7951 (Comp
, Prot_Typ
, Unprotected_Mode
));
7953 Insert_After
(Current_Node
, Sub
);
7956 Set_Protected_Body_Subprogram
7957 (Defining_Unit_Name
(Specification
(Comp
)),
7958 Defining_Unit_Name
(Specification
(Sub
)));
7959 Check_Inlining
(Defining_Unit_Name
(Specification
(Comp
)));
7961 -- Make the protected version of the subprogram available for
7962 -- expansion of external calls.
7964 Current_Node
:= Sub
;
7967 Make_Subprogram_Declaration
(Loc
,
7969 Build_Protected_Sub_Specification
7970 (Comp
, Prot_Typ
, Protected_Mode
));
7972 Insert_After
(Current_Node
, Sub
);
7975 Current_Node
:= Sub
;
7977 -- Generate an overriding primitive operation specification for
7978 -- this subprogram if the protected type implements an interface.
7980 if Ada_Version
>= Ada_05
7982 Present
(Interfaces
(Corresponding_Record_Type
(Prot_Typ
)))
7985 Make_Subprogram_Declaration
(Loc
,
7987 Build_Protected_Sub_Specification
7988 (Comp
, Prot_Typ
, Dispatching_Mode
));
7990 Insert_After
(Current_Node
, Sub
);
7993 Current_Node
:= Sub
;
7996 -- If a pragma Interrupt_Handler applies, build and add a call to
7997 -- Register_Interrupt_Handler to the freezing actions of the
7998 -- protected version (Current_Node) of the subprogram:
8000 -- system.interrupts.register_interrupt_handler
8001 -- (prot_procP'address);
8003 if not Restricted_Profile
8004 and then Is_Interrupt_Handler
8005 (Defining_Unit_Name
(Specification
(Comp
)))
8010 elsif Nkind
(Comp
) = N_Entry_Declaration
then
8011 E_Count
:= E_Count
+ 1;
8012 Comp_Id
:= Defining_Identifier
(Comp
);
8015 Make_Defining_Identifier
(Loc
,
8016 Build_Selected_Name
(Prot_Typ
, Comp_Id
, 'E'));
8018 Make_Subprogram_Declaration
(Loc
,
8020 Build_Protected_Entry_Specification
(Loc
, Edef
, Comp_Id
));
8022 Insert_After
(Current_Node
, Sub
);
8025 Set_Protected_Body_Subprogram
8026 (Defining_Identifier
(Comp
),
8027 Defining_Unit_Name
(Specification
(Sub
)));
8029 Current_Node
:= Sub
;
8032 Make_Defining_Identifier
(Loc
,
8033 Chars
=> Build_Selected_Name
(Prot_Typ
, Comp_Id
, 'B'));
8035 Make_Subprogram_Declaration
(Loc
,
8037 Build_Barrier_Function_Specification
(Loc
, Bdef
));
8039 Insert_After
(Current_Node
, Sub
);
8041 Set_Protected_Body_Subprogram
(Bdef
, Bdef
);
8042 Set_Barrier_Function
(Comp_Id
, Bdef
);
8043 Set_Scope
(Bdef
, Scope
(Comp_Id
));
8044 Current_Node
:= Sub
;
8046 -- Collect pointers to the protected subprogram and the barrier
8047 -- of the current entry, for insertion into Entry_Bodies_Array.
8050 Make_Aggregate
(Loc
,
8051 Expressions
=> New_List
(
8052 Make_Attribute_Reference
(Loc
,
8053 Prefix
=> New_Reference_To
(Bdef
, Loc
),
8054 Attribute_Name
=> Name_Unrestricted_Access
),
8055 Make_Attribute_Reference
(Loc
,
8056 Prefix
=> New_Reference_To
(Edef
, Loc
),
8057 Attribute_Name
=> Name_Unrestricted_Access
))),
8058 Expressions
(Entries_Aggr
));
8065 -- If there are some private entry declarations, expand it as if they
8066 -- were visible entries.
8068 if Present
(Private_Declarations
(Pdef
)) then
8069 Comp
:= First
(Private_Declarations
(Pdef
));
8070 while Present
(Comp
) loop
8071 if Nkind
(Comp
) = N_Entry_Declaration
then
8072 E_Count
:= E_Count
+ 1;
8073 Comp_Id
:= Defining_Identifier
(Comp
);
8076 Make_Defining_Identifier
(Loc
,
8077 Build_Selected_Name
(Prot_Typ
, Comp_Id
, 'E'));
8079 Make_Subprogram_Declaration
(Loc
,
8081 Build_Protected_Entry_Specification
(Loc
, Edef
, Comp_Id
));
8083 Insert_After
(Current_Node
, Sub
);
8086 Set_Protected_Body_Subprogram
8087 (Defining_Identifier
(Comp
),
8088 Defining_Unit_Name
(Specification
(Sub
)));
8090 Current_Node
:= Sub
;
8093 Make_Defining_Identifier
(Loc
,
8094 Chars
=> Build_Selected_Name
(Prot_Typ
, Comp_Id
, 'E'));
8097 Make_Subprogram_Declaration
(Loc
,
8099 Build_Barrier_Function_Specification
(Loc
, Bdef
));
8101 Insert_After
(Current_Node
, Sub
);
8103 Set_Protected_Body_Subprogram
(Bdef
, Bdef
);
8104 Set_Barrier_Function
(Comp_Id
, Bdef
);
8105 Set_Scope
(Bdef
, Scope
(Comp_Id
));
8106 Current_Node
:= Sub
;
8108 -- Collect pointers to the protected subprogram and the barrier
8109 -- of the current entry, for insertion into Entry_Bodies_Array.
8111 Append_To
(Expressions
(Entries_Aggr
),
8112 Make_Aggregate
(Loc
,
8113 Expressions
=> New_List
(
8114 Make_Attribute_Reference
(Loc
,
8115 Prefix
=> New_Reference_To
(Bdef
, Loc
),
8116 Attribute_Name
=> Name_Unrestricted_Access
),
8117 Make_Attribute_Reference
(Loc
,
8118 Prefix
=> New_Reference_To
(Edef
, Loc
),
8119 Attribute_Name
=> Name_Unrestricted_Access
))));
8126 -- Emit declaration for Entry_Bodies_Array, now that the addresses of
8127 -- all protected subprograms have been collected.
8129 if Has_Entries
(Prot_Typ
) then
8131 Make_Defining_Identifier
(Sloc
(Prot_Typ
),
8132 Chars
=> New_External_Name
(Chars
(Prot_Typ
), 'A'));
8134 case Corresponding_Runtime_Package
(Prot_Typ
) is
8135 when System_Tasking_Protected_Objects_Entries
=>
8136 Body_Arr
:= Make_Object_Declaration
(Loc
,
8137 Defining_Identifier
=> Body_Id
,
8138 Aliased_Present
=> True,
8139 Object_Definition
=>
8140 Make_Subtype_Indication
(Loc
,
8141 Subtype_Mark
=> New_Reference_To
(
8142 RTE
(RE_Protected_Entry_Body_Array
), Loc
),
8144 Make_Index_Or_Discriminant_Constraint
(Loc
,
8145 Constraints
=> New_List
(
8147 Make_Integer_Literal
(Loc
, 1),
8148 Make_Integer_Literal
(Loc
, E_Count
))))),
8149 Expression
=> Entries_Aggr
);
8151 when System_Tasking_Protected_Objects_Single_Entry
=>
8152 Body_Arr
:= Make_Object_Declaration
(Loc
,
8153 Defining_Identifier
=> Body_Id
,
8154 Aliased_Present
=> True,
8155 Object_Definition
=> New_Reference_To
8156 (RTE
(RE_Entry_Body
), Loc
),
8158 Make_Aggregate
(Loc
,
8159 Expressions
=> New_List
(
8160 Make_Attribute_Reference
(Loc
,
8161 Prefix
=> New_Reference_To
(Bdef
, Loc
),
8162 Attribute_Name
=> Name_Unrestricted_Access
),
8163 Make_Attribute_Reference
(Loc
,
8164 Prefix
=> New_Reference_To
(Edef
, Loc
),
8165 Attribute_Name
=> Name_Unrestricted_Access
))));
8168 raise Program_Error
;
8171 -- A pointer to this array will be placed in the corresponding record
8172 -- by its initialization procedure so this needs to be analyzed here.
8174 Insert_After
(Current_Node
, Body_Arr
);
8175 Current_Node
:= Body_Arr
;
8178 Set_Entry_Bodies_Array
(Prot_Typ
, Body_Id
);
8180 -- Finally, build the function that maps an entry index into the
8181 -- corresponding body. A pointer to this function is placed in each
8182 -- object of the type. Except for a ravenscar-like profile (no abort,
8183 -- no entry queue, 1 entry)
8185 if Corresponding_Runtime_Package
(Prot_Typ
) =
8186 System_Tasking_Protected_Objects_Entries
8189 Make_Subprogram_Declaration
(Loc
,
8190 Specification
=> Build_Find_Body_Index_Spec
(Prot_Typ
));
8191 Insert_After
(Current_Node
, Sub
);
8195 end Expand_N_Protected_Type_Declaration
;
8197 --------------------------------
8198 -- Expand_N_Requeue_Statement --
8199 --------------------------------
8201 -- A non-dispatching requeue statement is expanded into one of four GNARLI
8202 -- operations, depending on the source and destination (task or protected
8203 -- object). A dispatching requeue statement is expanded into a call to the
8204 -- predefined primitive _Disp_Requeue. In addition, code is generated to
8205 -- jump around the remainder of processing for the original entry and, if
8206 -- the destination is (different) protected object, to attempt to service
8207 -- it. The following illustrates the various cases:
8210 -- (O : System.Address;
8211 -- P : System.Address;
8212 -- E : Protected_Entry_Index)
8214 -- <discriminant renamings>
8215 -- <private object renamings>
8216 -- type poVP is access poV;
8217 -- _object : ptVP := ptVP!(O);
8221 -- <start of statement sequence for entry>
8223 -- -- Requeue from one protected entry body to another protected
8226 -- Requeue_Protected_Entry (
8227 -- _object._object'Access,
8228 -- new._object'Access,
8233 -- <some more of the statement sequence for entry>
8235 -- -- Requeue from an entry body to a task entry
8237 -- Requeue_Protected_To_Task_Entry (
8243 -- <rest of statement sequence for entry>
8244 -- Complete_Entry_Body (_object._object);
8247 -- when all others =>
8248 -- Exceptional_Complete_Entry_Body (
8249 -- _object._object, Get_GNAT_Exception);
8253 -- Requeue of a task entry call to a task entry
8255 -- Accept_Call (E, Ann);
8256 -- <start of statement sequence for accept statement>
8257 -- Requeue_Task_Entry (New._task_id, E, Abort_Present);
8259 -- <rest of statement sequence for accept statement>
8261 -- Complete_Rendezvous;
8264 -- when all others =>
8265 -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
8267 -- Requeue of a task entry call to a protected entry
8269 -- Accept_Call (E, Ann);
8270 -- <start of statement sequence for accept statement>
8271 -- Requeue_Task_To_Protected_Entry (
8272 -- new._object'Access,
8277 -- <rest of statement sequence for accept statement>
8279 -- Complete_Rendezvous;
8282 -- when all others =>
8283 -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
8285 -- Ada 2005 (AI05-0030): Dispatching requeue from protected to interface
8289 -- (O : System.Address;
8290 -- P : System.Address;
8291 -- E : Protected_Entry_Index)
8293 -- <discriminant renamings>
8294 -- <private object renamings>
8295 -- type poVP is access poV;
8296 -- _object : ptVP := ptVP!(O);
8300 -- <start of statement sequence for entry>
8303 -- (<interface class-wide object>,
8306 -- Ada.Tags.Get_Offset_Index
8308 -- <interface dispatch table index of target entry>),
8312 -- <rest of statement sequence for entry>
8313 -- Complete_Entry_Body (_object._object);
8316 -- when all others =>
8317 -- Exceptional_Complete_Entry_Body (
8318 -- _object._object, Get_GNAT_Exception);
8322 -- Ada 2005 (AI05-0030): Dispatching requeue from task to interface
8325 -- Accept_Call (E, Ann);
8326 -- <start of statement sequence for accept statement>
8328 -- (<interface class-wide object>,
8331 -- Ada.Tags.Get_Offset_Index
8333 -- <interface dispatch table index of target entrt>),
8337 -- <rest of statement sequence for accept statement>
8339 -- Complete_Rendezvous;
8342 -- when all others =>
8343 -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
8345 -- Further details on these expansions can be found in Expand_N_Protected_
8346 -- Body and Expand_N_Accept_Statement.
8348 procedure Expand_N_Requeue_Statement
(N
: Node_Id
) is
8349 Loc
: constant Source_Ptr
:= Sloc
(N
);
8350 Abortable
: Node_Id
;
8352 Conc_Typ
: Entity_Id
;
8357 New_Param
: Node_Id
;
8358 Old_Typ
: Entity_Id
;
8361 RTS_Call
: Entity_Id
;
8362 Self_Param
: Node_Id
;
8363 Skip_Stat
: Node_Id
;
8367 New_Occurrence_Of
(Boolean_Literals
(Abort_Present
(N
)), Loc
);
8369 -- Extract the components of the entry call
8371 Extract_Entry
(N
, Concval
, Ename
, Index
);
8372 Conc_Typ
:= Etype
(Concval
);
8374 -- Examine the scope stack in order to find nearest enclosing protected
8375 -- or task type. This will constitute our invocation source.
8377 Old_Typ
:= Current_Scope
;
8378 while Present
(Old_Typ
)
8379 and then not Is_Protected_Type
(Old_Typ
)
8380 and then not Is_Task_Type
(Old_Typ
)
8382 Old_Typ
:= Scope
(Old_Typ
);
8385 -- Generate the parameter list for all cases. The abortable flag is
8386 -- common among dispatching and regular requeue.
8388 Params
:= New_List
(Abortable
);
8390 -- Ada 2005 (AI05-0030): We have a dispatching requeue of the form
8391 -- Concval.Ename where the type of Concval is class-wide concurrent
8394 if Ada_Version
>= Ada_05
8395 and then Present
(Concval
)
8396 and then Is_Class_Wide_Type
(Conc_Typ
)
8397 and then Is_Concurrent_Interface
(Conc_Typ
)
8399 RTS_Call
:= Make_Identifier
(Loc
, Name_uDisp_Requeue
);
8402 -- Ada.Tags.Get_Offset_Index
8403 -- (Ada.Tags.Tag (Concval),
8404 -- <interface dispatch table position of Ename>)
8407 Make_Function_Call
(Loc
,
8409 New_Reference_To
(RTE
(RE_Get_Offset_Index
), Loc
),
8410 Parameter_Associations
=>
8412 Unchecked_Convert_To
(RTE
(RE_Tag
), Concval
),
8413 Make_Integer_Literal
(Loc
, DT_Position
(Entity
(Ename
))))));
8415 -- Specific actuals for protected to interface class-wide type
8418 if Is_Protected_Type
(Old_Typ
) then
8420 Make_Attribute_Reference
(Loc
, -- _object'Address
8422 Concurrent_Ref
(New_Occurrence_Of
(Old_Typ
, Loc
)),
8425 Prepend_To
(Params
, -- True
8426 New_Reference_To
(Standard_True
, Loc
));
8428 -- Specific actuals for task to interface class-wide type requeue
8431 pragma Assert
(Is_Task_Type
(Old_Typ
));
8433 Prepend_To
(Params
, -- null
8434 New_Reference_To
(RTE
(RE_Null_Address
), Loc
));
8435 Prepend_To
(Params
, -- False
8436 New_Reference_To
(Standard_False
, Loc
));
8439 -- Finally, add the common object parameter
8441 Prepend_To
(Params
, New_Copy_Tree
(Concval
));
8443 -- Regular requeue processing
8446 New_Param
:= Concurrent_Ref
(Concval
);
8448 -- The index expression is common among all four cases
8451 Entry_Index_Expression
(Loc
, Entity
(Ename
), Index
, Conc_Typ
));
8453 if Is_Protected_Type
(Old_Typ
) then
8455 Make_Attribute_Reference
(Loc
,
8457 Concurrent_Ref
(New_Occurrence_Of
(Old_Typ
, Loc
)),
8459 Name_Unchecked_Access
);
8461 -- Protected to protected requeue
8463 if Is_Protected_Type
(Conc_Typ
) then
8465 New_Reference_To
(RTE
(RE_Requeue_Protected_Entry
), Loc
);
8468 Make_Attribute_Reference
(Loc
,
8472 Name_Unchecked_Access
);
8474 -- Protected to task requeue
8477 pragma Assert
(Is_Task_Type
(Conc_Typ
));
8480 RTE
(RE_Requeue_Protected_To_Task_Entry
), Loc
);
8483 Prepend
(New_Param
, Params
);
8484 Prepend
(Self_Param
, Params
);
8487 pragma Assert
(Is_Task_Type
(Old_Typ
));
8489 -- Task to protected requeue
8491 if Is_Protected_Type
(Conc_Typ
) then
8494 RTE
(RE_Requeue_Task_To_Protected_Entry
), Loc
);
8497 Make_Attribute_Reference
(Loc
,
8501 Name_Unchecked_Access
);
8503 -- Task to task requeue
8506 pragma Assert
(Is_Task_Type
(Conc_Typ
));
8508 New_Reference_To
(RTE
(RE_Requeue_Task_Entry
), Loc
);
8511 Prepend
(New_Param
, Params
);
8515 -- Create the GNARLI or predefined primitive call
8518 Make_Procedure_Call_Statement
(Loc
,
8520 Parameter_Associations
=> Params
);
8525 if Is_Protected_Type
(Old_Typ
) then
8527 -- Build the return statement to skip the rest of the entry body
8529 Skip_Stat
:= Make_Simple_Return_Statement
(Loc
);
8532 -- If the requeue is within a task, find the end label of the
8533 -- enclosing accept statement.
8535 Acc_Stat
:= Parent
(N
);
8536 while Nkind
(Acc_Stat
) /= N_Accept_Statement
loop
8537 Acc_Stat
:= Parent
(Acc_Stat
);
8540 -- The last statement is the second label, used for completing the
8541 -- rendezvous the usual way. The label we are looking for is right
8545 Prev
(Last
(Statements
(Handled_Statement_Sequence
(Acc_Stat
))));
8547 pragma Assert
(Nkind
(Lab_Node
) = N_Label
);
8549 -- Build the goto statement to skip the rest of the accept
8553 Make_Goto_Statement
(Loc
,
8554 Name
=> New_Occurrence_Of
(Entity
(Identifier
(Lab_Node
)), Loc
));
8557 Set_Analyzed
(Skip_Stat
);
8559 Insert_After
(N
, Skip_Stat
);
8560 end Expand_N_Requeue_Statement
;
8562 -------------------------------
8563 -- Expand_N_Selective_Accept --
8564 -------------------------------
8566 procedure Expand_N_Selective_Accept
(N
: Node_Id
) is
8567 Loc
: constant Source_Ptr
:= Sloc
(N
);
8568 Alts
: constant List_Id
:= Select_Alternatives
(N
);
8570 -- Note: in the below declarations a lot of new lists are allocated
8571 -- unconditionally which may well not end up being used. That's
8572 -- not a good idea since it wastes space gratuitously ???
8574 Accept_Case
: List_Id
;
8575 Accept_List
: constant List_Id
:= New_List
;
8578 Alt_List
: constant List_Id
:= New_List
;
8579 Alt_Stats
: List_Id
;
8580 Ann
: Entity_Id
:= Empty
;
8583 Check_Guard
: Boolean := True;
8585 Decls
: constant List_Id
:= New_List
;
8586 Stats
: constant List_Id
:= New_List
;
8587 Body_List
: constant List_Id
:= New_List
;
8588 Trailing_List
: constant List_Id
:= New_List
;
8591 Else_Present
: Boolean := False;
8592 Terminate_Alt
: Node_Id
:= Empty
;
8593 Select_Mode
: Node_Id
;
8595 Delay_Case
: List_Id
;
8596 Delay_Count
: Integer := 0;
8597 Delay_Val
: Entity_Id
;
8598 Delay_Index
: Entity_Id
;
8599 Delay_Min
: Entity_Id
;
8600 Delay_Num
: Int
:= 1;
8601 Delay_Alt_List
: List_Id
:= New_List
;
8602 Delay_List
: constant List_Id
:= New_List
;
8606 First_Delay
: Boolean := True;
8607 Guard_Open
: Entity_Id
;
8613 Num_Accept
: Nat
:= 0;
8616 Time_Type
: Entity_Id
;
8618 Select_Call
: Node_Id
;
8620 Qnam
: constant Entity_Id
:=
8621 Make_Defining_Identifier
(Loc
, New_External_Name
('S', 0));
8623 Xnam
: constant Entity_Id
:=
8624 Make_Defining_Identifier
(Loc
, New_External_Name
('J', 1));
8626 -----------------------
8627 -- Local subprograms --
8628 -----------------------
8630 function Accept_Or_Raise
return List_Id
;
8631 -- For the rare case where delay alternatives all have guards, and
8632 -- all of them are closed, it is still possible that there were open
8633 -- accept alternatives with no callers. We must reexamine the
8634 -- Accept_List, and execute a selective wait with no else if some
8635 -- accept is open. If none, we raise program_error.
8637 procedure Add_Accept
(Alt
: Node_Id
);
8638 -- Process a single accept statement in a select alternative. Build
8639 -- procedure for body of accept, and add entry to dispatch table with
8640 -- expression for guard, in preparation for call to run time select.
8642 function Make_And_Declare_Label
(Num
: Int
) return Node_Id
;
8643 -- Manufacture a label using Num as a serial number and declare it.
8644 -- The declaration is appended to Decls. The label marks the trailing
8645 -- statements of an accept or delay alternative.
8647 function Make_Select_Call
(Select_Mode
: Entity_Id
) return Node_Id
;
8648 -- Build call to Selective_Wait runtime routine
8650 procedure Process_Delay_Alternative
(Alt
: Node_Id
; Index
: Int
);
8651 -- Add code to compare value of delay with previous values, and
8652 -- generate case entry for trailing statements.
8654 procedure Process_Accept_Alternative
8658 -- Add code to call corresponding procedure, and branch to
8659 -- trailing statements, if any.
8661 ---------------------
8662 -- Accept_Or_Raise --
8663 ---------------------
8665 function Accept_Or_Raise
return List_Id
is
8668 J
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
,
8669 New_Internal_Name
('J'));
8672 -- We generate the following:
8674 -- for J in q'range loop
8675 -- if q(J).S /=null_task_entry then
8676 -- selective_wait (simple_mode,...);
8682 -- if no rendez_vous then
8683 -- raise program_error;
8686 -- Note that the code needs to know that the selector name
8687 -- in an Accept_Alternative is named S.
8689 Cond
:= Make_Op_Ne
(Loc
,
8691 Make_Selected_Component
(Loc
,
8692 Prefix
=> Make_Indexed_Component
(Loc
,
8693 Prefix
=> New_Reference_To
(Qnam
, Loc
),
8694 Expressions
=> New_List
(New_Reference_To
(J
, Loc
))),
8695 Selector_Name
=> Make_Identifier
(Loc
, Name_S
)),
8697 New_Reference_To
(RTE
(RE_Null_Task_Entry
), Loc
));
8700 Make_Implicit_Loop_Statement
(N
,
8701 Identifier
=> Empty
,
8703 Make_Iteration_Scheme
(Loc
,
8704 Loop_Parameter_Specification
=>
8705 Make_Loop_Parameter_Specification
(Loc
,
8706 Defining_Identifier
=> J
,
8707 Discrete_Subtype_Definition
=>
8708 Make_Attribute_Reference
(Loc
,
8709 Prefix
=> New_Reference_To
(Qnam
, Loc
),
8710 Attribute_Name
=> Name_Range
,
8711 Expressions
=> New_List
(
8712 Make_Integer_Literal
(Loc
, 1))))),
8714 Statements
=> New_List
(
8715 Make_Implicit_If_Statement
(N
,
8717 Then_Statements
=> New_List
(
8719 New_Reference_To
(RTE
(RE_Simple_Mode
), Loc
)),
8720 Make_Exit_Statement
(Loc
))))));
8723 Make_Raise_Program_Error
(Loc
,
8724 Condition
=> Make_Op_Eq
(Loc
,
8725 Left_Opnd
=> New_Reference_To
(Xnam
, Loc
),
8727 New_Reference_To
(RTE
(RE_No_Rendezvous
), Loc
)),
8728 Reason
=> PE_All_Guards_Closed
));
8731 end Accept_Or_Raise
;
8737 procedure Add_Accept
(Alt
: Node_Id
) is
8738 Acc_Stm
: constant Node_Id
:= Accept_Statement
(Alt
);
8739 Ename
: constant Node_Id
:= Entry_Direct_Name
(Acc_Stm
);
8740 Eloc
: constant Source_Ptr
:= Sloc
(Ename
);
8741 Eent
: constant Entity_Id
:= Entity
(Ename
);
8742 Index
: constant Node_Id
:= Entry_Index
(Acc_Stm
);
8743 Null_Body
: Node_Id
;
8744 Proc_Body
: Node_Id
;
8751 Ann
:= Node
(Last_Elmt
(Accept_Address
(Eent
)));
8754 if Present
(Condition
(Alt
)) then
8756 Make_Conditional_Expression
(Eloc
, New_List
(
8758 Entry_Index_Expression
(Eloc
, Eent
, Index
, Scope
(Eent
)),
8759 New_Reference_To
(RTE
(RE_Null_Task_Entry
), Eloc
)));
8762 Entry_Index_Expression
8763 (Eloc
, Eent
, Index
, Scope
(Eent
));
8766 if Present
(Handled_Statement_Sequence
(Accept_Statement
(Alt
))) then
8767 Null_Body
:= New_Reference_To
(Standard_False
, Eloc
);
8769 if Abort_Allowed
then
8770 Call
:= Make_Procedure_Call_Statement
(Eloc
,
8771 Name
=> New_Reference_To
(RTE
(RE_Abort_Undefer
), Eloc
));
8772 Insert_Before
(First
(Statements
(Handled_Statement_Sequence
(
8773 Accept_Statement
(Alt
)))), Call
);
8778 Make_Defining_Identifier
(Eloc
,
8779 New_External_Name
(Chars
(Ename
), 'A', Num_Accept
));
8781 if Comes_From_Source
(Alt
) then
8782 Set_Debug_Info_Needed
(PB_Ent
);
8786 Make_Subprogram_Body
(Eloc
,
8788 Make_Procedure_Specification
(Eloc
,
8789 Defining_Unit_Name
=> PB_Ent
),
8790 Declarations
=> Declarations
(Acc_Stm
),
8791 Handled_Statement_Sequence
=>
8792 Build_Accept_Body
(Accept_Statement
(Alt
)));
8794 -- During the analysis of the body of the accept statement, any
8795 -- zero cost exception handler records were collected in the
8796 -- Accept_Handler_Records field of the N_Accept_Alternative node.
8797 -- This is where we move them to where they belong, namely the
8798 -- newly created procedure.
8800 Set_Handler_Records
(PB_Ent
, Accept_Handler_Records
(Alt
));
8801 Append
(Proc_Body
, Body_List
);
8804 Null_Body
:= New_Reference_To
(Standard_True
, Eloc
);
8806 -- if accept statement has declarations, insert above, given that
8807 -- we are not creating a body for the accept.
8809 if Present
(Declarations
(Acc_Stm
)) then
8810 Insert_Actions
(N
, Declarations
(Acc_Stm
));
8814 Append_To
(Accept_List
,
8815 Make_Aggregate
(Eloc
, Expressions
=> New_List
(Null_Body
, Expr
)));
8817 Num_Accept
:= Num_Accept
+ 1;
8820 ----------------------------
8821 -- Make_And_Declare_Label --
8822 ----------------------------
8824 function Make_And_Declare_Label
(Num
: Int
) return Node_Id
is
8828 Lab_Id
:= Make_Identifier
(Loc
, New_External_Name
('L', Num
));
8830 Make_Label
(Loc
, Lab_Id
);
8833 Make_Implicit_Label_Declaration
(Loc
,
8834 Defining_Identifier
=>
8835 Make_Defining_Identifier
(Loc
, Chars
(Lab_Id
)),
8836 Label_Construct
=> Lab
));
8839 end Make_And_Declare_Label
;
8841 ----------------------
8842 -- Make_Select_Call --
8843 ----------------------
8845 function Make_Select_Call
(Select_Mode
: Entity_Id
) return Node_Id
is
8846 Params
: constant List_Id
:= New_List
;
8850 Make_Attribute_Reference
(Loc
,
8851 Prefix
=> New_Reference_To
(Qnam
, Loc
),
8852 Attribute_Name
=> Name_Unchecked_Access
),
8854 Append
(Select_Mode
, Params
);
8855 Append
(New_Reference_To
(Ann
, Loc
), Params
);
8856 Append
(New_Reference_To
(Xnam
, Loc
), Params
);
8859 Make_Procedure_Call_Statement
(Loc
,
8860 Name
=> New_Reference_To
(RTE
(RE_Selective_Wait
), Loc
),
8861 Parameter_Associations
=> Params
);
8862 end Make_Select_Call
;
8864 --------------------------------
8865 -- Process_Accept_Alternative --
8866 --------------------------------
8868 procedure Process_Accept_Alternative
8873 Choices
: List_Id
:= No_List
;
8874 Alt_Stats
: List_Id
;
8877 Adjust_Condition
(Condition
(Alt
));
8878 Alt_Stats
:= No_List
;
8880 if Present
(Handled_Statement_Sequence
(Accept_Statement
(Alt
))) then
8881 Choices
:= New_List
(
8882 Make_Integer_Literal
(Loc
, Index
));
8884 Alt_Stats
:= New_List
(
8885 Make_Procedure_Call_Statement
(Sloc
(Proc
),
8886 Name
=> New_Reference_To
(
8887 Defining_Unit_Name
(Specification
(Proc
)), Sloc
(Proc
))));
8890 if Statements
(Alt
) /= Empty_List
then
8892 if No
(Alt_Stats
) then
8894 -- Accept with no body, followed by trailing statements
8896 Choices
:= New_List
(
8897 Make_Integer_Literal
(Loc
, Index
));
8899 Alt_Stats
:= New_List
;
8902 -- After the call, if any, branch to trailing statements. We
8903 -- create a label for each, as well as the corresponding label
8906 Lab
:= Make_And_Declare_Label
(Index
);
8907 Append_To
(Alt_Stats
,
8908 Make_Goto_Statement
(Loc
,
8909 Name
=> New_Copy
(Identifier
(Lab
))));
8911 Append
(Lab
, Trailing_List
);
8912 Append_List
(Statements
(Alt
), Trailing_List
);
8913 Append_To
(Trailing_List
,
8914 Make_Goto_Statement
(Loc
,
8915 Name
=> New_Copy
(Identifier
(End_Lab
))));
8918 if Present
(Alt_Stats
) then
8920 -- Procedure call. and/or trailing statements
8922 Append_To
(Alt_List
,
8923 Make_Case_Statement_Alternative
(Loc
,
8924 Discrete_Choices
=> Choices
,
8925 Statements
=> Alt_Stats
));
8927 end Process_Accept_Alternative
;
8929 -------------------------------
8930 -- Process_Delay_Alternative --
8931 -------------------------------
8933 procedure Process_Delay_Alternative
(Alt
: Node_Id
; Index
: Int
) is
8936 Delay_Alt
: List_Id
;
8939 -- Deal with C/Fortran boolean as delay condition
8941 Adjust_Condition
(Condition
(Alt
));
8943 -- Determine the smallest specified delay
8945 -- for each delay alternative generate:
8947 -- if guard-expression then
8948 -- Delay_Val := delay-expression;
8949 -- Guard_Open := True;
8950 -- if Delay_Val < Delay_Min then
8951 -- Delay_Min := Delay_Val;
8952 -- Delay_Index := Index;
8956 -- The enclosing if-statement is omitted if there is no guard
8961 First_Delay
:= False;
8963 Delay_Alt
:= New_List
(
8964 Make_Assignment_Statement
(Loc
,
8965 Name
=> New_Reference_To
(Delay_Min
, Loc
),
8966 Expression
=> Expression
(Delay_Statement
(Alt
))));
8968 if Delay_Count
> 1 then
8969 Append_To
(Delay_Alt
,
8970 Make_Assignment_Statement
(Loc
,
8971 Name
=> New_Reference_To
(Delay_Index
, Loc
),
8972 Expression
=> Make_Integer_Literal
(Loc
, Index
)));
8976 Delay_Alt
:= New_List
(
8977 Make_Assignment_Statement
(Loc
,
8978 Name
=> New_Reference_To
(Delay_Val
, Loc
),
8979 Expression
=> Expression
(Delay_Statement
(Alt
))));
8981 if Time_Type
= Standard_Duration
then
8984 Left_Opnd
=> New_Reference_To
(Delay_Val
, Loc
),
8985 Right_Opnd
=> New_Reference_To
(Delay_Min
, Loc
));
8988 -- The scope of the time type must define a comparison
8989 -- operator. The scope itself may not be visible, so we
8990 -- construct a node with entity information to insure that
8991 -- semantic analysis can find the proper operator.
8994 Make_Function_Call
(Loc
,
8995 Name
=> Make_Selected_Component
(Loc
,
8996 Prefix
=> New_Reference_To
(Scope
(Time_Type
), Loc
),
8998 Make_Operator_Symbol
(Loc
,
8999 Chars
=> Name_Op_Lt
,
9000 Strval
=> No_String
)),
9001 Parameter_Associations
=>
9003 New_Reference_To
(Delay_Val
, Loc
),
9004 New_Reference_To
(Delay_Min
, Loc
)));
9006 Set_Entity
(Prefix
(Name
(Cond
)), Scope
(Time_Type
));
9009 Append_To
(Delay_Alt
,
9010 Make_Implicit_If_Statement
(N
,
9012 Then_Statements
=> New_List
(
9013 Make_Assignment_Statement
(Loc
,
9014 Name
=> New_Reference_To
(Delay_Min
, Loc
),
9015 Expression
=> New_Reference_To
(Delay_Val
, Loc
)),
9017 Make_Assignment_Statement
(Loc
,
9018 Name
=> New_Reference_To
(Delay_Index
, Loc
),
9019 Expression
=> Make_Integer_Literal
(Loc
, Index
)))));
9023 Append_To
(Delay_Alt
,
9024 Make_Assignment_Statement
(Loc
,
9025 Name
=> New_Reference_To
(Guard_Open
, Loc
),
9026 Expression
=> New_Reference_To
(Standard_True
, Loc
)));
9029 if Present
(Condition
(Alt
)) then
9030 Delay_Alt
:= New_List
(
9031 Make_Implicit_If_Statement
(N
,
9032 Condition
=> Condition
(Alt
),
9033 Then_Statements
=> Delay_Alt
));
9036 Append_List
(Delay_Alt
, Delay_List
);
9038 -- If the delay alternative has a statement part, add choice to the
9039 -- case statements for delays.
9041 if Present
(Statements
(Alt
)) then
9043 if Delay_Count
= 1 then
9044 Append_List
(Statements
(Alt
), Delay_Alt_List
);
9047 Choices
:= New_List
(
9048 Make_Integer_Literal
(Loc
, Index
));
9050 Append_To
(Delay_Alt_List
,
9051 Make_Case_Statement_Alternative
(Loc
,
9052 Discrete_Choices
=> Choices
,
9053 Statements
=> Statements
(Alt
)));
9056 elsif Delay_Count
= 1 then
9058 -- If the single delay has no trailing statements, add a branch
9059 -- to the exit label to the selective wait.
9061 Delay_Alt_List
:= New_List
(
9062 Make_Goto_Statement
(Loc
,
9063 Name
=> New_Copy
(Identifier
(End_Lab
))));
9066 end Process_Delay_Alternative
;
9068 -- Start of processing for Expand_N_Selective_Accept
9071 -- First insert some declarations before the select. The first is:
9075 -- This variable holds the parameters passed to the accept body. This
9076 -- declaration has already been inserted by the time we get here by
9077 -- a call to Expand_Accept_Declarations made from the semantics when
9078 -- processing the first accept statement contained in the select. We
9079 -- can find this entity as Accept_Address (E), where E is any of the
9080 -- entries references by contained accept statements.
9082 -- The first step is to scan the list of Selective_Accept_Statements
9083 -- to find this entity, and also count the number of accepts, and
9084 -- determine if terminated, delay or else is present:
9088 Alt
:= First
(Alts
);
9089 while Present
(Alt
) loop
9091 if Nkind
(Alt
) = N_Accept_Alternative
then
9094 elsif Nkind
(Alt
) = N_Delay_Alternative
then
9095 Delay_Count
:= Delay_Count
+ 1;
9097 -- If the delays are relative delays, the delay expressions have
9098 -- type Standard_Duration. Otherwise they must have some time type
9099 -- recognized by GNAT.
9101 if Nkind
(Delay_Statement
(Alt
)) = N_Delay_Relative_Statement
then
9102 Time_Type
:= Standard_Duration
;
9104 Time_Type
:= Etype
(Expression
(Delay_Statement
(Alt
)));
9106 if Is_RTE
(Base_Type
(Etype
(Time_Type
)), RO_CA_Time
)
9107 or else Is_RTE
(Base_Type
(Etype
(Time_Type
)), RO_RT_Time
)
9112 "& is not a time type (RM 9.6(6))",
9113 Expression
(Delay_Statement
(Alt
)), Time_Type
);
9114 Time_Type
:= Standard_Duration
;
9115 Set_Etype
(Expression
(Delay_Statement
(Alt
)), Any_Type
);
9119 if No
(Condition
(Alt
)) then
9121 -- This guard will always be open
9123 Check_Guard
:= False;
9126 elsif Nkind
(Alt
) = N_Terminate_Alternative
then
9127 Adjust_Condition
(Condition
(Alt
));
9128 Terminate_Alt
:= Alt
;
9131 Num_Alts
:= Num_Alts
+ 1;
9135 Else_Present
:= Present
(Else_Statements
(N
));
9137 -- At the same time (see procedure Add_Accept) we build the accept list:
9139 -- Qnn : Accept_List (1 .. num-select) := (
9140 -- (null-body, entry-index),
9141 -- (null-body, entry-index),
9143 -- (null_body, entry-index));
9145 -- In the above declaration, null-body is True if the corresponding
9146 -- accept has no body, and false otherwise. The entry is either the
9147 -- entry index expression if there is no guard, or if a guard is
9148 -- present, then a conditional expression of the form:
9150 -- (if guard then entry-index else Null_Task_Entry)
9152 -- If a guard is statically known to be false, the entry can simply
9153 -- be omitted from the accept list.
9156 Make_Object_Declaration
(Loc
,
9157 Defining_Identifier
=> Qnam
,
9158 Object_Definition
=>
9159 New_Reference_To
(RTE
(RE_Accept_List
), Loc
),
9160 Aliased_Present
=> True,
9163 Make_Qualified_Expression
(Loc
,
9165 New_Reference_To
(RTE
(RE_Accept_List
), Loc
),
9167 Make_Aggregate
(Loc
, Expressions
=> Accept_List
)));
9171 -- Then we declare the variable that holds the index for the accept
9172 -- that will be selected for service:
9174 -- Xnn : Select_Index;
9177 Make_Object_Declaration
(Loc
,
9178 Defining_Identifier
=> Xnam
,
9179 Object_Definition
=>
9180 New_Reference_To
(RTE
(RE_Select_Index
), Loc
),
9182 New_Reference_To
(RTE
(RE_No_Rendezvous
), Loc
));
9186 -- After this follow procedure declarations for each accept body
9193 -- where the ... are statements from the corresponding procedure body.
9194 -- No parameters are involved, since the parameters are passed via Ann
9195 -- and the parameter references have already been expanded to be direct
9196 -- references to Ann (see Exp_Ch2.Expand_Entry_Parameter). Furthermore,
9197 -- any embedded tasking statements (which would normally be illegal in
9198 -- procedures), have been converted to calls to the tasking runtime so
9199 -- there is no problem in putting them into procedures.
9201 -- The original accept statement has been expanded into a block in
9202 -- the same fashion as for simple accepts (see Build_Accept_Body).
9204 -- Note: we don't really need to build these procedures for the case
9205 -- where no delay statement is present, but it is just as easy to
9206 -- build them unconditionally, and not significantly inefficient,
9207 -- since if they are short they will be inlined anyway.
9209 -- The procedure declarations have been assembled in Body_List
9211 -- If delays are present, we must compute the required delay.
9212 -- We first generate the declarations:
9214 -- Delay_Index : Boolean := 0;
9215 -- Delay_Min : Some_Time_Type.Time;
9216 -- Delay_Val : Some_Time_Type.Time;
9218 -- Delay_Index will be set to the index of the minimum delay, i.e. the
9219 -- active delay that is actually chosen as the basis for the possible
9220 -- delay if an immediate rendez-vous is not possible.
9222 -- In the most common case there is a single delay statement, and this
9223 -- is handled specially.
9225 if Delay_Count
> 0 then
9227 -- Generate the required declarations
9230 Make_Defining_Identifier
(Loc
, New_External_Name
('D', 1));
9232 Make_Defining_Identifier
(Loc
, New_External_Name
('D', 2));
9234 Make_Defining_Identifier
(Loc
, New_External_Name
('D', 3));
9237 Make_Object_Declaration
(Loc
,
9238 Defining_Identifier
=> Delay_Val
,
9239 Object_Definition
=> New_Reference_To
(Time_Type
, Loc
)));
9242 Make_Object_Declaration
(Loc
,
9243 Defining_Identifier
=> Delay_Index
,
9244 Object_Definition
=> New_Reference_To
(Standard_Integer
, Loc
),
9245 Expression
=> Make_Integer_Literal
(Loc
, 0)));
9248 Make_Object_Declaration
(Loc
,
9249 Defining_Identifier
=> Delay_Min
,
9250 Object_Definition
=> New_Reference_To
(Time_Type
, Loc
),
9252 Unchecked_Convert_To
(Time_Type
,
9253 Make_Attribute_Reference
(Loc
,
9255 New_Occurrence_Of
(Underlying_Type
(Time_Type
), Loc
),
9256 Attribute_Name
=> Name_Last
))));
9258 -- Create Duration and Delay_Mode objects used for passing a delay
9261 D
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('D'));
9262 M
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('M'));
9268 -- Note that these values are defined in s-osprim.ads and must
9271 -- Relative : constant := 0;
9272 -- Absolute_Calendar : constant := 1;
9273 -- Absolute_RT : constant := 2;
9275 if Time_Type
= Standard_Duration
then
9276 Discr
:= Make_Integer_Literal
(Loc
, 0);
9278 elsif Is_RTE
(Base_Type
(Etype
(Time_Type
)), RO_CA_Time
) then
9279 Discr
:= Make_Integer_Literal
(Loc
, 1);
9283 (Is_RTE
(Base_Type
(Etype
(Time_Type
)), RO_RT_Time
));
9284 Discr
:= Make_Integer_Literal
(Loc
, 2);
9288 Make_Object_Declaration
(Loc
,
9289 Defining_Identifier
=> D
,
9290 Object_Definition
=>
9291 New_Reference_To
(Standard_Duration
, Loc
)));
9294 Make_Object_Declaration
(Loc
,
9295 Defining_Identifier
=> M
,
9296 Object_Definition
=>
9297 New_Reference_To
(Standard_Integer
, Loc
),
9298 Expression
=> Discr
));
9303 Make_Defining_Identifier
(Loc
, New_External_Name
('G', 1));
9306 Make_Object_Declaration
(Loc
,
9307 Defining_Identifier
=> Guard_Open
,
9308 Object_Definition
=> New_Reference_To
(Standard_Boolean
, Loc
),
9309 Expression
=> New_Reference_To
(Standard_False
, Loc
)));
9312 -- Delay_Count is zero, don't need M and D set (suppress warning)
9319 if Present
(Terminate_Alt
) then
9321 -- If the terminate alternative guard is False, use
9322 -- Simple_Mode; otherwise use Terminate_Mode.
9324 if Present
(Condition
(Terminate_Alt
)) then
9325 Select_Mode
:= Make_Conditional_Expression
(Loc
,
9326 New_List
(Condition
(Terminate_Alt
),
9327 New_Reference_To
(RTE
(RE_Terminate_Mode
), Loc
),
9328 New_Reference_To
(RTE
(RE_Simple_Mode
), Loc
)));
9330 Select_Mode
:= New_Reference_To
(RTE
(RE_Terminate_Mode
), Loc
);
9333 elsif Else_Present
or Delay_Count
> 0 then
9334 Select_Mode
:= New_Reference_To
(RTE
(RE_Else_Mode
), Loc
);
9337 Select_Mode
:= New_Reference_To
(RTE
(RE_Simple_Mode
), Loc
);
9340 Select_Call
:= Make_Select_Call
(Select_Mode
);
9341 Append
(Select_Call
, Stats
);
9343 -- Now generate code to act on the result. There is an entry
9344 -- in this case for each accept statement with a non-null body,
9345 -- followed by a branch to the statements that follow the Accept.
9346 -- In the absence of delay alternatives, we generate:
9349 -- when No_Rendezvous => -- omitted if simple mode
9364 -- Lab0: Else_Statements;
9367 -- Lab1: Trailing_Statements1;
9370 -- Lab2: Trailing_Statements2;
9375 -- Generate label for common exit
9377 End_Lab
:= Make_And_Declare_Label
(Num_Alts
+ 1);
9379 -- First entry is the default case, when no rendezvous is possible
9381 Choices
:= New_List
(New_Reference_To
(RTE
(RE_No_Rendezvous
), Loc
));
9383 if Else_Present
then
9385 -- If no rendezvous is possible, the else part is executed
9387 Lab
:= Make_And_Declare_Label
(0);
9388 Alt_Stats
:= New_List
(
9389 Make_Goto_Statement
(Loc
,
9390 Name
=> New_Copy
(Identifier
(Lab
))));
9392 Append
(Lab
, Trailing_List
);
9393 Append_List
(Else_Statements
(N
), Trailing_List
);
9394 Append_To
(Trailing_List
,
9395 Make_Goto_Statement
(Loc
,
9396 Name
=> New_Copy
(Identifier
(End_Lab
))));
9398 Alt_Stats
:= New_List
(
9399 Make_Goto_Statement
(Loc
,
9400 Name
=> New_Copy
(Identifier
(End_Lab
))));
9403 Append_To
(Alt_List
,
9404 Make_Case_Statement_Alternative
(Loc
,
9405 Discrete_Choices
=> Choices
,
9406 Statements
=> Alt_Stats
));
9408 -- We make use of the fact that Accept_Index is an integer type, and
9409 -- generate successive literals for entries for each accept. Only those
9410 -- for which there is a body or trailing statements get a case entry.
9412 Alt
:= First
(Select_Alternatives
(N
));
9413 Proc
:= First
(Body_List
);
9414 while Present
(Alt
) loop
9416 if Nkind
(Alt
) = N_Accept_Alternative
then
9417 Process_Accept_Alternative
(Alt
, Index
, Proc
);
9421 (Handled_Statement_Sequence
(Accept_Statement
(Alt
)))
9426 elsif Nkind
(Alt
) = N_Delay_Alternative
then
9427 Process_Delay_Alternative
(Alt
, Delay_Num
);
9428 Delay_Num
:= Delay_Num
+ 1;
9434 -- An others choice is always added to the main case, as well
9435 -- as the delay case (to satisfy the compiler).
9437 Append_To
(Alt_List
,
9438 Make_Case_Statement_Alternative
(Loc
,
9440 New_List
(Make_Others_Choice
(Loc
)),
9442 New_List
(Make_Goto_Statement
(Loc
,
9443 Name
=> New_Copy
(Identifier
(End_Lab
))))));
9445 Accept_Case
:= New_List
(
9446 Make_Case_Statement
(Loc
,
9447 Expression
=> New_Reference_To
(Xnam
, Loc
),
9448 Alternatives
=> Alt_List
));
9450 Append_List
(Trailing_List
, Accept_Case
);
9451 Append
(End_Lab
, Accept_Case
);
9452 Append_List
(Body_List
, Decls
);
9454 -- Construct case statement for trailing statements of delay
9455 -- alternatives, if there are several of them.
9457 if Delay_Count
> 1 then
9458 Append_To
(Delay_Alt_List
,
9459 Make_Case_Statement_Alternative
(Loc
,
9461 New_List
(Make_Others_Choice
(Loc
)),
9463 New_List
(Make_Null_Statement
(Loc
))));
9465 Delay_Case
:= New_List
(
9466 Make_Case_Statement
(Loc
,
9467 Expression
=> New_Reference_To
(Delay_Index
, Loc
),
9468 Alternatives
=> Delay_Alt_List
));
9470 Delay_Case
:= Delay_Alt_List
;
9473 -- If there are no delay alternatives, we append the case statement
9474 -- to the statement list.
9476 if Delay_Count
= 0 then
9477 Append_List
(Accept_Case
, Stats
);
9479 -- Delay alternatives present
9482 -- If delay alternatives are present we generate:
9484 -- find minimum delay.
9485 -- DX := minimum delay;
9486 -- M := <delay mode>;
9487 -- Timed_Selective_Wait (Q'Unchecked_Access, Delay_Mode, P,
9490 -- if X = No_Rendezvous then
9491 -- case statement for delay statements.
9493 -- case statement for accept alternatives.
9504 -- The type of the delay expression is known to be legal
9506 if Time_Type
= Standard_Duration
then
9507 Conv
:= New_Reference_To
(Delay_Min
, Loc
);
9509 elsif Is_RTE
(Base_Type
(Etype
(Time_Type
)), RO_CA_Time
) then
9510 Conv
:= Make_Function_Call
(Loc
,
9511 New_Reference_To
(RTE
(RO_CA_To_Duration
), Loc
),
9512 New_List
(New_Reference_To
(Delay_Min
, Loc
)));
9516 (Is_RTE
(Base_Type
(Etype
(Time_Type
)), RO_RT_Time
));
9518 Conv
:= Make_Function_Call
(Loc
,
9519 New_Reference_To
(RTE
(RO_RT_To_Duration
), Loc
),
9520 New_List
(New_Reference_To
(Delay_Min
, Loc
)));
9523 Stmt
:= Make_Assignment_Statement
(Loc
,
9524 Name
=> New_Reference_To
(D
, Loc
),
9525 Expression
=> Conv
);
9527 -- Change the value for Accept_Modes. (Else_Mode -> Delay_Mode)
9529 Parms
:= Parameter_Associations
(Select_Call
);
9530 Parm
:= First
(Parms
);
9532 while Present
(Parm
)
9533 and then Parm
/= Select_Mode
9538 pragma Assert
(Present
(Parm
));
9539 Rewrite
(Parm
, New_Reference_To
(RTE
(RE_Delay_Mode
), Loc
));
9542 -- Prepare two new parameters of Duration and Delay_Mode type
9543 -- which represent the value and the mode of the minimum delay.
9546 Insert_After
(Parm
, New_Reference_To
(M
, Loc
));
9547 Insert_After
(Parm
, New_Reference_To
(D
, Loc
));
9549 -- Create a call to RTS
9551 Rewrite
(Select_Call
,
9552 Make_Procedure_Call_Statement
(Loc
,
9553 Name
=> New_Reference_To
(RTE
(RE_Timed_Selective_Wait
), Loc
),
9554 Parameter_Associations
=> Parms
));
9556 -- This new call should follow the calculation of the minimum
9559 Insert_List_Before
(Select_Call
, Delay_List
);
9563 Make_Implicit_If_Statement
(N
,
9564 Condition
=> New_Reference_To
(Guard_Open
, Loc
),
9566 New_List
(New_Copy_Tree
(Stmt
),
9567 New_Copy_Tree
(Select_Call
)),
9568 Else_Statements
=> Accept_Or_Raise
);
9569 Rewrite
(Select_Call
, Stmt
);
9571 Insert_Before
(Select_Call
, Stmt
);
9575 Make_Implicit_If_Statement
(N
,
9576 Condition
=> Make_Op_Eq
(Loc
,
9577 Left_Opnd
=> New_Reference_To
(Xnam
, Loc
),
9579 New_Reference_To
(RTE
(RE_No_Rendezvous
), Loc
)),
9581 Then_Statements
=> Delay_Case
,
9582 Else_Statements
=> Accept_Case
);
9584 Append
(Cases
, Stats
);
9588 -- Replace accept statement with appropriate block
9591 Make_Block_Statement
(Loc
,
9592 Declarations
=> Decls
,
9593 Handled_Statement_Sequence
=>
9594 Make_Handled_Sequence_Of_Statements
(Loc
,
9595 Statements
=> Stats
));
9600 -- Note: have to worry more about abort deferral in above code ???
9602 -- Final step is to unstack the Accept_Address entries for all accept
9603 -- statements appearing in accept alternatives in the select statement
9605 Alt
:= First
(Alts
);
9606 while Present
(Alt
) loop
9607 if Nkind
(Alt
) = N_Accept_Alternative
then
9608 Remove_Last_Elmt
(Accept_Address
9609 (Entity
(Entry_Direct_Name
(Accept_Statement
(Alt
)))));
9614 end Expand_N_Selective_Accept
;
9616 --------------------------------------
9617 -- Expand_N_Single_Task_Declaration --
9618 --------------------------------------
9620 -- Single task declarations should never be present after semantic
9621 -- analysis, since we expect them to be replaced by a declaration of an
9622 -- anonymous task type, followed by a declaration of the task object. We
9623 -- include this routine to make sure that is happening!
9625 procedure Expand_N_Single_Task_Declaration
(N
: Node_Id
) is
9627 raise Program_Error
;
9628 end Expand_N_Single_Task_Declaration
;
9630 ------------------------
9631 -- Expand_N_Task_Body --
9632 ------------------------
9634 -- Given a task body
9636 -- task body tname is
9642 -- This expansion routine converts it into a procedure and sets the
9643 -- elaboration flag for the procedure to true, to represent the fact
9644 -- that the task body is now elaborated:
9646 -- procedure tnameB (_Task : access tnameV) is
9647 -- discriminal : dtype renames _Task.discriminant;
9649 -- procedure _clean is
9653 -- Abort_Undefer.all;
9658 -- Abort_Undefer.all;
9660 -- System.Task_Stages.Complete_Activation;
9668 -- In addition, if the task body is an activator, then a call to activate
9669 -- tasks is added at the start of the statements, before the call to
9670 -- Complete_Activation, and if in addition the task is a master then it
9671 -- must be established as a master. These calls are inserted and analyzed
9672 -- in Expand_Cleanup_Actions, when the Handled_Sequence_Of_Statements is
9675 -- There is one discriminal declaration line generated for each
9676 -- discriminant that is present to provide an easy reference point for
9677 -- discriminant references inside the body (see Exp_Ch2.Expand_Name).
9679 -- Note on relationship to GNARLI definition. In the GNARLI definition,
9680 -- task body procedures have a profile (Arg : System.Address). That is
9681 -- needed because GNARLI has to use the same access-to-subprogram type
9682 -- for all task types. We depend here on knowing that in GNAT, passing
9683 -- an address argument by value is identical to passing a record value
9684 -- by access (in either case a single pointer is passed), so even though
9685 -- this procedure has the wrong profile. In fact it's all OK, since the
9686 -- callings sequence is identical.
9688 procedure Expand_N_Task_Body
(N
: Node_Id
) is
9689 Loc
: constant Source_Ptr
:= Sloc
(N
);
9690 Ttyp
: constant Entity_Id
:= Corresponding_Spec
(N
);
9694 Insert_Nod
: Node_Id
;
9695 -- Used to determine the proper location of wrapper body insertions
9698 -- Add renaming declarations for discriminals and a declaration for the
9699 -- entry family index (if applicable).
9701 Install_Private_Data_Declarations
9702 (Loc
, Task_Body_Procedure
(Ttyp
), Ttyp
, N
, Declarations
(N
));
9704 -- Add a call to Abort_Undefer at the very beginning of the task
9705 -- body since this body is called with abort still deferred.
9707 if Abort_Allowed
then
9708 Call
:= Build_Runtime_Call
(Loc
, RE_Abort_Undefer
);
9710 (First
(Statements
(Handled_Statement_Sequence
(N
))), Call
);
9714 -- The statement part has already been protected with an at_end and
9715 -- cleanup actions. The call to Complete_Activation must be placed
9716 -- at the head of the sequence of statements of that block. The
9717 -- declarations have been merged in this sequence of statements but
9718 -- the first real statement is accessible from the First_Real_Statement
9719 -- field (which was set for exactly this purpose).
9721 if Restricted_Profile
then
9722 Call
:= Build_Runtime_Call
(Loc
, RE_Complete_Restricted_Activation
);
9724 Call
:= Build_Runtime_Call
(Loc
, RE_Complete_Activation
);
9728 (First_Real_Statement
(Handled_Statement_Sequence
(N
)), Call
);
9732 Make_Subprogram_Body
(Loc
,
9733 Specification
=> Build_Task_Proc_Specification
(Ttyp
),
9734 Declarations
=> Declarations
(N
),
9735 Handled_Statement_Sequence
=> Handled_Statement_Sequence
(N
));
9737 -- If the task contains generic instantiations, cleanup actions are
9738 -- delayed until after instantiation. Transfer the activation chain to
9739 -- the subprogram, to insure that the activation call is properly
9740 -- generated. It the task body contains inner tasks, indicate that the
9741 -- subprogram is a task master.
9743 if Delay_Cleanups
(Ttyp
) then
9744 Set_Activation_Chain_Entity
(New_N
, Activation_Chain_Entity
(N
));
9745 Set_Is_Task_Master
(New_N
, Is_Task_Master
(N
));
9751 -- Set elaboration flag immediately after task body. If the body is a
9752 -- subunit, the flag is set in the declarative part containing the stub.
9754 if Nkind
(Parent
(N
)) /= N_Subunit
then
9756 Make_Assignment_Statement
(Loc
,
9758 Make_Identifier
(Loc
, New_External_Name
(Chars
(Ttyp
), 'E')),
9759 Expression
=> New_Reference_To
(Standard_True
, Loc
)));
9762 -- Ada 2005 (AI-345): Construct the primitive entry wrapper bodies after
9763 -- the task body. At this point all wrapper specs have been created,
9764 -- frozen and included in the dispatch table for the task type.
9766 if Ada_Version
>= Ada_05
then
9767 if Nkind
(Parent
(N
)) = N_Subunit
then
9768 Insert_Nod
:= Corresponding_Stub
(Parent
(N
));
9773 Build_Wrapper_Bodies
(Loc
, Ttyp
, Insert_Nod
);
9775 end Expand_N_Task_Body
;
9777 ------------------------------------
9778 -- Expand_N_Task_Type_Declaration --
9779 ------------------------------------
9781 -- We have several things to do. First we must create a Boolean flag used
9782 -- to mark if the body is elaborated yet. This variable gets set to True
9783 -- when the body of the task is elaborated (we can't rely on the normal
9784 -- ABE mechanism for the task body, since we need to pass an access to
9785 -- this elaboration boolean to the runtime routines).
9787 -- taskE : aliased Boolean := False;
9789 -- Next a variable is declared to hold the task stack size (either the
9790 -- default : Unspecified_Size, or a value that is set by a pragma
9791 -- Storage_Size). If the value of the pragma Storage_Size is static, then
9792 -- the variable is initialized with this value:
9794 -- taskZ : Size_Type := Unspecified_Size;
9796 -- taskZ : Size_Type := Size_Type (size_expression);
9798 -- Note: No variable is needed to hold the task relative deadline since
9799 -- its value would never be static because the parameter is of a private
9800 -- type (Ada.Real_Time.Time_Span).
9802 -- Next we create a corresponding record type declaration used to represent
9803 -- values of this task. The general form of this type declaration is
9805 -- type taskV (discriminants) is record
9806 -- _Task_Id : Task_Id;
9807 -- entry_family : array (bounds) of Void;
9808 -- _Priority : Integer := priority_expression;
9809 -- _Size : Size_Type := Size_Type (size_expression);
9810 -- _Task_Info : Task_Info_Type := task_info_expression;
9813 -- The discriminants are present only if the corresponding task type has
9814 -- discriminants, and they exactly mirror the task type discriminants.
9816 -- The Id field is always present. It contains the Task_Id value, as set by
9817 -- the call to Create_Task. Note that although the task is limited, the
9818 -- task value record type is not limited, so there is no problem in passing
9819 -- this field as an out parameter to Create_Task.
9821 -- One entry_family component is present for each entry family in the task
9822 -- definition. The bounds correspond to the bounds of the entry family
9823 -- (which may depend on discriminants). The element type is void, since we
9824 -- only need the bounds information for determining the entry index. Note
9825 -- that the use of an anonymous array would normally be illegal in this
9826 -- context, but this is a parser check, and the semantics is quite prepared
9827 -- to handle such a case.
9829 -- The _Size field is present only if a Storage_Size pragma appears in the
9830 -- task definition. The expression captures the argument that was present
9831 -- in the pragma, and is used to override the task stack size otherwise
9832 -- associated with the task type.
9834 -- The _Priority field is present only if a Priority or Interrupt_Priority
9835 -- pragma appears in the task definition. The expression captures the
9836 -- argument that was present in the pragma, and is used to provide the Size
9837 -- parameter to the call to Create_Task.
9839 -- The _Task_Info field is present only if a Task_Info pragma appears in
9840 -- the task definition. The expression captures the argument that was
9841 -- present in the pragma, and is used to provide the Task_Image parameter
9842 -- to the call to Create_Task.
9844 -- The _Relative_Deadline field is present only if a Relative_Deadline
9845 -- pragma appears in the task definition. The expression captures the
9846 -- argument that was present in the pragma, and is used to provide the
9847 -- Relative_Deadline parameter to the call to Create_Task.
9849 -- When a task is declared, an instance of the task value record is
9850 -- created. The elaboration of this declaration creates the correct bounds
9851 -- for the entry families, and also evaluates the size, priority, and
9852 -- task_Info expressions if needed. The initialization routine for the task
9853 -- type itself then calls Create_Task with appropriate parameters to
9854 -- initialize the value of the Task_Id field.
9856 -- Note: the address of this record is passed as the "Discriminants"
9857 -- parameter for Create_Task. Since Create_Task merely passes this onto the
9858 -- body procedure, it does not matter that it does not quite match the
9859 -- GNARLI model of what is being passed (the record contains more than just
9860 -- the discriminants, but the discriminants can be found from the record
9863 -- The Entity_Id for this created record type is placed in the
9864 -- Corresponding_Record_Type field of the associated task type entity.
9866 -- Next we create a procedure specification for the task body procedure:
9868 -- procedure taskB (_Task : access taskV);
9870 -- Note that this must come after the record type declaration, since
9871 -- the spec refers to this type. It turns out that the initialization
9872 -- procedure for the value type references the task body spec, but that's
9873 -- fine, since it won't be generated till the freeze point for the type,
9874 -- which is certainly after the task body spec declaration.
9876 -- Finally, we set the task index value field of the entry attribute in
9877 -- the case of a simple entry.
9879 procedure Expand_N_Task_Type_Declaration
(N
: Node_Id
) is
9880 Loc
: constant Source_Ptr
:= Sloc
(N
);
9881 Tasktyp
: constant Entity_Id
:= Etype
(Defining_Identifier
(N
));
9882 Tasknm
: constant Name_Id
:= Chars
(Tasktyp
);
9883 Taskdef
: constant Node_Id
:= Task_Definition
(N
);
9885 Proc_Spec
: Node_Id
;
9887 Rec_Ent
: Entity_Id
;
9889 Elab_Decl
: Node_Id
;
9890 Size_Decl
: Node_Id
;
9891 Body_Decl
: Node_Id
;
9892 Task_Size
: Node_Id
;
9893 Ent_Stack
: Entity_Id
;
9894 Decl_Stack
: Node_Id
;
9897 -- If already expanded, nothing to do
9899 if Present
(Corresponding_Record_Type
(Tasktyp
)) then
9903 -- Here we will do the expansion
9905 Rec_Decl
:= Build_Corresponding_Record
(N
, Tasktyp
, Loc
);
9907 -- Ada 2005 (AI-345): Propagate the attribute that contains the list
9908 -- of implemented interfaces.
9910 Set_Interface_List
(Type_Definition
(Rec_Decl
), Interface_List
(N
));
9912 Rec_Ent
:= Defining_Identifier
(Rec_Decl
);
9913 Cdecls
:= Component_Items
(Component_List
9914 (Type_Definition
(Rec_Decl
)));
9916 Qualify_Entity_Names
(N
);
9918 -- First create the elaboration variable
9921 Make_Object_Declaration
(Loc
,
9922 Defining_Identifier
=>
9923 Make_Defining_Identifier
(Sloc
(Tasktyp
),
9924 Chars
=> New_External_Name
(Tasknm
, 'E')),
9925 Aliased_Present
=> True,
9926 Object_Definition
=> New_Reference_To
(Standard_Boolean
, Loc
),
9927 Expression
=> New_Reference_To
(Standard_False
, Loc
));
9928 Insert_After
(N
, Elab_Decl
);
9930 -- Next create the declaration of the size variable (tasknmZ)
9932 Set_Storage_Size_Variable
(Tasktyp
,
9933 Make_Defining_Identifier
(Sloc
(Tasktyp
),
9934 Chars
=> New_External_Name
(Tasknm
, 'Z')));
9936 if Present
(Taskdef
) and then Has_Storage_Size_Pragma
(Taskdef
) and then
9937 Is_Static_Expression
(Expression
(First
(
9938 Pragma_Argument_Associations
(Find_Task_Or_Protected_Pragma
(
9939 Taskdef
, Name_Storage_Size
)))))
9942 Make_Object_Declaration
(Loc
,
9943 Defining_Identifier
=> Storage_Size_Variable
(Tasktyp
),
9944 Object_Definition
=> New_Reference_To
(RTE
(RE_Size_Type
), Loc
),
9946 Convert_To
(RTE
(RE_Size_Type
),
9949 Pragma_Argument_Associations
(
9950 Find_Task_Or_Protected_Pragma
9951 (Taskdef
, Name_Storage_Size
)))))));
9955 Make_Object_Declaration
(Loc
,
9956 Defining_Identifier
=> Storage_Size_Variable
(Tasktyp
),
9957 Object_Definition
=> New_Reference_To
(RTE
(RE_Size_Type
), Loc
),
9958 Expression
=> New_Reference_To
(RTE
(RE_Unspecified_Size
), Loc
));
9961 Insert_After
(Elab_Decl
, Size_Decl
);
9963 -- Next build the rest of the corresponding record declaration. This is
9964 -- done last, since the corresponding record initialization procedure
9965 -- will reference the previously created entities.
9967 -- Fill in the component declarations -- first the _Task_Id field
9970 Make_Component_Declaration
(Loc
,
9971 Defining_Identifier
=>
9972 Make_Defining_Identifier
(Loc
, Name_uTask_Id
),
9973 Component_Definition
=>
9974 Make_Component_Definition
(Loc
,
9975 Aliased_Present
=> False,
9976 Subtype_Indication
=> New_Reference_To
(RTE
(RO_ST_Task_Id
),
9979 -- Declare static ATCB (that is, created by the expander) if we are
9980 -- using the Restricted run time.
9982 if Restricted_Profile
then
9984 Make_Component_Declaration
(Loc
,
9985 Defining_Identifier
=>
9986 Make_Defining_Identifier
(Loc
, Name_uATCB
),
9988 Component_Definition
=>
9989 Make_Component_Definition
(Loc
,
9990 Aliased_Present
=> True,
9991 Subtype_Indication
=> Make_Subtype_Indication
(Loc
,
9992 Subtype_Mark
=> New_Occurrence_Of
9993 (RTE
(RE_Ada_Task_Control_Block
), Loc
),
9996 Make_Index_Or_Discriminant_Constraint
(Loc
,
9998 New_List
(Make_Integer_Literal
(Loc
, 0)))))));
10002 -- Declare static stack (that is, created by the expander) if we are
10003 -- using the Restricted run time on a bare board configuration.
10005 if Restricted_Profile
10006 and then Preallocated_Stacks_On_Target
10008 -- First we need to extract the appropriate stack size
10010 Ent_Stack
:= Make_Defining_Identifier
(Loc
, Name_uStack
);
10012 if Present
(Taskdef
) and then Has_Storage_Size_Pragma
(Taskdef
) then
10014 Expr_N
: constant Node_Id
:=
10015 Expression
(First
(
10016 Pragma_Argument_Associations
(
10017 Find_Task_Or_Protected_Pragma
10018 (Taskdef
, Name_Storage_Size
))));
10019 Etyp
: constant Entity_Id
:= Etype
(Expr_N
);
10020 P
: constant Node_Id
:= Parent
(Expr_N
);
10023 -- The stack is defined inside the corresponding record.
10024 -- Therefore if the size of the stack is set by means of
10025 -- a discriminant, we must reference the discriminant of the
10026 -- corresponding record type.
10028 if Nkind
(Expr_N
) in N_Has_Entity
10029 and then Present
(Discriminal_Link
(Entity
(Expr_N
)))
10033 (CR_Discriminant
(Discriminal_Link
(Entity
(Expr_N
))),
10035 Set_Parent
(Task_Size
, P
);
10036 Set_Etype
(Task_Size
, Etyp
);
10037 Set_Analyzed
(Task_Size
);
10040 Task_Size
:= Relocate_Node
(Expr_N
);
10046 New_Reference_To
(RTE
(RE_Default_Stack_Size
), Loc
);
10049 Decl_Stack
:= Make_Component_Declaration
(Loc
,
10050 Defining_Identifier
=> Ent_Stack
,
10052 Component_Definition
=>
10053 Make_Component_Definition
(Loc
,
10054 Aliased_Present
=> True,
10055 Subtype_Indication
=> Make_Subtype_Indication
(Loc
,
10057 New_Occurrence_Of
(RTE
(RE_Storage_Array
), Loc
),
10060 Make_Index_Or_Discriminant_Constraint
(Loc
,
10061 Constraints
=> New_List
(Make_Range
(Loc
,
10062 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
10063 High_Bound
=> Convert_To
(RTE
(RE_Storage_Offset
),
10066 Append_To
(Cdecls
, Decl_Stack
);
10068 -- The appropriate alignment for the stack is ensured by the run-time
10069 -- code in charge of task creation.
10073 -- Add components for entry families
10075 Collect_Entry_Families
(Loc
, Cdecls
, Size_Decl
, Tasktyp
);
10077 -- Add the _Priority component if a Priority pragma is present
10079 if Present
(Taskdef
) and then Has_Priority_Pragma
(Taskdef
) then
10081 Prag
: constant Node_Id
:=
10082 Find_Task_Or_Protected_Pragma
(Taskdef
, Name_Priority
);
10086 Expr
:= First
(Pragma_Argument_Associations
(Prag
));
10088 if Nkind
(Expr
) = N_Pragma_Argument_Association
then
10089 Expr
:= Expression
(Expr
);
10092 Expr
:= New_Copy_Tree
(Expr
);
10094 -- Add conversion to proper type to do range check if required
10095 -- Note that for runtime units, we allow out of range interrupt
10096 -- priority values to be used in a priority pragma. This is for
10097 -- the benefit of some versions of System.Interrupts which use
10098 -- a special server task with maximum interrupt priority.
10100 if Pragma_Name
(Prag
) = Name_Priority
10101 and then not GNAT_Mode
10103 Rewrite
(Expr
, Convert_To
(RTE
(RE_Priority
), Expr
));
10105 Rewrite
(Expr
, Convert_To
(RTE
(RE_Any_Priority
), Expr
));
10109 Make_Component_Declaration
(Loc
,
10110 Defining_Identifier
=>
10111 Make_Defining_Identifier
(Loc
, Name_uPriority
),
10112 Component_Definition
=>
10113 Make_Component_Definition
(Loc
,
10114 Aliased_Present
=> False,
10115 Subtype_Indication
=> New_Reference_To
(Standard_Integer
,
10117 Expression
=> Expr
));
10121 -- Add the _Task_Size component if a Storage_Size pragma is present
10123 if Present
(Taskdef
)
10124 and then Has_Storage_Size_Pragma
(Taskdef
)
10127 Make_Component_Declaration
(Loc
,
10128 Defining_Identifier
=>
10129 Make_Defining_Identifier
(Loc
, Name_uSize
),
10131 Component_Definition
=>
10132 Make_Component_Definition
(Loc
,
10133 Aliased_Present
=> False,
10134 Subtype_Indication
=> New_Reference_To
(RTE
(RE_Size_Type
),
10138 Convert_To
(RTE
(RE_Size_Type
),
10140 Expression
(First
(
10141 Pragma_Argument_Associations
(
10142 Find_Task_Or_Protected_Pragma
10143 (Taskdef
, Name_Storage_Size
))))))));
10146 -- Add the _Task_Info component if a Task_Info pragma is present
10148 if Present
(Taskdef
) and then Has_Task_Info_Pragma
(Taskdef
) then
10150 Make_Component_Declaration
(Loc
,
10151 Defining_Identifier
=>
10152 Make_Defining_Identifier
(Loc
, Name_uTask_Info
),
10154 Component_Definition
=>
10155 Make_Component_Definition
(Loc
,
10156 Aliased_Present
=> False,
10157 Subtype_Indication
=>
10158 New_Reference_To
(RTE
(RE_Task_Info_Type
), Loc
)),
10160 Expression
=> New_Copy
(
10161 Expression
(First
(
10162 Pragma_Argument_Associations
(
10163 Find_Task_Or_Protected_Pragma
10164 (Taskdef
, Name_Task_Info
)))))));
10167 -- Add the _Relative_Deadline component if a Relative_Deadline pragma is
10168 -- present. If we are using a restricted run time this component will
10169 -- not be added (deadlines are not allowed by the Ravenscar profile).
10171 if not Restricted_Profile
10172 and then Present
(Taskdef
)
10173 and then Has_Relative_Deadline_Pragma
(Taskdef
)
10176 Make_Component_Declaration
(Loc
,
10177 Defining_Identifier
=>
10178 Make_Defining_Identifier
(Loc
, Name_uRelative_Deadline
),
10180 Component_Definition
=>
10181 Make_Component_Definition
(Loc
,
10182 Aliased_Present
=> False,
10183 Subtype_Indication
=>
10184 New_Reference_To
(RTE
(RE_Time_Span
), Loc
)),
10187 Convert_To
(RTE
(RE_Time_Span
),
10189 Expression
(First
(
10190 Pragma_Argument_Associations
(
10191 Find_Task_Or_Protected_Pragma
10192 (Taskdef
, Name_Relative_Deadline
))))))));
10195 Insert_After
(Size_Decl
, Rec_Decl
);
10197 -- Analyze the record declaration immediately after construction,
10198 -- because the initialization procedure is needed for single task
10199 -- declarations before the next entity is analyzed.
10201 Analyze
(Rec_Decl
);
10203 -- Create the declaration of the task body procedure
10205 Proc_Spec
:= Build_Task_Proc_Specification
(Tasktyp
);
10207 Make_Subprogram_Declaration
(Loc
,
10208 Specification
=> Proc_Spec
);
10210 Insert_After
(Rec_Decl
, Body_Decl
);
10212 -- The subprogram does not comes from source, so we have to indicate the
10213 -- need for debugging information explicitly.
10215 if Comes_From_Source
(Original_Node
(N
)) then
10216 Set_Debug_Info_Needed
(Defining_Entity
(Proc_Spec
));
10219 -- Ada 2005 (AI-345): Construct the primitive entry wrapper specs before
10220 -- the corresponding record has been frozen.
10222 if Ada_Version
>= Ada_05
then
10223 Build_Wrapper_Specs
(Loc
, Tasktyp
, Rec_Decl
);
10226 -- Ada 2005 (AI-345): We must defer freezing to allow further
10227 -- declaration of primitive subprograms covering task interfaces
10229 if Ada_Version
<= Ada_95
then
10231 -- Now we can freeze the corresponding record. This needs manually
10232 -- freezing, since it is really part of the task type, and the task
10233 -- type is frozen at this stage. We of course need the initialization
10234 -- procedure for this corresponding record type and we won't get it
10235 -- in time if we don't freeze now.
10238 L
: constant List_Id
:= Freeze_Entity
(Rec_Ent
, Loc
);
10240 if Is_Non_Empty_List
(L
) then
10241 Insert_List_After
(Body_Decl
, L
);
10246 -- Complete the expansion of access types to the current task type, if
10247 -- any were declared.
10249 Expand_Previous_Access_Type
(Tasktyp
);
10250 end Expand_N_Task_Type_Declaration
;
10252 -------------------------------
10253 -- Expand_N_Timed_Entry_Call --
10254 -------------------------------
10256 -- A timed entry call in normal case is not implemented using ATC mechanism
10257 -- anymore for efficiency reason.
10267 -- is expanded as follow:
10269 -- 1) When T.E is a task entry_call;
10273 -- X : Task_Entry_Index := <entry index>;
10274 -- DX : Duration := To_Duration (D);
10275 -- M : Delay_Mode := <discriminant>;
10276 -- P : parms := (parm, parm, parm);
10279 -- Timed_Protected_Entry_Call
10280 -- (<acceptor-task>, X, P'Address, DX, M, B);
10288 -- 2) When T.E is a protected entry_call;
10292 -- X : Protected_Entry_Index := <entry index>;
10293 -- DX : Duration := To_Duration (D);
10294 -- M : Delay_Mode := <discriminant>;
10295 -- P : parms := (parm, parm, parm);
10298 -- Timed_Protected_Entry_Call
10299 -- (<object>'unchecked_access, X, P'Address, DX, M, B);
10307 -- 3) Ada 2005 (AI-345): When T.E is a dispatching procedure call;
10310 -- B : Boolean := False;
10311 -- C : Ada.Tags.Prim_Op_Kind;
10312 -- DX : Duration := To_Duration (D)
10313 -- K : Ada.Tags.Tagged_Kind :=
10314 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
10315 -- M : Integer :=...;
10316 -- P : Parameters := (Param1 .. ParamN);
10320 -- if K = Ada.Tags.TK_Limited_Tagged then
10321 -- <dispatching-call>;
10322 -- <triggering-statements>
10326 -- Ada.Tags.Get_Offset_Index
10327 -- (Ada.Tags.Tag (<object>), DT_Position (<dispatching-call>));
10329 -- _Disp_Timed_Select (<object>, S, P'Address, DX, M, C, B);
10331 -- if C = POK_Protected_Entry
10332 -- or else C = POK_Task_Entry
10334 -- Param1 := P.Param1;
10336 -- ParamN := P.ParamN;
10340 -- if C = POK_Procedure
10341 -- or else C = POK_Protected_Procedure
10342 -- or else C = POK_Task_Procedure
10344 -- <dispatching-call>;
10347 -- <triggering-statements>
10349 -- <timed-statements>
10354 procedure Expand_N_Timed_Entry_Call
(N
: Node_Id
) is
10355 Loc
: constant Source_Ptr
:= Sloc
(N
);
10357 E_Call
: Node_Id
:=
10358 Entry_Call_Statement
(Entry_Call_Alternative
(N
));
10359 E_Stats
: constant List_Id
:=
10360 Statements
(Entry_Call_Alternative
(N
));
10361 D_Stat
: Node_Id
:=
10362 Delay_Statement
(Delay_Alternative
(N
));
10363 D_Stats
: constant List_Id
:=
10364 Statements
(Delay_Alternative
(N
));
10367 Blk_Typ
: Entity_Id
;
10369 Call_Ent
: Entity_Id
;
10370 Conc_Typ_Stmts
: List_Id
;
10374 D_Type
: Entity_Id
;
10380 Is_Disp_Select
: Boolean;
10381 Lim_Typ_Stmts
: List_Id
;
10390 B
: Entity_Id
; -- Call status flag
10391 C
: Entity_Id
; -- Call kind
10392 D
: Entity_Id
; -- Delay
10393 K
: Entity_Id
; -- Tagged kind
10394 M
: Entity_Id
; -- Delay mode
10395 P
: Entity_Id
; -- Parameter block
10396 S
: Entity_Id
; -- Primitive operation slot
10399 -- Under the Ravenscar profile, timed entry calls are excluded. An error
10400 -- was already reported on spec, so do not attempt to expand the call.
10402 if Restriction_Active
(No_Select_Statements
) then
10406 -- The arguments in the call may require dynamic allocation, and the
10407 -- call statement may have been transformed into a block. The block
10408 -- may contain additional declarations for internal entities, and the
10409 -- original call is found by sequential search.
10411 if Nkind
(E_Call
) = N_Block_Statement
then
10412 E_Call
:= First
(Statements
(Handled_Statement_Sequence
(E_Call
)));
10413 while not Nkind_In
(E_Call
, N_Procedure_Call_Statement
,
10414 N_Entry_Call_Statement
)
10421 Ada_Version
>= Ada_05
10422 and then Nkind
(E_Call
) = N_Procedure_Call_Statement
;
10424 if Is_Disp_Select
then
10425 Extract_Dispatching_Call
(E_Call
, Call_Ent
, Obj
, Actuals
, Formals
);
10431 -- B : Boolean := False;
10433 B
:= Build_B
(Loc
, Decls
);
10436 -- C : Ada.Tags.Prim_Op_Kind;
10438 C
:= Build_C
(Loc
, Decls
);
10440 -- Because the analysis of all statements was disabled, manually
10441 -- analyze the delay statement.
10444 D_Stat
:= Original_Node
(D_Stat
);
10447 -- Build an entry call using Simple_Entry_Call
10449 Extract_Entry
(E_Call
, Concval
, Ename
, Index
);
10450 Build_Simple_Entry_Call
(E_Call
, Concval
, Ename
, Index
);
10452 Decls
:= Declarations
(E_Call
);
10453 Stmts
:= Statements
(Handled_Statement_Sequence
(E_Call
));
10462 B
:= Make_Defining_Identifier
(Loc
, Name_uB
);
10465 Make_Object_Declaration
(Loc
,
10466 Defining_Identifier
=>
10468 Object_Definition
=>
10469 New_Reference_To
(Standard_Boolean
, Loc
)));
10472 -- Duration and mode processing
10474 D_Type
:= Base_Type
(Etype
(Expression
(D_Stat
)));
10476 -- Use the type of the delay expression (Calendar or Real_Time) to
10477 -- generate the appropriate conversion.
10479 if Nkind
(D_Stat
) = N_Delay_Relative_Statement
then
10480 D_Disc
:= Make_Integer_Literal
(Loc
, 0);
10481 D_Conv
:= Relocate_Node
(Expression
(D_Stat
));
10483 elsif Is_RTE
(D_Type
, RO_CA_Time
) then
10484 D_Disc
:= Make_Integer_Literal
(Loc
, 1);
10485 D_Conv
:= Make_Function_Call
(Loc
,
10486 New_Reference_To
(RTE
(RO_CA_To_Duration
), Loc
),
10487 New_List
(New_Copy
(Expression
(D_Stat
))));
10489 else pragma Assert
(Is_RTE
(D_Type
, RO_RT_Time
));
10490 D_Disc
:= Make_Integer_Literal
(Loc
, 2);
10491 D_Conv
:= Make_Function_Call
(Loc
,
10492 New_Reference_To
(RTE
(RO_RT_To_Duration
), Loc
),
10493 New_List
(New_Copy
(Expression
(D_Stat
))));
10496 D
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('D'));
10502 Make_Object_Declaration
(Loc
,
10503 Defining_Identifier
=>
10505 Object_Definition
=>
10506 New_Reference_To
(Standard_Duration
, Loc
)));
10508 M
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('M'));
10511 -- M : Integer := (0 | 1 | 2);
10514 Make_Object_Declaration
(Loc
,
10515 Defining_Identifier
=>
10517 Object_Definition
=>
10518 New_Reference_To
(Standard_Integer
, Loc
),
10522 -- Do the assignment at this stage only because the evaluation of the
10523 -- expression must not occur before (see ACVC C97302A).
10526 Make_Assignment_Statement
(Loc
,
10528 New_Reference_To
(D
, Loc
),
10532 -- Parameter block processing
10534 -- Manually create the parameter block for dispatching calls. In the
10535 -- case of entries, the block has already been created during the call
10536 -- to Build_Simple_Entry_Call.
10538 if Is_Disp_Select
then
10540 -- Tagged kind processing, generate:
10541 -- K : Ada.Tags.Tagged_Kind :=
10542 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag <object>));
10544 K
:= Build_K
(Loc
, Decls
, Obj
);
10546 Blk_Typ
:= Build_Parameter_Block
(Loc
, Actuals
, Formals
, Decls
);
10547 P
:= Parameter_Block_Pack
10548 (Loc
, Blk_Typ
, Actuals
, Formals
, Decls
, Stmts
);
10550 -- Dispatch table slot processing, generate:
10553 S
:= Build_S
(Loc
, Decls
);
10556 -- S := Ada.Tags.Get_Offset_Index
10557 -- (Ada.Tags.Tag (<object>), DT_Position (Call_Ent));
10560 New_List
(Build_S_Assignment
(Loc
, S
, Obj
, Call_Ent
));
10563 -- _Disp_Timed_Select (<object>, S, P'Address, D, M, C, B);
10565 -- where Obj is the controlling formal parameter, S is the dispatch
10566 -- table slot number of the dispatching operation, P is the wrapped
10567 -- parameter block, D is the duration, M is the duration mode, C is
10568 -- the call kind and B is the call status.
10570 Params
:= New_List
;
10572 Append_To
(Params
, New_Copy_Tree
(Obj
));
10573 Append_To
(Params
, New_Reference_To
(S
, Loc
));
10574 Append_To
(Params
, Make_Attribute_Reference
(Loc
,
10575 Prefix
=> New_Reference_To
(P
, Loc
),
10576 Attribute_Name
=> Name_Address
));
10577 Append_To
(Params
, New_Reference_To
(D
, Loc
));
10578 Append_To
(Params
, New_Reference_To
(M
, Loc
));
10579 Append_To
(Params
, New_Reference_To
(C
, Loc
));
10580 Append_To
(Params
, New_Reference_To
(B
, Loc
));
10582 Append_To
(Conc_Typ_Stmts
,
10583 Make_Procedure_Call_Statement
(Loc
,
10586 Find_Prim_Op
(Etype
(Etype
(Obj
)),
10587 Name_uDisp_Timed_Select
),
10589 Parameter_Associations
=>
10593 -- if C = POK_Protected_Entry
10594 -- or else C = POK_Task_Entry
10596 -- Param1 := P.Param1;
10598 -- ParamN := P.ParamN;
10601 Unpack
:= Parameter_Block_Unpack
(Loc
, P
, Actuals
, Formals
);
10603 -- Generate the if statement only when the packed parameters need
10604 -- explicit assignments to their corresponding actuals.
10606 if Present
(Unpack
) then
10607 Append_To
(Conc_Typ_Stmts
,
10608 Make_If_Statement
(Loc
,
10615 New_Reference_To
(C
, Loc
),
10617 New_Reference_To
(RTE
(
10618 RE_POK_Protected_Entry
), Loc
)),
10622 New_Reference_To
(C
, Loc
),
10624 New_Reference_To
(RTE
(RE_POK_Task_Entry
), Loc
))),
10633 -- if C = POK_Procedure
10634 -- or else C = POK_Protected_Procedure
10635 -- or else C = POK_Task_Procedure
10637 -- <dispatching-call>
10639 -- <triggering-statements>
10641 -- <timed-statements>
10644 N_Stats
:= New_Copy_List_Tree
(E_Stats
);
10646 Prepend_To
(N_Stats
,
10647 Make_If_Statement
(Loc
,
10654 New_Reference_To
(C
, Loc
),
10656 New_Reference_To
(RTE
(RE_POK_Procedure
), Loc
)),
10662 New_Reference_To
(C
, Loc
),
10664 New_Reference_To
(RTE
(
10665 RE_POK_Protected_Procedure
), Loc
)),
10669 New_Reference_To
(C
, Loc
),
10671 New_Reference_To
(RTE
(
10672 RE_POK_Task_Procedure
), Loc
)))),
10675 New_List
(E_Call
)));
10677 Append_To
(Conc_Typ_Stmts
,
10678 Make_If_Statement
(Loc
,
10679 Condition
=> New_Reference_To
(B
, Loc
),
10680 Then_Statements
=> N_Stats
,
10681 Else_Statements
=> D_Stats
));
10684 -- <dispatching-call>;
10685 -- <triggering-statements>
10687 Lim_Typ_Stmts
:= New_Copy_List_Tree
(E_Stats
);
10688 Prepend_To
(Lim_Typ_Stmts
, New_Copy_Tree
(E_Call
));
10691 -- if K = Ada.Tags.TK_Limited_Tagged then
10698 Make_If_Statement
(Loc
,
10702 New_Reference_To
(K
, Loc
),
10704 New_Reference_To
(RTE
(RE_TK_Limited_Tagged
), Loc
)),
10713 -- Skip assignments to temporaries created for in-out parameters.
10714 -- This makes unwarranted assumptions about the shape of the expanded
10715 -- tree for the call, and should be cleaned up ???
10717 Stmt
:= First
(Stmts
);
10718 while Nkind
(Stmt
) /= N_Procedure_Call_Statement
loop
10722 -- Do the assignment at this stage only because the evaluation
10723 -- of the expression must not occur before (see ACVC C97302A).
10725 Insert_Before
(Stmt
,
10726 Make_Assignment_Statement
(Loc
,
10727 Name
=> New_Reference_To
(D
, Loc
),
10728 Expression
=> D_Conv
));
10731 Params
:= Parameter_Associations
(Call
);
10733 -- For a protected type, we build a Timed_Protected_Entry_Call
10735 if Is_Protected_Type
(Etype
(Concval
)) then
10737 -- Create a new call statement
10739 Param
:= First
(Params
);
10740 while Present
(Param
)
10741 and then not Is_RTE
(Etype
(Param
), RE_Call_Modes
)
10746 Dummy
:= Remove_Next
(Next
(Param
));
10748 -- Remove garbage is following the Cancel_Param if present
10750 Dummy
:= Next
(Param
);
10752 -- Remove the mode of the Protected_Entry_Call call, then remove
10753 -- the Communication_Block of the Protected_Entry_Call call, and
10754 -- finally add Duration and a Delay_Mode parameter
10756 pragma Assert
(Present
(Param
));
10757 Rewrite
(Param
, New_Reference_To
(D
, Loc
));
10759 Rewrite
(Dummy
, New_Reference_To
(M
, Loc
));
10761 -- Add a Boolean flag for successful entry call
10763 Append_To
(Params
, New_Reference_To
(B
, Loc
));
10765 case Corresponding_Runtime_Package
(Etype
(Concval
)) is
10766 when System_Tasking_Protected_Objects_Entries
=>
10768 Make_Procedure_Call_Statement
(Loc
,
10771 (RTE
(RE_Timed_Protected_Entry_Call
), Loc
),
10772 Parameter_Associations
=> Params
));
10774 when System_Tasking_Protected_Objects_Single_Entry
=>
10775 Param
:= First
(Params
);
10776 while Present
(Param
)
10778 Is_RTE
(Etype
(Param
), RE_Protected_Entry_Index
)
10786 Make_Procedure_Call_Statement
(Loc
,
10787 Name
=> New_Reference_To
(
10788 RTE
(RE_Timed_Protected_Single_Entry_Call
), Loc
),
10789 Parameter_Associations
=> Params
));
10792 raise Program_Error
;
10795 -- For the task case, build a Timed_Task_Entry_Call
10798 -- Create a new call statement
10800 Append_To
(Params
, New_Reference_To
(D
, Loc
));
10801 Append_To
(Params
, New_Reference_To
(M
, Loc
));
10802 Append_To
(Params
, New_Reference_To
(B
, Loc
));
10805 Make_Procedure_Call_Statement
(Loc
,
10807 New_Reference_To
(RTE
(RE_Timed_Task_Entry_Call
), Loc
),
10808 Parameter_Associations
=> Params
));
10812 Make_Implicit_If_Statement
(N
,
10813 Condition
=> New_Reference_To
(B
, Loc
),
10814 Then_Statements
=> E_Stats
,
10815 Else_Statements
=> D_Stats
));
10819 Make_Block_Statement
(Loc
,
10820 Declarations
=> Decls
,
10821 Handled_Statement_Sequence
=>
10822 Make_Handled_Sequence_Of_Statements
(Loc
, Stmts
)));
10825 end Expand_N_Timed_Entry_Call
;
10827 ----------------------------------------
10828 -- Expand_Protected_Body_Declarations --
10829 ----------------------------------------
10831 procedure Expand_Protected_Body_Declarations
10833 Spec_Id
: Entity_Id
)
10836 if No_Run_Time_Mode
then
10837 Error_Msg_CRT
("protected body", N
);
10840 elsif Expander_Active
then
10842 -- Associate discriminals with the first subprogram or entry body to
10845 if Present
(First_Protected_Operation
(Declarations
(N
))) then
10846 Set_Discriminals
(Parent
(Spec_Id
));
10849 end Expand_Protected_Body_Declarations
;
10851 -------------------------
10852 -- External_Subprogram --
10853 -------------------------
10855 function External_Subprogram
(E
: Entity_Id
) return Entity_Id
is
10856 Subp
: constant Entity_Id
:= Protected_Body_Subprogram
(E
);
10859 -- The internal and external subprograms follow each other on the entity
10860 -- chain. Note that previously private operations had no separate
10861 -- external subprogram. We now create one in all cases, because a
10862 -- private operation may actually appear in an external call, through
10863 -- a 'Access reference used for a callback.
10865 -- If the operation is a function that returns an anonymous access type,
10866 -- the corresponding itype appears before the operation, and must be
10869 -- This mechanism is fragile, there should be a real link between the
10870 -- two versions of the operation, but there is no place to put it ???
10872 if Is_Access_Type
(Next_Entity
(Subp
)) then
10873 return Next_Entity
(Next_Entity
(Subp
));
10875 return Next_Entity
(Subp
);
10877 end External_Subprogram
;
10879 ------------------------------
10880 -- Extract_Dispatching_Call --
10881 ------------------------------
10883 procedure Extract_Dispatching_Call
10885 Call_Ent
: out Entity_Id
;
10886 Object
: out Entity_Id
;
10887 Actuals
: out List_Id
;
10888 Formals
: out List_Id
)
10890 Call_Nam
: Node_Id
;
10893 pragma Assert
(Nkind
(N
) = N_Procedure_Call_Statement
);
10895 if Present
(Original_Node
(N
)) then
10896 Call_Nam
:= Name
(Original_Node
(N
));
10898 Call_Nam
:= Name
(N
);
10901 -- Retrieve the name of the dispatching procedure. It contains the
10902 -- dispatch table slot number.
10905 case Nkind
(Call_Nam
) is
10906 when N_Identifier
=>
10909 when N_Selected_Component
=>
10910 Call_Nam
:= Selector_Name
(Call_Nam
);
10913 raise Program_Error
;
10918 Actuals
:= Parameter_Associations
(N
);
10919 Call_Ent
:= Entity
(Call_Nam
);
10920 Formals
:= Parameter_Specifications
(Parent
(Call_Ent
));
10921 Object
:= First
(Actuals
);
10923 if Present
(Original_Node
(Object
)) then
10924 Object
:= Original_Node
(Object
);
10926 end Extract_Dispatching_Call
;
10928 -------------------
10929 -- Extract_Entry --
10930 -------------------
10932 procedure Extract_Entry
10934 Concval
: out Node_Id
;
10935 Ename
: out Node_Id
;
10936 Index
: out Node_Id
)
10938 Nam
: constant Node_Id
:= Name
(N
);
10941 -- For a simple entry, the name is a selected component, with the
10942 -- prefix being the task value, and the selector being the entry.
10944 if Nkind
(Nam
) = N_Selected_Component
then
10945 Concval
:= Prefix
(Nam
);
10946 Ename
:= Selector_Name
(Nam
);
10949 -- For a member of an entry family, the name is an indexed component
10950 -- where the prefix is a selected component, whose prefix in turn is
10951 -- the task value, and whose selector is the entry family. The single
10952 -- expression in the expressions list of the indexed component is the
10953 -- subscript for the family.
10955 else pragma Assert
(Nkind
(Nam
) = N_Indexed_Component
);
10956 Concval
:= Prefix
(Prefix
(Nam
));
10957 Ename
:= Selector_Name
(Prefix
(Nam
));
10958 Index
:= First
(Expressions
(Nam
));
10962 -------------------
10963 -- Family_Offset --
10964 -------------------
10966 function Family_Offset
10971 Cap
: Boolean) return Node_Id
10977 function Convert_Discriminant_Ref
(Bound
: Node_Id
) return Node_Id
;
10978 -- If one of the bounds is a reference to a discriminant, replace with
10979 -- corresponding discriminal of type. Within the body of a task retrieve
10980 -- the renamed discriminant by simple visibility, using its generated
10981 -- name. Within a protected object, find the original discriminant and
10982 -- replace it with the discriminal of the current protected operation.
10984 ------------------------------
10985 -- Convert_Discriminant_Ref --
10986 ------------------------------
10988 function Convert_Discriminant_Ref
(Bound
: Node_Id
) return Node_Id
is
10989 Loc
: constant Source_Ptr
:= Sloc
(Bound
);
10994 if Is_Entity_Name
(Bound
)
10995 and then Ekind
(Entity
(Bound
)) = E_Discriminant
10997 if Is_Task_Type
(Ttyp
)
10998 and then Has_Completion
(Ttyp
)
11000 B
:= Make_Identifier
(Loc
, Chars
(Entity
(Bound
)));
11001 Find_Direct_Name
(B
);
11003 elsif Is_Protected_Type
(Ttyp
) then
11004 D
:= First_Discriminant
(Ttyp
);
11005 while Chars
(D
) /= Chars
(Entity
(Bound
)) loop
11006 Next_Discriminant
(D
);
11009 B
:= New_Reference_To
(Discriminal
(D
), Loc
);
11012 B
:= New_Reference_To
(Discriminal
(Entity
(Bound
)), Loc
);
11015 elsif Nkind
(Bound
) = N_Attribute_Reference
then
11019 B
:= New_Copy_Tree
(Bound
);
11023 Make_Attribute_Reference
(Loc
,
11024 Attribute_Name
=> Name_Pos
,
11025 Prefix
=> New_Occurrence_Of
(Etype
(Bound
), Loc
),
11026 Expressions
=> New_List
(B
));
11027 end Convert_Discriminant_Ref
;
11029 -- Start of processing for Family_Offset
11032 Real_Hi
:= Convert_Discriminant_Ref
(Hi
);
11033 Real_Lo
:= Convert_Discriminant_Ref
(Lo
);
11036 if Is_Task_Type
(Ttyp
) then
11037 Ityp
:= RTE
(RE_Task_Entry_Index
);
11039 Ityp
:= RTE
(RE_Protected_Entry_Index
);
11043 Make_Attribute_Reference
(Loc
,
11044 Prefix
=> New_Reference_To
(Ityp
, Loc
),
11045 Attribute_Name
=> Name_Min
,
11046 Expressions
=> New_List
(
11048 Make_Integer_Literal
(Loc
, Entry_Family_Bound
- 1)));
11051 Make_Attribute_Reference
(Loc
,
11052 Prefix
=> New_Reference_To
(Ityp
, Loc
),
11053 Attribute_Name
=> Name_Max
,
11054 Expressions
=> New_List
(
11056 Make_Integer_Literal
(Loc
, -Entry_Family_Bound
)));
11059 return Make_Op_Subtract
(Loc
, Real_Hi
, Real_Lo
);
11066 function Family_Size
11071 Cap
: Boolean) return Node_Id
11076 if Is_Task_Type
(Ttyp
) then
11077 Ityp
:= RTE
(RE_Task_Entry_Index
);
11079 Ityp
:= RTE
(RE_Protected_Entry_Index
);
11083 Make_Attribute_Reference
(Loc
,
11084 Prefix
=> New_Reference_To
(Ityp
, Loc
),
11085 Attribute_Name
=> Name_Max
,
11086 Expressions
=> New_List
(
11089 Family_Offset
(Loc
, Hi
, Lo
, Ttyp
, Cap
),
11091 Make_Integer_Literal
(Loc
, 1)),
11092 Make_Integer_Literal
(Loc
, 0)));
11095 -----------------------------------
11096 -- Find_Task_Or_Protected_Pragma --
11097 -----------------------------------
11099 function Find_Task_Or_Protected_Pragma
11101 P
: Name_Id
) return Node_Id
11106 N
:= First
(Visible_Declarations
(T
));
11107 while Present
(N
) loop
11108 if Nkind
(N
) = N_Pragma
then
11109 if Pragma_Name
(N
) = P
then
11112 elsif P
= Name_Priority
11113 and then Pragma_Name
(N
) = Name_Interrupt_Priority
11126 N
:= First
(Private_Declarations
(T
));
11127 while Present
(N
) loop
11128 if Nkind
(N
) = N_Pragma
then
11129 if Pragma_Name
(N
) = P
then
11132 elsif P
= Name_Priority
11133 and then Pragma_Name
(N
) = Name_Interrupt_Priority
11146 raise Program_Error
;
11147 end Find_Task_Or_Protected_Pragma
;
11149 -------------------------------
11150 -- First_Protected_Operation --
11151 -------------------------------
11153 function First_Protected_Operation
(D
: List_Id
) return Node_Id
is
11154 First_Op
: Node_Id
;
11157 First_Op
:= First
(D
);
11158 while Present
(First_Op
)
11159 and then not Nkind_In
(First_Op
, N_Subprogram_Body
, N_Entry_Body
)
11165 end First_Protected_Operation
;
11167 ---------------------------------------
11168 -- Install_Private_Data_Declarations --
11169 ---------------------------------------
11171 procedure Install_Private_Data_Declarations
11173 Spec_Id
: Entity_Id
;
11174 Conc_Typ
: Entity_Id
;
11175 Body_Nod
: Node_Id
;
11177 Barrier
: Boolean := False;
11178 Family
: Boolean := False)
11180 Is_Protected
: constant Boolean := Is_Protected_Type
(Conc_Typ
);
11183 Insert_Node
: Node_Id
:= Empty
;
11184 Obj_Ent
: Entity_Id
;
11186 procedure Add
(Decl
: Node_Id
);
11187 -- Add a single declaration after Insert_Node. If this is the first
11188 -- addition, Decl is added to the front of Decls and it becomes the
11191 function Replace_Bound
(Bound
: Node_Id
) return Node_Id
;
11192 -- The bounds of an entry index may depend on discriminants, create a
11193 -- reference to the corresponding prival. Otherwise return a duplicate
11194 -- of the original bound.
11200 procedure Add
(Decl
: Node_Id
) is
11202 if No
(Insert_Node
) then
11203 Prepend_To
(Decls
, Decl
);
11205 Insert_After
(Insert_Node
, Decl
);
11208 Insert_Node
:= Decl
;
11211 --------------------------
11212 -- Replace_Discriminant --
11213 --------------------------
11215 function Replace_Bound
(Bound
: Node_Id
) return Node_Id
is
11217 if Nkind
(Bound
) = N_Identifier
11218 and then Is_Discriminal
(Entity
(Bound
))
11220 return Make_Identifier
(Loc
, Chars
(Entity
(Bound
)));
11222 return Duplicate_Subexpr
(Bound
);
11226 -- Start of processing for Install_Private_Data_Declarations
11229 -- Step 1: Retrieve the concurrent object entity. Obj_Ent can denote
11230 -- formal parameter _O, _object or _task depending on the context.
11232 Obj_Ent
:= Concurrent_Object
(Spec_Id
, Conc_Typ
);
11234 -- Special processing of _O for barrier functions, protected entries
11241 (Ekind
(Spec_Id
) = E_Entry
11242 or else Ekind
(Spec_Id
) = E_Entry_Family
))
11245 Conc_Rec
: constant Entity_Id
:=
11246 Corresponding_Record_Type
(Conc_Typ
);
11247 Typ_Id
: constant Entity_Id
:=
11248 Make_Defining_Identifier
(Loc
,
11249 New_External_Name
(Chars
(Conc_Rec
), 'P'));
11252 -- type prot_typVP is access prot_typV;
11255 Make_Full_Type_Declaration
(Loc
,
11256 Defining_Identifier
=> Typ_Id
,
11258 Make_Access_To_Object_Definition
(Loc
,
11259 Subtype_Indication
=>
11260 New_Reference_To
(Conc_Rec
, Loc
)));
11264 -- _object : prot_typVP := prot_typV (_O);
11267 Make_Object_Declaration
(Loc
,
11268 Defining_Identifier
=>
11269 Make_Defining_Identifier
(Loc
, Name_uObject
),
11270 Object_Definition
=> New_Reference_To
(Typ_Id
, Loc
),
11272 Unchecked_Convert_To
(Typ_Id
,
11273 New_Reference_To
(Obj_Ent
, Loc
)));
11276 -- Set the reference to the concurrent object
11278 Obj_Ent
:= Defining_Identifier
(Decl
);
11282 -- Step 2: Create the Protection object and build its declaration for
11283 -- any protected entry (family) of subprogram.
11285 if Is_Protected
then
11287 Prot_Ent
: constant Entity_Id
:=
11288 Make_Defining_Identifier
(Loc
,
11289 New_Internal_Name
('R'));
11293 Set_Protection_Object
(Spec_Id
, Prot_Ent
);
11295 -- Determine the proper protection type
11297 if Has_Attach_Handler
(Conc_Typ
)
11298 and then not Restricted_Profile
11300 Prot_Typ
:= RE_Static_Interrupt_Protection
;
11302 elsif Has_Interrupt_Handler
(Conc_Typ
) then
11303 Prot_Typ
:= RE_Dynamic_Interrupt_Protection
;
11305 -- The type has explicit entries or generated primitive entry
11308 elsif Has_Entries
(Conc_Typ
)
11310 (Ada_Version
>= Ada_05
11311 and then Present
(Interface_List
(Parent
(Conc_Typ
))))
11313 case Corresponding_Runtime_Package
(Conc_Typ
) is
11314 when System_Tasking_Protected_Objects_Entries
=>
11315 Prot_Typ
:= RE_Protection_Entries
;
11317 when System_Tasking_Protected_Objects_Single_Entry
=>
11318 Prot_Typ
:= RE_Protection_Entry
;
11321 raise Program_Error
;
11325 Prot_Typ
:= RE_Protection
;
11329 -- conc_typR : protection_typ renames _object._object;
11332 Make_Object_Renaming_Declaration
(Loc
,
11333 Defining_Identifier
=> Prot_Ent
,
11335 New_Reference_To
(RTE
(Prot_Typ
), Loc
),
11337 Make_Selected_Component
(Loc
,
11339 New_Reference_To
(Obj_Ent
, Loc
),
11341 Make_Identifier
(Loc
, Name_uObject
)));
11346 -- Step 3: Add discriminant renamings (if any)
11348 if Has_Discriminants
(Conc_Typ
) then
11353 D
:= First_Discriminant
(Conc_Typ
);
11354 while Present
(D
) loop
11356 -- Adjust the source location
11358 Set_Sloc
(Discriminal
(D
), Loc
);
11361 -- discr_name : discr_typ renames _object.discr_name;
11363 -- discr_name : discr_typ renames _task.discr_name;
11366 Make_Object_Renaming_Declaration
(Loc
,
11367 Defining_Identifier
=> Discriminal
(D
),
11368 Subtype_Mark
=> New_Reference_To
(Etype
(D
), Loc
),
11370 Make_Selected_Component
(Loc
,
11371 Prefix
=> New_Reference_To
(Obj_Ent
, Loc
),
11372 Selector_Name
=> Make_Identifier
(Loc
, Chars
(D
))));
11375 Next_Discriminant
(D
);
11380 -- Step 4: Add private component renamings (if any)
11382 if Is_Protected
then
11383 Def
:= Protected_Definition
(Parent
(Conc_Typ
));
11385 if Present
(Private_Declarations
(Def
)) then
11388 Comp_Id
: Entity_Id
;
11389 Decl_Id
: Entity_Id
;
11392 Comp
:= First
(Private_Declarations
(Def
));
11393 while Present
(Comp
) loop
11394 if Nkind
(Comp
) = N_Component_Declaration
then
11395 Comp_Id
:= Defining_Identifier
(Comp
);
11397 Make_Defining_Identifier
(Loc
, Chars
(Comp_Id
));
11399 -- Minimal decoration
11401 if Ekind
(Spec_Id
) = E_Function
then
11402 Set_Ekind
(Decl_Id
, E_Constant
);
11404 Set_Ekind
(Decl_Id
, E_Variable
);
11407 Set_Prival
(Comp_Id
, Decl_Id
);
11408 Set_Prival_Link
(Decl_Id
, Comp_Id
);
11409 Set_Is_Aliased
(Decl_Id
, Is_Aliased
(Comp_Id
));
11412 -- comp_name : comp_typ renames _object.comp_name;
11415 Make_Object_Renaming_Declaration
(Loc
,
11416 Defining_Identifier
=> Decl_Id
,
11418 New_Reference_To
(Etype
(Comp_Id
), Loc
),
11420 Make_Selected_Component
(Loc
,
11422 New_Reference_To
(Obj_Ent
, Loc
),
11424 Make_Identifier
(Loc
, Chars
(Comp_Id
))));
11434 -- Step 5: Add the declaration of the entry index and the associated
11435 -- type for barrier functions and entry families.
11437 if (Barrier
and then Family
)
11438 or else Ekind
(Spec_Id
) = E_Entry_Family
11441 E
: constant Entity_Id
:= Index_Object
(Spec_Id
);
11442 Index
: constant Entity_Id
:=
11443 Defining_Identifier
(
11444 Entry_Index_Specification
(
11445 Entry_Body_Formal_Part
(Body_Nod
)));
11446 Index_Con
: constant Entity_Id
:=
11447 Make_Defining_Identifier
(Loc
, Chars
(Index
));
11449 Index_Typ
: Entity_Id
;
11453 -- Minimal decoration
11455 Set_Ekind
(Index_Con
, E_Constant
);
11456 Set_Entry_Index_Constant
(Index
, Index_Con
);
11457 Set_Discriminal_Link
(Index_Con
, Index
);
11459 -- Retrieve the bounds of the entry family
11461 High
:= Type_High_Bound
(Etype
(Index
));
11462 Low
:= Type_Low_Bound
(Etype
(Index
));
11464 -- In the simple case the entry family is given by a subtype
11465 -- mark and the index constant has the same type.
11467 if Is_Entity_Name
(Original_Node
(
11468 Discrete_Subtype_Definition
(Parent
(Index
))))
11470 Index_Typ
:= Etype
(Index
);
11472 -- Otherwise a new subtype declaration is required
11475 High
:= Replace_Bound
(High
);
11476 Low
:= Replace_Bound
(Low
);
11479 Make_Defining_Identifier
(Loc
, New_Internal_Name
('J'));
11482 -- subtype Jnn is <Etype of Index> range Low .. High;
11485 Make_Subtype_Declaration
(Loc
,
11486 Defining_Identifier
=> Index_Typ
,
11487 Subtype_Indication
=>
11488 Make_Subtype_Indication
(Loc
,
11490 New_Reference_To
(Base_Type
(Etype
(Index
)), Loc
),
11492 Make_Range_Constraint
(Loc
,
11493 Range_Expression
=>
11494 Make_Range
(Loc
, Low
, High
))));
11498 Set_Etype
(Index_Con
, Index_Typ
);
11500 -- Create the object which designates the index:
11501 -- J : constant Jnn :=
11502 -- Jnn'Val (_E - <index expr> + Jnn'Pos (Jnn'First));
11504 -- where Jnn is the subtype created above or the original type of
11505 -- the index, _E is a formal of the protected body subprogram and
11506 -- <index expr> is the index of the first family member.
11509 Make_Object_Declaration
(Loc
,
11510 Defining_Identifier
=> Index_Con
,
11511 Constant_Present
=> True,
11512 Object_Definition
=>
11513 New_Reference_To
(Index_Typ
, Loc
),
11516 Make_Attribute_Reference
(Loc
,
11518 New_Reference_To
(Index_Typ
, Loc
),
11519 Attribute_Name
=> Name_Val
,
11521 Expressions
=> New_List
(
11525 Make_Op_Subtract
(Loc
,
11527 New_Reference_To
(E
, Loc
),
11529 Entry_Index_Expression
(Loc
,
11530 Defining_Identifier
(Body_Nod
),
11534 Make_Attribute_Reference
(Loc
,
11536 New_Reference_To
(Index_Typ
, Loc
),
11537 Attribute_Name
=> Name_Pos
,
11538 Expressions
=> New_List
(
11539 Make_Attribute_Reference
(Loc
,
11541 New_Reference_To
(Index_Typ
, Loc
),
11542 Attribute_Name
=> Name_First
)))))));
11546 end Install_Private_Data_Declarations
;
11548 ---------------------------------
11549 -- Is_Potentially_Large_Family --
11550 ---------------------------------
11552 function Is_Potentially_Large_Family
11553 (Base_Index
: Entity_Id
;
11554 Conctyp
: Entity_Id
;
11556 Hi
: Node_Id
) return Boolean
11559 return Scope
(Base_Index
) = Standard_Standard
11560 and then Base_Index
= Base_Type
(Standard_Integer
)
11561 and then Has_Discriminants
(Conctyp
)
11563 (Discriminant_Default_Value
(First_Discriminant
(Conctyp
)))
11565 (Denotes_Discriminant
(Lo
, True)
11566 or else Denotes_Discriminant
(Hi
, True));
11567 end Is_Potentially_Large_Family
;
11569 -------------------------------------
11570 -- Is_Private_Primitive_Subprogram --
11571 -------------------------------------
11573 function Is_Private_Primitive_Subprogram
(Id
: Entity_Id
) return Boolean is
11576 (Ekind
(Id
) = E_Function
or else Ekind
(Id
) = E_Procedure
)
11577 and then Is_Private_Primitive
(Id
);
11578 end Is_Private_Primitive_Subprogram
;
11584 function Index_Object
(Spec_Id
: Entity_Id
) return Entity_Id
is
11585 Bod_Subp
: constant Entity_Id
:= Protected_Body_Subprogram
(Spec_Id
);
11586 Formal
: Entity_Id
;
11589 Formal
:= First_Formal
(Bod_Subp
);
11590 while Present
(Formal
) loop
11592 -- Look for formal parameter _E
11594 if Chars
(Formal
) = Name_uE
then
11598 Next_Formal
(Formal
);
11601 -- A protected body subprogram should always have the parameter in
11604 raise Program_Error
;
11607 --------------------------------
11608 -- Make_Initialize_Protection --
11609 --------------------------------
11611 function Make_Initialize_Protection
11612 (Protect_Rec
: Entity_Id
) return List_Id
11614 Loc
: constant Source_Ptr
:= Sloc
(Protect_Rec
);
11618 Ptyp
: constant Node_Id
:=
11619 Corresponding_Concurrent_Type
(Protect_Rec
);
11621 L
: constant List_Id
:= New_List
;
11622 Has_Entry
: constant Boolean := Has_Entries
(Ptyp
);
11623 Restricted
: constant Boolean := Restricted_Profile
;
11626 -- We may need two calls to properly initialize the object, one to
11627 -- Initialize_Protection, and possibly one to Install_Handlers if we
11628 -- have a pragma Attach_Handler.
11630 -- Get protected declaration. In the case of a task type declaration,
11631 -- this is simply the parent of the protected type entity. In the single
11632 -- protected object declaration, this parent will be the implicit type,
11633 -- and we can find the corresponding single protected object declaration
11634 -- by searching forward in the declaration list in the tree.
11636 -- Is the test for N_Single_Protected_Declaration needed here??? Nodes
11637 -- of this type should have been removed during semantic analysis.
11639 Pdec
:= Parent
(Ptyp
);
11640 while not Nkind_In
(Pdec
, N_Protected_Type_Declaration
,
11641 N_Single_Protected_Declaration
)
11646 -- Now we can find the object definition from this declaration
11648 Pdef
:= Protected_Definition
(Pdec
);
11650 -- Build the parameter list for the call. Note that _Init is the name
11651 -- of the formal for the object to be initialized, which is the task
11652 -- value record itself.
11656 -- Object parameter. This is a pointer to the object of type
11657 -- Protection used by the GNARL to control the protected object.
11660 Make_Attribute_Reference
(Loc
,
11662 Make_Selected_Component
(Loc
,
11663 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
11664 Selector_Name
=> Make_Identifier
(Loc
, Name_uObject
)),
11665 Attribute_Name
=> Name_Unchecked_Access
));
11667 -- Priority parameter. Set to Unspecified_Priority unless there is a
11668 -- priority pragma, in which case we take the value from the pragma,
11669 -- or there is an interrupt pragma and no priority pragma, and we
11670 -- set the ceiling to Interrupt_Priority'Last, an implementation-
11671 -- defined value, see D.3(10).
11674 and then Has_Priority_Pragma
(Pdef
)
11677 Prio
: constant Node_Id
:=
11680 (Pragma_Argument_Associations
11681 (Find_Task_Or_Protected_Pragma
11682 (Pdef
, Name_Priority
))));
11686 -- If priority is a static expression, then we can duplicate it
11687 -- with no problem and simply append it to the argument list.
11689 if Is_Static_Expression
(Prio
) then
11691 Duplicate_Subexpr_No_Checks
(Prio
));
11693 -- Otherwise, the priority may be a per-object expression, if it
11694 -- depends on a discriminant of the type. In this case, create
11695 -- local variable to capture the expression. Note that it is
11696 -- really necessary to create this variable explicitly. It might
11697 -- be thought that removing side effects would the appropriate
11698 -- approach, but that could generate declarations improperly
11699 -- placed in the enclosing scope.
11701 -- Note: Use System.Any_Priority as the expected type for the
11702 -- non-static priority expression, in case the expression has not
11703 -- been analyzed yet (as occurs for example with pragma
11704 -- Interrupt_Priority).
11708 Make_Defining_Identifier
(Loc
, New_Internal_Name
('R'));
11711 Make_Object_Declaration
(Loc
,
11712 Defining_Identifier
=> Temp
,
11713 Object_Definition
=>
11714 New_Occurrence_Of
(RTE
(RE_Any_Priority
), Loc
),
11715 Expression
=> Relocate_Node
(Prio
)));
11717 Append_To
(Args
, New_Occurrence_Of
(Temp
, Loc
));
11721 -- When no priority is specified but an xx_Handler pragma is, we default
11722 -- to System.Interrupts.Default_Interrupt_Priority, see D.3(10).
11724 elsif Has_Interrupt_Handler
(Ptyp
)
11725 or else Has_Attach_Handler
(Ptyp
)
11728 New_Reference_To
(RTE
(RE_Default_Interrupt_Priority
), Loc
));
11730 -- Normal case, no priority or xx_Handler specified, default priority
11734 New_Reference_To
(RTE
(RE_Unspecified_Priority
), Loc
));
11737 -- Test for Compiler_Info parameter. This parameter allows entry body
11738 -- procedures and barrier functions to be called from the runtime. It
11739 -- is a pointer to the record generated by the compiler to represent
11740 -- the protected object.
11743 or else Has_Interrupt_Handler
(Ptyp
)
11744 or else Has_Attach_Handler
(Ptyp
)
11745 or else Has_Interfaces
(Protect_Rec
)
11748 Pkg_Id
: constant RTU_Id
:=
11749 Corresponding_Runtime_Package
(Ptyp
);
11750 Called_Subp
: RE_Id
;
11754 when System_Tasking_Protected_Objects_Entries
=>
11755 Called_Subp
:= RE_Initialize_Protection_Entries
;
11757 when System_Tasking_Protected_Objects
=>
11758 Called_Subp
:= RE_Initialize_Protection
;
11760 when System_Tasking_Protected_Objects_Single_Entry
=>
11761 Called_Subp
:= RE_Initialize_Protection_Entry
;
11764 raise Program_Error
;
11767 if Has_Entry
or else not Restricted
then
11769 Make_Attribute_Reference
(Loc
,
11770 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
11771 Attribute_Name
=> Name_Address
));
11774 -- Entry_Bodies parameter. This is a pointer to an array of
11775 -- pointers to the entry body procedures and barrier functions of
11776 -- the object. If the protected type has no entries this object
11777 -- will not exist, in this case, pass a null.
11780 P_Arr
:= Entry_Bodies_Array
(Ptyp
);
11783 Make_Attribute_Reference
(Loc
,
11784 Prefix
=> New_Reference_To
(P_Arr
, Loc
),
11785 Attribute_Name
=> Name_Unrestricted_Access
));
11787 if Pkg_Id
= System_Tasking_Protected_Objects_Entries
then
11789 -- Find index mapping function (clumsy but ok for now)
11791 while Ekind
(P_Arr
) /= E_Function
loop
11792 Next_Entity
(P_Arr
);
11796 Make_Attribute_Reference
(Loc
,
11798 New_Reference_To
(P_Arr
, Loc
),
11799 Attribute_Name
=> Name_Unrestricted_Access
));
11801 -- Build_Entry_Names generation flag. When set to true, the
11802 -- runtime will allocate an array to hold the string names
11803 -- of protected entries.
11805 if not Restricted_Profile
then
11806 if Entry_Names_OK
then
11808 New_Reference_To
(Standard_True
, Loc
));
11811 New_Reference_To
(Standard_False
, Loc
));
11816 elsif Pkg_Id
= System_Tasking_Protected_Objects_Single_Entry
then
11817 Append_To
(Args
, Make_Null
(Loc
));
11819 elsif Pkg_Id
= System_Tasking_Protected_Objects_Entries
then
11820 Append_To
(Args
, Make_Null
(Loc
));
11821 Append_To
(Args
, Make_Null
(Loc
));
11822 Append_To
(Args
, New_Reference_To
(Standard_False
, Loc
));
11826 Make_Procedure_Call_Statement
(Loc
,
11827 Name
=> New_Reference_To
(RTE
(Called_Subp
), Loc
),
11828 Parameter_Associations
=> Args
));
11832 Make_Procedure_Call_Statement
(Loc
,
11833 Name
=> New_Reference_To
(RTE
(RE_Initialize_Protection
), Loc
),
11834 Parameter_Associations
=> Args
));
11837 if Has_Attach_Handler
(Ptyp
) then
11839 -- We have a list of N Attach_Handler (ProcI, ExprI), and we have to
11840 -- make the following call:
11842 -- Install_Handlers (_object,
11843 -- ((Expr1, Proc1'access), ...., (ExprN, ProcN'access));
11845 -- or, in the case of Ravenscar:
11847 -- Install_Restricted_Handlers
11848 -- ((Expr1, Proc1'access), ...., (ExprN, ProcN'access));
11851 Args
: constant List_Id
:= New_List
;
11852 Table
: constant List_Id
:= New_List
;
11853 Ritem
: Node_Id
:= First_Rep_Item
(Ptyp
);
11856 -- Build the Attach_Handler table argument
11858 while Present
(Ritem
) loop
11859 if Nkind
(Ritem
) = N_Pragma
11860 and then Pragma_Name
(Ritem
) = Name_Attach_Handler
11863 Handler
: constant Node_Id
:=
11864 First
(Pragma_Argument_Associations
(Ritem
));
11866 Interrupt
: constant Node_Id
:= Next
(Handler
);
11867 Expr
: constant Node_Id
:= Expression
(Interrupt
);
11871 Make_Aggregate
(Loc
, Expressions
=> New_List
(
11872 Unchecked_Convert_To
11873 (RTE
(RE_System_Interrupt_Id
), Expr
),
11874 Make_Attribute_Reference
(Loc
,
11875 Prefix
=> Make_Selected_Component
(Loc
,
11876 Make_Identifier
(Loc
, Name_uInit
),
11877 Duplicate_Subexpr_No_Checks
11878 (Expression
(Handler
))),
11879 Attribute_Name
=> Name_Access
))));
11883 Next_Rep_Item
(Ritem
);
11886 -- Append the table argument we just built
11888 Append_To
(Args
, Make_Aggregate
(Loc
, Table
));
11890 -- Append the Install_Handlers (or Install_Restricted_Handlers)
11891 -- call to the statements.
11894 -- Call a simplified version of Install_Handlers to be used
11895 -- when the Ravenscar restrictions are in effect
11896 -- (Install_Restricted_Handlers).
11899 Make_Procedure_Call_Statement
(Loc
,
11902 (RTE
(RE_Install_Restricted_Handlers
), Loc
),
11903 Parameter_Associations
=> Args
));
11906 -- First, prepends the _object argument
11909 Make_Attribute_Reference
(Loc
,
11911 Make_Selected_Component
(Loc
,
11912 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
11913 Selector_Name
=> Make_Identifier
(Loc
, Name_uObject
)),
11914 Attribute_Name
=> Name_Unchecked_Access
));
11916 -- Then, insert call to Install_Handlers
11919 Make_Procedure_Call_Statement
(Loc
,
11920 Name
=> New_Reference_To
(RTE
(RE_Install_Handlers
), Loc
),
11921 Parameter_Associations
=> Args
));
11927 end Make_Initialize_Protection
;
11929 ---------------------------
11930 -- Make_Task_Create_Call --
11931 ---------------------------
11933 function Make_Task_Create_Call
(Task_Rec
: Entity_Id
) return Node_Id
is
11934 Loc
: constant Source_Ptr
:= Sloc
(Task_Rec
);
11944 Ttyp
:= Corresponding_Concurrent_Type
(Task_Rec
);
11945 Tnam
:= Chars
(Ttyp
);
11947 -- Get task declaration. In the case of a task type declaration, this is
11948 -- simply the parent of the task type entity. In the single task
11949 -- declaration, this parent will be the implicit type, and we can find
11950 -- the corresponding single task declaration by searching forward in the
11951 -- declaration list in the tree.
11953 -- Is the test for N_Single_Task_Declaration needed here??? Nodes of
11954 -- this type should have been removed during semantic analysis.
11956 Tdec
:= Parent
(Ttyp
);
11957 while not Nkind_In
(Tdec
, N_Task_Type_Declaration
,
11958 N_Single_Task_Declaration
)
11963 -- Now we can find the task definition from this declaration
11965 Tdef
:= Task_Definition
(Tdec
);
11967 -- Build the parameter list for the call. Note that _Init is the name
11968 -- of the formal for the object to be initialized, which is the task
11969 -- value record itself.
11973 -- Priority parameter. Set to Unspecified_Priority unless there is a
11974 -- priority pragma, in which case we take the value from the pragma.
11976 if Present
(Tdef
) and then Has_Priority_Pragma
(Tdef
) then
11978 Make_Selected_Component
(Loc
,
11979 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
11980 Selector_Name
=> Make_Identifier
(Loc
, Name_uPriority
)));
11983 New_Reference_To
(RTE
(RE_Unspecified_Priority
), Loc
));
11986 -- Optional Stack parameter
11988 if Restricted_Profile
then
11990 -- If the stack has been preallocated by the expander then
11991 -- pass its address. Otherwise, pass a null address.
11993 if Preallocated_Stacks_On_Target
then
11995 Make_Attribute_Reference
(Loc
,
11996 Prefix
=> Make_Selected_Component
(Loc
,
11997 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
11999 Make_Identifier
(Loc
, Name_uStack
)),
12000 Attribute_Name
=> Name_Address
));
12004 New_Reference_To
(RTE
(RE_Null_Address
), Loc
));
12008 -- Size parameter. If no Storage_Size pragma is present, then
12009 -- the size is taken from the taskZ variable for the type, which
12010 -- is either Unspecified_Size, or has been reset by the use of
12011 -- a Storage_Size attribute definition clause. If a pragma is
12012 -- present, then the size is taken from the _Size field of the
12013 -- task value record, which was set from the pragma value.
12016 and then Has_Storage_Size_Pragma
(Tdef
)
12019 Make_Selected_Component
(Loc
,
12020 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
12021 Selector_Name
=> Make_Identifier
(Loc
, Name_uSize
)));
12025 New_Reference_To
(Storage_Size_Variable
(Ttyp
), Loc
));
12028 -- Task_Info parameter. Set to Unspecified_Task_Info unless there is a
12029 -- Task_Info pragma, in which case we take the value from the pragma.
12032 and then Has_Task_Info_Pragma
(Tdef
)
12035 Make_Selected_Component
(Loc
,
12036 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
12037 Selector_Name
=> Make_Identifier
(Loc
, Name_uTask_Info
)));
12041 New_Reference_To
(RTE
(RE_Unspecified_Task_Info
), Loc
));
12044 if not Restricted_Profile
then
12046 -- Deadline parameter. If no Relative_Deadline pragma is present,
12047 -- then the deadline is Time_Span_Zero. If a pragma is present, then
12048 -- the deadline is taken from the _Relative_Deadline field of the
12049 -- task value record, which was set from the pragma value. Note that
12050 -- this parameter must not be generated for the restricted profiles
12051 -- since Ravenscar does not allow deadlines.
12053 -- Case where pragma Relative_Deadline applies: use given value
12055 if Present
(Tdef
) and then Has_Relative_Deadline_Pragma
(Tdef
) then
12057 Make_Selected_Component
(Loc
,
12058 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
12060 Make_Identifier
(Loc
, Name_uRelative_Deadline
)));
12062 -- No pragma Relative_Deadline apply to the task
12066 New_Reference_To
(RTE
(RE_Time_Span_Zero
), Loc
));
12069 -- Number of entries. This is an expression of the form:
12071 -- n + _Init.a'Length + _Init.a'B'Length + ...
12073 -- where a,b... are the entry family names for the task definition
12076 Build_Entry_Count_Expression
12081 (Parent
(Corresponding_Record_Type
(Ttyp
))))),
12083 Append_To
(Args
, Ecount
);
12085 -- Master parameter. This is a reference to the _Master parameter of
12086 -- the initialization procedure, except in the case of the pragma
12087 -- Restrictions (No_Task_Hierarchy) where the value is fixed to 3.
12088 -- See comments in System.Tasking.Initialization.Init_RTS for the
12091 if Restriction_Active
(No_Task_Hierarchy
) = False then
12092 Append_To
(Args
, Make_Identifier
(Loc
, Name_uMaster
));
12094 Append_To
(Args
, Make_Integer_Literal
(Loc
, 3));
12098 -- State parameter. This is a pointer to the task body procedure. The
12099 -- required value is obtained by taking 'Unrestricted_Access of the task
12100 -- body procedure and converting it (with an unchecked conversion) to
12101 -- the type required by the task kernel. For further details, see the
12102 -- description of Expand_N_Task_Body. We use 'Unrestricted_Access rather
12103 -- than 'Address in order to avoid creating trampolines.
12106 Body_Proc
: constant Node_Id
:= Get_Task_Body_Procedure
(Ttyp
);
12107 Subp_Ptr_Typ
: constant Node_Id
:=
12108 Create_Itype
(E_Access_Subprogram_Type
, Tdec
);
12109 Ref
: constant Node_Id
:= Make_Itype_Reference
(Loc
);
12112 Set_Directly_Designated_Type
(Subp_Ptr_Typ
, Body_Proc
);
12113 Set_Etype
(Subp_Ptr_Typ
, Subp_Ptr_Typ
);
12115 -- Be sure to freeze a reference to the access-to-subprogram type,
12116 -- otherwise gigi will complain that it's in the wrong scope, because
12117 -- it's actually inside the init procedure for the record type that
12118 -- corresponds to the task type.
12120 -- This processing is causing a crash in the .NET/JVM back ends that
12121 -- is not yet understood, so skip it in these cases ???
12123 if VM_Target
= No_VM
then
12124 Set_Itype
(Ref
, Subp_Ptr_Typ
);
12125 Append_Freeze_Action
(Task_Rec
, Ref
);
12128 Unchecked_Convert_To
(RTE
(RE_Task_Procedure_Access
),
12129 Make_Qualified_Expression
(Loc
,
12130 Subtype_Mark
=> New_Reference_To
(Subp_Ptr_Typ
, Loc
),
12132 Make_Attribute_Reference
(Loc
,
12134 New_Occurrence_Of
(Body_Proc
, Loc
),
12135 Attribute_Name
=> Name_Unrestricted_Access
))));
12137 -- For the .NET/JVM cases revert to the original code below ???
12141 Unchecked_Convert_To
(RTE
(RE_Task_Procedure_Access
),
12142 Make_Attribute_Reference
(Loc
,
12144 New_Occurrence_Of
(Body_Proc
, Loc
),
12145 Attribute_Name
=> Name_Address
)));
12149 -- Discriminants parameter. This is just the address of the task
12150 -- value record itself (which contains the discriminant values
12153 Make_Attribute_Reference
(Loc
,
12154 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
12155 Attribute_Name
=> Name_Address
));
12157 -- Elaborated parameter. This is an access to the elaboration Boolean
12160 Make_Attribute_Reference
(Loc
,
12161 Prefix
=> Make_Identifier
(Loc
, New_External_Name
(Tnam
, 'E')),
12162 Attribute_Name
=> Name_Unchecked_Access
));
12164 -- Chain parameter. This is a reference to the _Chain parameter of
12165 -- the initialization procedure.
12167 Append_To
(Args
, Make_Identifier
(Loc
, Name_uChain
));
12169 -- Task name parameter. Take this from the _Task_Id parameter to the
12170 -- init call unless there is a Task_Name pragma, in which case we take
12171 -- the value from the pragma.
12174 and then Has_Task_Name_Pragma
(Tdef
)
12176 -- Copy expression in full, because it may be dynamic and have
12182 (Pragma_Argument_Associations
12183 (Find_Task_Or_Protected_Pragma
12184 (Tdef
, Name_Task_Name
))))));
12187 Append_To
(Args
, Make_Identifier
(Loc
, Name_uTask_Name
));
12190 -- Created_Task parameter. This is the _Task_Id field of the task
12194 Make_Selected_Component
(Loc
,
12195 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
12196 Selector_Name
=> Make_Identifier
(Loc
, Name_uTask_Id
)));
12198 -- Build_Entry_Names generation flag. When set to true, the runtime
12199 -- will allocate an array to hold the string names of task entries.
12201 if not Restricted_Profile
then
12202 if Has_Entries
(Ttyp
)
12203 and then Entry_Names_OK
12205 Append_To
(Args
, New_Reference_To
(Standard_True
, Loc
));
12207 Append_To
(Args
, New_Reference_To
(Standard_False
, Loc
));
12211 if Restricted_Profile
then
12212 Name
:= New_Reference_To
(RTE
(RE_Create_Restricted_Task
), Loc
);
12214 Name
:= New_Reference_To
(RTE
(RE_Create_Task
), Loc
);
12218 Make_Procedure_Call_Statement
(Loc
,
12220 Parameter_Associations
=> Args
);
12221 end Make_Task_Create_Call
;
12223 ------------------------------
12224 -- Next_Protected_Operation --
12225 ------------------------------
12227 function Next_Protected_Operation
(N
: Node_Id
) return Node_Id
is
12231 Next_Op
:= Next
(N
);
12232 while Present
(Next_Op
)
12233 and then not Nkind_In
(Next_Op
, N_Subprogram_Body
, N_Entry_Body
)
12239 end Next_Protected_Operation
;
12241 ---------------------
12242 -- Null_Statements --
12243 ---------------------
12245 function Null_Statements
(Stats
: List_Id
) return Boolean is
12249 Stmt
:= First
(Stats
);
12250 while Nkind
(Stmt
) /= N_Empty
12251 and then (Nkind_In
(Stmt
, N_Null_Statement
, N_Label
)
12253 (Nkind
(Stmt
) = N_Pragma
12254 and then (Pragma_Name
(Stmt
) = Name_Unreferenced
12256 Pragma_Name
(Stmt
) = Name_Unmodified
12258 Pragma_Name
(Stmt
) = Name_Warnings
)))
12263 return Nkind
(Stmt
) = N_Empty
;
12264 end Null_Statements
;
12266 --------------------------
12267 -- Parameter_Block_Pack --
12268 --------------------------
12270 function Parameter_Block_Pack
12272 Blk_Typ
: Entity_Id
;
12276 Stmts
: List_Id
) return Node_Id
12278 Actual
: Entity_Id
;
12279 Expr
: Node_Id
:= Empty
;
12280 Formal
: Entity_Id
;
12281 Has_Param
: Boolean := False;
12284 Temp_Asn
: Node_Id
;
12285 Temp_Nam
: Node_Id
;
12288 Actual
:= First
(Actuals
);
12289 Formal
:= Defining_Identifier
(First
(Formals
));
12290 Params
:= New_List
;
12292 while Present
(Actual
) loop
12293 if Is_By_Copy_Type
(Etype
(Actual
)) then
12295 -- Jnn : aliased <formal-type>
12298 Make_Defining_Identifier
(Loc
, New_Internal_Name
('J'));
12301 Make_Object_Declaration
(Loc
,
12304 Defining_Identifier
=>
12306 Object_Definition
=>
12307 New_Reference_To
(Etype
(Formal
), Loc
)));
12309 if Ekind
(Formal
) /= E_Out_Parameter
then
12315 New_Reference_To
(Temp_Nam
, Loc
);
12317 Set_Assignment_OK
(Temp_Asn
);
12320 Make_Assignment_Statement
(Loc
,
12324 New_Copy_Tree
(Actual
)));
12328 -- Jnn'unchecked_access
12331 Make_Attribute_Reference
(Loc
,
12333 Name_Unchecked_Access
,
12335 New_Reference_To
(Temp_Nam
, Loc
)));
12339 -- The controlling parameter is omitted
12342 if not Is_Controlling_Actual
(Actual
) then
12344 Make_Reference
(Loc
, New_Copy_Tree
(Actual
)));
12350 Next_Actual
(Actual
);
12351 Next_Formal_With_Extras
(Formal
);
12355 Expr
:= Make_Aggregate
(Loc
, Params
);
12360 -- J1'unchecked_access;
12361 -- <actual2>'reference;
12364 P
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('P'));
12367 Make_Object_Declaration
(Loc
,
12368 Defining_Identifier
=>
12370 Object_Definition
=>
12371 New_Reference_To
(Blk_Typ
, Loc
),
12376 end Parameter_Block_Pack
;
12378 ----------------------------
12379 -- Parameter_Block_Unpack --
12380 ----------------------------
12382 function Parameter_Block_Unpack
12386 Formals
: List_Id
) return List_Id
12388 Actual
: Entity_Id
;
12390 Formal
: Entity_Id
;
12391 Has_Asnmt
: Boolean := False;
12392 Result
: constant List_Id
:= New_List
;
12395 Actual
:= First
(Actuals
);
12396 Formal
:= Defining_Identifier
(First
(Formals
));
12397 while Present
(Actual
) loop
12398 if Is_By_Copy_Type
(Etype
(Actual
))
12399 and then Ekind
(Formal
) /= E_In_Parameter
12402 -- <actual> := P.<formal>;
12405 Make_Assignment_Statement
(Loc
,
12409 Make_Explicit_Dereference
(Loc
,
12410 Make_Selected_Component
(Loc
,
12412 New_Reference_To
(P
, Loc
),
12414 Make_Identifier
(Loc
, Chars
(Formal
)))));
12416 Set_Assignment_OK
(Name
(Asnmt
));
12417 Append_To
(Result
, Asnmt
);
12422 Next_Actual
(Actual
);
12423 Next_Formal_With_Extras
(Formal
);
12429 return New_List
(Make_Null_Statement
(Loc
));
12431 end Parameter_Block_Unpack
;
12433 ----------------------
12434 -- Set_Discriminals --
12435 ----------------------
12437 procedure Set_Discriminals
(Dec
: Node_Id
) is
12440 D_Minal
: Entity_Id
;
12443 pragma Assert
(Nkind
(Dec
) = N_Protected_Type_Declaration
);
12444 Pdef
:= Defining_Identifier
(Dec
);
12446 if Has_Discriminants
(Pdef
) then
12447 D
:= First_Discriminant
(Pdef
);
12448 while Present
(D
) loop
12450 Make_Defining_Identifier
(Sloc
(D
),
12451 Chars
=> New_External_Name
(Chars
(D
), 'D'));
12453 Set_Ekind
(D_Minal
, E_Constant
);
12454 Set_Etype
(D_Minal
, Etype
(D
));
12455 Set_Scope
(D_Minal
, Pdef
);
12456 Set_Discriminal
(D
, D_Minal
);
12457 Set_Discriminal_Link
(D_Minal
, D
);
12459 Next_Discriminant
(D
);
12462 end Set_Discriminals
;
12464 -----------------------
12465 -- Trivial_Accept_OK --
12466 -----------------------
12468 function Trivial_Accept_OK
return Boolean is
12470 case Opt
.Task_Dispatching_Policy
is
12472 -- If we have the default task dispatching policy in effect, we can
12473 -- definitely do the optimization (one way of looking at this is to
12474 -- think of the formal definition of the default policy being allowed
12475 -- to run any task it likes after a rendezvous, so even if notionally
12476 -- a full rescheduling occurs, we can say that our dispatching policy
12477 -- (i.e. the default dispatching policy) reorders the queue to be the
12478 -- same as just before the call.
12483 -- FIFO_Within_Priorities certainly does not permit this
12484 -- optimization since the Rendezvous is a scheduling action that may
12485 -- require some other task to be run.
12490 -- For now, disallow the optimization for all other policies. This
12491 -- may be over-conservative, but it is certainly not incorrect.
12497 end Trivial_Accept_OK
;