Implement -mmemcpy-strategy= and -mmemset-strategy= options
[official-gcc.git] / gcc / ada / exp_ch9.adb
blobfdafd22a6d2d4118ca09724ddf7b6af1770f14bd
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- E X P _ C H 9 --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2013, Free Software Foundation, Inc. --
10 -- --
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. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Atree; use Atree;
27 with Checks; use Checks;
28 with Einfo; use Einfo;
29 with Elists; use Elists;
30 with Errout; use Errout;
31 with Exp_Ch3; use Exp_Ch3;
32 with Exp_Ch6; use Exp_Ch6;
33 with Exp_Ch11; use Exp_Ch11;
34 with Exp_Dbug; use Exp_Dbug;
35 with Exp_Disp; use Exp_Disp;
36 with Exp_Sel; use Exp_Sel;
37 with Exp_Smem; use Exp_Smem;
38 with Exp_Tss; use Exp_Tss;
39 with Exp_Util; use Exp_Util;
40 with Freeze; use Freeze;
41 with Hostparm;
42 with Itypes; use Itypes;
43 with Namet; use Namet;
44 with Nlists; use Nlists;
45 with Nmake; use Nmake;
46 with Opt; use Opt;
47 with Restrict; use Restrict;
48 with Rident; use Rident;
49 with Rtsfind; use Rtsfind;
50 with Sem; use Sem;
51 with Sem_Aux; use Sem_Aux;
52 with Sem_Ch6; use Sem_Ch6;
53 with Sem_Ch8; use Sem_Ch8;
54 with Sem_Ch9; use Sem_Ch9;
55 with Sem_Ch11; use Sem_Ch11;
56 with Sem_Elab; use Sem_Elab;
57 with Sem_Eval; use Sem_Eval;
58 with Sem_Res; use Sem_Res;
59 with Sem_Util; use Sem_Util;
60 with Sinfo; use Sinfo;
61 with Snames; use Snames;
62 with Stand; use Stand;
63 with Stringt; use Stringt;
64 with Targparm; use Targparm;
65 with Tbuild; use Tbuild;
66 with Uintp; use Uintp;
68 package body Exp_Ch9 is
70 -- The following constant establishes the upper bound for the index of
71 -- an entry family. It is used to limit the allocated size of protected
72 -- types with defaulted discriminant of an integer type, when the bound
73 -- of some entry family depends on a discriminant. The limitation to
74 -- entry families of 128K should be reasonable in all cases, and is a
75 -- documented implementation restriction.
77 Entry_Family_Bound : constant Int := 2**16;
79 -----------------------
80 -- Local Subprograms --
81 -----------------------
83 function Actual_Index_Expression
84 (Sloc : Source_Ptr;
85 Ent : Entity_Id;
86 Index : Node_Id;
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
93 (Loc : Source_Ptr;
94 Conc_Typ : Entity_Id;
95 Decls : List_Id);
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
99 -- procedures.
101 procedure Add_Formal_Renamings
102 (Spec : Node_Id;
103 Decls : List_Id;
104 Ent : Entity_Id;
105 Loc : Source_Ptr);
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
119 (N : Node_Id;
120 Ent : Entity_Id;
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
126 (Loc : Source_Ptr;
127 Def_Id : Entity_Id) return Node_Id;
128 -- Build a specification for a function implementing the protected entry
129 -- barrier of the specified entry body.
131 function Build_Corresponding_Record
132 (N : Node_Id;
133 Ctyp : Node_Id;
134 Loc : Source_Ptr) return Node_Id;
135 -- Common to tasks and protected types. Copy discriminant specifications,
136 -- build record declaration. N is the type declaration, Ctyp is the
137 -- concurrent entity (task type or protected type).
139 function Build_Entry_Count_Expression
140 (Concurrent_Type : Node_Id;
141 Component_List : List_Id;
142 Loc : Source_Ptr) return Node_Id;
143 -- Compute number of entries for concurrent object. This is a count of
144 -- simple entries, followed by an expression that computes the length
145 -- of the range of each entry family. A single array with that size is
146 -- allocated for each concurrent object of the type.
148 function Build_Find_Body_Index (Typ : Entity_Id) return Node_Id;
149 -- Build the function that translates the entry index in the call
150 -- (which depends on the size of entry families) into an index into the
151 -- Entry_Bodies_Array, to determine the body and barrier function used
152 -- in a protected entry call. A pointer to this function appears in every
153 -- protected object.
155 function Build_Find_Body_Index_Spec (Typ : Entity_Id) return Node_Id;
156 -- Build subprogram declaration for previous one
158 function Build_Lock_Free_Protected_Subprogram_Body
159 (N : Node_Id;
160 Prot_Typ : Node_Id;
161 Unprot_Spec : Node_Id) return Node_Id;
162 -- N denotes a subprogram body of protected type Prot_Typ. Unprot_Spec is
163 -- the subprogram specification of the unprotected version of N. Transform
164 -- N such that it invokes the unprotected version of the body.
166 function Build_Lock_Free_Unprotected_Subprogram_Body
167 (N : Node_Id;
168 Prot_Typ : Node_Id) return Node_Id;
169 -- N denotes a subprogram body of protected type Prot_Typ. Build a version
170 -- of N where the original statements of N are synchronized through atomic
171 -- actions such as compare and exchange. Prior to invoking this routine, it
172 -- has been established that N can be implemented in a lock-free fashion.
174 function Build_Parameter_Block
175 (Loc : Source_Ptr;
176 Actuals : List_Id;
177 Formals : List_Id;
178 Decls : List_Id) return Entity_Id;
179 -- Generate an access type for each actual parameter in the list Actuals.
180 -- Create an encapsulating record that contains all the actuals and return
181 -- its type. Generate:
182 -- type Ann1 is access all <actual1-type>
183 -- ...
184 -- type AnnN is access all <actualN-type>
185 -- type Pnn is record
186 -- <formal1> : Ann1;
187 -- ...
188 -- <formalN> : AnnN;
189 -- end record;
191 procedure Build_PPC_Wrapper (E : Entity_Id; Decl : Node_Id);
192 -- Build body of wrapper procedure for an entry or entry family that has
193 -- pre/postconditions. The body gathers the PPC's and expands them in the
194 -- usual way, and performs the entry call itself. This way preconditions
195 -- are evaluated before the call is queued. E is the entry in question,
196 -- and Decl is the enclosing synchronized type declaration at whose
197 -- freeze point the generated body is analyzed.
199 function Build_Protected_Entry
200 (N : Node_Id;
201 Ent : Entity_Id;
202 Pid : Node_Id) return Node_Id;
203 -- Build the procedure implementing the statement sequence of the specified
204 -- entry body.
206 function Build_Protected_Entry_Specification
207 (Loc : Source_Ptr;
208 Def_Id : Entity_Id;
209 Ent_Id : Entity_Id) return Node_Id;
210 -- Build a specification for the procedure implementing the statements of
211 -- the specified entry body. Add attributes associating it with the entry
212 -- defining identifier Ent_Id.
214 function Build_Protected_Spec
215 (N : Node_Id;
216 Obj_Type : Entity_Id;
217 Ident : Entity_Id;
218 Unprotected : Boolean := False) return List_Id;
219 -- Utility shared by Build_Protected_Sub_Spec and Expand_Access_Protected_
220 -- Subprogram_Type. Builds signature of protected subprogram, adding the
221 -- formal that corresponds to the object itself. For an access to protected
222 -- subprogram, there is no object type to specify, so the parameter has
223 -- type Address and mode In. An indirect call through such a pointer will
224 -- convert the address to a reference to the actual object. The object is
225 -- a limited record and therefore a by_reference type.
227 function Build_Protected_Subprogram_Body
228 (N : Node_Id;
229 Pid : Node_Id;
230 N_Op_Spec : Node_Id) return Node_Id;
231 -- This function is used to construct the protected version of a protected
232 -- subprogram. Its statement sequence first defers abort, then locks
233 -- the associated protected object, and then enters a block that contains
234 -- a call to the unprotected version of the subprogram (for details, see
235 -- Build_Unprotected_Subprogram_Body). This block statement requires
236 -- a cleanup handler that unlocks the object in all cases.
237 -- (see Exp_Ch7.Expand_Cleanup_Actions).
239 function Build_Renamed_Formal_Declaration
240 (New_F : Entity_Id;
241 Formal : Entity_Id;
242 Comp : Entity_Id;
243 Renamed_Formal : Node_Id) return Node_Id;
244 -- Create a renaming declaration for a formal, within a protected entry
245 -- body or an accept body. The renamed object is a component of the
246 -- parameter block that is a parameter in the entry call.
248 -- In Ada 2012, if the formal is an incomplete tagged type, the renaming
249 -- does not dereference the corresponding component to prevent an illegal
250 -- use of the incomplete type (AI05-0151).
252 function Build_Selected_Name
253 (Prefix : Entity_Id;
254 Selector : Entity_Id;
255 Append_Char : Character := ' ') return Name_Id;
256 -- Build a name in the form of Prefix__Selector, with an optional
257 -- character appended. This is used for internal subprograms generated
258 -- for operations of protected types, including barrier functions.
259 -- For the subprograms generated for entry bodies and entry barriers,
260 -- the generated name includes a sequence number that makes names
261 -- unique in the presence of entry overloading. This is necessary
262 -- because entry body procedures and barrier functions all have the
263 -- same signature.
265 procedure Build_Simple_Entry_Call
266 (N : Node_Id;
267 Concval : Node_Id;
268 Ename : Node_Id;
269 Index : Node_Id);
270 -- Some comments here would be useful ???
272 function Build_Task_Proc_Specification (T : Entity_Id) return Node_Id;
273 -- This routine constructs a specification for the procedure that we will
274 -- build for the task body for task type T. The spec has the form:
276 -- procedure tnameB (_Task : access tnameV);
278 -- where name is the character name taken from the task type entity that
279 -- is passed as the argument to the procedure, and tnameV is the task
280 -- value type that is associated with the task type.
282 function Build_Unprotected_Subprogram_Body
283 (N : Node_Id;
284 Pid : Node_Id) return Node_Id;
285 -- This routine constructs the unprotected version of a protected
286 -- subprogram body, which is contains all of the code in the
287 -- original, unexpanded body. This is the version of the protected
288 -- subprogram that is called from all protected operations on the same
289 -- object, including the protected version of the same subprogram.
291 procedure Build_Wrapper_Bodies
292 (Loc : Source_Ptr;
293 Typ : Entity_Id;
294 N : Node_Id);
295 -- Ada 2005 (AI-345): Typ is either a concurrent type or the corresponding
296 -- record of a concurrent type. N is the insertion node where all bodies
297 -- will be placed. This routine builds the bodies of the subprograms which
298 -- serve as an indirection mechanism to overriding primitives of concurrent
299 -- types, entries and protected procedures. Any new body is analyzed.
301 procedure Build_Wrapper_Specs
302 (Loc : Source_Ptr;
303 Typ : Entity_Id;
304 N : in out Node_Id);
305 -- Ada 2005 (AI-345): Typ is either a concurrent type or the corresponding
306 -- record of a concurrent type. N is the insertion node where all specs
307 -- will be placed. This routine builds the specs of the subprograms which
308 -- serve as an indirection mechanism to overriding primitives of concurrent
309 -- types, entries and protected procedures. Any new spec is analyzed.
311 procedure Collect_Entry_Families
312 (Loc : Source_Ptr;
313 Cdecls : List_Id;
314 Current_Node : in out Node_Id;
315 Conctyp : Entity_Id);
316 -- For each entry family in a concurrent type, create an anonymous array
317 -- type of the right size, and add a component to the corresponding_record.
319 function Concurrent_Object
320 (Spec_Id : Entity_Id;
321 Conc_Typ : Entity_Id) return Entity_Id;
322 -- Given a subprogram entity Spec_Id and concurrent type Conc_Typ, return
323 -- the entity associated with the concurrent object in the Protected_Body_
324 -- Subprogram or the Task_Body_Procedure of Spec_Id. The returned entity
325 -- denotes formal parameter _O, _object or _task.
327 function Copy_Result_Type (Res : Node_Id) return Node_Id;
328 -- Copy the result type of a function specification, when building the
329 -- internal operation corresponding to a protected function, or when
330 -- expanding an access to protected function. If the result is an anonymous
331 -- access to subprogram itself, we need to create a new signature with the
332 -- same parameter names and the same resolved types, but with new entities
333 -- for the formals.
335 procedure Debug_Private_Data_Declarations (Decls : List_Id);
336 -- Decls is a list which may contain the declarations created by Install_
337 -- Private_Data_Declarations. All generated entities are marked as needing
338 -- debug info and debug nodes are manually generation where necessary. This
339 -- step of the expansion must to be done after private data has been moved
340 -- to its final resting scope to ensure proper visibility of debug objects.
342 procedure Ensure_Statement_Present (Loc : Source_Ptr; Alt : Node_Id);
343 -- If control flow optimizations are suppressed, and Alt is an accept,
344 -- delay, or entry call alternative with no trailing statements, insert a
345 -- null trailing statement with the given Loc (which is the sloc of the
346 -- accept, delay, or entry call statement). There might not be any
347 -- generated code for the accept, delay, or entry call itself (the
348 -- effect of these statements is part of the general processsing done
349 -- for the enclosing selective accept, timed entry call, or asynchronous
350 -- select), and the null statement is there to carry the sloc of that
351 -- statement to the back-end for trace-based coverage analysis purposes.
353 procedure Extract_Dispatching_Call
354 (N : Node_Id;
355 Call_Ent : out Entity_Id;
356 Object : out Entity_Id;
357 Actuals : out List_Id;
358 Formals : out List_Id);
359 -- Given a dispatching call, extract the entity of the name of the call,
360 -- its actual dispatching object, its actual parameters and the formal
361 -- parameters of the overridden interface-level version. If the type of
362 -- the dispatching object is an access type then an explicit dereference
363 -- is returned in Object.
365 procedure Extract_Entry
366 (N : Node_Id;
367 Concval : out Node_Id;
368 Ename : out Node_Id;
369 Index : out Node_Id);
370 -- Given an entry call, returns the associated concurrent object,
371 -- the entry name, and the entry family index.
373 function Family_Offset
374 (Loc : Source_Ptr;
375 Hi : Node_Id;
376 Lo : Node_Id;
377 Ttyp : Entity_Id;
378 Cap : Boolean) return Node_Id;
379 -- Compute (Hi - Lo) for two entry family indexes. Hi is the index in
380 -- an accept statement, or the upper bound in the discrete subtype of
381 -- an entry declaration. Lo is the corresponding lower bound. Ttyp is
382 -- the concurrent type of the entry. If Cap is true, the result is
383 -- capped according to Entry_Family_Bound.
385 function Family_Size
386 (Loc : Source_Ptr;
387 Hi : Node_Id;
388 Lo : Node_Id;
389 Ttyp : Entity_Id;
390 Cap : Boolean) return Node_Id;
391 -- Compute (Hi - Lo) + 1 Max 0, to determine the number of entries in
392 -- a family, and handle properly the superflat case. This is equivalent
393 -- to the use of 'Length on the index type, but must use Family_Offset
394 -- to handle properly the case of bounds that depend on discriminants.
395 -- If Cap is true, the result is capped according to Entry_Family_Bound.
397 procedure Find_Enclosing_Context
398 (N : Node_Id;
399 Context : out Node_Id;
400 Context_Id : out Entity_Id;
401 Context_Decls : out List_Id);
402 -- Subsidiary routine to procedures Build_Activation_Chain_Entity and
403 -- Build_Master_Entity. Given an arbitrary node in the tree, find the
404 -- nearest enclosing body, block, package or return statement and return
405 -- its constituents. Context is the enclosing construct, Context_Id is
406 -- the scope of Context_Id and Context_Decls is the declarative list of
407 -- Context.
409 function Index_Object (Spec_Id : Entity_Id) return Entity_Id;
410 -- Given a subprogram identifier, return the entity which is associated
411 -- with the protection entry index in the Protected_Body_Subprogram or the
412 -- Task_Body_Procedure of Spec_Id. The returned entity denotes formal
413 -- parameter _E.
415 function Is_Exception_Safe (Subprogram : Node_Id) return Boolean;
416 -- Tell whether a given subprogram cannot raise an exception
418 function Is_Potentially_Large_Family
419 (Base_Index : Entity_Id;
420 Conctyp : Entity_Id;
421 Lo : Node_Id;
422 Hi : Node_Id) return Boolean;
424 function Is_Private_Primitive_Subprogram (Id : Entity_Id) return Boolean;
425 -- Determine whether Id is a function or a procedure and is marked as a
426 -- private primitive.
428 function Null_Statements (Stats : List_Id) return Boolean;
429 -- Used to check DO-END sequence. Checks for equivalent of DO NULL; END.
430 -- Allows labels, and pragma Warnings/Unreferenced in the sequence as
431 -- well to still count as null. Returns True for a null sequence. The
432 -- argument is the list of statements from the DO-END sequence.
434 function Parameter_Block_Pack
435 (Loc : Source_Ptr;
436 Blk_Typ : Entity_Id;
437 Actuals : List_Id;
438 Formals : List_Id;
439 Decls : List_Id;
440 Stmts : List_Id) return Entity_Id;
441 -- Set the components of the generated parameter block with the values of
442 -- the actual parameters. Generate aliased temporaries to capture the
443 -- values for types that are passed by copy. Otherwise generate a reference
444 -- to the actual's value. Return the address of the aggregate block.
445 -- Generate:
446 -- Jnn1 : alias <formal-type1>;
447 -- Jnn1 := <actual1>;
448 -- ...
449 -- P : Blk_Typ := (
450 -- Jnn1'unchecked_access;
451 -- <actual2>'reference;
452 -- ...);
454 function Parameter_Block_Unpack
455 (Loc : Source_Ptr;
456 P : Entity_Id;
457 Actuals : List_Id;
458 Formals : List_Id) return List_Id;
459 -- Retrieve the values of the components from the parameter block and
460 -- assign then to the original actual parameters. Generate:
461 -- <actual1> := P.<formal1>;
462 -- ...
463 -- <actualN> := P.<formalN>;
465 function Trivial_Accept_OK return Boolean;
466 -- If there is no DO-END block for an accept, or if the DO-END block has
467 -- only null statements, then it is possible to do the Rendezvous with much
468 -- less overhead using the Accept_Trivial routine in the run-time library.
469 -- However, this is not always a valid optimization. Whether it is valid or
470 -- not depends on the Task_Dispatching_Policy. The issue is whether a full
471 -- rescheduling action is required or not. In FIFO_Within_Priorities, such
472 -- a rescheduling is required, so this optimization is not allowed. This
473 -- function returns True if the optimization is permitted.
475 -----------------------------
476 -- Actual_Index_Expression --
477 -----------------------------
479 function Actual_Index_Expression
480 (Sloc : Source_Ptr;
481 Ent : Entity_Id;
482 Index : Node_Id;
483 Tsk : Entity_Id) return Node_Id
485 Ttyp : constant Entity_Id := Etype (Tsk);
486 Expr : Node_Id;
487 Num : Node_Id;
488 Lo : Node_Id;
489 Hi : Node_Id;
490 Prev : Entity_Id;
491 S : Node_Id;
493 function Actual_Family_Offset (Hi, Lo : Node_Id) return Node_Id;
494 -- Compute difference between bounds of entry family
496 --------------------------
497 -- Actual_Family_Offset --
498 --------------------------
500 function Actual_Family_Offset (Hi, Lo : Node_Id) return Node_Id is
502 function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id;
503 -- Replace a reference to a discriminant with a selected component
504 -- denoting the discriminant of the target task.
506 -----------------------------
507 -- Actual_Discriminant_Ref --
508 -----------------------------
510 function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id is
511 Typ : constant Entity_Id := Etype (Bound);
512 B : Node_Id;
514 begin
515 if not Is_Entity_Name (Bound)
516 or else Ekind (Entity (Bound)) /= E_Discriminant
517 then
518 if Nkind (Bound) = N_Attribute_Reference then
519 return Bound;
520 else
521 B := New_Copy_Tree (Bound);
522 end if;
524 else
525 B :=
526 Make_Selected_Component (Sloc,
527 Prefix => New_Copy_Tree (Tsk),
528 Selector_Name => New_Occurrence_Of (Entity (Bound), Sloc));
530 Analyze_And_Resolve (B, Typ);
531 end if;
533 return
534 Make_Attribute_Reference (Sloc,
535 Attribute_Name => Name_Pos,
536 Prefix => New_Occurrence_Of (Etype (Bound), Sloc),
537 Expressions => New_List (B));
538 end Actual_Discriminant_Ref;
540 -- Start of processing for Actual_Family_Offset
542 begin
543 return
544 Make_Op_Subtract (Sloc,
545 Left_Opnd => Actual_Discriminant_Ref (Hi),
546 Right_Opnd => Actual_Discriminant_Ref (Lo));
547 end Actual_Family_Offset;
549 -- Start of processing for Actual_Index_Expression
551 begin
552 -- The queues of entries and entry families appear in textual order in
553 -- the associated record. The entry index is computed as the sum of the
554 -- number of queues for all entries that precede the designated one, to
555 -- which is added the index expression, if this expression denotes a
556 -- member of a family.
558 -- The following is a place holder for the count of simple entries
560 Num := Make_Integer_Literal (Sloc, 1);
562 -- We construct an expression which is a series of addition operations.
563 -- See comments in Entry_Index_Expression, which is identical in
564 -- structure.
566 if Present (Index) then
567 S := Etype (Discrete_Subtype_Definition (Declaration_Node (Ent)));
569 Expr :=
570 Make_Op_Add (Sloc,
571 Left_Opnd => Num,
573 Right_Opnd =>
574 Actual_Family_Offset (
575 Make_Attribute_Reference (Sloc,
576 Attribute_Name => Name_Pos,
577 Prefix => New_Reference_To (Base_Type (S), Sloc),
578 Expressions => New_List (Relocate_Node (Index))),
579 Type_Low_Bound (S)));
580 else
581 Expr := Num;
582 end if;
584 -- Now add lengths of preceding entries and entry families
586 Prev := First_Entity (Ttyp);
588 while Chars (Prev) /= Chars (Ent)
589 or else (Ekind (Prev) /= Ekind (Ent))
590 or else not Sem_Ch6.Type_Conformant (Ent, Prev)
591 loop
592 if Ekind (Prev) = E_Entry then
593 Set_Intval (Num, Intval (Num) + 1);
595 elsif Ekind (Prev) = E_Entry_Family then
596 S :=
597 Etype (Discrete_Subtype_Definition (Declaration_Node (Prev)));
599 -- The need for the following full view retrieval stems from
600 -- this complex case of nested generics and tasking:
602 -- generic
603 -- type Formal_Index is range <>;
604 -- ...
605 -- package Outer is
606 -- type Index is private;
607 -- generic
608 -- ...
609 -- package Inner is
610 -- procedure P;
611 -- end Inner;
612 -- private
613 -- type Index is new Formal_Index range 1 .. 10;
614 -- end Outer;
616 -- package body Outer is
617 -- task type T is
618 -- entry Fam (Index); -- (2)
619 -- entry E;
620 -- end T;
621 -- package body Inner is -- (3)
622 -- procedure P is
623 -- begin
624 -- T.E; -- (1)
625 -- end P;
626 -- end Inner;
627 -- ...
629 -- We are currently building the index expression for the entry
630 -- call "T.E" (1). Part of the expansion must mention the range
631 -- of the discrete type "Index" (2) of entry family "Fam".
632 -- However only the private view of type "Index" is available to
633 -- the inner generic (3) because there was no prior mention of
634 -- the type inside "Inner". This visibility requirement is
635 -- implicit and cannot be detected during the construction of
636 -- the generic trees and needs special handling.
638 if In_Instance_Body
639 and then Is_Private_Type (S)
640 and then Present (Full_View (S))
641 then
642 S := Full_View (S);
643 end if;
645 Lo := Type_Low_Bound (S);
646 Hi := Type_High_Bound (S);
648 Expr :=
649 Make_Op_Add (Sloc,
650 Left_Opnd => Expr,
651 Right_Opnd =>
652 Make_Op_Add (Sloc,
653 Left_Opnd =>
654 Actual_Family_Offset (Hi, Lo),
655 Right_Opnd =>
656 Make_Integer_Literal (Sloc, 1)));
658 -- Other components are anonymous types to be ignored
660 else
661 null;
662 end if;
664 Next_Entity (Prev);
665 end loop;
667 return Expr;
668 end Actual_Index_Expression;
670 --------------------------
671 -- Add_Formal_Renamings --
672 --------------------------
674 procedure Add_Formal_Renamings
675 (Spec : Node_Id;
676 Decls : List_Id;
677 Ent : Entity_Id;
678 Loc : Source_Ptr)
680 Ptr : constant Entity_Id :=
681 Defining_Identifier
682 (Next (First (Parameter_Specifications (Spec))));
683 -- The name of the formal that holds the address of the parameter block
684 -- for the call.
686 Comp : Entity_Id;
687 Decl : Node_Id;
688 Formal : Entity_Id;
689 New_F : Entity_Id;
690 Renamed_Formal : Node_Id;
692 begin
693 Formal := First_Formal (Ent);
694 while Present (Formal) loop
695 Comp := Entry_Component (Formal);
696 New_F :=
697 Make_Defining_Identifier (Sloc (Formal),
698 Chars => Chars (Formal));
699 Set_Etype (New_F, Etype (Formal));
700 Set_Scope (New_F, Ent);
702 -- Now we set debug info needed on New_F even though it does not
703 -- come from source, so that the debugger will get the right
704 -- information for these generated names.
706 Set_Debug_Info_Needed (New_F);
708 if Ekind (Formal) = E_In_Parameter then
709 Set_Ekind (New_F, E_Constant);
710 else
711 Set_Ekind (New_F, E_Variable);
712 Set_Extra_Constrained (New_F, Extra_Constrained (Formal));
713 end if;
715 Set_Actual_Subtype (New_F, Actual_Subtype (Formal));
717 Renamed_Formal :=
718 Make_Selected_Component (Loc,
719 Prefix =>
720 Unchecked_Convert_To (Entry_Parameters_Type (Ent),
721 Make_Identifier (Loc, Chars (Ptr))),
722 Selector_Name => New_Reference_To (Comp, Loc));
724 Decl :=
725 Build_Renamed_Formal_Declaration
726 (New_F, Formal, Comp, Renamed_Formal);
728 Append (Decl, Decls);
729 Set_Renamed_Object (Formal, New_F);
730 Next_Formal (Formal);
731 end loop;
732 end Add_Formal_Renamings;
734 ------------------------
735 -- Add_Object_Pointer --
736 ------------------------
738 procedure Add_Object_Pointer
739 (Loc : Source_Ptr;
740 Conc_Typ : Entity_Id;
741 Decls : List_Id)
743 Rec_Typ : constant Entity_Id := Corresponding_Record_Type (Conc_Typ);
744 Decl : Node_Id;
745 Obj_Ptr : Node_Id;
747 begin
748 -- Create the renaming declaration for the Protection object of a
749 -- protected type. _Object is used by Complete_Entry_Body.
750 -- ??? An attempt to make this a renaming was unsuccessful.
752 -- Build the entity for the access type
754 Obj_Ptr :=
755 Make_Defining_Identifier (Loc,
756 New_External_Name (Chars (Rec_Typ), 'P'));
758 -- Generate:
759 -- _object : poVP := poVP!O;
761 Decl :=
762 Make_Object_Declaration (Loc,
763 Defining_Identifier =>
764 Make_Defining_Identifier (Loc, Name_uObject),
765 Object_Definition =>
766 New_Reference_To (Obj_Ptr, Loc),
767 Expression =>
768 Unchecked_Convert_To (Obj_Ptr, Make_Identifier (Loc, Name_uO)));
769 Set_Debug_Info_Needed (Defining_Identifier (Decl));
770 Prepend_To (Decls, Decl);
772 -- Generate:
773 -- type poVP is access poV;
775 Decl :=
776 Make_Full_Type_Declaration (Loc,
777 Defining_Identifier =>
778 Obj_Ptr,
779 Type_Definition =>
780 Make_Access_To_Object_Definition (Loc,
781 Subtype_Indication =>
782 New_Reference_To (Rec_Typ, Loc)));
783 Set_Debug_Info_Needed (Defining_Identifier (Decl));
784 Prepend_To (Decls, Decl);
785 end Add_Object_Pointer;
787 -----------------------
788 -- Build_Accept_Body --
789 -----------------------
791 function Build_Accept_Body (Astat : Node_Id) return Node_Id is
792 Loc : constant Source_Ptr := Sloc (Astat);
793 Stats : constant Node_Id := Handled_Statement_Sequence (Astat);
794 New_S : Node_Id;
795 Hand : Node_Id;
796 Call : Node_Id;
797 Ohandle : Node_Id;
799 begin
800 -- At the end of the statement sequence, Complete_Rendezvous is called.
801 -- A label skipping the Complete_Rendezvous, and all other accept
802 -- processing, has already been added for the expansion of requeue
803 -- statements. The Sloc is copied from the last statement since it
804 -- is really part of this last statement.
806 Call :=
807 Build_Runtime_Call
808 (Sloc (Last (Statements (Stats))), RE_Complete_Rendezvous);
809 Insert_Before (Last (Statements (Stats)), Call);
810 Analyze (Call);
812 -- If exception handlers are present, then append Complete_Rendezvous
813 -- calls to the handlers, and construct the required outer block. As
814 -- above, the Sloc is copied from the last statement in the sequence.
816 if Present (Exception_Handlers (Stats)) then
817 Hand := First (Exception_Handlers (Stats));
818 while Present (Hand) loop
819 Call :=
820 Build_Runtime_Call
821 (Sloc (Last (Statements (Hand))), RE_Complete_Rendezvous);
822 Append (Call, Statements (Hand));
823 Analyze (Call);
824 Next (Hand);
825 end loop;
827 New_S :=
828 Make_Handled_Sequence_Of_Statements (Loc,
829 Statements => New_List (
830 Make_Block_Statement (Loc,
831 Handled_Statement_Sequence => Stats)));
833 else
834 New_S := Stats;
835 end if;
837 -- At this stage we know that the new statement sequence does not
838 -- have an exception handler part, so we supply one to call
839 -- Exceptional_Complete_Rendezvous. This handler is
841 -- when all others =>
842 -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
844 -- We handle Abort_Signal to make sure that we properly catch the abort
845 -- case and wake up the caller.
847 Ohandle := Make_Others_Choice (Loc);
848 Set_All_Others (Ohandle);
850 Set_Exception_Handlers (New_S,
851 New_List (
852 Make_Implicit_Exception_Handler (Loc,
853 Exception_Choices => New_List (Ohandle),
855 Statements => New_List (
856 Make_Procedure_Call_Statement (Sloc (Stats),
857 Name => New_Reference_To (
858 RTE (RE_Exceptional_Complete_Rendezvous), Sloc (Stats)),
859 Parameter_Associations => New_List (
860 Make_Function_Call (Sloc (Stats),
861 Name => New_Reference_To (
862 RTE (RE_Get_GNAT_Exception), Sloc (Stats)))))))));
864 Set_Parent (New_S, Astat); -- temp parent for Analyze call
865 Analyze_Exception_Handlers (Exception_Handlers (New_S));
866 Expand_Exception_Handlers (New_S);
868 -- Exceptional_Complete_Rendezvous must be called with abort
869 -- still deferred, which is the case for a "when all others" handler.
871 return New_S;
872 end Build_Accept_Body;
874 -----------------------------------
875 -- Build_Activation_Chain_Entity --
876 -----------------------------------
878 procedure Build_Activation_Chain_Entity (N : Node_Id) is
879 function Has_Activation_Chain (Stmt : Node_Id) return Boolean;
880 -- Determine whether an extended return statement has an activation
881 -- chain.
883 --------------------------
884 -- Has_Activation_Chain --
885 --------------------------
887 function Has_Activation_Chain (Stmt : Node_Id) return Boolean is
888 Decl : Node_Id;
890 begin
891 Decl := First (Return_Object_Declarations (Stmt));
892 while Present (Decl) loop
893 if Nkind (Decl) = N_Object_Declaration
894 and then Chars (Defining_Identifier (Decl)) = Name_uChain
895 then
896 return True;
897 end if;
899 Next (Decl);
900 end loop;
902 return False;
903 end Has_Activation_Chain;
905 -- Local variables
907 Context : Node_Id;
908 Context_Id : Entity_Id;
909 Decls : List_Id;
911 -- Start of processing for Build_Activation_Chain_Entity
913 begin
914 -- Activation chain is never used for sequential elaboration policy, see
915 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
917 if Partition_Elaboration_Policy = 'S' then
918 return;
919 end if;
921 Find_Enclosing_Context (N, Context, Context_Id, Decls);
923 -- If activation chain entity has not been declared already, create one
925 if Nkind (Context) = N_Extended_Return_Statement
926 or else No (Activation_Chain_Entity (Context))
927 then
928 -- Since extended return statements do not store the entity of the
929 -- chain, examine the return object declarations to avoid creating
930 -- a duplicate.
932 if Nkind (Context) = N_Extended_Return_Statement
933 and then Has_Activation_Chain (Context)
934 then
935 return;
936 end if;
938 declare
939 Loc : constant Source_Ptr := Sloc (Context);
940 Chain : Entity_Id;
941 Decl : Node_Id;
943 begin
944 Chain := Make_Defining_Identifier (Sloc (N), Name_uChain);
946 -- Note: An extended return statement is not really a task
947 -- activator, but it does have an activation chain on which to
948 -- store the tasks temporarily. On successful return, the tasks
949 -- on this chain are moved to the chain passed in by the caller.
950 -- We do not build an Activation_Chain_Entity for an extended
951 -- return statement, because we do not want to build a call to
952 -- Activate_Tasks. Task activation is the responsibility of the
953 -- caller.
955 if Nkind (Context) /= N_Extended_Return_Statement then
956 Set_Activation_Chain_Entity (Context, Chain);
957 end if;
959 Decl :=
960 Make_Object_Declaration (Loc,
961 Defining_Identifier => Chain,
962 Aliased_Present => True,
963 Object_Definition =>
964 New_Reference_To (RTE (RE_Activation_Chain), Loc));
966 Prepend_To (Decls, Decl);
968 -- Ensure that the _chain appears in the proper scope of the
969 -- context.
971 if Context_Id /= Current_Scope then
972 Push_Scope (Context_Id);
973 Analyze (Decl);
974 Pop_Scope;
975 else
976 Analyze (Decl);
977 end if;
978 end;
979 end if;
980 end Build_Activation_Chain_Entity;
982 ----------------------------
983 -- Build_Barrier_Function --
984 ----------------------------
986 function Build_Barrier_Function
987 (N : Node_Id;
988 Ent : Entity_Id;
989 Pid : Node_Id) return Node_Id
991 Ent_Formals : constant Node_Id := Entry_Body_Formal_Part (N);
992 Cond : constant Node_Id := Condition (Ent_Formals);
993 Loc : constant Source_Ptr := Sloc (Cond);
994 Func_Id : constant Entity_Id := Barrier_Function (Ent);
995 Op_Decls : constant List_Id := New_List;
996 Stmt : Node_Id;
997 Func_Body : Node_Id;
999 begin
1000 -- Add a declaration for the Protection object, renaming declarations
1001 -- for the discriminals and privals and finally a declaration for the
1002 -- entry family index (if applicable).
1004 Install_Private_Data_Declarations (Sloc (N),
1005 Spec_Id => Func_Id,
1006 Conc_Typ => Pid,
1007 Body_Nod => N,
1008 Decls => Op_Decls,
1009 Barrier => True,
1010 Family => Ekind (Ent) = E_Entry_Family);
1012 -- If compiling with -fpreserve-control-flow, make sure we insert an
1013 -- IF statement so that the back-end knows to generate a conditional
1014 -- branch instruction, even if the condition is just the name of a
1015 -- boolean object.
1017 if Opt.Suppress_Control_Flow_Optimizations then
1018 Stmt := Make_Implicit_If_Statement (Cond,
1019 Condition => Cond,
1020 Then_Statements => New_List (
1021 Make_Simple_Return_Statement (Loc,
1022 New_Occurrence_Of (Standard_True, Loc))),
1023 Else_Statements => New_List (
1024 Make_Simple_Return_Statement (Loc,
1025 New_Occurrence_Of (Standard_False, Loc))));
1027 else
1028 Stmt := Make_Simple_Return_Statement (Loc, Cond);
1029 end if;
1031 -- Note: the condition in the barrier function needs to be properly
1032 -- processed for the C/Fortran boolean possibility, but this happens
1033 -- automatically since the return statement does this normalization.
1035 Func_Body :=
1036 Make_Subprogram_Body (Loc,
1037 Specification =>
1038 Build_Barrier_Function_Specification (Loc,
1039 Make_Defining_Identifier (Loc, Chars (Func_Id))),
1040 Declarations => Op_Decls,
1041 Handled_Statement_Sequence =>
1042 Make_Handled_Sequence_Of_Statements (Loc,
1043 Statements => New_List (Stmt)));
1044 Set_Is_Entry_Barrier_Function (Func_Body);
1046 return Func_Body;
1047 end Build_Barrier_Function;
1049 ------------------------------------------
1050 -- Build_Barrier_Function_Specification --
1051 ------------------------------------------
1053 function Build_Barrier_Function_Specification
1054 (Loc : Source_Ptr;
1055 Def_Id : Entity_Id) return Node_Id
1057 begin
1058 Set_Debug_Info_Needed (Def_Id);
1060 return Make_Function_Specification (Loc,
1061 Defining_Unit_Name => Def_Id,
1062 Parameter_Specifications => New_List (
1063 Make_Parameter_Specification (Loc,
1064 Defining_Identifier =>
1065 Make_Defining_Identifier (Loc, Name_uO),
1066 Parameter_Type =>
1067 New_Reference_To (RTE (RE_Address), Loc)),
1069 Make_Parameter_Specification (Loc,
1070 Defining_Identifier =>
1071 Make_Defining_Identifier (Loc, Name_uE),
1072 Parameter_Type =>
1073 New_Reference_To (RTE (RE_Protected_Entry_Index), Loc))),
1075 Result_Definition =>
1076 New_Reference_To (Standard_Boolean, Loc));
1077 end Build_Barrier_Function_Specification;
1079 --------------------------
1080 -- Build_Call_With_Task --
1081 --------------------------
1083 function Build_Call_With_Task
1084 (N : Node_Id;
1085 E : Entity_Id) return Node_Id
1087 Loc : constant Source_Ptr := Sloc (N);
1088 begin
1089 return
1090 Make_Function_Call (Loc,
1091 Name => New_Reference_To (E, Loc),
1092 Parameter_Associations => New_List (Concurrent_Ref (N)));
1093 end Build_Call_With_Task;
1095 -----------------------------
1096 -- Build_Class_Wide_Master --
1097 -----------------------------
1099 procedure Build_Class_Wide_Master (Typ : Entity_Id) is
1100 Loc : constant Source_Ptr := Sloc (Typ);
1101 Master_Id : Entity_Id;
1102 Master_Scope : Entity_Id;
1103 Name_Id : Node_Id;
1104 Related_Node : Node_Id;
1105 Ren_Decl : Node_Id;
1107 begin
1108 -- Nothing to do if there is no task hierarchy
1110 if Restriction_Active (No_Task_Hierarchy) then
1111 return;
1112 end if;
1114 -- Find the declaration that created the access type. It is either a
1115 -- type declaration, or an object declaration with an access definition,
1116 -- in which case the type is anonymous.
1118 if Is_Itype (Typ) then
1119 Related_Node := Associated_Node_For_Itype (Typ);
1120 else
1121 Related_Node := Parent (Typ);
1122 end if;
1124 Master_Scope := Find_Master_Scope (Typ);
1126 -- Nothing to do if the master scope already contains a _master entity.
1127 -- The only exception to this is the following scenario:
1129 -- Source_Scope
1130 -- Transient_Scope_1
1131 -- _master
1133 -- Transient_Scope_2
1134 -- use of master
1136 -- In this case the source scope is marked as having the master entity
1137 -- even though the actual declaration appears inside an inner scope. If
1138 -- the second transient scope requires a _master, it cannot use the one
1139 -- already declared because the entity is not visible.
1141 Name_Id := Make_Identifier (Loc, Name_uMaster);
1143 if not Has_Master_Entity (Master_Scope)
1144 or else No (Current_Entity_In_Scope (Name_Id))
1145 then
1146 declare
1147 Master_Decl : Node_Id;
1149 begin
1150 Set_Has_Master_Entity (Master_Scope);
1152 -- Generate:
1153 -- _master : constant Integer := Current_Master.all;
1155 Master_Decl :=
1156 Make_Object_Declaration (Loc,
1157 Defining_Identifier =>
1158 Make_Defining_Identifier (Loc, Name_uMaster),
1159 Constant_Present => True,
1160 Object_Definition =>
1161 New_Reference_To (Standard_Integer, Loc),
1162 Expression =>
1163 Make_Explicit_Dereference (Loc,
1164 New_Reference_To (RTE (RE_Current_Master), Loc)));
1166 Insert_Action (Related_Node, Master_Decl);
1167 Analyze (Master_Decl);
1169 -- Mark the containing scope as a task master. Masters associated
1170 -- with return statements are already marked at this stage (see
1171 -- Analyze_Subprogram_Body).
1173 if Ekind (Current_Scope) /= E_Return_Statement then
1174 declare
1175 Par : Node_Id := Related_Node;
1177 begin
1178 while Nkind (Par) /= N_Compilation_Unit loop
1179 Par := Parent (Par);
1181 -- If we fall off the top, we are at the outer level, and
1182 -- the environment task is our effective master, so
1183 -- nothing to mark.
1185 if Nkind_In (Par, N_Block_Statement,
1186 N_Subprogram_Body,
1187 N_Task_Body)
1188 then
1189 Set_Is_Task_Master (Par);
1190 exit;
1191 end if;
1192 end loop;
1193 end;
1194 end if;
1195 end;
1196 end if;
1198 Master_Id :=
1199 Make_Defining_Identifier (Loc,
1200 New_External_Name (Chars (Typ), 'M'));
1202 -- Generate:
1203 -- Mnn renames _master;
1205 Ren_Decl :=
1206 Make_Object_Renaming_Declaration (Loc,
1207 Defining_Identifier => Master_Id,
1208 Subtype_Mark => New_Reference_To (Standard_Integer, Loc),
1209 Name => Name_Id);
1211 Insert_Action (Related_Node, Ren_Decl);
1213 Set_Master_Id (Typ, Master_Id);
1214 end Build_Class_Wide_Master;
1216 --------------------------------
1217 -- Build_Corresponding_Record --
1218 --------------------------------
1220 function Build_Corresponding_Record
1221 (N : Node_Id;
1222 Ctyp : Entity_Id;
1223 Loc : Source_Ptr) return Node_Id
1225 Rec_Ent : constant Entity_Id :=
1226 Make_Defining_Identifier
1227 (Loc, New_External_Name (Chars (Ctyp), 'V'));
1228 Disc : Entity_Id;
1229 Dlist : List_Id;
1230 New_Disc : Entity_Id;
1231 Cdecls : List_Id;
1233 begin
1234 Set_Corresponding_Record_Type (Ctyp, Rec_Ent);
1235 Set_Ekind (Rec_Ent, E_Record_Type);
1236 Set_Has_Delayed_Freeze (Rec_Ent, Has_Delayed_Freeze (Ctyp));
1237 Set_Is_Concurrent_Record_Type (Rec_Ent, True);
1238 Set_Corresponding_Concurrent_Type (Rec_Ent, Ctyp);
1239 Set_Stored_Constraint (Rec_Ent, No_Elist);
1240 Cdecls := New_List;
1242 -- Use discriminals to create list of discriminants for record, and
1243 -- create new discriminals for use in default expressions, etc. It is
1244 -- worth noting that a task discriminant gives rise to 5 entities;
1246 -- a) The original discriminant.
1247 -- b) The discriminal for use in the task.
1248 -- c) The discriminant of the corresponding record.
1249 -- d) The discriminal for the init proc of the corresponding record.
1250 -- e) The local variable that renames the discriminant in the procedure
1251 -- for the task body.
1253 -- In fact the discriminals b) are used in the renaming declarations
1254 -- for e). See details in einfo (Handling of Discriminants).
1256 if Present (Discriminant_Specifications (N)) then
1257 Dlist := New_List;
1258 Disc := First_Discriminant (Ctyp);
1260 while Present (Disc) loop
1261 New_Disc := CR_Discriminant (Disc);
1263 Append_To (Dlist,
1264 Make_Discriminant_Specification (Loc,
1265 Defining_Identifier => New_Disc,
1266 Discriminant_Type =>
1267 New_Occurrence_Of (Etype (Disc), Loc),
1268 Expression =>
1269 New_Copy (Discriminant_Default_Value (Disc))));
1271 Next_Discriminant (Disc);
1272 end loop;
1274 else
1275 Dlist := No_List;
1276 end if;
1278 -- Now we can construct the record type declaration. Note that this
1279 -- record is "limited tagged". It is "limited" to reflect the underlying
1280 -- limitedness of the task or protected object that it represents, and
1281 -- ensuring for example that it is properly passed by reference. It is
1282 -- "tagged" to give support to dispatching calls through interfaces. We
1283 -- propagate here the list of interfaces covered by the concurrent type
1284 -- (Ada 2005: AI-345).
1286 return
1287 Make_Full_Type_Declaration (Loc,
1288 Defining_Identifier => Rec_Ent,
1289 Discriminant_Specifications => Dlist,
1290 Type_Definition =>
1291 Make_Record_Definition (Loc,
1292 Component_List =>
1293 Make_Component_List (Loc,
1294 Component_Items => Cdecls),
1295 Tagged_Present =>
1296 Ada_Version >= Ada_2005 and then Is_Tagged_Type (Ctyp),
1297 Interface_List => Interface_List (N),
1298 Limited_Present => True));
1299 end Build_Corresponding_Record;
1301 ----------------------------------
1302 -- Build_Entry_Count_Expression --
1303 ----------------------------------
1305 function Build_Entry_Count_Expression
1306 (Concurrent_Type : Node_Id;
1307 Component_List : List_Id;
1308 Loc : Source_Ptr) return Node_Id
1310 Eindx : Nat;
1311 Ent : Entity_Id;
1312 Ecount : Node_Id;
1313 Comp : Node_Id;
1314 Lo : Node_Id;
1315 Hi : Node_Id;
1316 Typ : Entity_Id;
1317 Large : Boolean;
1319 begin
1320 -- Count number of non-family entries
1322 Eindx := 0;
1323 Ent := First_Entity (Concurrent_Type);
1324 while Present (Ent) loop
1325 if Ekind (Ent) = E_Entry then
1326 Eindx := Eindx + 1;
1327 end if;
1329 Next_Entity (Ent);
1330 end loop;
1332 Ecount := Make_Integer_Literal (Loc, Eindx);
1334 -- Loop through entry families building the addition nodes
1336 Ent := First_Entity (Concurrent_Type);
1337 Comp := First (Component_List);
1338 while Present (Ent) loop
1339 if Ekind (Ent) = E_Entry_Family then
1340 while Chars (Ent) /= Chars (Defining_Identifier (Comp)) loop
1341 Next (Comp);
1342 end loop;
1344 Typ := Etype (Discrete_Subtype_Definition (Parent (Ent)));
1345 Hi := Type_High_Bound (Typ);
1346 Lo := Type_Low_Bound (Typ);
1347 Large := Is_Potentially_Large_Family
1348 (Base_Type (Typ), Concurrent_Type, Lo, Hi);
1349 Ecount :=
1350 Make_Op_Add (Loc,
1351 Left_Opnd => Ecount,
1352 Right_Opnd => Family_Size
1353 (Loc, Hi, Lo, Concurrent_Type, Large));
1354 end if;
1356 Next_Entity (Ent);
1357 end loop;
1359 return Ecount;
1360 end Build_Entry_Count_Expression;
1362 -----------------------
1363 -- Build_Entry_Names --
1364 -----------------------
1366 procedure Build_Entry_Names
1367 (Obj_Ref : Node_Id;
1368 Obj_Typ : Entity_Id;
1369 Stmts : List_Id)
1371 Loc : constant Source_Ptr := Sloc (Obj_Ref);
1372 Data : Entity_Id := Empty;
1373 Index : Entity_Id := Empty;
1374 Typ : Entity_Id := Obj_Typ;
1376 procedure Build_Entry_Name (Comp_Id : Entity_Id);
1377 -- Given an entry [family], create a static string which denotes the
1378 -- name of Comp_Id and assign it to the underlying data structure which
1379 -- contains the entry names of a concurrent object.
1381 function Object_Reference return Node_Id;
1382 -- Return a reference to field _object or _task_id depending on the
1383 -- concurrent object being processed.
1385 ----------------------
1386 -- Build_Entry_Name --
1387 ----------------------
1389 procedure Build_Entry_Name (Comp_Id : Entity_Id) is
1390 function Build_Range (Def : Node_Id) return Node_Id;
1391 -- Given a discrete subtype definition of an entry family, generate a
1392 -- range node which covers the range of Def's type.
1394 procedure Create_Index_And_Data;
1395 -- Generate the declarations of variables Index and Data. Subsequent
1396 -- calls do nothing.
1398 function Increment_Index return Node_Id;
1399 -- Increment the index used in the assignment of string names to the
1400 -- Data array.
1402 function Name_Declaration (Def_Id : Entity_Id) return Node_Id;
1403 -- Given the name of a temporary variable, create the following
1404 -- declaration for it:
1406 -- Def_Id : aliased constant String := <String_Name_From_Buffer>;
1408 function Set_Entry_Name (Def_Id : Entity_Id) return Node_Id;
1409 -- Given the name of a temporary variable, place it in the array of
1410 -- string names. Generate:
1412 -- Data (Index) := Def_Id'Unchecked_Access;
1414 -----------------
1415 -- Build_Range --
1416 -----------------
1418 function Build_Range (Def : Node_Id) return Node_Id is
1419 High : Node_Id := Type_High_Bound (Etype (Def));
1420 Low : Node_Id := Type_Low_Bound (Etype (Def));
1422 begin
1423 -- If a bound references a discriminant, generate an identifier
1424 -- with the same name. Resolution will map it to the formals of
1425 -- the init proc.
1427 if Is_Entity_Name (Low)
1428 and then Ekind (Entity (Low)) = E_Discriminant
1429 then
1430 Low :=
1431 Make_Selected_Component (Loc,
1432 Prefix => New_Copy_Tree (Obj_Ref),
1433 Selector_Name => Make_Identifier (Loc, Chars (Low)));
1434 else
1435 Low := New_Copy_Tree (Low);
1436 end if;
1438 if Is_Entity_Name (High)
1439 and then Ekind (Entity (High)) = E_Discriminant
1440 then
1441 High :=
1442 Make_Selected_Component (Loc,
1443 Prefix => New_Copy_Tree (Obj_Ref),
1444 Selector_Name => Make_Identifier (Loc, Chars (High)));
1445 else
1446 High := New_Copy_Tree (High);
1447 end if;
1449 return
1450 Make_Range (Loc,
1451 Low_Bound => Low,
1452 High_Bound => High);
1453 end Build_Range;
1455 ---------------------------
1456 -- Create_Index_And_Data --
1457 ---------------------------
1459 procedure Create_Index_And_Data is
1460 begin
1461 if No (Index) and then No (Data) then
1462 declare
1463 Count : RE_Id;
1464 Data_Typ : RE_Id;
1465 Size : Entity_Id;
1467 begin
1468 if Is_Protected_Type (Typ) then
1469 Count := RO_PE_Number_Of_Entries;
1470 Data_Typ := RE_Protected_Entry_Names_Array;
1471 else
1472 Count := RO_ST_Number_Of_Entries;
1473 Data_Typ := RE_Task_Entry_Names_Array;
1474 end if;
1476 -- Step 1: Generate the declaration of the index variable:
1478 -- Index : Entry_Index := 1;
1480 Index := Make_Temporary (Loc, 'I');
1482 Append_To (Stmts,
1483 Make_Object_Declaration (Loc,
1484 Defining_Identifier => Index,
1485 Object_Definition =>
1486 New_Reference_To (RTE (RE_Entry_Index), Loc),
1487 Expression => Make_Integer_Literal (Loc, 1)));
1489 -- Step 2: Generate the declaration of an array to house all
1490 -- names:
1492 -- Size : constant Entry_Index := <Count> (Obj_Ref);
1493 -- Data : aliased <Data_Typ> := (1 .. Size => null);
1495 Size := Make_Temporary (Loc, 'S');
1497 Append_To (Stmts,
1498 Make_Object_Declaration (Loc,
1499 Defining_Identifier => Size,
1500 Constant_Present => True,
1501 Object_Definition =>
1502 New_Reference_To (RTE (RE_Entry_Index), Loc),
1503 Expression =>
1504 Make_Function_Call (Loc,
1505 Name =>
1506 New_Reference_To (RTE (Count), Loc),
1507 Parameter_Associations =>
1508 New_List (Object_Reference))));
1510 Data := Make_Temporary (Loc, 'A');
1512 Append_To (Stmts,
1513 Make_Object_Declaration (Loc,
1514 Defining_Identifier => Data,
1515 Aliased_Present => True,
1516 Object_Definition =>
1517 New_Reference_To (RTE (Data_Typ), Loc),
1518 Expression =>
1519 Make_Aggregate (Loc,
1520 Component_Associations => New_List (
1521 Make_Component_Association (Loc,
1522 Choices => New_List (
1523 Make_Range (Loc,
1524 Low_Bound => Make_Integer_Literal (Loc, 1),
1525 High_Bound => New_Reference_To (Size, Loc))),
1526 Expression => Make_Null (Loc))))));
1527 end;
1528 end if;
1529 end Create_Index_And_Data;
1531 ---------------------
1532 -- Increment_Index --
1533 ---------------------
1535 function Increment_Index return Node_Id is
1536 begin
1537 return
1538 Make_Assignment_Statement (Loc,
1539 Name => New_Reference_To (Index, Loc),
1540 Expression =>
1541 Make_Op_Add (Loc,
1542 Left_Opnd => New_Reference_To (Index, Loc),
1543 Right_Opnd => Make_Integer_Literal (Loc, 1)));
1544 end Increment_Index;
1546 ----------------------
1547 -- Name_Declaration --
1548 ----------------------
1550 function Name_Declaration (Def_Id : Entity_Id) return Node_Id is
1551 begin
1552 return
1553 Make_Object_Declaration (Loc,
1554 Defining_Identifier => Def_Id,
1555 Aliased_Present => True,
1556 Constant_Present => True,
1557 Object_Definition => New_Reference_To (Standard_String, Loc),
1558 Expression =>
1559 Make_String_Literal (Loc, String_From_Name_Buffer));
1560 end Name_Declaration;
1562 --------------------
1563 -- Set_Entry_Name --
1564 --------------------
1566 function Set_Entry_Name (Def_Id : Entity_Id) return Node_Id is
1567 begin
1568 return
1569 Make_Assignment_Statement (Loc,
1570 Name =>
1571 Make_Indexed_Component (Loc,
1572 Prefix => New_Reference_To (Data, Loc),
1573 Expressions => New_List (New_Reference_To (Index, Loc))),
1575 Expression =>
1576 Make_Attribute_Reference (Loc,
1577 Prefix => New_Reference_To (Def_Id, Loc),
1578 Attribute_Name => Name_Unchecked_Access));
1579 end Set_Entry_Name;
1581 -- Local variables
1583 Temp_Id : Entity_Id;
1584 Subt_Def : Node_Id;
1586 -- Start of processing for Build_Entry_Name
1588 begin
1589 if Ekind (Comp_Id) = E_Entry_Family then
1590 Subt_Def := Discrete_Subtype_Definition (Parent (Comp_Id));
1592 Create_Index_And_Data;
1594 -- Step 1: Create the string name of the entry family.
1595 -- Generate:
1596 -- Temp : aliased constant String := "name ()";
1598 Temp_Id := Make_Temporary (Loc, 'S');
1599 Get_Name_String (Chars (Comp_Id));
1600 Add_Char_To_Name_Buffer (' ');
1601 Add_Char_To_Name_Buffer ('(');
1602 Add_Char_To_Name_Buffer (')');
1604 Append_To (Stmts, Name_Declaration (Temp_Id));
1606 -- Generate:
1607 -- for Member in Family_Low .. Family_High loop
1608 -- Set_Entry_Name (...);
1609 -- Index := Index + 1;
1610 -- end loop;
1612 Append_To (Stmts,
1613 Make_Loop_Statement (Loc,
1614 Iteration_Scheme =>
1615 Make_Iteration_Scheme (Loc,
1616 Loop_Parameter_Specification =>
1617 Make_Loop_Parameter_Specification (Loc,
1618 Defining_Identifier =>
1619 Make_Temporary (Loc, 'L'),
1620 Discrete_Subtype_Definition =>
1621 Build_Range (Subt_Def))),
1623 Statements => New_List (
1624 Set_Entry_Name (Temp_Id),
1625 Increment_Index),
1626 End_Label => Empty));
1628 -- Entry
1630 else
1631 Create_Index_And_Data;
1633 -- Step 1: Create the string name of the entry. Generate:
1634 -- Temp : aliased constant String := "name";
1636 Temp_Id := Make_Temporary (Loc, 'S');
1637 Get_Name_String (Chars (Comp_Id));
1639 Append_To (Stmts, Name_Declaration (Temp_Id));
1641 -- Step 2: Associate the string name with the underlying data
1642 -- structure.
1644 Append_To (Stmts, Set_Entry_Name (Temp_Id));
1645 Append_To (Stmts, Increment_Index);
1646 end if;
1647 end Build_Entry_Name;
1649 ----------------------
1650 -- Object_Reference --
1651 ----------------------
1653 function Object_Reference return Node_Id is
1654 Conc_Typ : constant Entity_Id := Corresponding_Record_Type (Typ);
1655 Field : Name_Id;
1656 Ref : Node_Id;
1658 begin
1659 if Is_Protected_Type (Typ) then
1660 Field := Name_uObject;
1661 else
1662 Field := Name_uTask_Id;
1663 end if;
1665 Ref :=
1666 Make_Selected_Component (Loc,
1667 Prefix =>
1668 Unchecked_Convert_To (Conc_Typ, New_Copy_Tree (Obj_Ref)),
1669 Selector_Name => Make_Identifier (Loc, Field));
1671 if Is_Protected_Type (Typ) then
1672 Ref :=
1673 Make_Attribute_Reference (Loc,
1674 Prefix => Ref,
1675 Attribute_Name => Name_Unchecked_Access);
1676 end if;
1678 return Ref;
1679 end Object_Reference;
1681 -- Local variables
1683 Comp : Node_Id;
1684 Proc : RE_Id;
1686 -- Start of processing for Build_Entry_Names
1688 begin
1689 -- Retrieve the original concurrent type
1691 if Is_Concurrent_Record_Type (Typ) then
1692 Typ := Corresponding_Concurrent_Type (Typ);
1693 end if;
1695 pragma Assert (Is_Concurrent_Type (Typ));
1697 -- Nothing to do if the type has no entries
1699 if not Has_Entries (Typ) then
1700 return;
1701 end if;
1703 -- Avoid generating entry names for a protected type with only one entry
1705 if Is_Protected_Type (Typ)
1706 and then Find_Protection_Type (Base_Type (Typ)) /=
1707 RTE (RE_Protection_Entries)
1708 then
1709 return;
1710 end if;
1712 -- Step 1: Populate the array with statically generated strings denoting
1713 -- entries and entry family names.
1715 Comp := First_Entity (Typ);
1716 while Present (Comp) loop
1717 if Comes_From_Source (Comp)
1718 and then Ekind_In (Comp, E_Entry, E_Entry_Family)
1719 then
1720 Build_Entry_Name (Comp);
1721 end if;
1723 Next_Entity (Comp);
1724 end loop;
1726 -- Step 2: Associate the array with the related concurrent object:
1728 -- Set_Entry_Names (Obj_Ref, <Data>'Unchecked_Access);
1730 if Present (Data) then
1731 if Is_Protected_Type (Typ) then
1732 Proc := RO_PE_Set_Entry_Names;
1733 else
1734 Proc := RO_ST_Set_Entry_Names;
1735 end if;
1737 Append_To (Stmts,
1738 Make_Procedure_Call_Statement (Loc,
1739 Name => New_Reference_To (RTE (Proc), Loc),
1740 Parameter_Associations => New_List (
1741 Object_Reference,
1742 Make_Attribute_Reference (Loc,
1743 Prefix => New_Reference_To (Data, Loc),
1744 Attribute_Name => Name_Unchecked_Access))));
1745 end if;
1746 end Build_Entry_Names;
1748 ---------------------------
1749 -- Build_Parameter_Block --
1750 ---------------------------
1752 function Build_Parameter_Block
1753 (Loc : Source_Ptr;
1754 Actuals : List_Id;
1755 Formals : List_Id;
1756 Decls : List_Id) return Entity_Id
1758 Actual : Entity_Id;
1759 Comp_Nam : Node_Id;
1760 Comps : List_Id;
1761 Formal : Entity_Id;
1762 Has_Comp : Boolean := False;
1763 Rec_Nam : Node_Id;
1765 begin
1766 Actual := First (Actuals);
1767 Comps := New_List;
1768 Formal := Defining_Identifier (First (Formals));
1770 while Present (Actual) loop
1771 if not Is_Controlling_Actual (Actual) then
1773 -- Generate:
1774 -- type Ann is access all <actual-type>
1776 Comp_Nam := Make_Temporary (Loc, 'A');
1778 Append_To (Decls,
1779 Make_Full_Type_Declaration (Loc,
1780 Defining_Identifier => Comp_Nam,
1781 Type_Definition =>
1782 Make_Access_To_Object_Definition (Loc,
1783 All_Present => True,
1784 Constant_Present => Ekind (Formal) = E_In_Parameter,
1785 Subtype_Indication =>
1786 New_Reference_To (Etype (Actual), Loc))));
1788 -- Generate:
1789 -- Param : Ann;
1791 Append_To (Comps,
1792 Make_Component_Declaration (Loc,
1793 Defining_Identifier =>
1794 Make_Defining_Identifier (Loc, Chars (Formal)),
1795 Component_Definition =>
1796 Make_Component_Definition (Loc,
1797 Aliased_Present =>
1798 False,
1799 Subtype_Indication =>
1800 New_Reference_To (Comp_Nam, Loc))));
1802 Has_Comp := True;
1803 end if;
1805 Next_Actual (Actual);
1806 Next_Formal_With_Extras (Formal);
1807 end loop;
1809 Rec_Nam := Make_Temporary (Loc, 'P');
1811 if Has_Comp then
1813 -- Generate:
1814 -- type Pnn is record
1815 -- Param1 : Ann1;
1816 -- ...
1817 -- ParamN : AnnN;
1819 -- where Pnn is a parameter wrapping record, Param1 .. ParamN are
1820 -- the original parameter names and Ann1 .. AnnN are the access to
1821 -- actual types.
1823 Append_To (Decls,
1824 Make_Full_Type_Declaration (Loc,
1825 Defining_Identifier =>
1826 Rec_Nam,
1827 Type_Definition =>
1828 Make_Record_Definition (Loc,
1829 Component_List =>
1830 Make_Component_List (Loc, Comps))));
1831 else
1832 -- Generate:
1833 -- type Pnn is null record;
1835 Append_To (Decls,
1836 Make_Full_Type_Declaration (Loc,
1837 Defining_Identifier =>
1838 Rec_Nam,
1839 Type_Definition =>
1840 Make_Record_Definition (Loc,
1841 Null_Present => True,
1842 Component_List => Empty)));
1843 end if;
1845 return Rec_Nam;
1846 end Build_Parameter_Block;
1848 --------------------------------------
1849 -- Build_Renamed_Formal_Declaration --
1850 --------------------------------------
1852 function Build_Renamed_Formal_Declaration
1853 (New_F : Entity_Id;
1854 Formal : Entity_Id;
1855 Comp : Entity_Id;
1856 Renamed_Formal : Node_Id) return Node_Id
1858 Loc : constant Source_Ptr := Sloc (New_F);
1859 Decl : Node_Id;
1861 begin
1862 -- If the formal is a tagged incomplete type, it is already passed
1863 -- by reference, so it is sufficient to rename the pointer component
1864 -- that corresponds to the actual. Otherwise we need to dereference
1865 -- the pointer component to obtain the actual.
1867 if Is_Incomplete_Type (Etype (Formal))
1868 and then Is_Tagged_Type (Etype (Formal))
1869 then
1870 Decl :=
1871 Make_Object_Renaming_Declaration (Loc,
1872 Defining_Identifier => New_F,
1873 Subtype_Mark => New_Reference_To (Etype (Comp), Loc),
1874 Name => Renamed_Formal);
1876 else
1877 Decl :=
1878 Make_Object_Renaming_Declaration (Loc,
1879 Defining_Identifier => New_F,
1880 Subtype_Mark => New_Reference_To (Etype (Formal), Loc),
1881 Name =>
1882 Make_Explicit_Dereference (Loc, Renamed_Formal));
1883 end if;
1885 return Decl;
1886 end Build_Renamed_Formal_Declaration;
1888 -----------------------
1889 -- Build_PPC_Wrapper --
1890 -----------------------
1892 procedure Build_PPC_Wrapper (E : Entity_Id; Decl : Node_Id) is
1893 Loc : constant Source_Ptr := Sloc (E);
1894 Synch_Type : constant Entity_Id := Scope (E);
1896 Wrapper_Id : constant Entity_Id :=
1897 Make_Defining_Identifier (Loc,
1898 Chars => New_External_Name (Chars (E), 'E'));
1899 -- the wrapper procedure name
1901 Wrapper_Body : Node_Id;
1903 Synch_Id : constant Entity_Id :=
1904 Make_Defining_Identifier (Loc,
1905 Chars => New_External_Name (Chars (Scope (E)), 'A'));
1906 -- The parameter that designates the synchronized object in the call
1908 Actuals : constant List_Id := New_List;
1909 -- The actuals in the entry call
1911 Decls : constant List_Id := New_List;
1913 Entry_Call : Node_Id;
1914 Entry_Name : Node_Id;
1916 Specs : List_Id;
1917 -- The specification of the wrapper procedure
1919 begin
1921 -- Only build the wrapper if entry has pre/postconditions.
1922 -- Should this be done unconditionally instead ???
1924 declare
1925 P : Node_Id;
1927 begin
1928 P := Pre_Post_Conditions (Contract (E));
1930 if No (P) then
1931 return;
1932 end if;
1934 -- Transfer ppc pragmas to the declarations of the wrapper
1936 while Present (P) loop
1937 if Nam_In (Pragma_Name (P), Name_Precondition,
1938 Name_Postcondition)
1939 then
1940 Append (Relocate_Node (P), Decls);
1941 Set_Analyzed (Last (Decls), False);
1942 end if;
1944 P := Next_Pragma (P);
1945 end loop;
1946 end;
1948 -- First formal is synchronized object
1950 Specs := New_List (
1951 Make_Parameter_Specification (Loc,
1952 Defining_Identifier => Synch_Id,
1953 Out_Present => True,
1954 In_Present => True,
1955 Parameter_Type => New_Occurrence_Of (Scope (E), Loc)));
1957 Entry_Name :=
1958 Make_Selected_Component (Loc,
1959 Prefix => New_Occurrence_Of (Synch_Id, Loc),
1960 Selector_Name => New_Occurrence_Of (E, Loc));
1962 -- If entity is entry family, second formal is the corresponding index,
1963 -- and entry name is an indexed component.
1965 if Ekind (E) = E_Entry_Family then
1966 declare
1967 Index : constant Entity_Id :=
1968 Make_Defining_Identifier (Loc, Name_I);
1969 begin
1970 Append_To (Specs,
1971 Make_Parameter_Specification (Loc,
1972 Defining_Identifier => Index,
1973 Parameter_Type =>
1974 New_Occurrence_Of (Entry_Index_Type (E), Loc)));
1976 Entry_Name :=
1977 Make_Indexed_Component (Loc,
1978 Prefix => Entry_Name,
1979 Expressions => New_List (New_Occurrence_Of (Index, Loc)));
1980 end;
1981 end if;
1983 Entry_Call :=
1984 Make_Procedure_Call_Statement (Loc,
1985 Name => Entry_Name,
1986 Parameter_Associations => Actuals);
1988 -- Now add formals that match those of the entry, and build actuals for
1989 -- the nested entry call.
1991 declare
1992 Form : Entity_Id;
1993 New_Form : Entity_Id;
1994 Parm_Spec : Node_Id;
1996 begin
1997 Form := First_Formal (E);
1998 while Present (Form) loop
1999 New_Form := Make_Defining_Identifier (Loc, Chars (Form));
2000 Parm_Spec :=
2001 Make_Parameter_Specification (Loc,
2002 Defining_Identifier => New_Form,
2003 Out_Present => Out_Present (Parent (Form)),
2004 In_Present => In_Present (Parent (Form)),
2005 Parameter_Type => New_Occurrence_Of (Etype (Form), Loc));
2007 Append (Parm_Spec, Specs);
2008 Append (New_Occurrence_Of (New_Form, Loc), Actuals);
2009 Next_Formal (Form);
2010 end loop;
2011 end;
2013 -- Add renaming declarations for the discriminants of the enclosing
2014 -- type, which may be visible in the preconditions.
2016 if Has_Discriminants (Synch_Type) then
2017 declare
2018 D : Entity_Id;
2019 Decl : Node_Id;
2021 begin
2022 D := First_Discriminant (Synch_Type);
2023 while Present (D) loop
2024 Decl :=
2025 Make_Object_Renaming_Declaration (Loc,
2026 Defining_Identifier =>
2027 Make_Defining_Identifier (Loc, Chars (D)),
2028 Subtype_Mark => New_Reference_To (Etype (D), Loc),
2029 Name =>
2030 Make_Selected_Component (Loc,
2031 Prefix => New_Reference_To (Synch_Id, Loc),
2032 Selector_Name => Make_Identifier (Loc, Chars (D))));
2033 Prepend (Decl, Decls);
2034 Next_Discriminant (D);
2035 end loop;
2036 end;
2037 end if;
2039 Set_PPC_Wrapper (E, Wrapper_Id);
2040 Wrapper_Body :=
2041 Make_Subprogram_Body (Loc,
2042 Specification =>
2043 Make_Procedure_Specification (Loc,
2044 Defining_Unit_Name => Wrapper_Id,
2045 Parameter_Specifications => Specs),
2046 Declarations => Decls,
2047 Handled_Statement_Sequence =>
2048 Make_Handled_Sequence_Of_Statements (Loc,
2049 Statements => New_List (Entry_Call)));
2051 -- The wrapper body is analyzed when the enclosing type is frozen
2053 Append_Freeze_Action (Defining_Entity (Decl), Wrapper_Body);
2054 end Build_PPC_Wrapper;
2056 --------------------------
2057 -- Build_Wrapper_Bodies --
2058 --------------------------
2060 procedure Build_Wrapper_Bodies
2061 (Loc : Source_Ptr;
2062 Typ : Entity_Id;
2063 N : Node_Id)
2065 Rec_Typ : Entity_Id;
2067 function Build_Wrapper_Body
2068 (Loc : Source_Ptr;
2069 Subp_Id : Entity_Id;
2070 Obj_Typ : Entity_Id;
2071 Formals : List_Id) return Node_Id;
2072 -- Ada 2005 (AI-345): Build the body that wraps a primitive operation
2073 -- associated with a protected or task type. Subp_Id is the subprogram
2074 -- name which will be wrapped. Obj_Typ is the type of the new formal
2075 -- parameter which handles dispatching and object notation. Formals are
2076 -- the original formals of Subp_Id which will be explicitly replicated.
2078 ------------------------
2079 -- Build_Wrapper_Body --
2080 ------------------------
2082 function Build_Wrapper_Body
2083 (Loc : Source_Ptr;
2084 Subp_Id : Entity_Id;
2085 Obj_Typ : Entity_Id;
2086 Formals : List_Id) return Node_Id
2088 Body_Spec : Node_Id;
2090 begin
2091 Body_Spec := Build_Wrapper_Spec (Subp_Id, Obj_Typ, Formals);
2093 -- The subprogram is not overriding or is not a primitive declared
2094 -- between two views.
2096 if No (Body_Spec) then
2097 return Empty;
2098 end if;
2100 declare
2101 Actuals : List_Id := No_List;
2102 Conv_Id : Node_Id;
2103 First_Form : Node_Id;
2104 Formal : Node_Id;
2105 Nam : Node_Id;
2107 begin
2108 -- Map formals to actuals. Use the list built for the wrapper
2109 -- spec, skipping the object notation parameter.
2111 First_Form := First (Parameter_Specifications (Body_Spec));
2113 Formal := First_Form;
2114 Next (Formal);
2116 if Present (Formal) then
2117 Actuals := New_List;
2118 while Present (Formal) loop
2119 Append_To (Actuals,
2120 Make_Identifier (Loc,
2121 Chars => Chars (Defining_Identifier (Formal))));
2122 Next (Formal);
2123 end loop;
2124 end if;
2126 -- Special processing for primitives declared between a private
2127 -- type and its completion: the wrapper needs a properly typed
2128 -- parameter if the wrapped operation has a controlling first
2129 -- parameter. Note that this might not be the case for a function
2130 -- with a controlling result.
2132 if Is_Private_Primitive_Subprogram (Subp_Id) then
2133 if No (Actuals) then
2134 Actuals := New_List;
2135 end if;
2137 if Is_Controlling_Formal (First_Formal (Subp_Id)) then
2138 Prepend_To (Actuals,
2139 Unchecked_Convert_To
2140 (Corresponding_Concurrent_Type (Obj_Typ),
2141 Make_Identifier (Loc, Name_uO)));
2143 else
2144 Prepend_To (Actuals,
2145 Make_Identifier (Loc,
2146 Chars => Chars (Defining_Identifier (First_Form))));
2147 end if;
2149 Nam := New_Reference_To (Subp_Id, Loc);
2150 else
2151 -- An access-to-variable object parameter requires an explicit
2152 -- dereference in the unchecked conversion. This case occurs
2153 -- when a protected entry wrapper must override an interface
2154 -- level procedure with interface access as first parameter.
2156 -- O.all.Subp_Id (Formal_1, ..., Formal_N)
2158 if Nkind (Parameter_Type (First_Form)) =
2159 N_Access_Definition
2160 then
2161 Conv_Id :=
2162 Make_Explicit_Dereference (Loc,
2163 Prefix => Make_Identifier (Loc, Name_uO));
2164 else
2165 Conv_Id := Make_Identifier (Loc, Name_uO);
2166 end if;
2168 Nam :=
2169 Make_Selected_Component (Loc,
2170 Prefix =>
2171 Unchecked_Convert_To
2172 (Corresponding_Concurrent_Type (Obj_Typ), Conv_Id),
2173 Selector_Name => New_Reference_To (Subp_Id, Loc));
2174 end if;
2176 -- Create the subprogram body. For a function, the call to the
2177 -- actual subprogram has to be converted to the corresponding
2178 -- record if it is a controlling result.
2180 if Ekind (Subp_Id) = E_Function then
2181 declare
2182 Res : Node_Id;
2184 begin
2185 Res :=
2186 Make_Function_Call (Loc,
2187 Name => Nam,
2188 Parameter_Associations => Actuals);
2190 if Has_Controlling_Result (Subp_Id) then
2191 Res :=
2192 Unchecked_Convert_To
2193 (Corresponding_Record_Type (Etype (Subp_Id)), Res);
2194 end if;
2196 return
2197 Make_Subprogram_Body (Loc,
2198 Specification => Body_Spec,
2199 Declarations => Empty_List,
2200 Handled_Statement_Sequence =>
2201 Make_Handled_Sequence_Of_Statements (Loc,
2202 Statements => New_List (
2203 Make_Simple_Return_Statement (Loc, Res))));
2204 end;
2206 else
2207 return
2208 Make_Subprogram_Body (Loc,
2209 Specification => Body_Spec,
2210 Declarations => Empty_List,
2211 Handled_Statement_Sequence =>
2212 Make_Handled_Sequence_Of_Statements (Loc,
2213 Statements => New_List (
2214 Make_Procedure_Call_Statement (Loc,
2215 Name => Nam,
2216 Parameter_Associations => Actuals))));
2217 end if;
2218 end;
2219 end Build_Wrapper_Body;
2221 -- Start of processing for Build_Wrapper_Bodies
2223 begin
2224 if Is_Concurrent_Type (Typ) then
2225 Rec_Typ := Corresponding_Record_Type (Typ);
2226 else
2227 Rec_Typ := Typ;
2228 end if;
2230 -- Generate wrapper bodies for a concurrent type which implements an
2231 -- interface.
2233 if Present (Interfaces (Rec_Typ)) then
2234 declare
2235 Insert_Nod : Node_Id;
2236 Prim : Entity_Id;
2237 Prim_Elmt : Elmt_Id;
2238 Prim_Decl : Node_Id;
2239 Subp : Entity_Id;
2240 Wrap_Body : Node_Id;
2241 Wrap_Id : Entity_Id;
2243 begin
2244 Insert_Nod := N;
2246 -- Examine all primitive operations of the corresponding record
2247 -- type, looking for wrapper specs. Generate bodies in order to
2248 -- complete them.
2250 Prim_Elmt := First_Elmt (Primitive_Operations (Rec_Typ));
2251 while Present (Prim_Elmt) loop
2252 Prim := Node (Prim_Elmt);
2254 if (Ekind (Prim) = E_Function
2255 or else Ekind (Prim) = E_Procedure)
2256 and then Is_Primitive_Wrapper (Prim)
2257 then
2258 Subp := Wrapped_Entity (Prim);
2259 Prim_Decl := Parent (Parent (Prim));
2261 Wrap_Body :=
2262 Build_Wrapper_Body (Loc,
2263 Subp_Id => Subp,
2264 Obj_Typ => Rec_Typ,
2265 Formals => Parameter_Specifications (Parent (Subp)));
2266 Wrap_Id := Defining_Unit_Name (Specification (Wrap_Body));
2268 Set_Corresponding_Spec (Wrap_Body, Prim);
2269 Set_Corresponding_Body (Prim_Decl, Wrap_Id);
2271 Insert_After (Insert_Nod, Wrap_Body);
2272 Insert_Nod := Wrap_Body;
2274 Analyze (Wrap_Body);
2275 end if;
2277 Next_Elmt (Prim_Elmt);
2278 end loop;
2279 end;
2280 end if;
2281 end Build_Wrapper_Bodies;
2283 ------------------------
2284 -- Build_Wrapper_Spec --
2285 ------------------------
2287 function Build_Wrapper_Spec
2288 (Subp_Id : Entity_Id;
2289 Obj_Typ : Entity_Id;
2290 Formals : List_Id) return Node_Id
2292 Loc : constant Source_Ptr := Sloc (Subp_Id);
2293 First_Param : Node_Id;
2294 Iface : Entity_Id;
2295 Iface_Elmt : Elmt_Id;
2296 Iface_Op : Entity_Id;
2297 Iface_Op_Elmt : Elmt_Id;
2299 function Overriding_Possible
2300 (Iface_Op : Entity_Id;
2301 Wrapper : Entity_Id) return Boolean;
2302 -- Determine whether a primitive operation can be overridden by Wrapper.
2303 -- Iface_Op is the candidate primitive operation of an interface type,
2304 -- Wrapper is the generated entry wrapper.
2306 function Replicate_Formals
2307 (Loc : Source_Ptr;
2308 Formals : List_Id) return List_Id;
2309 -- An explicit parameter replication is required due to the Is_Entry_
2310 -- Formal flag being set for all the formals of an entry. The explicit
2311 -- replication removes the flag that would otherwise cause a different
2312 -- path of analysis.
2314 -------------------------
2315 -- Overriding_Possible --
2316 -------------------------
2318 function Overriding_Possible
2319 (Iface_Op : Entity_Id;
2320 Wrapper : Entity_Id) return Boolean
2322 Iface_Op_Spec : constant Node_Id := Parent (Iface_Op);
2323 Wrapper_Spec : constant Node_Id := Parent (Wrapper);
2325 function Type_Conformant_Parameters
2326 (Iface_Op_Params : List_Id;
2327 Wrapper_Params : List_Id) return Boolean;
2328 -- Determine whether the parameters of the generated entry wrapper
2329 -- and those of a primitive operation are type conformant. During
2330 -- this check, the first parameter of the primitive operation is
2331 -- skipped if it is a controlling argument: protected functions
2332 -- may have a controlling result.
2334 --------------------------------
2335 -- Type_Conformant_Parameters --
2336 --------------------------------
2338 function Type_Conformant_Parameters
2339 (Iface_Op_Params : List_Id;
2340 Wrapper_Params : List_Id) return Boolean
2342 Iface_Op_Param : Node_Id;
2343 Iface_Op_Typ : Entity_Id;
2344 Wrapper_Param : Node_Id;
2345 Wrapper_Typ : Entity_Id;
2347 begin
2348 -- Skip the first (controlling) parameter of primitive operation
2350 Iface_Op_Param := First (Iface_Op_Params);
2352 if Present (First_Formal (Iface_Op))
2353 and then Is_Controlling_Formal (First_Formal (Iface_Op))
2354 then
2355 Iface_Op_Param := Next (Iface_Op_Param);
2356 end if;
2358 Wrapper_Param := First (Wrapper_Params);
2359 while Present (Iface_Op_Param)
2360 and then Present (Wrapper_Param)
2361 loop
2362 Iface_Op_Typ := Find_Parameter_Type (Iface_Op_Param);
2363 Wrapper_Typ := Find_Parameter_Type (Wrapper_Param);
2365 -- The two parameters must be mode conformant
2367 if not Conforming_Types
2368 (Iface_Op_Typ, Wrapper_Typ, Mode_Conformant)
2369 then
2370 return False;
2371 end if;
2373 Next (Iface_Op_Param);
2374 Next (Wrapper_Param);
2375 end loop;
2377 -- One of the lists is longer than the other
2379 if Present (Iface_Op_Param) or else Present (Wrapper_Param) then
2380 return False;
2381 end if;
2383 return True;
2384 end Type_Conformant_Parameters;
2386 -- Start of processing for Overriding_Possible
2388 begin
2389 if Chars (Iface_Op) /= Chars (Wrapper) then
2390 return False;
2391 end if;
2393 -- If an inherited subprogram is implemented by a protected procedure
2394 -- or an entry, then the first parameter of the inherited subprogram
2395 -- shall be of mode OUT or IN OUT, or access-to-variable parameter.
2397 if Ekind (Iface_Op) = E_Procedure
2398 and then Present (Parameter_Specifications (Iface_Op_Spec))
2399 then
2400 declare
2401 Obj_Param : constant Node_Id :=
2402 First (Parameter_Specifications (Iface_Op_Spec));
2403 begin
2404 if not Out_Present (Obj_Param)
2405 and then Nkind (Parameter_Type (Obj_Param)) /=
2406 N_Access_Definition
2407 then
2408 return False;
2409 end if;
2410 end;
2411 end if;
2413 return
2414 Type_Conformant_Parameters (
2415 Parameter_Specifications (Iface_Op_Spec),
2416 Parameter_Specifications (Wrapper_Spec));
2417 end Overriding_Possible;
2419 -----------------------
2420 -- Replicate_Formals --
2421 -----------------------
2423 function Replicate_Formals
2424 (Loc : Source_Ptr;
2425 Formals : List_Id) return List_Id
2427 New_Formals : constant List_Id := New_List;
2428 Formal : Node_Id;
2429 Param_Type : Node_Id;
2431 begin
2432 Formal := First (Formals);
2434 -- Skip the object parameter when dealing with primitives declared
2435 -- between two views.
2437 if Is_Private_Primitive_Subprogram (Subp_Id)
2438 and then not Has_Controlling_Result (Subp_Id)
2439 then
2440 Formal := Next (Formal);
2441 end if;
2443 while Present (Formal) loop
2445 -- Create an explicit copy of the entry parameter
2447 -- When creating the wrapper subprogram for a primitive operation
2448 -- of a protected interface we must construct an equivalent
2449 -- signature to that of the overriding operation. For regular
2450 -- parameters we can just use the type of the formal, but for
2451 -- access to subprogram parameters we need to reanalyze the
2452 -- parameter type to create local entities for the signature of
2453 -- the subprogram type. Using the entities of the overriding
2454 -- subprogram will result in out-of-scope errors in the back-end.
2456 if Nkind (Parameter_Type (Formal)) = N_Access_Definition then
2457 Param_Type := Copy_Separate_Tree (Parameter_Type (Formal));
2458 else
2459 Param_Type :=
2460 New_Reference_To (Etype (Parameter_Type (Formal)), Loc);
2461 end if;
2463 Append_To (New_Formals,
2464 Make_Parameter_Specification (Loc,
2465 Defining_Identifier =>
2466 Make_Defining_Identifier (Loc,
2467 Chars => Chars (Defining_Identifier (Formal))),
2468 In_Present => In_Present (Formal),
2469 Out_Present => Out_Present (Formal),
2470 Parameter_Type => Param_Type));
2472 Next (Formal);
2473 end loop;
2475 return New_Formals;
2476 end Replicate_Formals;
2478 -- Start of processing for Build_Wrapper_Spec
2480 begin
2481 -- There is no point in building wrappers for non-tagged concurrent
2482 -- types.
2484 pragma Assert (Is_Tagged_Type (Obj_Typ));
2486 -- An entry or a protected procedure can override a routine where the
2487 -- controlling formal is either IN OUT, OUT or is of access-to-variable
2488 -- type. Since the wrapper must have the exact same signature as that of
2489 -- the overridden subprogram, we try to find the overriding candidate
2490 -- and use its controlling formal.
2492 First_Param := Empty;
2494 -- Check every implemented interface
2496 if Present (Interfaces (Obj_Typ)) then
2497 Iface_Elmt := First_Elmt (Interfaces (Obj_Typ));
2498 Search : while Present (Iface_Elmt) loop
2499 Iface := Node (Iface_Elmt);
2501 -- Check every interface primitive
2503 if Present (Primitive_Operations (Iface)) then
2504 Iface_Op_Elmt := First_Elmt (Primitive_Operations (Iface));
2505 while Present (Iface_Op_Elmt) loop
2506 Iface_Op := Node (Iface_Op_Elmt);
2508 -- Ignore predefined primitives
2510 if not Is_Predefined_Dispatching_Operation (Iface_Op) then
2511 Iface_Op := Ultimate_Alias (Iface_Op);
2513 -- The current primitive operation can be overridden by
2514 -- the generated entry wrapper.
2516 if Overriding_Possible (Iface_Op, Subp_Id) then
2517 First_Param :=
2518 First (Parameter_Specifications (Parent (Iface_Op)));
2520 exit Search;
2521 end if;
2522 end if;
2524 Next_Elmt (Iface_Op_Elmt);
2525 end loop;
2526 end if;
2528 Next_Elmt (Iface_Elmt);
2529 end loop Search;
2530 end if;
2532 -- Ada 2012 (AI05-0090-1): If no interface primitive is covered by
2533 -- this subprogram and this is not a primitive declared between two
2534 -- views then force the generation of a wrapper. As an optimization,
2535 -- previous versions of the frontend avoid generating the wrapper;
2536 -- however, the wrapper facilitates locating and reporting an error
2537 -- when a duplicate declaration is found later. See example in
2538 -- AI05-0090-1.
2540 if No (First_Param)
2541 and then not Is_Private_Primitive_Subprogram (Subp_Id)
2542 then
2543 if Is_Task_Type
2544 (Corresponding_Concurrent_Type (Obj_Typ))
2545 then
2546 First_Param :=
2547 Make_Parameter_Specification (Loc,
2548 Defining_Identifier => Make_Defining_Identifier (Loc, Name_uO),
2549 In_Present => True,
2550 Out_Present => False,
2551 Parameter_Type => New_Reference_To (Obj_Typ, Loc));
2553 -- For entries and procedures of protected types the mode of
2554 -- the controlling argument must be in-out.
2556 else
2557 First_Param :=
2558 Make_Parameter_Specification (Loc,
2559 Defining_Identifier =>
2560 Make_Defining_Identifier (Loc,
2561 Chars => Name_uO),
2562 In_Present => True,
2563 Out_Present => (Ekind (Subp_Id) /= E_Function),
2564 Parameter_Type => New_Reference_To (Obj_Typ, Loc));
2565 end if;
2566 end if;
2568 declare
2569 Wrapper_Id : constant Entity_Id :=
2570 Make_Defining_Identifier (Loc, Chars (Subp_Id));
2571 New_Formals : List_Id;
2572 Obj_Param : Node_Id;
2573 Obj_Param_Typ : Entity_Id;
2575 begin
2576 -- Minimum decoration is needed to catch the entity in
2577 -- Sem_Ch6.Override_Dispatching_Operation.
2579 if Ekind (Subp_Id) = E_Function then
2580 Set_Ekind (Wrapper_Id, E_Function);
2581 else
2582 Set_Ekind (Wrapper_Id, E_Procedure);
2583 end if;
2585 Set_Is_Primitive_Wrapper (Wrapper_Id);
2586 Set_Wrapped_Entity (Wrapper_Id, Subp_Id);
2587 Set_Is_Private_Primitive (Wrapper_Id,
2588 Is_Private_Primitive_Subprogram (Subp_Id));
2590 -- Process the formals
2592 New_Formals := Replicate_Formals (Loc, Formals);
2594 -- A function with a controlling result and no first controlling
2595 -- formal needs no additional parameter.
2597 if Has_Controlling_Result (Subp_Id)
2598 and then
2599 (No (First_Formal (Subp_Id))
2600 or else not Is_Controlling_Formal (First_Formal (Subp_Id)))
2601 then
2602 null;
2604 -- Routine Subp_Id has been found to override an interface primitive.
2605 -- If the interface operation has an access parameter, create a copy
2606 -- of it, with the same null exclusion indicator if present.
2608 elsif Present (First_Param) then
2609 if Nkind (Parameter_Type (First_Param)) = N_Access_Definition then
2610 Obj_Param_Typ :=
2611 Make_Access_Definition (Loc,
2612 Subtype_Mark =>
2613 New_Reference_To (Obj_Typ, Loc));
2614 Set_Null_Exclusion_Present (Obj_Param_Typ,
2615 Null_Exclusion_Present (Parameter_Type (First_Param)));
2617 else
2618 Obj_Param_Typ := New_Reference_To (Obj_Typ, Loc);
2619 end if;
2621 Obj_Param :=
2622 Make_Parameter_Specification (Loc,
2623 Defining_Identifier =>
2624 Make_Defining_Identifier (Loc,
2625 Chars => Name_uO),
2626 In_Present => In_Present (First_Param),
2627 Out_Present => Out_Present (First_Param),
2628 Parameter_Type => Obj_Param_Typ);
2630 Prepend_To (New_Formals, Obj_Param);
2632 -- If we are dealing with a primitive declared between two views,
2633 -- implemented by a synchronized operation, we need to create
2634 -- a default parameter. The mode of the parameter must match that
2635 -- of the primitive operation.
2637 else
2638 pragma Assert (Is_Private_Primitive_Subprogram (Subp_Id));
2639 Obj_Param :=
2640 Make_Parameter_Specification (Loc,
2641 Defining_Identifier =>
2642 Make_Defining_Identifier (Loc, Name_uO),
2643 In_Present => In_Present (Parent (First_Entity (Subp_Id))),
2644 Out_Present => Ekind (Subp_Id) /= E_Function,
2645 Parameter_Type => New_Reference_To (Obj_Typ, Loc));
2646 Prepend_To (New_Formals, Obj_Param);
2647 end if;
2649 -- Build the final spec. If it is a function with a controlling
2650 -- result, it is a primitive operation of the corresponding
2651 -- record type, so mark the spec accordingly.
2653 if Ekind (Subp_Id) = E_Function then
2654 declare
2655 Res_Def : Node_Id;
2657 begin
2658 if Has_Controlling_Result (Subp_Id) then
2659 Res_Def :=
2660 New_Occurrence_Of
2661 (Corresponding_Record_Type (Etype (Subp_Id)), Loc);
2662 else
2663 Res_Def := New_Copy (Result_Definition (Parent (Subp_Id)));
2664 end if;
2666 return
2667 Make_Function_Specification (Loc,
2668 Defining_Unit_Name => Wrapper_Id,
2669 Parameter_Specifications => New_Formals,
2670 Result_Definition => Res_Def);
2671 end;
2672 else
2673 return
2674 Make_Procedure_Specification (Loc,
2675 Defining_Unit_Name => Wrapper_Id,
2676 Parameter_Specifications => New_Formals);
2677 end if;
2678 end;
2679 end Build_Wrapper_Spec;
2681 -------------------------
2682 -- Build_Wrapper_Specs --
2683 -------------------------
2685 procedure Build_Wrapper_Specs
2686 (Loc : Source_Ptr;
2687 Typ : Entity_Id;
2688 N : in out Node_Id)
2690 Def : Node_Id;
2691 Rec_Typ : Entity_Id;
2692 procedure Scan_Declarations (L : List_Id);
2693 -- Common processing for visible and private declarations
2694 -- of a protected type.
2696 procedure Scan_Declarations (L : List_Id) is
2697 Decl : Node_Id;
2698 Wrap_Decl : Node_Id;
2699 Wrap_Spec : Node_Id;
2701 begin
2702 if No (L) then
2703 return;
2704 end if;
2706 Decl := First (L);
2707 while Present (Decl) loop
2708 Wrap_Spec := Empty;
2710 if Nkind (Decl) = N_Entry_Declaration
2711 and then Ekind (Defining_Identifier (Decl)) = E_Entry
2712 then
2713 Wrap_Spec :=
2714 Build_Wrapper_Spec
2715 (Subp_Id => Defining_Identifier (Decl),
2716 Obj_Typ => Rec_Typ,
2717 Formals => Parameter_Specifications (Decl));
2719 elsif Nkind (Decl) = N_Subprogram_Declaration then
2720 Wrap_Spec :=
2721 Build_Wrapper_Spec
2722 (Subp_Id => Defining_Unit_Name (Specification (Decl)),
2723 Obj_Typ => Rec_Typ,
2724 Formals =>
2725 Parameter_Specifications (Specification (Decl)));
2726 end if;
2728 if Present (Wrap_Spec) then
2729 Wrap_Decl :=
2730 Make_Subprogram_Declaration (Loc,
2731 Specification => Wrap_Spec);
2733 Insert_After (N, Wrap_Decl);
2734 N := Wrap_Decl;
2736 Analyze (Wrap_Decl);
2737 end if;
2739 Next (Decl);
2740 end loop;
2741 end Scan_Declarations;
2743 -- start of processing for Build_Wrapper_Specs
2745 begin
2746 if Is_Protected_Type (Typ) then
2747 Def := Protected_Definition (Parent (Typ));
2748 else pragma Assert (Is_Task_Type (Typ));
2749 Def := Task_Definition (Parent (Typ));
2750 end if;
2752 Rec_Typ := Corresponding_Record_Type (Typ);
2754 -- Generate wrapper specs for a concurrent type which implements an
2755 -- interface. Operations in both the visible and private parts may
2756 -- implement progenitor operations.
2758 if Present (Interfaces (Rec_Typ))
2759 and then Present (Def)
2760 then
2761 Scan_Declarations (Visible_Declarations (Def));
2762 Scan_Declarations (Private_Declarations (Def));
2763 end if;
2764 end Build_Wrapper_Specs;
2766 ---------------------------
2767 -- Build_Find_Body_Index --
2768 ---------------------------
2770 function Build_Find_Body_Index (Typ : Entity_Id) return Node_Id is
2771 Loc : constant Source_Ptr := Sloc (Typ);
2772 Ent : Entity_Id;
2773 E_Typ : Entity_Id;
2774 Has_F : Boolean := False;
2775 Index : Nat;
2776 If_St : Node_Id := Empty;
2777 Lo : Node_Id;
2778 Hi : Node_Id;
2779 Decls : List_Id := New_List;
2780 Ret : Node_Id;
2781 Spec : Node_Id;
2782 Siz : Node_Id := Empty;
2784 procedure Add_If_Clause (Expr : Node_Id);
2785 -- Add test for range of current entry
2787 function Convert_Discriminant_Ref (Bound : Node_Id) return Node_Id;
2788 -- If a bound of an entry is given by a discriminant, retrieve the
2789 -- actual value of the discriminant from the enclosing object.
2791 -------------------
2792 -- Add_If_Clause --
2793 -------------------
2795 procedure Add_If_Clause (Expr : Node_Id) is
2796 Cond : Node_Id;
2797 Stats : constant List_Id :=
2798 New_List (
2799 Make_Simple_Return_Statement (Loc,
2800 Expression => Make_Integer_Literal (Loc, Index + 1)));
2802 begin
2803 -- Index for current entry body
2805 Index := Index + 1;
2807 -- Compute total length of entry queues so far
2809 if No (Siz) then
2810 Siz := Expr;
2811 else
2812 Siz :=
2813 Make_Op_Add (Loc,
2814 Left_Opnd => Siz,
2815 Right_Opnd => Expr);
2816 end if;
2818 Cond :=
2819 Make_Op_Le (Loc,
2820 Left_Opnd => Make_Identifier (Loc, Name_uE),
2821 Right_Opnd => Siz);
2823 -- Map entry queue indexes in the range of the current family
2824 -- into the current index, that designates the entry body.
2826 if No (If_St) then
2827 If_St :=
2828 Make_Implicit_If_Statement (Typ,
2829 Condition => Cond,
2830 Then_Statements => Stats,
2831 Elsif_Parts => New_List);
2832 Ret := If_St;
2834 else
2835 Append_To (Elsif_Parts (If_St),
2836 Make_Elsif_Part (Loc,
2837 Condition => Cond,
2838 Then_Statements => Stats));
2839 end if;
2840 end Add_If_Clause;
2842 ------------------------------
2843 -- Convert_Discriminant_Ref --
2844 ------------------------------
2846 function Convert_Discriminant_Ref (Bound : Node_Id) return Node_Id is
2847 B : Node_Id;
2849 begin
2850 if Is_Entity_Name (Bound)
2851 and then Ekind (Entity (Bound)) = E_Discriminant
2852 then
2853 B :=
2854 Make_Selected_Component (Loc,
2855 Prefix =>
2856 Unchecked_Convert_To (Corresponding_Record_Type (Typ),
2857 Make_Explicit_Dereference (Loc,
2858 Make_Identifier (Loc, Name_uObject))),
2859 Selector_Name => Make_Identifier (Loc, Chars (Bound)));
2860 Set_Etype (B, Etype (Entity (Bound)));
2861 else
2862 B := New_Copy_Tree (Bound);
2863 end if;
2865 return B;
2866 end Convert_Discriminant_Ref;
2868 -- Start of processing for Build_Find_Body_Index
2870 begin
2871 Spec := Build_Find_Body_Index_Spec (Typ);
2873 Ent := First_Entity (Typ);
2874 while Present (Ent) loop
2875 if Ekind (Ent) = E_Entry_Family then
2876 Has_F := True;
2877 exit;
2878 end if;
2880 Next_Entity (Ent);
2881 end loop;
2883 if not Has_F then
2885 -- If the protected type has no entry families, there is a one-one
2886 -- correspondence between entry queue and entry body.
2888 Ret :=
2889 Make_Simple_Return_Statement (Loc,
2890 Expression => Make_Identifier (Loc, Name_uE));
2892 else
2893 -- Suppose entries e1, e2, ... have size l1, l2, ... we generate
2894 -- the following:
2896 -- if E <= l1 then return 1;
2897 -- elsif E <= l1 + l2 then return 2;
2898 -- ...
2900 Index := 0;
2901 Siz := Empty;
2902 Ent := First_Entity (Typ);
2904 Add_Object_Pointer (Loc, Typ, Decls);
2906 while Present (Ent) loop
2907 if Ekind (Ent) = E_Entry then
2908 Add_If_Clause (Make_Integer_Literal (Loc, 1));
2910 elsif Ekind (Ent) = E_Entry_Family then
2911 E_Typ := Etype (Discrete_Subtype_Definition (Parent (Ent)));
2912 Hi := Convert_Discriminant_Ref (Type_High_Bound (E_Typ));
2913 Lo := Convert_Discriminant_Ref (Type_Low_Bound (E_Typ));
2914 Add_If_Clause (Family_Size (Loc, Hi, Lo, Typ, False));
2915 end if;
2917 Next_Entity (Ent);
2918 end loop;
2920 if Index = 1 then
2921 Decls := New_List;
2922 Ret :=
2923 Make_Simple_Return_Statement (Loc,
2924 Expression => Make_Integer_Literal (Loc, 1));
2926 elsif Nkind (Ret) = N_If_Statement then
2928 -- Ranges are in increasing order, so last one doesn't need guard
2930 declare
2931 Nod : constant Node_Id := Last (Elsif_Parts (Ret));
2932 begin
2933 Remove (Nod);
2934 Set_Else_Statements (Ret, Then_Statements (Nod));
2935 end;
2936 end if;
2937 end if;
2939 return
2940 Make_Subprogram_Body (Loc,
2941 Specification => Spec,
2942 Declarations => Decls,
2943 Handled_Statement_Sequence =>
2944 Make_Handled_Sequence_Of_Statements (Loc,
2945 Statements => New_List (Ret)));
2946 end Build_Find_Body_Index;
2948 --------------------------------
2949 -- Build_Find_Body_Index_Spec --
2950 --------------------------------
2952 function Build_Find_Body_Index_Spec (Typ : Entity_Id) return Node_Id is
2953 Loc : constant Source_Ptr := Sloc (Typ);
2954 Id : constant Entity_Id :=
2955 Make_Defining_Identifier (Loc,
2956 Chars => New_External_Name (Chars (Typ), 'F'));
2957 Parm1 : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uO);
2958 Parm2 : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uE);
2960 begin
2961 return
2962 Make_Function_Specification (Loc,
2963 Defining_Unit_Name => Id,
2964 Parameter_Specifications => New_List (
2965 Make_Parameter_Specification (Loc,
2966 Defining_Identifier => Parm1,
2967 Parameter_Type =>
2968 New_Reference_To (RTE (RE_Address), Loc)),
2970 Make_Parameter_Specification (Loc,
2971 Defining_Identifier => Parm2,
2972 Parameter_Type =>
2973 New_Reference_To (RTE (RE_Protected_Entry_Index), Loc))),
2975 Result_Definition => New_Occurrence_Of (
2976 RTE (RE_Protected_Entry_Index), Loc));
2977 end Build_Find_Body_Index_Spec;
2979 -----------------------------------------------
2980 -- Build_Lock_Free_Protected_Subprogram_Body --
2981 -----------------------------------------------
2983 function Build_Lock_Free_Protected_Subprogram_Body
2984 (N : Node_Id;
2985 Prot_Typ : Node_Id;
2986 Unprot_Spec : Node_Id) return Node_Id
2988 Actuals : constant List_Id := New_List;
2989 Loc : constant Source_Ptr := Sloc (N);
2990 Spec : constant Node_Id := Specification (N);
2991 Unprot_Id : constant Entity_Id := Defining_Unit_Name (Unprot_Spec);
2992 Formal : Node_Id;
2993 Prot_Spec : Node_Id;
2994 Stmt : Node_Id;
2996 begin
2997 -- Create the protected version of the body
2999 Prot_Spec :=
3000 Build_Protected_Sub_Specification (N, Prot_Typ, Protected_Mode);
3002 -- Build the actual parameters which appear in the call to the
3003 -- unprotected version of the body.
3005 Formal := First (Parameter_Specifications (Prot_Spec));
3006 while Present (Formal) loop
3007 Append_To (Actuals,
3008 Make_Identifier (Loc, Chars (Defining_Identifier (Formal))));
3010 Next (Formal);
3011 end loop;
3013 -- Function case, generate:
3014 -- return <Unprot_Func_Call>;
3016 if Nkind (Spec) = N_Function_Specification then
3017 Stmt :=
3018 Make_Simple_Return_Statement (Loc,
3019 Expression =>
3020 Make_Function_Call (Loc,
3021 Name =>
3022 Make_Identifier (Loc, Chars (Unprot_Id)),
3023 Parameter_Associations => Actuals));
3025 -- Procedure case, call the unprotected version
3027 else
3028 Stmt :=
3029 Make_Procedure_Call_Statement (Loc,
3030 Name =>
3031 Make_Identifier (Loc, Chars (Unprot_Id)),
3032 Parameter_Associations => Actuals);
3033 end if;
3035 return
3036 Make_Subprogram_Body (Loc,
3037 Declarations => Empty_List,
3038 Specification => Prot_Spec,
3039 Handled_Statement_Sequence =>
3040 Make_Handled_Sequence_Of_Statements (Loc,
3041 Statements => New_List (Stmt)));
3042 end Build_Lock_Free_Protected_Subprogram_Body;
3044 -------------------------------------------------
3045 -- Build_Lock_Free_Unprotected_Subprogram_Body --
3046 -------------------------------------------------
3048 -- Procedures which meet the lock-free implementation requirements and
3049 -- reference a unique scalar component Comp are expanded in the following
3050 -- manner:
3052 -- procedure P (...) is
3053 -- Expected_Comp : constant Comp_Type :=
3054 -- Comp_Type
3055 -- (System.Atomic_Primitives.Lock_Free_Read_N
3056 -- (_Object.Comp'Address));
3057 -- begin
3058 -- loop
3059 -- declare
3060 -- <original declarations before the object renaming declaration
3061 -- of Comp>
3063 -- Desired_Comp : Comp_Type := Expected_Comp;
3064 -- Comp : Comp_Type renames Desired_Comp;
3066 -- <original delarations after the object renaming declaration
3067 -- of Comp>
3069 -- begin
3070 -- <original statements>
3071 -- exit when System.Atomic_Primitives.Lock_Free_Try_Write_N
3072 -- (_Object.Comp'Address,
3073 -- Interfaces.Unsigned_N (Expected_Comp),
3074 -- Interfaces.Unsigned_N (Desired_Comp));
3075 -- end;
3076 -- end loop;
3077 -- end P;
3079 -- Each return and raise statement of P is transformed into an atomic
3080 -- status check:
3082 -- if System.Atomic_Primitives.Lock_Free_Try_Write_N
3083 -- (_Object.Comp'Address,
3084 -- Interfaces.Unsigned_N (Expected_Comp),
3085 -- Interfaces.Unsigned_N (Desired_Comp));
3086 -- then
3087 -- <original statement>
3088 -- else
3089 -- goto L0;
3090 -- end if;
3092 -- Functions which meet the lock-free implementation requirements and
3093 -- reference a unique scalar component Comp are expanded in the following
3094 -- manner:
3096 -- function F (...) return ... is
3097 -- <original declarations before the object renaming declaration
3098 -- of Comp>
3100 -- Expected_Comp : constant Comp_Type :=
3101 -- Comp_Type
3102 -- (System.Atomic_Primitives.Lock_Free_Read_N
3103 -- (_Object.Comp'Address));
3104 -- Comp : Comp_Type renames Expected_Comp;
3106 -- <original delarations after the object renaming declaration of
3107 -- Comp>
3109 -- begin
3110 -- <original statements>
3111 -- end F;
3113 function Build_Lock_Free_Unprotected_Subprogram_Body
3114 (N : Node_Id;
3115 Prot_Typ : Node_Id) return Node_Id
3117 function Referenced_Component (N : Node_Id) return Entity_Id;
3118 -- Subprograms which meet the lock-free implementation criteria are
3119 -- allowed to reference only one unique component. Return the prival
3120 -- of the said component.
3122 --------------------------
3123 -- Referenced_Component --
3124 --------------------------
3126 function Referenced_Component (N : Node_Id) return Entity_Id is
3127 Comp : Entity_Id;
3128 Decl : Node_Id;
3129 Source_Comp : Entity_Id := Empty;
3131 begin
3132 -- Find the unique source component which N references in its
3133 -- statements.
3135 for Index in 1 .. Lock_Free_Subprogram_Table.Last loop
3136 declare
3137 Element : Lock_Free_Subprogram renames
3138 Lock_Free_Subprogram_Table.Table (Index);
3139 begin
3140 if Element.Sub_Body = N then
3141 Source_Comp := Element.Comp_Id;
3142 exit;
3143 end if;
3144 end;
3145 end loop;
3147 if No (Source_Comp) then
3148 return Empty;
3149 end if;
3151 -- Find the prival which corresponds to the source component within
3152 -- the declarations of N.
3154 Decl := First (Declarations (N));
3155 while Present (Decl) loop
3157 -- Privals appear as object renamings
3159 if Nkind (Decl) = N_Object_Renaming_Declaration then
3160 Comp := Defining_Identifier (Decl);
3162 if Present (Prival_Link (Comp))
3163 and then Prival_Link (Comp) = Source_Comp
3164 then
3165 return Comp;
3166 end if;
3167 end if;
3169 Next (Decl);
3170 end loop;
3172 return Empty;
3173 end Referenced_Component;
3175 -- Local variables
3177 Comp : constant Entity_Id := Referenced_Component (N);
3178 Loc : constant Source_Ptr := Sloc (N);
3179 Hand_Stmt_Seq : Node_Id := Handled_Statement_Sequence (N);
3180 Decls : List_Id := Declarations (N);
3182 -- Start of processing for Build_Lock_Free_Unprotected_Subprogram_Body
3184 begin
3185 -- Add renamings for the protection object, discriminals, privals and
3186 -- the entry index constant for use by debugger.
3188 Debug_Private_Data_Declarations (Decls);
3190 -- Perform the lock-free expansion when the subprogram references a
3191 -- protected component.
3193 if Present (Comp) then
3194 Protected_Component_Ref : declare
3195 Comp_Decl : constant Node_Id := Parent (Comp);
3196 Comp_Sel_Nam : constant Node_Id := Name (Comp_Decl);
3197 Comp_Type : constant Entity_Id := Etype (Comp);
3199 Is_Procedure : constant Boolean :=
3200 Ekind (Corresponding_Spec (N)) = E_Procedure;
3201 -- Indicates if N is a protected procedure body
3203 Block_Decls : List_Id;
3204 Try_Write : Entity_Id;
3205 Desired_Comp : Entity_Id;
3206 Decl : Node_Id;
3207 Label : Node_Id;
3208 Label_Id : Entity_Id := Empty;
3209 Read : Entity_Id;
3210 Expected_Comp : Entity_Id;
3211 Stmt : Node_Id;
3212 Stmts : List_Id :=
3213 New_Copy_List (Statements (Hand_Stmt_Seq));
3214 Typ_Size : Int;
3215 Unsigned : Entity_Id;
3217 function Process_Node (N : Node_Id) return Traverse_Result;
3218 -- Transform a single node if it is a return statement, a raise
3219 -- statement or a reference to Comp.
3221 procedure Process_Stmts (Stmts : List_Id);
3222 -- Given a statement sequence Stmts, wrap any return or raise
3223 -- statements in the following manner:
3225 -- if System.Atomic_Primitives.Lock_Free_Try_Write_N
3226 -- (_Object.Comp'Address,
3227 -- Interfaces.Unsigned_N (Expected_Comp),
3228 -- Interfaces.Unsigned_N (Desired_Comp))
3229 -- then
3230 -- <Stmt>;
3231 -- else
3232 -- goto L0;
3233 -- end if;
3235 ------------------
3236 -- Process_Node --
3237 ------------------
3239 function Process_Node (N : Node_Id) return Traverse_Result is
3241 procedure Wrap_Statement (Stmt : Node_Id);
3242 -- Wrap an arbitrary statement inside an if statement where the
3243 -- condition does an atomic check on the state of the object.
3245 --------------------
3246 -- Wrap_Statement --
3247 --------------------
3249 procedure Wrap_Statement (Stmt : Node_Id) is
3250 begin
3251 -- The first time through, create the declaration of a label
3252 -- which is used to skip the remainder of source statements
3253 -- if the state of the object has changed.
3255 if No (Label_Id) then
3256 Label_Id :=
3257 Make_Identifier (Loc, New_External_Name ('L', 0));
3258 Set_Entity (Label_Id,
3259 Make_Defining_Identifier (Loc, Chars (Label_Id)));
3260 end if;
3262 -- Generate:
3263 -- if System.Atomic_Primitives.Lock_Free_Try_Write_N
3264 -- (_Object.Comp'Address,
3265 -- Interfaces.Unsigned_N (Expected_Comp),
3266 -- Interfaces.Unsigned_N (Desired_Comp))
3267 -- then
3268 -- <Stmt>;
3269 -- else
3270 -- goto L0;
3271 -- end if;
3273 Rewrite (Stmt,
3274 Make_Implicit_If_Statement (N,
3275 Condition =>
3276 Make_Function_Call (Loc,
3277 Name =>
3278 New_Reference_To (Try_Write, Loc),
3279 Parameter_Associations => New_List (
3280 Make_Attribute_Reference (Loc,
3281 Prefix => Relocate_Node (Comp_Sel_Nam),
3282 Attribute_Name => Name_Address),
3284 Unchecked_Convert_To (Unsigned,
3285 New_Reference_To (Expected_Comp, Loc)),
3287 Unchecked_Convert_To (Unsigned,
3288 New_Reference_To (Desired_Comp, Loc)))),
3290 Then_Statements => New_List (Relocate_Node (Stmt)),
3292 Else_Statements => New_List (
3293 Make_Goto_Statement (Loc,
3294 Name =>
3295 New_Reference_To (Entity (Label_Id), Loc)))));
3296 end Wrap_Statement;
3298 -- Start of processing for Process_Node
3300 begin
3301 -- Wrap each return and raise statement that appear inside a
3302 -- procedure. Skip the last return statement which is added by
3303 -- default since it is transformed into an exit statement.
3305 if Is_Procedure
3306 and then ((Nkind (N) = N_Simple_Return_Statement
3307 and then N /= Last (Stmts))
3308 or else Nkind (N) = N_Extended_Return_Statement
3309 or else (Nkind_In (N, N_Raise_Constraint_Error,
3310 N_Raise_Program_Error,
3311 N_Raise_Statement,
3312 N_Raise_Storage_Error)
3313 and then Comes_From_Source (N)))
3314 then
3315 Wrap_Statement (N);
3316 return Skip;
3317 end if;
3319 -- Force reanalysis
3321 Set_Analyzed (N, False);
3323 return OK;
3324 end Process_Node;
3326 procedure Process_Nodes is new Traverse_Proc (Process_Node);
3328 -------------------
3329 -- Process_Stmts --
3330 -------------------
3332 procedure Process_Stmts (Stmts : List_Id) is
3333 Stmt : Node_Id;
3334 begin
3335 Stmt := First (Stmts);
3336 while Present (Stmt) loop
3337 Process_Nodes (Stmt);
3338 Next (Stmt);
3339 end loop;
3340 end Process_Stmts;
3342 -- Start of processing for Protected_Component_Ref
3344 begin
3345 -- Get the type size
3347 if Known_Static_Esize (Comp_Type) then
3348 Typ_Size := UI_To_Int (Esize (Comp_Type));
3350 -- If the Esize (Object_Size) is unknown at compile time, look at
3351 -- the RM_Size (Value_Size) since it may have been set by an
3352 -- explicit representation clause.
3354 elsif Known_Static_RM_Size (Comp_Type) then
3355 Typ_Size := UI_To_Int (RM_Size (Comp_Type));
3357 -- Should not happen since this has already been checked in
3358 -- Allows_Lock_Free_Implementation (see Sem_Ch9).
3360 else
3361 raise Program_Error;
3362 end if;
3364 -- Retrieve all relevant atomic routines and types
3366 case Typ_Size is
3367 when 8 =>
3368 Try_Write := RTE (RE_Lock_Free_Try_Write_8);
3369 Read := RTE (RE_Lock_Free_Read_8);
3370 Unsigned := RTE (RE_Uint8);
3372 when 16 =>
3373 Try_Write := RTE (RE_Lock_Free_Try_Write_16);
3374 Read := RTE (RE_Lock_Free_Read_16);
3375 Unsigned := RTE (RE_Uint16);
3377 when 32 =>
3378 Try_Write := RTE (RE_Lock_Free_Try_Write_32);
3379 Read := RTE (RE_Lock_Free_Read_32);
3380 Unsigned := RTE (RE_Uint32);
3382 when 64 =>
3383 Try_Write := RTE (RE_Lock_Free_Try_Write_64);
3384 Read := RTE (RE_Lock_Free_Read_64);
3385 Unsigned := RTE (RE_Uint64);
3387 when others =>
3388 raise Program_Error;
3389 end case;
3391 -- Generate:
3392 -- Expected_Comp : constant Comp_Type :=
3393 -- Comp_Type
3394 -- (System.Atomic_Primitives.Lock_Free_Read_N
3395 -- (_Object.Comp'Address));
3397 Expected_Comp :=
3398 Make_Defining_Identifier (Loc,
3399 New_External_Name (Chars (Comp), Suffix => "_saved"));
3401 Decl :=
3402 Make_Object_Declaration (Loc,
3403 Defining_Identifier => Expected_Comp,
3404 Object_Definition => New_Reference_To (Comp_Type, Loc),
3405 Constant_Present => True,
3406 Expression =>
3407 Unchecked_Convert_To (Comp_Type,
3408 Make_Function_Call (Loc,
3409 Name => New_Reference_To (Read, Loc),
3410 Parameter_Associations => New_List (
3411 Make_Attribute_Reference (Loc,
3412 Prefix => Relocate_Node (Comp_Sel_Nam),
3413 Attribute_Name => Name_Address)))));
3415 -- Protected procedures
3417 if Is_Procedure then
3418 -- Move the original declarations inside the generated block
3420 Block_Decls := Decls;
3422 -- Reset the declarations list of the protected procedure to
3423 -- contain only Decl.
3425 Decls := New_List (Decl);
3427 -- Generate:
3428 -- Desired_Comp : Comp_Type := Expected_Comp;
3430 Desired_Comp :=
3431 Make_Defining_Identifier (Loc,
3432 New_External_Name (Chars (Comp), Suffix => "_current"));
3434 -- Insert the declarations of Expected_Comp and Desired_Comp in
3435 -- the block declarations right before the renaming of the
3436 -- protected component.
3438 Insert_Before (Comp_Decl,
3439 Make_Object_Declaration (Loc,
3440 Defining_Identifier => Desired_Comp,
3441 Object_Definition => New_Reference_To (Comp_Type, Loc),
3442 Expression =>
3443 New_Reference_To (Expected_Comp, Loc)));
3445 -- Protected function
3447 else
3448 Desired_Comp := Expected_Comp;
3450 -- Insert the declaration of Expected_Comp in the function
3451 -- declarations right before the renaming of the protected
3452 -- component.
3454 Insert_Before (Comp_Decl, Decl);
3455 end if;
3457 -- Rewrite the protected component renaming declaration to be a
3458 -- renaming of Desired_Comp.
3460 -- Generate:
3461 -- Comp : Comp_Type renames Desired_Comp;
3463 Rewrite (Comp_Decl,
3464 Make_Object_Renaming_Declaration (Loc,
3465 Defining_Identifier =>
3466 Defining_Identifier (Comp_Decl),
3467 Subtype_Mark =>
3468 New_Occurrence_Of (Comp_Type, Loc),
3469 Name =>
3470 New_Reference_To (Desired_Comp, Loc)));
3472 -- Wrap any return or raise statements in Stmts in same the manner
3473 -- described in Process_Stmts.
3475 Process_Stmts (Stmts);
3477 -- Generate:
3478 -- exit when System.Atomic_Primitives.Lock_Free_Try_Write_N
3479 -- (_Object.Comp'Address,
3480 -- Interfaces.Unsigned_N (Expected_Comp),
3481 -- Interfaces.Unsigned_N (Desired_Comp))
3483 if Is_Procedure then
3484 Stmt :=
3485 Make_Exit_Statement (Loc,
3486 Condition =>
3487 Make_Function_Call (Loc,
3488 Name =>
3489 New_Reference_To (Try_Write, Loc),
3490 Parameter_Associations => New_List (
3491 Make_Attribute_Reference (Loc,
3492 Prefix => Relocate_Node (Comp_Sel_Nam),
3493 Attribute_Name => Name_Address),
3495 Unchecked_Convert_To (Unsigned,
3496 New_Reference_To (Expected_Comp, Loc)),
3498 Unchecked_Convert_To (Unsigned,
3499 New_Reference_To (Desired_Comp, Loc)))));
3501 -- Small optimization: transform the default return statement
3502 -- of a procedure into the atomic exit statement.
3504 if Nkind (Last (Stmts)) = N_Simple_Return_Statement then
3505 Rewrite (Last (Stmts), Stmt);
3506 else
3507 Append_To (Stmts, Stmt);
3508 end if;
3509 end if;
3511 -- Create the declaration of the label used to skip the rest of
3512 -- the source statements when the object state changes.
3514 if Present (Label_Id) then
3515 Label := Make_Label (Loc, Label_Id);
3516 Append_To (Decls,
3517 Make_Implicit_Label_Declaration (Loc,
3518 Defining_Identifier => Entity (Label_Id),
3519 Label_Construct => Label));
3520 Append_To (Stmts, Label);
3521 end if;
3523 -- Generate:
3524 -- loop
3525 -- declare
3526 -- <Decls>
3527 -- begin
3528 -- <Stmts>
3529 -- end;
3530 -- end loop;
3532 if Is_Procedure then
3533 Stmts :=
3534 New_List (
3535 Make_Loop_Statement (Loc,
3536 Statements => New_List (
3537 Make_Block_Statement (Loc,
3538 Declarations => Block_Decls,
3539 Handled_Statement_Sequence =>
3540 Make_Handled_Sequence_Of_Statements (Loc,
3541 Statements => Stmts))),
3542 End_Label => Empty));
3543 end if;
3545 Hand_Stmt_Seq :=
3546 Make_Handled_Sequence_Of_Statements (Loc, Statements => Stmts);
3547 end Protected_Component_Ref;
3548 end if;
3550 -- Make an unprotected version of the subprogram for use within the same
3551 -- object, with new name and extra parameter representing the object.
3553 return
3554 Make_Subprogram_Body (Loc,
3555 Specification =>
3556 Build_Protected_Sub_Specification (N, Prot_Typ, Unprotected_Mode),
3557 Declarations => Decls,
3558 Handled_Statement_Sequence => Hand_Stmt_Seq);
3559 end Build_Lock_Free_Unprotected_Subprogram_Body;
3561 -------------------------
3562 -- Build_Master_Entity --
3563 -------------------------
3565 procedure Build_Master_Entity (Obj_Or_Typ : Entity_Id) is
3566 Loc : constant Source_Ptr := Sloc (Obj_Or_Typ);
3567 Context : Node_Id;
3568 Context_Id : Entity_Id;
3569 Decl : Node_Id;
3570 Decls : List_Id;
3571 Par : Node_Id;
3573 begin
3574 if Is_Itype (Obj_Or_Typ) then
3575 Par := Associated_Node_For_Itype (Obj_Or_Typ);
3576 else
3577 Par := Parent (Obj_Or_Typ);
3578 end if;
3580 -- When creating a master for a record component which is either a task
3581 -- or access-to-task, the enclosing record is the master scope and the
3582 -- proper insertion point is the component list.
3584 if Is_Record_Type (Current_Scope) then
3585 Context := Par;
3586 Context_Id := Current_Scope;
3587 Decls := List_Containing (Context);
3589 -- Default case for object declarations and access types. Note that the
3590 -- context is updated to the nearest enclosing body, block, package or
3591 -- return statement.
3593 else
3594 Find_Enclosing_Context (Par, Context, Context_Id, Decls);
3595 end if;
3597 -- Do not create a master if one already exists or there is no task
3598 -- hierarchy.
3600 if Has_Master_Entity (Context_Id)
3601 or else Restriction_Active (No_Task_Hierarchy)
3602 then
3603 return;
3604 end if;
3606 -- Create a master, generate:
3607 -- _Master : constant Master_Id := Current_Master.all;
3609 Decl :=
3610 Make_Object_Declaration (Loc,
3611 Defining_Identifier =>
3612 Make_Defining_Identifier (Loc, Name_uMaster),
3613 Constant_Present => True,
3614 Object_Definition => New_Reference_To (RTE (RE_Master_Id), Loc),
3615 Expression =>
3616 Make_Explicit_Dereference (Loc,
3617 New_Reference_To (RTE (RE_Current_Master), Loc)));
3619 -- The master is inserted at the start of the declarative list of the
3620 -- context.
3622 Prepend_To (Decls, Decl);
3624 -- In certain cases where transient scopes are involved, the immediate
3625 -- scope is not always the proper master scope. Ensure that the master
3626 -- declaration and entity appear in the same context.
3628 if Context_Id /= Current_Scope then
3629 Push_Scope (Context_Id);
3630 Analyze (Decl);
3631 Pop_Scope;
3632 else
3633 Analyze (Decl);
3634 end if;
3636 -- Mark the enclosing scope and its associated construct as being task
3637 -- masters.
3639 Set_Has_Master_Entity (Context_Id);
3641 while Present (Context)
3642 and then Nkind (Context) /= N_Compilation_Unit
3643 loop
3644 if Nkind_In (Context, N_Block_Statement,
3645 N_Subprogram_Body,
3646 N_Task_Body)
3647 then
3648 Set_Is_Task_Master (Context);
3649 exit;
3651 elsif Nkind (Parent (Context)) = N_Subunit then
3652 Context := Corresponding_Stub (Parent (Context));
3653 end if;
3655 Context := Parent (Context);
3656 end loop;
3657 end Build_Master_Entity;
3659 ---------------------------
3660 -- Build_Master_Renaming --
3661 ---------------------------
3663 procedure Build_Master_Renaming
3664 (Ptr_Typ : Entity_Id;
3665 Ins_Nod : Node_Id := Empty)
3667 Loc : constant Source_Ptr := Sloc (Ptr_Typ);
3668 Context : Node_Id;
3669 Master_Decl : Node_Id;
3670 Master_Id : Entity_Id;
3672 begin
3673 -- Nothing to do if there is no task hierarchy
3675 if Restriction_Active (No_Task_Hierarchy) then
3676 return;
3677 end if;
3679 -- Determine the proper context to insert the master renaming
3681 if Present (Ins_Nod) then
3682 Context := Ins_Nod;
3683 elsif Is_Itype (Ptr_Typ) then
3684 Context := Associated_Node_For_Itype (Ptr_Typ);
3685 else
3686 Context := Parent (Ptr_Typ);
3687 end if;
3689 -- Generate:
3690 -- <Ptr_Typ>M : Master_Id renames _Master;
3692 Master_Id :=
3693 Make_Defining_Identifier (Loc,
3694 New_External_Name (Chars (Ptr_Typ), 'M'));
3696 Master_Decl :=
3697 Make_Object_Renaming_Declaration (Loc,
3698 Defining_Identifier => Master_Id,
3699 Subtype_Mark => New_Reference_To (RTE (RE_Master_Id), Loc),
3700 Name => Make_Identifier (Loc, Name_uMaster));
3702 Insert_Action (Context, Master_Decl);
3704 -- The renamed master now services the access type
3706 Set_Master_Id (Ptr_Typ, Master_Id);
3707 end Build_Master_Renaming;
3709 -----------------------------------------
3710 -- Build_Private_Protected_Declaration --
3711 -----------------------------------------
3713 function Build_Private_Protected_Declaration
3714 (N : Node_Id) return Entity_Id
3716 Loc : constant Source_Ptr := Sloc (N);
3717 Body_Id : constant Entity_Id := Defining_Entity (N);
3718 Decl : Node_Id;
3719 Plist : List_Id;
3720 Formal : Entity_Id;
3721 New_Spec : Node_Id;
3722 Spec_Id : Entity_Id;
3724 begin
3725 Formal := First_Formal (Body_Id);
3727 -- The protected operation always has at least one formal, namely the
3728 -- object itself, but it is only placed in the parameter list if
3729 -- expansion is enabled.
3731 if Present (Formal) or else Expander_Active then
3732 Plist := Copy_Parameter_List (Body_Id);
3733 else
3734 Plist := No_List;
3735 end if;
3737 if Nkind (Specification (N)) = N_Procedure_Specification then
3738 New_Spec :=
3739 Make_Procedure_Specification (Loc,
3740 Defining_Unit_Name =>
3741 Make_Defining_Identifier (Sloc (Body_Id),
3742 Chars => Chars (Body_Id)),
3743 Parameter_Specifications =>
3744 Plist);
3745 else
3746 New_Spec :=
3747 Make_Function_Specification (Loc,
3748 Defining_Unit_Name =>
3749 Make_Defining_Identifier (Sloc (Body_Id),
3750 Chars => Chars (Body_Id)),
3751 Parameter_Specifications => Plist,
3752 Result_Definition =>
3753 New_Occurrence_Of (Etype (Body_Id), Loc));
3754 end if;
3756 Decl := Make_Subprogram_Declaration (Loc, Specification => New_Spec);
3757 Insert_Before (N, Decl);
3758 Spec_Id := Defining_Unit_Name (New_Spec);
3760 -- Indicate that the entity comes from source, to ensure that cross-
3761 -- reference information is properly generated. The body itself is
3762 -- rewritten during expansion, and the body entity will not appear in
3763 -- calls to the operation.
3765 Set_Comes_From_Source (Spec_Id, True);
3766 Analyze (Decl);
3767 Set_Has_Completion (Spec_Id);
3768 Set_Convention (Spec_Id, Convention_Protected);
3769 return Spec_Id;
3770 end Build_Private_Protected_Declaration;
3772 ---------------------------
3773 -- Build_Protected_Entry --
3774 ---------------------------
3776 function Build_Protected_Entry
3777 (N : Node_Id;
3778 Ent : Entity_Id;
3779 Pid : Node_Id) return Node_Id
3781 Loc : constant Source_Ptr := Sloc (N);
3783 Decls : constant List_Id := Declarations (N);
3784 End_Lab : constant Node_Id :=
3785 End_Label (Handled_Statement_Sequence (N));
3786 End_Loc : constant Source_Ptr :=
3787 Sloc (Last (Statements (Handled_Statement_Sequence (N))));
3788 -- Used for the generated call to Complete_Entry_Body
3790 Han_Loc : Source_Ptr;
3791 -- Used for the exception handler, inserted at end of the body
3793 Op_Decls : constant List_Id := New_List;
3794 Complete : Node_Id;
3795 Edef : Entity_Id;
3796 Espec : Node_Id;
3797 Ohandle : Node_Id;
3798 Op_Stats : List_Id;
3800 begin
3801 -- Set the source location on the exception handler only when debugging
3802 -- the expanded code (see Make_Implicit_Exception_Handler).
3804 if Debug_Generated_Code then
3805 Han_Loc := End_Loc;
3807 -- Otherwise the inserted code should not be visible to the debugger
3809 else
3810 Han_Loc := No_Location;
3811 end if;
3813 Edef :=
3814 Make_Defining_Identifier (Loc,
3815 Chars => Chars (Protected_Body_Subprogram (Ent)));
3816 Espec :=
3817 Build_Protected_Entry_Specification (Loc, Edef, Empty);
3819 -- Add the following declarations:
3820 -- type poVP is access poV;
3821 -- _object : poVP := poVP (_O);
3823 -- where _O is the formal parameter associated with the concurrent
3824 -- object. These declarations are needed for Complete_Entry_Body.
3826 Add_Object_Pointer (Loc, Pid, Op_Decls);
3828 -- Add renamings for all formals, the Protection object, discriminals,
3829 -- privals and the entry index constant for use by debugger.
3831 Add_Formal_Renamings (Espec, Op_Decls, Ent, Loc);
3832 Debug_Private_Data_Declarations (Decls);
3834 case Corresponding_Runtime_Package (Pid) is
3835 when System_Tasking_Protected_Objects_Entries =>
3836 Complete :=
3837 New_Reference_To (RTE (RE_Complete_Entry_Body), Loc);
3839 when System_Tasking_Protected_Objects_Single_Entry =>
3840 Complete :=
3841 New_Reference_To (RTE (RE_Complete_Single_Entry_Body), Loc);
3843 when others =>
3844 raise Program_Error;
3845 end case;
3847 Op_Stats := New_List (
3848 Make_Block_Statement (Loc,
3849 Declarations => Decls,
3850 Handled_Statement_Sequence =>
3851 Handled_Statement_Sequence (N)),
3853 Make_Procedure_Call_Statement (End_Loc,
3854 Name => Complete,
3855 Parameter_Associations => New_List (
3856 Make_Attribute_Reference (End_Loc,
3857 Prefix =>
3858 Make_Selected_Component (End_Loc,
3859 Prefix => Make_Identifier (End_Loc, Name_uObject),
3860 Selector_Name => Make_Identifier (End_Loc, Name_uObject)),
3861 Attribute_Name => Name_Unchecked_Access))));
3863 -- When exceptions can not be propagated, we never need to call
3864 -- Exception_Complete_Entry_Body
3866 if No_Exception_Handlers_Set then
3867 return
3868 Make_Subprogram_Body (Loc,
3869 Specification => Espec,
3870 Declarations => Op_Decls,
3871 Handled_Statement_Sequence =>
3872 Make_Handled_Sequence_Of_Statements (Loc,
3873 Statements => Op_Stats,
3874 End_Label => End_Lab));
3876 else
3877 Ohandle := Make_Others_Choice (Loc);
3878 Set_All_Others (Ohandle);
3880 case Corresponding_Runtime_Package (Pid) is
3881 when System_Tasking_Protected_Objects_Entries =>
3882 Complete :=
3883 New_Reference_To
3884 (RTE (RE_Exceptional_Complete_Entry_Body), Loc);
3886 when System_Tasking_Protected_Objects_Single_Entry =>
3887 Complete :=
3888 New_Reference_To
3889 (RTE (RE_Exceptional_Complete_Single_Entry_Body), Loc);
3891 when others =>
3892 raise Program_Error;
3893 end case;
3895 -- Establish link between subprogram body entity and source entry
3897 Set_Corresponding_Protected_Entry (Edef, Ent);
3899 -- Create body of entry procedure. The renaming declarations are
3900 -- placed ahead of the block that contains the actual entry body.
3902 return
3903 Make_Subprogram_Body (Loc,
3904 Specification => Espec,
3905 Declarations => Op_Decls,
3906 Handled_Statement_Sequence =>
3907 Make_Handled_Sequence_Of_Statements (Loc,
3908 Statements => Op_Stats,
3909 End_Label => End_Lab,
3910 Exception_Handlers => New_List (
3911 Make_Implicit_Exception_Handler (Han_Loc,
3912 Exception_Choices => New_List (Ohandle),
3914 Statements => New_List (
3915 Make_Procedure_Call_Statement (Han_Loc,
3916 Name => Complete,
3917 Parameter_Associations => New_List (
3918 Make_Attribute_Reference (Han_Loc,
3919 Prefix =>
3920 Make_Selected_Component (Han_Loc,
3921 Prefix =>
3922 Make_Identifier (Han_Loc, Name_uObject),
3923 Selector_Name =>
3924 Make_Identifier (Han_Loc, Name_uObject)),
3925 Attribute_Name => Name_Unchecked_Access),
3927 Make_Function_Call (Han_Loc,
3928 Name => New_Reference_To (
3929 RTE (RE_Get_GNAT_Exception), Loc)))))))));
3930 end if;
3931 end Build_Protected_Entry;
3933 -----------------------------------------
3934 -- Build_Protected_Entry_Specification --
3935 -----------------------------------------
3937 function Build_Protected_Entry_Specification
3938 (Loc : Source_Ptr;
3939 Def_Id : Entity_Id;
3940 Ent_Id : Entity_Id) return Node_Id
3942 P : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uP);
3944 begin
3945 Set_Debug_Info_Needed (Def_Id);
3947 if Present (Ent_Id) then
3948 Append_Elmt (P, Accept_Address (Ent_Id));
3949 end if;
3951 return
3952 Make_Procedure_Specification (Loc,
3953 Defining_Unit_Name => Def_Id,
3954 Parameter_Specifications => New_List (
3955 Make_Parameter_Specification (Loc,
3956 Defining_Identifier =>
3957 Make_Defining_Identifier (Loc, Name_uO),
3958 Parameter_Type =>
3959 New_Reference_To (RTE (RE_Address), Loc)),
3961 Make_Parameter_Specification (Loc,
3962 Defining_Identifier => P,
3963 Parameter_Type =>
3964 New_Reference_To (RTE (RE_Address), Loc)),
3966 Make_Parameter_Specification (Loc,
3967 Defining_Identifier =>
3968 Make_Defining_Identifier (Loc, Name_uE),
3969 Parameter_Type =>
3970 New_Reference_To (RTE (RE_Protected_Entry_Index), Loc))));
3971 end Build_Protected_Entry_Specification;
3973 --------------------------
3974 -- Build_Protected_Spec --
3975 --------------------------
3977 function Build_Protected_Spec
3978 (N : Node_Id;
3979 Obj_Type : Entity_Id;
3980 Ident : Entity_Id;
3981 Unprotected : Boolean := False) return List_Id
3983 Loc : constant Source_Ptr := Sloc (N);
3984 Decl : Node_Id;
3985 Formal : Entity_Id;
3986 New_Plist : List_Id;
3987 New_Param : Node_Id;
3989 begin
3990 New_Plist := New_List;
3992 Formal := First_Formal (Ident);
3993 while Present (Formal) loop
3994 New_Param :=
3995 Make_Parameter_Specification (Loc,
3996 Defining_Identifier =>
3997 Make_Defining_Identifier (Sloc (Formal), Chars (Formal)),
3998 In_Present => In_Present (Parent (Formal)),
3999 Out_Present => Out_Present (Parent (Formal)),
4000 Parameter_Type => New_Reference_To (Etype (Formal), Loc));
4002 if Unprotected then
4003 Set_Protected_Formal (Formal, Defining_Identifier (New_Param));
4004 end if;
4006 Append (New_Param, New_Plist);
4007 Next_Formal (Formal);
4008 end loop;
4010 -- If the subprogram is a procedure and the context is not an access
4011 -- to protected subprogram, the parameter is in-out. Otherwise it is
4012 -- an in parameter.
4014 Decl :=
4015 Make_Parameter_Specification (Loc,
4016 Defining_Identifier =>
4017 Make_Defining_Identifier (Loc, Name_uObject),
4018 In_Present => True,
4019 Out_Present =>
4020 (Etype (Ident) = Standard_Void_Type
4021 and then not Is_RTE (Obj_Type, RE_Address)),
4022 Parameter_Type =>
4023 New_Reference_To (Obj_Type, Loc));
4024 Set_Debug_Info_Needed (Defining_Identifier (Decl));
4025 Prepend_To (New_Plist, Decl);
4027 return New_Plist;
4028 end Build_Protected_Spec;
4030 ---------------------------------------
4031 -- Build_Protected_Sub_Specification --
4032 ---------------------------------------
4034 function Build_Protected_Sub_Specification
4035 (N : Node_Id;
4036 Prot_Typ : Entity_Id;
4037 Mode : Subprogram_Protection_Mode) return Node_Id
4039 Loc : constant Source_Ptr := Sloc (N);
4040 Decl : Node_Id;
4041 Def_Id : Entity_Id;
4042 New_Id : Entity_Id;
4043 New_Plist : List_Id;
4044 New_Spec : Node_Id;
4046 Append_Chr : constant array (Subprogram_Protection_Mode) of Character :=
4047 (Dispatching_Mode => ' ',
4048 Protected_Mode => 'P',
4049 Unprotected_Mode => 'N');
4051 begin
4052 if Ekind (Defining_Unit_Name (Specification (N))) =
4053 E_Subprogram_Body
4054 then
4055 Decl := Unit_Declaration_Node (Corresponding_Spec (N));
4056 else
4057 Decl := N;
4058 end if;
4060 Def_Id := Defining_Unit_Name (Specification (Decl));
4062 New_Plist :=
4063 Build_Protected_Spec
4064 (Decl, Corresponding_Record_Type (Prot_Typ), Def_Id,
4065 Mode = Unprotected_Mode);
4066 New_Id :=
4067 Make_Defining_Identifier (Loc,
4068 Chars => Build_Selected_Name (Prot_Typ, Def_Id, Append_Chr (Mode)));
4070 -- The unprotected operation carries the user code, and debugging
4071 -- information must be generated for it, even though this spec does
4072 -- not come from source. It is also convenient to allow gdb to step
4073 -- into the protected operation, even though it only contains lock/
4074 -- unlock calls.
4076 Set_Debug_Info_Needed (New_Id);
4078 -- If a pragma Eliminate applies to the source entity, the internal
4079 -- subprograms will be eliminated as well.
4081 Set_Is_Eliminated (New_Id, Is_Eliminated (Def_Id));
4083 if Nkind (Specification (Decl)) = N_Procedure_Specification then
4084 New_Spec :=
4085 Make_Procedure_Specification (Loc,
4086 Defining_Unit_Name => New_Id,
4087 Parameter_Specifications => New_Plist);
4089 -- Create a new specification for the anonymous subprogram type
4091 else
4092 New_Spec :=
4093 Make_Function_Specification (Loc,
4094 Defining_Unit_Name => New_Id,
4095 Parameter_Specifications => New_Plist,
4096 Result_Definition =>
4097 Copy_Result_Type (Result_Definition (Specification (Decl))));
4099 Set_Return_Present (Defining_Unit_Name (New_Spec));
4100 end if;
4102 return New_Spec;
4103 end Build_Protected_Sub_Specification;
4105 -------------------------------------
4106 -- Build_Protected_Subprogram_Body --
4107 -------------------------------------
4109 function Build_Protected_Subprogram_Body
4110 (N : Node_Id;
4111 Pid : Node_Id;
4112 N_Op_Spec : Node_Id) return Node_Id
4114 Loc : constant Source_Ptr := Sloc (N);
4115 Op_Spec : Node_Id;
4116 P_Op_Spec : Node_Id;
4117 Uactuals : List_Id;
4118 Pformal : Node_Id;
4119 Unprot_Call : Node_Id;
4120 Sub_Body : Node_Id;
4121 Lock_Name : Node_Id;
4122 Lock_Stmt : Node_Id;
4123 Service_Name : Node_Id;
4124 R : Node_Id;
4125 Return_Stmt : Node_Id := Empty; -- init to avoid gcc 3 warning
4126 Pre_Stmts : List_Id := No_List; -- init to avoid gcc 3 warning
4127 Stmts : List_Id;
4128 Object_Parm : Node_Id;
4129 Exc_Safe : Boolean;
4130 Lock_Kind : RE_Id;
4132 begin
4133 Op_Spec := Specification (N);
4134 Exc_Safe := Is_Exception_Safe (N);
4136 P_Op_Spec :=
4137 Build_Protected_Sub_Specification (N, Pid, Protected_Mode);
4139 -- Build a list of the formal parameters of the protected version of
4140 -- the subprogram to use as the actual parameters of the unprotected
4141 -- version.
4143 Uactuals := New_List;
4144 Pformal := First (Parameter_Specifications (P_Op_Spec));
4145 while Present (Pformal) loop
4146 Append_To (Uactuals,
4147 Make_Identifier (Loc, Chars (Defining_Identifier (Pformal))));
4148 Next (Pformal);
4149 end loop;
4151 -- Make a call to the unprotected version of the subprogram built above
4152 -- for use by the protected version built below.
4154 if Nkind (Op_Spec) = N_Function_Specification then
4155 if Exc_Safe then
4156 R := Make_Temporary (Loc, 'R');
4157 Unprot_Call :=
4158 Make_Object_Declaration (Loc,
4159 Defining_Identifier => R,
4160 Constant_Present => True,
4161 Object_Definition => New_Copy (Result_Definition (N_Op_Spec)),
4162 Expression =>
4163 Make_Function_Call (Loc,
4164 Name => Make_Identifier (Loc,
4165 Chars => Chars (Defining_Unit_Name (N_Op_Spec))),
4166 Parameter_Associations => Uactuals));
4168 Return_Stmt :=
4169 Make_Simple_Return_Statement (Loc,
4170 Expression => New_Reference_To (R, Loc));
4172 else
4173 Unprot_Call := Make_Simple_Return_Statement (Loc,
4174 Expression => Make_Function_Call (Loc,
4175 Name =>
4176 Make_Identifier (Loc,
4177 Chars => Chars (Defining_Unit_Name (N_Op_Spec))),
4178 Parameter_Associations => Uactuals));
4179 end if;
4181 Lock_Kind := RE_Lock_Read_Only;
4183 else
4184 Unprot_Call :=
4185 Make_Procedure_Call_Statement (Loc,
4186 Name =>
4187 Make_Identifier (Loc, Chars (Defining_Unit_Name (N_Op_Spec))),
4188 Parameter_Associations => Uactuals);
4190 Lock_Kind := RE_Lock;
4191 end if;
4193 -- Wrap call in block that will be covered by an at_end handler
4195 if not Exc_Safe then
4196 Unprot_Call := Make_Block_Statement (Loc,
4197 Handled_Statement_Sequence =>
4198 Make_Handled_Sequence_Of_Statements (Loc,
4199 Statements => New_List (Unprot_Call)));
4200 end if;
4202 -- Make the protected subprogram body. This locks the protected
4203 -- object and calls the unprotected version of the subprogram.
4205 case Corresponding_Runtime_Package (Pid) is
4206 when System_Tasking_Protected_Objects_Entries =>
4207 Lock_Name := New_Reference_To (RTE (RE_Lock_Entries), Loc);
4208 Service_Name := New_Reference_To (RTE (RE_Service_Entries), Loc);
4210 when System_Tasking_Protected_Objects_Single_Entry =>
4211 Lock_Name := New_Reference_To (RTE (RE_Lock_Entry), Loc);
4212 Service_Name := New_Reference_To (RTE (RE_Service_Entry), Loc);
4214 when System_Tasking_Protected_Objects =>
4215 Lock_Name := New_Reference_To (RTE (Lock_Kind), Loc);
4216 Service_Name := New_Reference_To (RTE (RE_Unlock), Loc);
4218 when others =>
4219 raise Program_Error;
4220 end case;
4222 Object_Parm :=
4223 Make_Attribute_Reference (Loc,
4224 Prefix =>
4225 Make_Selected_Component (Loc,
4226 Prefix => Make_Identifier (Loc, Name_uObject),
4227 Selector_Name => Make_Identifier (Loc, Name_uObject)),
4228 Attribute_Name => Name_Unchecked_Access);
4230 Lock_Stmt := Make_Procedure_Call_Statement (Loc,
4231 Name => Lock_Name,
4232 Parameter_Associations => New_List (Object_Parm));
4234 if Abort_Allowed then
4235 Stmts := New_List (
4236 Make_Procedure_Call_Statement (Loc,
4237 Name => New_Reference_To (RTE (RE_Abort_Defer), Loc),
4238 Parameter_Associations => Empty_List),
4239 Lock_Stmt);
4241 else
4242 Stmts := New_List (Lock_Stmt);
4243 end if;
4245 if not Exc_Safe then
4246 Append (Unprot_Call, Stmts);
4247 else
4248 if Nkind (Op_Spec) = N_Function_Specification then
4249 Pre_Stmts := Stmts;
4250 Stmts := Empty_List;
4251 else
4252 Append (Unprot_Call, Stmts);
4253 end if;
4255 Append (
4256 Make_Procedure_Call_Statement (Loc,
4257 Name => Service_Name,
4258 Parameter_Associations =>
4259 New_List (New_Copy_Tree (Object_Parm))),
4260 Stmts);
4262 if Abort_Allowed then
4263 Append (
4264 Make_Procedure_Call_Statement (Loc,
4265 Name => New_Reference_To (RTE (RE_Abort_Undefer), Loc),
4266 Parameter_Associations => Empty_List),
4267 Stmts);
4268 end if;
4270 if Nkind (Op_Spec) = N_Function_Specification then
4271 Append (Return_Stmt, Stmts);
4272 Append (Make_Block_Statement (Loc,
4273 Declarations => New_List (Unprot_Call),
4274 Handled_Statement_Sequence =>
4275 Make_Handled_Sequence_Of_Statements (Loc,
4276 Statements => Stmts)), Pre_Stmts);
4277 Stmts := Pre_Stmts;
4278 end if;
4279 end if;
4281 Sub_Body :=
4282 Make_Subprogram_Body (Loc,
4283 Declarations => Empty_List,
4284 Specification => P_Op_Spec,
4285 Handled_Statement_Sequence =>
4286 Make_Handled_Sequence_Of_Statements (Loc, Statements => Stmts));
4288 if not Exc_Safe then
4289 Set_Is_Protected_Subprogram_Body (Sub_Body);
4290 end if;
4292 return Sub_Body;
4293 end Build_Protected_Subprogram_Body;
4295 -------------------------------------
4296 -- Build_Protected_Subprogram_Call --
4297 -------------------------------------
4299 procedure Build_Protected_Subprogram_Call
4300 (N : Node_Id;
4301 Name : Node_Id;
4302 Rec : Node_Id;
4303 External : Boolean := True)
4305 Loc : constant Source_Ptr := Sloc (N);
4306 Sub : constant Entity_Id := Entity (Name);
4307 New_Sub : Node_Id;
4308 Params : List_Id;
4310 begin
4311 if External then
4312 New_Sub := New_Occurrence_Of (External_Subprogram (Sub), Loc);
4313 else
4314 New_Sub :=
4315 New_Occurrence_Of (Protected_Body_Subprogram (Sub), Loc);
4316 end if;
4318 if Present (Parameter_Associations (N)) then
4319 Params := New_Copy_List_Tree (Parameter_Associations (N));
4320 else
4321 Params := New_List;
4322 end if;
4324 -- If the type is an untagged derived type, convert to the root type,
4325 -- which is the one on which the operations are defined.
4327 if Nkind (Rec) = N_Unchecked_Type_Conversion
4328 and then not Is_Tagged_Type (Etype (Rec))
4329 and then Is_Derived_Type (Etype (Rec))
4330 then
4331 Set_Etype (Rec, Root_Type (Etype (Rec)));
4332 Set_Subtype_Mark (Rec,
4333 New_Occurrence_Of (Root_Type (Etype (Rec)), Sloc (N)));
4334 end if;
4336 Prepend (Rec, Params);
4338 if Ekind (Sub) = E_Procedure then
4339 Rewrite (N,
4340 Make_Procedure_Call_Statement (Loc,
4341 Name => New_Sub,
4342 Parameter_Associations => Params));
4344 else
4345 pragma Assert (Ekind (Sub) = E_Function);
4346 Rewrite (N,
4347 Make_Function_Call (Loc,
4348 Name => New_Sub,
4349 Parameter_Associations => Params));
4350 end if;
4352 if External
4353 and then Nkind (Rec) = N_Unchecked_Type_Conversion
4354 and then Is_Entity_Name (Expression (Rec))
4355 and then Is_Shared_Passive (Entity (Expression (Rec)))
4356 then
4357 Add_Shared_Var_Lock_Procs (N);
4358 end if;
4359 end Build_Protected_Subprogram_Call;
4361 -------------------------
4362 -- Build_Selected_Name --
4363 -------------------------
4365 function Build_Selected_Name
4366 (Prefix : Entity_Id;
4367 Selector : Entity_Id;
4368 Append_Char : Character := ' ') return Name_Id
4370 Select_Buffer : String (1 .. Hostparm.Max_Name_Length);
4371 Select_Len : Natural;
4373 begin
4374 Get_Name_String (Chars (Selector));
4375 Select_Len := Name_Len;
4376 Select_Buffer (1 .. Select_Len) := Name_Buffer (1 .. Name_Len);
4377 Get_Name_String (Chars (Prefix));
4379 -- If scope is anonymous type, discard suffix to recover name of
4380 -- single protected object. Otherwise use protected type name.
4382 if Name_Buffer (Name_Len) = 'T' then
4383 Name_Len := Name_Len - 1;
4384 end if;
4386 Add_Str_To_Name_Buffer ("__");
4387 for J in 1 .. Select_Len loop
4388 Add_Char_To_Name_Buffer (Select_Buffer (J));
4389 end loop;
4391 -- Now add the Append_Char if specified. The encoding to follow
4392 -- depends on the type of entity. If Append_Char is either 'N' or 'P',
4393 -- then the entity is associated to a protected type subprogram.
4394 -- Otherwise, it is a protected type entry. For each case, the
4395 -- encoding to follow for the suffix is documented in exp_dbug.ads.
4397 -- It would be better to encapsulate this as a routine in Exp_Dbug ???
4399 if Append_Char /= ' ' then
4400 if Append_Char = 'P' or Append_Char = 'N' then
4401 Add_Char_To_Name_Buffer (Append_Char);
4402 return Name_Find;
4403 else
4404 Add_Str_To_Name_Buffer ((1 => '_', 2 => Append_Char));
4405 return New_External_Name (Name_Find, ' ', -1);
4406 end if;
4407 else
4408 return Name_Find;
4409 end if;
4410 end Build_Selected_Name;
4412 -----------------------------
4413 -- Build_Simple_Entry_Call --
4414 -----------------------------
4416 -- A task entry call is converted to a call to Call_Simple
4418 -- declare
4419 -- P : parms := (parm, parm, parm);
4420 -- begin
4421 -- Call_Simple (acceptor-task, entry-index, P'Address);
4422 -- parm := P.param;
4423 -- parm := P.param;
4424 -- ...
4425 -- end;
4427 -- Here Pnn is an aggregate of the type constructed for the entry to hold
4428 -- the parameters, and the constructed aggregate value contains either the
4429 -- parameters or, in the case of non-elementary types, references to these
4430 -- parameters. Then the address of this aggregate is passed to the runtime
4431 -- routine, along with the task id value and the task entry index value.
4432 -- Pnn is only required if parameters are present.
4434 -- The assignments after the call are present only in the case of in-out
4435 -- or out parameters for elementary types, and are used to assign back the
4436 -- resulting values of such parameters.
4438 -- Note: the reason that we insert a block here is that in the context
4439 -- of selects, conditional entry calls etc. the entry call statement
4440 -- appears on its own, not as an element of a list.
4442 -- A protected entry call is converted to a Protected_Entry_Call:
4444 -- declare
4445 -- P : E1_Params := (param, param, param);
4446 -- Pnn : Boolean;
4447 -- Bnn : Communications_Block;
4449 -- declare
4450 -- P : E1_Params := (param, param, param);
4451 -- Bnn : Communications_Block;
4453 -- begin
4454 -- Protected_Entry_Call (
4455 -- Object => po._object'Access,
4456 -- E => <entry index>;
4457 -- Uninterpreted_Data => P'Address;
4458 -- Mode => Simple_Call;
4459 -- Block => Bnn);
4460 -- parm := P.param;
4461 -- parm := P.param;
4462 -- ...
4463 -- end;
4465 procedure Build_Simple_Entry_Call
4466 (N : Node_Id;
4467 Concval : Node_Id;
4468 Ename : Node_Id;
4469 Index : Node_Id)
4471 begin
4472 Expand_Call (N);
4474 -- If call has been inlined, nothing left to do
4476 if Nkind (N) = N_Block_Statement then
4477 return;
4478 end if;
4480 -- Convert entry call to Call_Simple call
4482 declare
4483 Loc : constant Source_Ptr := Sloc (N);
4484 Parms : constant List_Id := Parameter_Associations (N);
4485 Stats : constant List_Id := New_List;
4486 Actual : Node_Id;
4487 Call : Node_Id;
4488 Comm_Name : Entity_Id;
4489 Conctyp : Node_Id;
4490 Decls : List_Id;
4491 Ent : Entity_Id;
4492 Ent_Acc : Entity_Id;
4493 Formal : Node_Id;
4494 Iface_Tag : Entity_Id;
4495 Iface_Typ : Entity_Id;
4496 N_Node : Node_Id;
4497 N_Var : Node_Id;
4498 P : Entity_Id;
4499 Parm1 : Node_Id;
4500 Parm2 : Node_Id;
4501 Parm3 : Node_Id;
4502 Pdecl : Node_Id;
4503 Plist : List_Id;
4504 X : Entity_Id;
4505 Xdecl : Node_Id;
4507 begin
4508 -- Simple entry and entry family cases merge here
4510 Ent := Entity (Ename);
4511 Ent_Acc := Entry_Parameters_Type (Ent);
4512 Conctyp := Etype (Concval);
4514 -- If prefix is an access type, dereference to obtain the task type
4516 if Is_Access_Type (Conctyp) then
4517 Conctyp := Designated_Type (Conctyp);
4518 end if;
4520 -- Special case for protected subprogram calls
4522 if Is_Protected_Type (Conctyp)
4523 and then Is_Subprogram (Entity (Ename))
4524 then
4525 if not Is_Eliminated (Entity (Ename)) then
4526 Build_Protected_Subprogram_Call
4527 (N, Ename, Convert_Concurrent (Concval, Conctyp));
4528 Analyze (N);
4529 end if;
4531 return;
4532 end if;
4534 -- First parameter is the Task_Id value from the task value or the
4535 -- Object from the protected object value, obtained by selecting
4536 -- the _Task_Id or _Object from the result of doing an unchecked
4537 -- conversion to convert the value to the corresponding record type.
4539 if Nkind (Concval) = N_Function_Call
4540 and then Is_Task_Type (Conctyp)
4541 and then Ada_Version >= Ada_2005
4542 then
4543 declare
4544 ExpR : constant Node_Id := Relocate_Node (Concval);
4545 Obj : constant Entity_Id := Make_Temporary (Loc, 'F', ExpR);
4546 Decl : Node_Id;
4548 begin
4549 Decl :=
4550 Make_Object_Declaration (Loc,
4551 Defining_Identifier => Obj,
4552 Object_Definition => New_Occurrence_Of (Conctyp, Loc),
4553 Expression => ExpR);
4554 Set_Etype (Obj, Conctyp);
4555 Decls := New_List (Decl);
4556 Rewrite (Concval, New_Occurrence_Of (Obj, Loc));
4557 end;
4559 else
4560 Decls := New_List;
4561 end if;
4563 Parm1 := Concurrent_Ref (Concval);
4565 -- Second parameter is the entry index, computed by the routine
4566 -- provided for this purpose. The value of this expression is
4567 -- assigned to an intermediate variable to assure that any entry
4568 -- family index expressions are evaluated before the entry
4569 -- parameters.
4571 if Abort_Allowed
4572 or else Restriction_Active (No_Entry_Queue) = False
4573 or else not Is_Protected_Type (Conctyp)
4574 or else Number_Entries (Conctyp) > 1
4575 or else (Has_Attach_Handler (Conctyp)
4576 and then not Restricted_Profile)
4577 then
4578 X := Make_Defining_Identifier (Loc, Name_uX);
4580 Xdecl :=
4581 Make_Object_Declaration (Loc,
4582 Defining_Identifier => X,
4583 Object_Definition =>
4584 New_Reference_To (RTE (RE_Task_Entry_Index), Loc),
4585 Expression => Actual_Index_Expression (
4586 Loc, Entity (Ename), Index, Concval));
4588 Append_To (Decls, Xdecl);
4589 Parm2 := New_Reference_To (X, Loc);
4591 else
4592 Xdecl := Empty;
4593 Parm2 := Empty;
4594 end if;
4596 -- The third parameter is the packaged parameters. If there are
4597 -- none, then it is just the null address, since nothing is passed.
4599 if No (Parms) then
4600 Parm3 := New_Reference_To (RTE (RE_Null_Address), Loc);
4601 P := Empty;
4603 -- Case of parameters present, where third argument is the address
4604 -- of a packaged record containing the required parameter values.
4606 else
4607 -- First build a list of parameter values, which are references to
4608 -- objects of the parameter types.
4610 Plist := New_List;
4612 Actual := First_Actual (N);
4613 Formal := First_Formal (Ent);
4615 while Present (Actual) loop
4617 -- If it is a by_copy_type, copy it to a new variable. The
4618 -- packaged record has a field that points to this variable.
4620 if Is_By_Copy_Type (Etype (Actual)) then
4621 N_Node :=
4622 Make_Object_Declaration (Loc,
4623 Defining_Identifier => Make_Temporary (Loc, 'J'),
4624 Aliased_Present => True,
4625 Object_Definition =>
4626 New_Reference_To (Etype (Formal), Loc));
4628 -- Mark the object as not needing initialization since the
4629 -- initialization is performed separately, avoiding errors
4630 -- on cases such as formals of null-excluding access types.
4632 Set_No_Initialization (N_Node);
4634 -- We must make an assignment statement separate for the
4635 -- case of limited type. We cannot assign it unless the
4636 -- Assignment_OK flag is set first. An out formal of an
4637 -- access type must also be initialized from the actual,
4638 -- as stated in RM 6.4.1 (13).
4640 if Ekind (Formal) /= E_Out_Parameter
4641 or else Is_Access_Type (Etype (Formal))
4642 then
4643 N_Var :=
4644 New_Reference_To (Defining_Identifier (N_Node), Loc);
4645 Set_Assignment_OK (N_Var);
4646 Append_To (Stats,
4647 Make_Assignment_Statement (Loc,
4648 Name => N_Var,
4649 Expression => Relocate_Node (Actual)));
4650 end if;
4652 Append (N_Node, Decls);
4654 Append_To (Plist,
4655 Make_Attribute_Reference (Loc,
4656 Attribute_Name => Name_Unchecked_Access,
4657 Prefix =>
4658 New_Reference_To (Defining_Identifier (N_Node), Loc)));
4660 -- If it is a VM_By_Copy_Actual, copy it to a new variable
4662 elsif Is_VM_By_Copy_Actual (Actual) then
4663 N_Node :=
4664 Make_Object_Declaration (Loc,
4665 Defining_Identifier => Make_Temporary (Loc, 'J'),
4666 Aliased_Present => True,
4667 Object_Definition =>
4668 New_Reference_To (Etype (Formal), Loc),
4669 Expression => New_Copy_Tree (Actual));
4670 Set_Assignment_OK (N_Node);
4672 Append (N_Node, Decls);
4674 Append_To (Plist,
4675 Make_Attribute_Reference (Loc,
4676 Attribute_Name => Name_Unchecked_Access,
4677 Prefix =>
4678 New_Reference_To (Defining_Identifier (N_Node), Loc)));
4680 else
4681 -- Interface class-wide formal
4683 if Ada_Version >= Ada_2005
4684 and then Ekind (Etype (Formal)) = E_Class_Wide_Type
4685 and then Is_Interface (Etype (Formal))
4686 then
4687 Iface_Typ := Etype (Etype (Formal));
4689 -- Generate:
4690 -- formal_iface_type! (actual.iface_tag)'reference
4692 Iface_Tag :=
4693 Find_Interface_Tag (Etype (Actual), Iface_Typ);
4694 pragma Assert (Present (Iface_Tag));
4696 Append_To (Plist,
4697 Make_Reference (Loc,
4698 Unchecked_Convert_To (Iface_Typ,
4699 Make_Selected_Component (Loc,
4700 Prefix =>
4701 Relocate_Node (Actual),
4702 Selector_Name =>
4703 New_Reference_To (Iface_Tag, Loc)))));
4704 else
4705 -- Generate:
4706 -- actual'reference
4708 Append_To (Plist,
4709 Make_Reference (Loc, Relocate_Node (Actual)));
4710 end if;
4711 end if;
4713 Next_Actual (Actual);
4714 Next_Formal_With_Extras (Formal);
4715 end loop;
4717 -- Now build the declaration of parameters initialized with the
4718 -- aggregate containing this constructed parameter list.
4720 P := Make_Defining_Identifier (Loc, Name_uP);
4722 Pdecl :=
4723 Make_Object_Declaration (Loc,
4724 Defining_Identifier => P,
4725 Object_Definition =>
4726 New_Reference_To (Designated_Type (Ent_Acc), Loc),
4727 Expression =>
4728 Make_Aggregate (Loc, Expressions => Plist));
4730 Parm3 :=
4731 Make_Attribute_Reference (Loc,
4732 Prefix => New_Reference_To (P, Loc),
4733 Attribute_Name => Name_Address);
4735 Append (Pdecl, Decls);
4736 end if;
4738 -- Now we can create the call, case of protected type
4740 if Is_Protected_Type (Conctyp) then
4741 case Corresponding_Runtime_Package (Conctyp) is
4742 when System_Tasking_Protected_Objects_Entries =>
4744 -- Change the type of the index declaration
4746 Set_Object_Definition (Xdecl,
4747 New_Reference_To (RTE (RE_Protected_Entry_Index), Loc));
4749 -- Some additional declarations for protected entry calls
4751 if No (Decls) then
4752 Decls := New_List;
4753 end if;
4755 -- Bnn : Communications_Block;
4757 Comm_Name := Make_Temporary (Loc, 'B');
4759 Append_To (Decls,
4760 Make_Object_Declaration (Loc,
4761 Defining_Identifier => Comm_Name,
4762 Object_Definition =>
4763 New_Reference_To (RTE (RE_Communication_Block), Loc)));
4765 -- Some additional statements for protected entry calls
4767 -- Protected_Entry_Call (
4768 -- Object => po._object'Access,
4769 -- E => <entry index>;
4770 -- Uninterpreted_Data => P'Address;
4771 -- Mode => Simple_Call;
4772 -- Block => Bnn);
4774 Call :=
4775 Make_Procedure_Call_Statement (Loc,
4776 Name =>
4777 New_Reference_To (RTE (RE_Protected_Entry_Call), Loc),
4779 Parameter_Associations => New_List (
4780 Make_Attribute_Reference (Loc,
4781 Attribute_Name => Name_Unchecked_Access,
4782 Prefix => Parm1),
4783 Parm2,
4784 Parm3,
4785 New_Reference_To (RTE (RE_Simple_Call), Loc),
4786 New_Occurrence_Of (Comm_Name, Loc)));
4788 when System_Tasking_Protected_Objects_Single_Entry =>
4789 -- Protected_Single_Entry_Call (
4790 -- Object => po._object'Access,
4791 -- Uninterpreted_Data => P'Address;
4792 -- Mode => Simple_Call);
4794 Call :=
4795 Make_Procedure_Call_Statement (Loc,
4796 Name => New_Reference_To (
4797 RTE (RE_Protected_Single_Entry_Call), Loc),
4799 Parameter_Associations => New_List (
4800 Make_Attribute_Reference (Loc,
4801 Attribute_Name => Name_Unchecked_Access,
4802 Prefix => Parm1),
4803 Parm3,
4804 New_Reference_To (RTE (RE_Simple_Call), Loc)));
4806 when others =>
4807 raise Program_Error;
4808 end case;
4810 -- Case of task type
4812 else
4813 Call :=
4814 Make_Procedure_Call_Statement (Loc,
4815 Name => New_Reference_To (RTE (RE_Call_Simple), Loc),
4816 Parameter_Associations => New_List (Parm1, Parm2, Parm3));
4818 end if;
4820 Append_To (Stats, Call);
4822 -- If there are out or in/out parameters by copy add assignment
4823 -- statements for the result values.
4825 if Present (Parms) then
4826 Actual := First_Actual (N);
4827 Formal := First_Formal (Ent);
4829 Set_Assignment_OK (Actual);
4830 while Present (Actual) loop
4831 if (Is_By_Copy_Type (Etype (Actual))
4832 or else Is_VM_By_Copy_Actual (Actual))
4833 and then Ekind (Formal) /= E_In_Parameter
4834 then
4835 N_Node :=
4836 Make_Assignment_Statement (Loc,
4837 Name => New_Copy (Actual),
4838 Expression =>
4839 Make_Explicit_Dereference (Loc,
4840 Make_Selected_Component (Loc,
4841 Prefix => New_Reference_To (P, Loc),
4842 Selector_Name =>
4843 Make_Identifier (Loc, Chars (Formal)))));
4845 -- In all cases (including limited private types) we want
4846 -- the assignment to be valid.
4848 Set_Assignment_OK (Name (N_Node));
4850 -- If the call is the triggering alternative in an
4851 -- asynchronous select, or the entry_call alternative of a
4852 -- conditional entry call, the assignments for in-out
4853 -- parameters are incorporated into the statement list that
4854 -- follows, so that there are executed only if the entry
4855 -- call succeeds.
4857 if (Nkind (Parent (N)) = N_Triggering_Alternative
4858 and then N = Triggering_Statement (Parent (N)))
4859 or else
4860 (Nkind (Parent (N)) = N_Entry_Call_Alternative
4861 and then N = Entry_Call_Statement (Parent (N)))
4862 then
4863 if No (Statements (Parent (N))) then
4864 Set_Statements (Parent (N), New_List);
4865 end if;
4867 Prepend (N_Node, Statements (Parent (N)));
4869 else
4870 Insert_After (Call, N_Node);
4871 end if;
4872 end if;
4874 Next_Actual (Actual);
4875 Next_Formal_With_Extras (Formal);
4876 end loop;
4877 end if;
4879 -- Finally, create block and analyze it
4881 Rewrite (N,
4882 Make_Block_Statement (Loc,
4883 Declarations => Decls,
4884 Handled_Statement_Sequence =>
4885 Make_Handled_Sequence_Of_Statements (Loc,
4886 Statements => Stats)));
4888 Analyze (N);
4889 end;
4890 end Build_Simple_Entry_Call;
4892 --------------------------------
4893 -- Build_Task_Activation_Call --
4894 --------------------------------
4896 procedure Build_Task_Activation_Call (N : Node_Id) is
4897 Loc : constant Source_Ptr := Sloc (N);
4898 Chain : Entity_Id;
4899 Call : Node_Id;
4900 Name : Node_Id;
4901 P : Node_Id;
4903 begin
4904 -- For sequential elaboration policy, all the tasks will be activated at
4905 -- the end of the elaboration.
4907 if Partition_Elaboration_Policy = 'S' then
4908 return;
4909 end if;
4911 -- Get the activation chain entity. Except in the case of a package
4912 -- body, this is in the node that was passed. For a package body, we
4913 -- have to find the corresponding package declaration node.
4915 if Nkind (N) = N_Package_Body then
4916 P := Corresponding_Spec (N);
4917 loop
4918 P := Parent (P);
4919 exit when Nkind (P) = N_Package_Declaration;
4920 end loop;
4922 Chain := Activation_Chain_Entity (P);
4924 else
4925 Chain := Activation_Chain_Entity (N);
4926 end if;
4928 if Present (Chain) then
4929 if Restricted_Profile then
4930 Name := New_Reference_To (RTE (RE_Activate_Restricted_Tasks), Loc);
4931 else
4932 Name := New_Reference_To (RTE (RE_Activate_Tasks), Loc);
4933 end if;
4935 Call :=
4936 Make_Procedure_Call_Statement (Loc,
4937 Name => Name,
4938 Parameter_Associations =>
4939 New_List (Make_Attribute_Reference (Loc,
4940 Prefix => New_Occurrence_Of (Chain, Loc),
4941 Attribute_Name => Name_Unchecked_Access)));
4943 if Nkind (N) = N_Package_Declaration then
4944 if Present (Corresponding_Body (N)) then
4945 null;
4947 elsif Present (Private_Declarations (Specification (N))) then
4948 Append (Call, Private_Declarations (Specification (N)));
4950 else
4951 Append (Call, Visible_Declarations (Specification (N)));
4952 end if;
4954 else
4955 if Present (Handled_Statement_Sequence (N)) then
4957 -- The call goes at the start of the statement sequence
4958 -- after the start of exception range label if one is present.
4960 declare
4961 Stm : Node_Id;
4963 begin
4964 Stm := First (Statements (Handled_Statement_Sequence (N)));
4966 -- A special case, skip exception range label if one is
4967 -- present (from front end zcx processing).
4969 if Nkind (Stm) = N_Label and then Exception_Junk (Stm) then
4970 Next (Stm);
4971 end if;
4973 -- Another special case, if the first statement is a block
4974 -- from optimization of a local raise to a goto, then the
4975 -- call goes inside this block.
4977 if Nkind (Stm) = N_Block_Statement
4978 and then Exception_Junk (Stm)
4979 then
4980 Stm :=
4981 First (Statements (Handled_Statement_Sequence (Stm)));
4982 end if;
4984 -- Insertion point is after any exception label pushes,
4985 -- since we want it covered by any local handlers.
4987 while Nkind (Stm) in N_Push_xxx_Label loop
4988 Next (Stm);
4989 end loop;
4991 -- Now we have the proper insertion point
4993 Insert_Before (Stm, Call);
4994 end;
4996 else
4997 Set_Handled_Statement_Sequence (N,
4998 Make_Handled_Sequence_Of_Statements (Loc,
4999 Statements => New_List (Call)));
5000 end if;
5001 end if;
5003 Analyze (Call);
5004 Check_Task_Activation (N);
5005 end if;
5006 end Build_Task_Activation_Call;
5008 -------------------------------
5009 -- Build_Task_Allocate_Block --
5010 -------------------------------
5012 procedure Build_Task_Allocate_Block
5013 (Actions : List_Id;
5014 N : Node_Id;
5015 Args : List_Id)
5017 T : constant Entity_Id := Entity (Expression (N));
5018 Init : constant Entity_Id := Base_Init_Proc (T);
5019 Loc : constant Source_Ptr := Sloc (N);
5020 Chain : constant Entity_Id :=
5021 Make_Defining_Identifier (Loc, Name_uChain);
5022 Blkent : constant Entity_Id := Make_Temporary (Loc, 'A');
5023 Block : Node_Id;
5025 begin
5026 Block :=
5027 Make_Block_Statement (Loc,
5028 Identifier => New_Reference_To (Blkent, Loc),
5029 Declarations => New_List (
5031 -- _Chain : Activation_Chain;
5033 Make_Object_Declaration (Loc,
5034 Defining_Identifier => Chain,
5035 Aliased_Present => True,
5036 Object_Definition =>
5037 New_Reference_To (RTE (RE_Activation_Chain), Loc))),
5039 Handled_Statement_Sequence =>
5040 Make_Handled_Sequence_Of_Statements (Loc,
5042 Statements => New_List (
5044 -- Init (Args);
5046 Make_Procedure_Call_Statement (Loc,
5047 Name => New_Reference_To (Init, Loc),
5048 Parameter_Associations => Args),
5050 -- Activate_Tasks (_Chain);
5052 Make_Procedure_Call_Statement (Loc,
5053 Name => New_Reference_To (RTE (RE_Activate_Tasks), Loc),
5054 Parameter_Associations => New_List (
5055 Make_Attribute_Reference (Loc,
5056 Prefix => New_Reference_To (Chain, Loc),
5057 Attribute_Name => Name_Unchecked_Access))))),
5059 Has_Created_Identifier => True,
5060 Is_Task_Allocation_Block => True);
5062 Append_To (Actions,
5063 Make_Implicit_Label_Declaration (Loc,
5064 Defining_Identifier => Blkent,
5065 Label_Construct => Block));
5067 Append_To (Actions, Block);
5069 Set_Activation_Chain_Entity (Block, Chain);
5070 end Build_Task_Allocate_Block;
5072 -----------------------------------------------
5073 -- Build_Task_Allocate_Block_With_Init_Stmts --
5074 -----------------------------------------------
5076 procedure Build_Task_Allocate_Block_With_Init_Stmts
5077 (Actions : List_Id;
5078 N : Node_Id;
5079 Init_Stmts : List_Id)
5081 Loc : constant Source_Ptr := Sloc (N);
5082 Chain : constant Entity_Id :=
5083 Make_Defining_Identifier (Loc, Name_uChain);
5084 Blkent : constant Entity_Id := Make_Temporary (Loc, 'A');
5085 Block : Node_Id;
5087 begin
5088 Append_To (Init_Stmts,
5089 Make_Procedure_Call_Statement (Loc,
5090 Name => New_Reference_To (RTE (RE_Activate_Tasks), Loc),
5091 Parameter_Associations => New_List (
5092 Make_Attribute_Reference (Loc,
5093 Prefix => New_Reference_To (Chain, Loc),
5094 Attribute_Name => Name_Unchecked_Access))));
5096 Block :=
5097 Make_Block_Statement (Loc,
5098 Identifier => New_Reference_To (Blkent, Loc),
5099 Declarations => New_List (
5101 -- _Chain : Activation_Chain;
5103 Make_Object_Declaration (Loc,
5104 Defining_Identifier => Chain,
5105 Aliased_Present => True,
5106 Object_Definition =>
5107 New_Reference_To (RTE (RE_Activation_Chain), Loc))),
5109 Handled_Statement_Sequence =>
5110 Make_Handled_Sequence_Of_Statements (Loc, Init_Stmts),
5112 Has_Created_Identifier => True,
5113 Is_Task_Allocation_Block => True);
5115 Append_To (Actions,
5116 Make_Implicit_Label_Declaration (Loc,
5117 Defining_Identifier => Blkent,
5118 Label_Construct => Block));
5120 Append_To (Actions, Block);
5122 Set_Activation_Chain_Entity (Block, Chain);
5123 end Build_Task_Allocate_Block_With_Init_Stmts;
5125 -----------------------------------
5126 -- Build_Task_Proc_Specification --
5127 -----------------------------------
5129 function Build_Task_Proc_Specification (T : Entity_Id) return Node_Id is
5130 Loc : constant Source_Ptr := Sloc (T);
5131 Spec_Id : Entity_Id;
5133 begin
5134 -- Case of explicit task type, suffix TB
5136 if Comes_From_Source (T) then
5137 Spec_Id :=
5138 Make_Defining_Identifier (Loc,
5139 Chars => New_External_Name (Chars (T), "TB"));
5141 -- Case of anonymous task type, suffix B
5143 else
5144 Spec_Id :=
5145 Make_Defining_Identifier (Loc,
5146 Chars => New_External_Name (Chars (T), 'B'));
5147 end if;
5149 Set_Is_Internal (Spec_Id);
5151 -- Associate the procedure with the task, if this is the declaration
5152 -- (and not the body) of the procedure.
5154 if No (Task_Body_Procedure (T)) then
5155 Set_Task_Body_Procedure (T, Spec_Id);
5156 end if;
5158 return
5159 Make_Procedure_Specification (Loc,
5160 Defining_Unit_Name => Spec_Id,
5161 Parameter_Specifications => New_List (
5162 Make_Parameter_Specification (Loc,
5163 Defining_Identifier =>
5164 Make_Defining_Identifier (Loc, Name_uTask),
5165 Parameter_Type =>
5166 Make_Access_Definition (Loc,
5167 Subtype_Mark =>
5168 New_Reference_To (Corresponding_Record_Type (T), Loc)))));
5169 end Build_Task_Proc_Specification;
5171 ---------------------------------------
5172 -- Build_Unprotected_Subprogram_Body --
5173 ---------------------------------------
5175 function Build_Unprotected_Subprogram_Body
5176 (N : Node_Id;
5177 Pid : Node_Id) return Node_Id
5179 Decls : constant List_Id := Declarations (N);
5181 begin
5182 -- Add renamings for the Protection object, discriminals, privals and
5183 -- the entry index constant for use by debugger.
5185 Debug_Private_Data_Declarations (Decls);
5187 -- Make an unprotected version of the subprogram for use within the same
5188 -- object, with a new name and an additional parameter representing the
5189 -- object.
5191 return
5192 Make_Subprogram_Body (Sloc (N),
5193 Specification =>
5194 Build_Protected_Sub_Specification (N, Pid, Unprotected_Mode),
5195 Declarations => Decls,
5196 Handled_Statement_Sequence => Handled_Statement_Sequence (N));
5197 end Build_Unprotected_Subprogram_Body;
5199 ----------------------------
5200 -- Collect_Entry_Families --
5201 ----------------------------
5203 procedure Collect_Entry_Families
5204 (Loc : Source_Ptr;
5205 Cdecls : List_Id;
5206 Current_Node : in out Node_Id;
5207 Conctyp : Entity_Id)
5209 Efam : Entity_Id;
5210 Efam_Decl : Node_Id;
5211 Efam_Type : Entity_Id;
5213 begin
5214 Efam := First_Entity (Conctyp);
5215 while Present (Efam) loop
5216 if Ekind (Efam) = E_Entry_Family then
5217 Efam_Type := Make_Temporary (Loc, 'F');
5219 declare
5220 Bas : Entity_Id :=
5221 Base_Type
5222 (Etype (Discrete_Subtype_Definition (Parent (Efam))));
5224 Bas_Decl : Node_Id := Empty;
5225 Lo, Hi : Node_Id;
5227 begin
5228 Get_Index_Bounds
5229 (Discrete_Subtype_Definition (Parent (Efam)), Lo, Hi);
5231 if Is_Potentially_Large_Family (Bas, Conctyp, Lo, Hi) then
5232 Bas := Make_Temporary (Loc, 'B');
5234 Bas_Decl :=
5235 Make_Subtype_Declaration (Loc,
5236 Defining_Identifier => Bas,
5237 Subtype_Indication =>
5238 Make_Subtype_Indication (Loc,
5239 Subtype_Mark =>
5240 New_Occurrence_Of (Standard_Integer, Loc),
5241 Constraint =>
5242 Make_Range_Constraint (Loc,
5243 Range_Expression => Make_Range (Loc,
5244 Make_Integer_Literal
5245 (Loc, -Entry_Family_Bound),
5246 Make_Integer_Literal
5247 (Loc, Entry_Family_Bound - 1)))));
5249 Insert_After (Current_Node, Bas_Decl);
5250 Current_Node := Bas_Decl;
5251 Analyze (Bas_Decl);
5252 end if;
5254 Efam_Decl :=
5255 Make_Full_Type_Declaration (Loc,
5256 Defining_Identifier => Efam_Type,
5257 Type_Definition =>
5258 Make_Unconstrained_Array_Definition (Loc,
5259 Subtype_Marks =>
5260 (New_List (New_Occurrence_Of (Bas, Loc))),
5262 Component_Definition =>
5263 Make_Component_Definition (Loc,
5264 Aliased_Present => False,
5265 Subtype_Indication =>
5266 New_Reference_To (Standard_Character, Loc))));
5267 end;
5269 Insert_After (Current_Node, Efam_Decl);
5270 Current_Node := Efam_Decl;
5271 Analyze (Efam_Decl);
5273 Append_To (Cdecls,
5274 Make_Component_Declaration (Loc,
5275 Defining_Identifier =>
5276 Make_Defining_Identifier (Loc, Chars (Efam)),
5278 Component_Definition =>
5279 Make_Component_Definition (Loc,
5280 Aliased_Present => False,
5281 Subtype_Indication =>
5282 Make_Subtype_Indication (Loc,
5283 Subtype_Mark =>
5284 New_Occurrence_Of (Efam_Type, Loc),
5286 Constraint =>
5287 Make_Index_Or_Discriminant_Constraint (Loc,
5288 Constraints => New_List (
5289 New_Occurrence_Of
5290 (Etype (Discrete_Subtype_Definition
5291 (Parent (Efam))), Loc)))))));
5293 end if;
5295 Next_Entity (Efam);
5296 end loop;
5297 end Collect_Entry_Families;
5299 -----------------------
5300 -- Concurrent_Object --
5301 -----------------------
5303 function Concurrent_Object
5304 (Spec_Id : Entity_Id;
5305 Conc_Typ : Entity_Id) return Entity_Id
5307 begin
5308 -- Parameter _O or _object
5310 if Is_Protected_Type (Conc_Typ) then
5311 return First_Formal (Protected_Body_Subprogram (Spec_Id));
5313 -- Parameter _task
5315 else
5316 pragma Assert (Is_Task_Type (Conc_Typ));
5317 return First_Formal (Task_Body_Procedure (Conc_Typ));
5318 end if;
5319 end Concurrent_Object;
5321 ----------------------
5322 -- Copy_Result_Type --
5323 ----------------------
5325 function Copy_Result_Type (Res : Node_Id) return Node_Id is
5326 New_Res : constant Node_Id := New_Copy_Tree (Res);
5327 Par_Spec : Node_Id;
5328 Formal : Entity_Id;
5330 begin
5331 -- If the result type is an access_to_subprogram, we must create new
5332 -- entities for its spec.
5334 if Nkind (New_Res) = N_Access_Definition
5335 and then Present (Access_To_Subprogram_Definition (New_Res))
5336 then
5337 -- Provide new entities for the formals
5339 Par_Spec := First (Parameter_Specifications
5340 (Access_To_Subprogram_Definition (New_Res)));
5341 while Present (Par_Spec) loop
5342 Formal := Defining_Identifier (Par_Spec);
5343 Set_Defining_Identifier (Par_Spec,
5344 Make_Defining_Identifier (Sloc (Formal), Chars (Formal)));
5345 Next (Par_Spec);
5346 end loop;
5347 end if;
5349 return New_Res;
5350 end Copy_Result_Type;
5352 --------------------
5353 -- Concurrent_Ref --
5354 --------------------
5356 -- The expression returned for a reference to a concurrent object has the
5357 -- form:
5359 -- taskV!(name)._Task_Id
5361 -- for a task, and
5363 -- objectV!(name)._Object
5365 -- for a protected object. For the case of an access to a concurrent
5366 -- object, there is an extra explicit dereference:
5368 -- taskV!(name.all)._Task_Id
5369 -- objectV!(name.all)._Object
5371 -- here taskV and objectV are the types for the associated records, which
5372 -- contain the required _Task_Id and _Object fields for tasks and protected
5373 -- objects, respectively.
5375 -- For the case of a task type name, the expression is
5377 -- Self;
5379 -- i.e. a call to the Self function which returns precisely this Task_Id
5381 -- For the case of a protected type name, the expression is
5383 -- objectR
5385 -- which is a renaming of the _object field of the current object
5386 -- record, passed into protected operations as a parameter.
5388 function Concurrent_Ref (N : Node_Id) return Node_Id is
5389 Loc : constant Source_Ptr := Sloc (N);
5390 Ntyp : constant Entity_Id := Etype (N);
5391 Dtyp : Entity_Id;
5392 Sel : Name_Id;
5394 function Is_Current_Task (T : Entity_Id) return Boolean;
5395 -- Check whether the reference is to the immediately enclosing task
5396 -- type, or to an outer one (rare but legal).
5398 ---------------------
5399 -- Is_Current_Task --
5400 ---------------------
5402 function Is_Current_Task (T : Entity_Id) return Boolean is
5403 Scop : Entity_Id;
5405 begin
5406 Scop := Current_Scope;
5407 while Present (Scop)
5408 and then Scop /= Standard_Standard
5409 loop
5411 if Scop = T then
5412 return True;
5414 elsif Is_Task_Type (Scop) then
5415 return False;
5417 -- If this is a procedure nested within the task type, we must
5418 -- assume that it can be called from an inner task, and therefore
5419 -- cannot treat it as a local reference.
5421 elsif Is_Overloadable (Scop)
5422 and then In_Open_Scopes (T)
5423 then
5424 return False;
5426 else
5427 Scop := Scope (Scop);
5428 end if;
5429 end loop;
5431 -- We know that we are within the task body, so should have found it
5432 -- in scope.
5434 raise Program_Error;
5435 end Is_Current_Task;
5437 -- Start of processing for Concurrent_Ref
5439 begin
5440 if Is_Access_Type (Ntyp) then
5441 Dtyp := Designated_Type (Ntyp);
5443 if Is_Protected_Type (Dtyp) then
5444 Sel := Name_uObject;
5445 else
5446 Sel := Name_uTask_Id;
5447 end if;
5449 return
5450 Make_Selected_Component (Loc,
5451 Prefix =>
5452 Unchecked_Convert_To (Corresponding_Record_Type (Dtyp),
5453 Make_Explicit_Dereference (Loc, N)),
5454 Selector_Name => Make_Identifier (Loc, Sel));
5456 elsif Is_Entity_Name (N) and then Is_Concurrent_Type (Entity (N)) then
5457 if Is_Task_Type (Entity (N)) then
5459 if Is_Current_Task (Entity (N)) then
5460 return
5461 Make_Function_Call (Loc,
5462 Name => New_Reference_To (RTE (RE_Self), Loc));
5464 else
5465 declare
5466 Decl : Node_Id;
5467 T_Self : constant Entity_Id := Make_Temporary (Loc, 'T');
5468 T_Body : constant Node_Id :=
5469 Parent (Corresponding_Body (Parent (Entity (N))));
5471 begin
5472 Decl :=
5473 Make_Object_Declaration (Loc,
5474 Defining_Identifier => T_Self,
5475 Object_Definition =>
5476 New_Occurrence_Of (RTE (RO_ST_Task_Id), Loc),
5477 Expression =>
5478 Make_Function_Call (Loc,
5479 Name => New_Reference_To (RTE (RE_Self), Loc)));
5480 Prepend (Decl, Declarations (T_Body));
5481 Analyze (Decl);
5482 Set_Scope (T_Self, Entity (N));
5483 return New_Occurrence_Of (T_Self, Loc);
5484 end;
5485 end if;
5487 else
5488 pragma Assert (Is_Protected_Type (Entity (N)));
5490 return
5491 New_Reference_To (Find_Protection_Object (Current_Scope), Loc);
5492 end if;
5494 else
5495 if Is_Protected_Type (Ntyp) then
5496 Sel := Name_uObject;
5498 elsif Is_Task_Type (Ntyp) then
5499 Sel := Name_uTask_Id;
5501 else
5502 raise Program_Error;
5503 end if;
5505 return
5506 Make_Selected_Component (Loc,
5507 Prefix =>
5508 Unchecked_Convert_To (Corresponding_Record_Type (Ntyp),
5509 New_Copy_Tree (N)),
5510 Selector_Name => Make_Identifier (Loc, Sel));
5511 end if;
5512 end Concurrent_Ref;
5514 ------------------------
5515 -- Convert_Concurrent --
5516 ------------------------
5518 function Convert_Concurrent
5519 (N : Node_Id;
5520 Typ : Entity_Id) return Node_Id
5522 begin
5523 if not Is_Concurrent_Type (Typ) then
5524 return N;
5525 else
5526 return
5527 Unchecked_Convert_To
5528 (Corresponding_Record_Type (Typ), New_Copy_Tree (N));
5529 end if;
5530 end Convert_Concurrent;
5532 -------------------------------------
5533 -- Debug_Private_Data_Declarations --
5534 -------------------------------------
5536 procedure Debug_Private_Data_Declarations (Decls : List_Id) is
5537 Debug_Nod : Node_Id;
5538 Decl : Node_Id;
5540 begin
5541 Decl := First (Decls);
5542 while Present (Decl) and then not Comes_From_Source (Decl) loop
5543 -- Declaration for concurrent entity _object and its access type,
5544 -- along with the entry index subtype:
5545 -- type prot_typVP is access prot_typV;
5546 -- _object : prot_typVP := prot_typV (_O);
5547 -- subtype Jnn is <Type of Index> range Low .. High;
5549 if Nkind_In (Decl, N_Full_Type_Declaration, N_Object_Declaration) then
5550 Set_Debug_Info_Needed (Defining_Identifier (Decl));
5552 -- Declaration for the Protection object, discriminals, privals and
5553 -- entry index constant:
5554 -- conc_typR : protection_typ renames _object._object;
5555 -- discr_nameD : discr_typ renames _object.discr_name;
5556 -- discr_nameD : discr_typ renames _task.discr_name;
5557 -- prival_name : comp_typ renames _object.comp_name;
5558 -- J : constant Jnn :=
5559 -- Jnn'Val (_E - <Index expression> + Jnn'Pos (Jnn'First));
5561 elsif Nkind (Decl) = N_Object_Renaming_Declaration then
5562 Set_Debug_Info_Needed (Defining_Identifier (Decl));
5563 Debug_Nod := Debug_Renaming_Declaration (Decl);
5565 if Present (Debug_Nod) then
5566 Insert_After (Decl, Debug_Nod);
5567 end if;
5568 end if;
5570 Next (Decl);
5571 end loop;
5572 end Debug_Private_Data_Declarations;
5574 ------------------------------
5575 -- Ensure_Statement_Present --
5576 ------------------------------
5578 procedure Ensure_Statement_Present (Loc : Source_Ptr; Alt : Node_Id) is
5579 Stmt : Node_Id;
5581 begin
5582 if Opt.Suppress_Control_Flow_Optimizations
5583 and then Is_Empty_List (Statements (Alt))
5584 then
5585 Stmt := Make_Null_Statement (Loc);
5587 -- Mark NULL statement as coming from source so that it is not
5588 -- eliminated by GIGI.
5590 -- Another covert channel! If this is a requirement, it must be
5591 -- documented in sinfo/einfo ???
5593 Set_Comes_From_Source (Stmt, True);
5595 Set_Statements (Alt, New_List (Stmt));
5596 end if;
5597 end Ensure_Statement_Present;
5599 ----------------------------
5600 -- Entry_Index_Expression --
5601 ----------------------------
5603 function Entry_Index_Expression
5604 (Sloc : Source_Ptr;
5605 Ent : Entity_Id;
5606 Index : Node_Id;
5607 Ttyp : Entity_Id) return Node_Id
5609 Expr : Node_Id;
5610 Num : Node_Id;
5611 Lo : Node_Id;
5612 Hi : Node_Id;
5613 Prev : Entity_Id;
5614 S : Node_Id;
5616 begin
5617 -- The queues of entries and entry families appear in textual order in
5618 -- the associated record. The entry index is computed as the sum of the
5619 -- number of queues for all entries that precede the designated one, to
5620 -- which is added the index expression, if this expression denotes a
5621 -- member of a family.
5623 -- The following is a place holder for the count of simple entries
5625 Num := Make_Integer_Literal (Sloc, 1);
5627 -- We construct an expression which is a series of addition operations.
5628 -- The first operand is the number of single entries that precede this
5629 -- one, the second operand is the index value relative to the start of
5630 -- the referenced family, and the remaining operands are the lengths of
5631 -- the entry families that precede this entry, i.e. the constructed
5632 -- expression is:
5634 -- number_simple_entries +
5635 -- (s'pos (index-value) - s'pos (family'first)) + 1 +
5636 -- family'length + ...
5638 -- where index-value is the given index value, and s is the index
5639 -- subtype (we have to use pos because the subtype might be an
5640 -- enumeration type preventing direct subtraction). Note that the task
5641 -- entry array is one-indexed.
5643 -- The upper bound of the entry family may be a discriminant, so we
5644 -- retrieve the lower bound explicitly to compute offset, rather than
5645 -- using the index subtype which may mention a discriminant.
5647 if Present (Index) then
5648 S := Etype (Discrete_Subtype_Definition (Declaration_Node (Ent)));
5650 Expr :=
5651 Make_Op_Add (Sloc,
5652 Left_Opnd => Num,
5654 Right_Opnd =>
5655 Family_Offset (
5656 Sloc,
5657 Make_Attribute_Reference (Sloc,
5658 Attribute_Name => Name_Pos,
5659 Prefix => New_Reference_To (Base_Type (S), Sloc),
5660 Expressions => New_List (Relocate_Node (Index))),
5661 Type_Low_Bound (S),
5662 Ttyp,
5663 False));
5664 else
5665 Expr := Num;
5666 end if;
5668 -- Now add lengths of preceding entries and entry families
5670 Prev := First_Entity (Ttyp);
5672 while Chars (Prev) /= Chars (Ent)
5673 or else (Ekind (Prev) /= Ekind (Ent))
5674 or else not Sem_Ch6.Type_Conformant (Ent, Prev)
5675 loop
5676 if Ekind (Prev) = E_Entry then
5677 Set_Intval (Num, Intval (Num) + 1);
5679 elsif Ekind (Prev) = E_Entry_Family then
5680 S :=
5681 Etype (Discrete_Subtype_Definition (Declaration_Node (Prev)));
5682 Lo := Type_Low_Bound (S);
5683 Hi := Type_High_Bound (S);
5685 Expr :=
5686 Make_Op_Add (Sloc,
5687 Left_Opnd => Expr,
5688 Right_Opnd => Family_Size (Sloc, Hi, Lo, Ttyp, False));
5690 -- Other components are anonymous types to be ignored
5692 else
5693 null;
5694 end if;
5696 Next_Entity (Prev);
5697 end loop;
5699 return Expr;
5700 end Entry_Index_Expression;
5702 ---------------------------
5703 -- Establish_Task_Master --
5704 ---------------------------
5706 procedure Establish_Task_Master (N : Node_Id) is
5707 Call : Node_Id;
5709 begin
5710 if Restriction_Active (No_Task_Hierarchy) = False then
5711 Call := Build_Runtime_Call (Sloc (N), RE_Enter_Master);
5713 -- The block may have no declarations, and nevertheless be a task
5714 -- master, if it contains a call that may return an object that
5715 -- contains tasks.
5717 if No (Declarations (N)) then
5718 Set_Declarations (N, New_List (Call));
5719 else
5720 Prepend_To (Declarations (N), Call);
5721 end if;
5723 Analyze (Call);
5724 end if;
5725 end Establish_Task_Master;
5727 --------------------------------
5728 -- Expand_Accept_Declarations --
5729 --------------------------------
5731 -- Part of the expansion of an accept statement involves the creation of
5732 -- a declaration that can be referenced from the statement sequence of
5733 -- the accept:
5735 -- Ann : Address;
5737 -- This declaration is inserted immediately before the accept statement
5738 -- and it is important that it be inserted before the statements of the
5739 -- statement sequence are analyzed. Thus it would be too late to create
5740 -- this declaration in the Expand_N_Accept_Statement routine, which is
5741 -- why there is a separate procedure to be called directly from Sem_Ch9.
5743 -- Ann is used to hold the address of the record containing the parameters
5744 -- (see Expand_N_Entry_Call for more details on how this record is built).
5745 -- References to the parameters do an unchecked conversion of this address
5746 -- to a pointer to the required record type, and then access the field that
5747 -- holds the value of the required parameter. The entity for the address
5748 -- variable is held as the top stack element (i.e. the last element) of the
5749 -- Accept_Address stack in the corresponding entry entity, and this element
5750 -- must be set in place before the statements are processed.
5752 -- The above description applies to the case of a stand alone accept
5753 -- statement, i.e. one not appearing as part of a select alternative.
5755 -- For the case of an accept that appears as part of a select alternative
5756 -- of a selective accept, we must still create the declaration right away,
5757 -- since Ann is needed immediately, but there is an important difference:
5759 -- The declaration is inserted before the selective accept, not before
5760 -- the accept statement (which is not part of a list anyway, and so would
5761 -- not accommodate inserted declarations)
5763 -- We only need one address variable for the entire selective accept. So
5764 -- the Ann declaration is created only for the first accept alternative,
5765 -- and subsequent accept alternatives reference the same Ann variable.
5767 -- We can distinguish the two cases by seeing whether the accept statement
5768 -- is part of a list. If not, then it must be in an accept alternative.
5770 -- To expand the requeue statement, a label is provided at the end of the
5771 -- accept statement or alternative of which it is a part, so that the
5772 -- statement can be skipped after the requeue is complete. This label is
5773 -- created here rather than during the expansion of the accept statement,
5774 -- because it will be needed by any requeue statements within the accept,
5775 -- which are expanded before the accept.
5777 procedure Expand_Accept_Declarations (N : Node_Id; Ent : Entity_Id) is
5778 Loc : constant Source_Ptr := Sloc (N);
5779 Stats : constant Node_Id := Handled_Statement_Sequence (N);
5780 Ann : Entity_Id := Empty;
5781 Adecl : Node_Id;
5782 Lab : Node_Id;
5783 Ldecl : Node_Id;
5784 Ldecl2 : Node_Id;
5786 begin
5787 if Full_Expander_Active then
5789 -- If we have no handled statement sequence, we may need to build
5790 -- a dummy sequence consisting of a null statement. This can be
5791 -- skipped if the trivial accept optimization is permitted.
5793 if not Trivial_Accept_OK
5794 and then
5795 (No (Stats) or else Null_Statements (Statements (Stats)))
5796 then
5797 Set_Handled_Statement_Sequence (N,
5798 Make_Handled_Sequence_Of_Statements (Loc,
5799 Statements => New_List (Make_Null_Statement (Loc))));
5800 end if;
5802 -- Create and declare two labels to be placed at the end of the
5803 -- accept statement. The first label is used to allow requeues to
5804 -- skip the remainder of entry processing. The second label is used
5805 -- to skip the remainder of entry processing if the rendezvous
5806 -- completes in the middle of the accept body.
5808 if Present (Handled_Statement_Sequence (N)) then
5809 declare
5810 Ent : Entity_Id;
5812 begin
5813 Ent := Make_Temporary (Loc, 'L');
5814 Lab := Make_Label (Loc, New_Reference_To (Ent, Loc));
5815 Ldecl :=
5816 Make_Implicit_Label_Declaration (Loc,
5817 Defining_Identifier => Ent,
5818 Label_Construct => Lab);
5819 Append (Lab, Statements (Handled_Statement_Sequence (N)));
5821 Ent := Make_Temporary (Loc, 'L');
5822 Lab := Make_Label (Loc, New_Reference_To (Ent, Loc));
5823 Ldecl2 :=
5824 Make_Implicit_Label_Declaration (Loc,
5825 Defining_Identifier => Ent,
5826 Label_Construct => Lab);
5827 Append (Lab, Statements (Handled_Statement_Sequence (N)));
5828 end;
5830 else
5831 Ldecl := Empty;
5832 Ldecl2 := Empty;
5833 end if;
5835 -- Case of stand alone accept statement
5837 if Is_List_Member (N) then
5839 if Present (Handled_Statement_Sequence (N)) then
5840 Ann := Make_Temporary (Loc, 'A');
5842 Adecl :=
5843 Make_Object_Declaration (Loc,
5844 Defining_Identifier => Ann,
5845 Object_Definition =>
5846 New_Reference_To (RTE (RE_Address), Loc));
5848 Insert_Before_And_Analyze (N, Adecl);
5849 Insert_Before_And_Analyze (N, Ldecl);
5850 Insert_Before_And_Analyze (N, Ldecl2);
5851 end if;
5853 -- Case of accept statement which is in an accept alternative
5855 else
5856 declare
5857 Acc_Alt : constant Node_Id := Parent (N);
5858 Sel_Acc : constant Node_Id := Parent (Acc_Alt);
5859 Alt : Node_Id;
5861 begin
5862 pragma Assert (Nkind (Acc_Alt) = N_Accept_Alternative);
5863 pragma Assert (Nkind (Sel_Acc) = N_Selective_Accept);
5865 -- ??? Consider a single label for select statements
5867 if Present (Handled_Statement_Sequence (N)) then
5868 Prepend (Ldecl2,
5869 Statements (Handled_Statement_Sequence (N)));
5870 Analyze (Ldecl2);
5872 Prepend (Ldecl,
5873 Statements (Handled_Statement_Sequence (N)));
5874 Analyze (Ldecl);
5875 end if;
5877 -- Find first accept alternative of the selective accept. A
5878 -- valid selective accept must have at least one accept in it.
5880 Alt := First (Select_Alternatives (Sel_Acc));
5882 while Nkind (Alt) /= N_Accept_Alternative loop
5883 Next (Alt);
5884 end loop;
5886 -- If we are the first accept statement, then we have to create
5887 -- the Ann variable, as for the stand alone case, except that
5888 -- it is inserted before the selective accept. Similarly, a
5889 -- label for requeue expansion must be declared.
5891 if N = Accept_Statement (Alt) then
5892 Ann := Make_Temporary (Loc, 'A');
5893 Adecl :=
5894 Make_Object_Declaration (Loc,
5895 Defining_Identifier => Ann,
5896 Object_Definition =>
5897 New_Reference_To (RTE (RE_Address), Loc));
5899 Insert_Before_And_Analyze (Sel_Acc, Adecl);
5901 -- If we are not the first accept statement, then find the Ann
5902 -- variable allocated by the first accept and use it.
5904 else
5905 Ann :=
5906 Node (Last_Elmt (Accept_Address
5907 (Entity (Entry_Direct_Name (Accept_Statement (Alt))))));
5908 end if;
5909 end;
5910 end if;
5912 -- Merge here with Ann either created or referenced, and Adecl
5913 -- pointing to the corresponding declaration. Remaining processing
5914 -- is the same for the two cases.
5916 if Present (Ann) then
5917 Append_Elmt (Ann, Accept_Address (Ent));
5918 Set_Debug_Info_Needed (Ann);
5919 end if;
5921 -- Create renaming declarations for the entry formals. Each reference
5922 -- to a formal becomes a dereference of a component of the parameter
5923 -- block, whose address is held in Ann. These declarations are
5924 -- eventually inserted into the accept block, and analyzed there so
5925 -- that they have the proper scope for gdb and do not conflict with
5926 -- other declarations.
5928 if Present (Parameter_Specifications (N))
5929 and then Present (Handled_Statement_Sequence (N))
5930 then
5931 declare
5932 Comp : Entity_Id;
5933 Decl : Node_Id;
5934 Formal : Entity_Id;
5935 New_F : Entity_Id;
5936 Renamed_Formal : Node_Id;
5938 begin
5939 Push_Scope (Ent);
5940 Formal := First_Formal (Ent);
5942 while Present (Formal) loop
5943 Comp := Entry_Component (Formal);
5944 New_F := Make_Defining_Identifier (Loc, Chars (Formal));
5946 Set_Etype (New_F, Etype (Formal));
5947 Set_Scope (New_F, Ent);
5949 -- Now we set debug info needed on New_F even though it does
5950 -- not come from source, so that the debugger will get the
5951 -- right information for these generated names.
5953 Set_Debug_Info_Needed (New_F);
5955 if Ekind (Formal) = E_In_Parameter then
5956 Set_Ekind (New_F, E_Constant);
5957 else
5958 Set_Ekind (New_F, E_Variable);
5959 Set_Extra_Constrained (New_F, Extra_Constrained (Formal));
5960 end if;
5962 Set_Actual_Subtype (New_F, Actual_Subtype (Formal));
5964 Renamed_Formal :=
5965 Make_Selected_Component (Loc,
5966 Prefix =>
5967 Unchecked_Convert_To (
5968 Entry_Parameters_Type (Ent),
5969 New_Reference_To (Ann, Loc)),
5970 Selector_Name =>
5971 New_Reference_To (Comp, Loc));
5973 Decl :=
5974 Build_Renamed_Formal_Declaration
5975 (New_F, Formal, Comp, Renamed_Formal);
5977 if No (Declarations (N)) then
5978 Set_Declarations (N, New_List);
5979 end if;
5981 Append (Decl, Declarations (N));
5982 Set_Renamed_Object (Formal, New_F);
5983 Next_Formal (Formal);
5984 end loop;
5986 End_Scope;
5987 end;
5988 end if;
5989 end if;
5990 end Expand_Accept_Declarations;
5992 ---------------------------------------------
5993 -- Expand_Access_Protected_Subprogram_Type --
5994 ---------------------------------------------
5996 procedure Expand_Access_Protected_Subprogram_Type (N : Node_Id) is
5997 Loc : constant Source_Ptr := Sloc (N);
5998 Comps : List_Id;
5999 T : constant Entity_Id := Defining_Identifier (N);
6000 D_T : constant Entity_Id := Designated_Type (T);
6001 D_T2 : constant Entity_Id := Make_Temporary (Loc, 'D');
6002 E_T : constant Entity_Id := Make_Temporary (Loc, 'E');
6003 P_List : constant List_Id := Build_Protected_Spec
6004 (N, RTE (RE_Address), D_T, False);
6005 Decl1 : Node_Id;
6006 Decl2 : Node_Id;
6007 Def1 : Node_Id;
6009 begin
6010 -- Create access to subprogram with full signature
6012 if Etype (D_T) /= Standard_Void_Type then
6013 Def1 :=
6014 Make_Access_Function_Definition (Loc,
6015 Parameter_Specifications => P_List,
6016 Result_Definition =>
6017 Copy_Result_Type (Result_Definition (Type_Definition (N))));
6019 else
6020 Def1 :=
6021 Make_Access_Procedure_Definition (Loc,
6022 Parameter_Specifications => P_List);
6023 end if;
6025 Decl1 :=
6026 Make_Full_Type_Declaration (Loc,
6027 Defining_Identifier => D_T2,
6028 Type_Definition => Def1);
6030 Insert_After_And_Analyze (N, Decl1);
6032 -- Associate the access to subprogram with its original access to
6033 -- protected subprogram type. Needed by the backend to know that this
6034 -- type corresponds with an access to protected subprogram type.
6036 Set_Original_Access_Type (D_T2, T);
6038 -- Create Equivalent_Type, a record with two components for an access to
6039 -- object and an access to subprogram.
6041 Comps := New_List (
6042 Make_Component_Declaration (Loc,
6043 Defining_Identifier => Make_Temporary (Loc, 'P'),
6044 Component_Definition =>
6045 Make_Component_Definition (Loc,
6046 Aliased_Present => False,
6047 Subtype_Indication =>
6048 New_Occurrence_Of (RTE (RE_Address), Loc))),
6050 Make_Component_Declaration (Loc,
6051 Defining_Identifier => Make_Temporary (Loc, 'S'),
6052 Component_Definition =>
6053 Make_Component_Definition (Loc,
6054 Aliased_Present => False,
6055 Subtype_Indication => New_Occurrence_Of (D_T2, Loc))));
6057 Decl2 :=
6058 Make_Full_Type_Declaration (Loc,
6059 Defining_Identifier => E_T,
6060 Type_Definition =>
6061 Make_Record_Definition (Loc,
6062 Component_List =>
6063 Make_Component_List (Loc, Component_Items => Comps)));
6065 Insert_After_And_Analyze (Decl1, Decl2);
6066 Set_Equivalent_Type (T, E_T);
6067 end Expand_Access_Protected_Subprogram_Type;
6069 --------------------------
6070 -- Expand_Entry_Barrier --
6071 --------------------------
6073 procedure Expand_Entry_Barrier (N : Node_Id; Ent : Entity_Id) is
6074 Cond : constant Node_Id :=
6075 Condition (Entry_Body_Formal_Part (N));
6076 Prot : constant Entity_Id := Scope (Ent);
6077 Spec_Decl : constant Node_Id := Parent (Prot);
6078 Func : Node_Id;
6079 B_F : Node_Id;
6080 Body_Decl : Node_Id;
6082 begin
6083 if No_Run_Time_Mode then
6084 Error_Msg_CRT ("entry barrier", N);
6085 return;
6086 end if;
6088 -- The body of the entry barrier must be analyzed in the context of the
6089 -- protected object, but its scope is external to it, just as any other
6090 -- unprotected version of a protected operation. The specification has
6091 -- been produced when the protected type declaration was elaborated. We
6092 -- build the body, insert it in the enclosing scope, but analyze it in
6093 -- the current context. A more uniform approach would be to treat the
6094 -- barrier just as a protected function, and discard the protected
6095 -- version of it because it is never called.
6097 if Full_Expander_Active then
6098 B_F := Build_Barrier_Function (N, Ent, Prot);
6099 Func := Barrier_Function (Ent);
6100 Set_Corresponding_Spec (B_F, Func);
6102 Body_Decl := Parent (Corresponding_Body (Spec_Decl));
6104 if Nkind (Parent (Body_Decl)) = N_Subunit then
6105 Body_Decl := Corresponding_Stub (Parent (Body_Decl));
6106 end if;
6108 Insert_Before_And_Analyze (Body_Decl, B_F);
6110 Set_Discriminals (Spec_Decl);
6111 Set_Scope (Func, Scope (Prot));
6113 else
6114 Analyze_And_Resolve (Cond, Any_Boolean);
6115 end if;
6117 -- The Ravenscar profile restricts barriers to simple variables declared
6118 -- within the protected object. We also allow Boolean constants, since
6119 -- these appear in several published examples and are also allowed by
6120 -- the Aonix compiler.
6122 -- Note that after analysis variables in this context will be replaced
6123 -- by the corresponding prival, that is to say a renaming of a selected
6124 -- component of the form _Object.Var. If expansion is disabled, as
6125 -- within a generic, we check that the entity appears in the current
6126 -- scope.
6128 if Is_Entity_Name (Cond) then
6130 -- A small optimization of useless renamings. If the scope of the
6131 -- entity of the condition is not the barrier function, then the
6132 -- condition does not reference any of the generated renamings
6133 -- within the function.
6135 if Full_Expander_Active and then Scope (Entity (Cond)) /= Func then
6136 Set_Declarations (B_F, Empty_List);
6137 end if;
6139 if Entity (Cond) = Standard_False
6140 or else
6141 Entity (Cond) = Standard_True
6142 then
6143 return;
6145 elsif not Expander_Active
6146 and then Scope (Entity (Cond)) = Current_Scope
6147 then
6148 return;
6150 -- Check for case of _object.all.field (note that the explicit
6151 -- dereference gets inserted by analyze/expand of _object.field)
6153 elsif Present (Renamed_Object (Entity (Cond)))
6154 and then
6155 Nkind (Renamed_Object (Entity (Cond))) = N_Selected_Component
6156 and then
6157 Chars
6158 (Prefix
6159 (Prefix (Renamed_Object (Entity (Cond))))) = Name_uObject
6160 then
6161 return;
6162 end if;
6163 end if;
6165 -- It is not a boolean variable or literal, so check the restriction
6167 Check_Restriction (Simple_Barriers, Cond);
6168 end Expand_Entry_Barrier;
6170 ------------------------------
6171 -- Expand_N_Abort_Statement --
6172 ------------------------------
6174 -- Expand abort T1, T2, .. Tn; into:
6175 -- Abort_Tasks (Task_List'(1 => T1.Task_Id, 2 => T2.Task_Id ...))
6177 procedure Expand_N_Abort_Statement (N : Node_Id) is
6178 Loc : constant Source_Ptr := Sloc (N);
6179 Tlist : constant List_Id := Names (N);
6180 Count : Nat;
6181 Aggr : Node_Id;
6182 Tasknm : Node_Id;
6184 begin
6185 Aggr := Make_Aggregate (Loc, Component_Associations => New_List);
6186 Count := 0;
6188 Tasknm := First (Tlist);
6190 while Present (Tasknm) loop
6191 Count := Count + 1;
6193 -- A task interface class-wide type object is being aborted.
6194 -- Retrieve its _task_id by calling a dispatching routine.
6196 if Ada_Version >= Ada_2005
6197 and then Ekind (Etype (Tasknm)) = E_Class_Wide_Type
6198 and then Is_Interface (Etype (Tasknm))
6199 and then Is_Task_Interface (Etype (Tasknm))
6200 then
6201 Append_To (Component_Associations (Aggr),
6202 Make_Component_Association (Loc,
6203 Choices => New_List (Make_Integer_Literal (Loc, Count)),
6204 Expression =>
6206 -- Task_Id (Tasknm._disp_get_task_id)
6208 Make_Unchecked_Type_Conversion (Loc,
6209 Subtype_Mark =>
6210 New_Reference_To (RTE (RO_ST_Task_Id), Loc),
6211 Expression =>
6212 Make_Selected_Component (Loc,
6213 Prefix => New_Copy_Tree (Tasknm),
6214 Selector_Name =>
6215 Make_Identifier (Loc, Name_uDisp_Get_Task_Id)))));
6217 else
6218 Append_To (Component_Associations (Aggr),
6219 Make_Component_Association (Loc,
6220 Choices => New_List (Make_Integer_Literal (Loc, Count)),
6221 Expression => Concurrent_Ref (Tasknm)));
6222 end if;
6224 Next (Tasknm);
6225 end loop;
6227 Rewrite (N,
6228 Make_Procedure_Call_Statement (Loc,
6229 Name => New_Reference_To (RTE (RE_Abort_Tasks), Loc),
6230 Parameter_Associations => New_List (
6231 Make_Qualified_Expression (Loc,
6232 Subtype_Mark => New_Reference_To (RTE (RE_Task_List), Loc),
6233 Expression => Aggr))));
6235 Analyze (N);
6236 end Expand_N_Abort_Statement;
6238 -------------------------------
6239 -- Expand_N_Accept_Statement --
6240 -------------------------------
6242 -- This procedure handles expansion of accept statements that stand
6243 -- alone, i.e. they are not part of an accept alternative. The expansion
6244 -- of accept statement in accept alternatives is handled by the routines
6245 -- Expand_N_Accept_Alternative and Expand_N_Selective_Accept. The
6246 -- following description applies only to stand alone accept statements.
6248 -- If there is no handled statement sequence, or only null statements,
6249 -- then this is called a trivial accept, and the expansion is:
6251 -- Accept_Trivial (entry-index)
6253 -- If there is a handled statement sequence, then the expansion is:
6255 -- Ann : Address;
6256 -- {Lnn : Label}
6258 -- begin
6259 -- begin
6260 -- Accept_Call (entry-index, Ann);
6261 -- Renaming_Declarations for formals
6262 -- <statement sequence from N_Accept_Statement node>
6263 -- Complete_Rendezvous;
6264 -- <<Lnn>>
6266 -- exception
6267 -- when ... =>
6268 -- <exception handler from N_Accept_Statement node>
6269 -- Complete_Rendezvous;
6270 -- when ... =>
6271 -- <exception handler from N_Accept_Statement node>
6272 -- Complete_Rendezvous;
6273 -- ...
6274 -- end;
6276 -- exception
6277 -- when all others =>
6278 -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
6279 -- end;
6281 -- The first three declarations were already inserted ahead of the accept
6282 -- statement by the Expand_Accept_Declarations procedure, which was called
6283 -- directly from the semantics during analysis of the accept statement,
6284 -- before analyzing its contained statements.
6286 -- The declarations from the N_Accept_Statement, as noted in Sinfo, come
6287 -- from possible expansion activity (the original source of course does
6288 -- not have any declarations associated with the accept statement, since
6289 -- an accept statement has no declarative part). In particular, if the
6290 -- expander is active, the first such declaration is the declaration of
6291 -- the Accept_Params_Ptr entity (see Sem_Ch9.Analyze_Accept_Statement).
6293 -- The two blocks are merged into a single block if the inner block has
6294 -- no exception handlers, but otherwise two blocks are required, since
6295 -- exceptions might be raised in the exception handlers of the inner
6296 -- block, and Exceptional_Complete_Rendezvous must be called.
6298 procedure Expand_N_Accept_Statement (N : Node_Id) is
6299 Loc : constant Source_Ptr := Sloc (N);
6300 Stats : constant Node_Id := Handled_Statement_Sequence (N);
6301 Ename : constant Node_Id := Entry_Direct_Name (N);
6302 Eindx : constant Node_Id := Entry_Index (N);
6303 Eent : constant Entity_Id := Entity (Ename);
6304 Acstack : constant Elist_Id := Accept_Address (Eent);
6305 Ann : constant Entity_Id := Node (Last_Elmt (Acstack));
6306 Ttyp : constant Entity_Id := Etype (Scope (Eent));
6307 Blkent : Entity_Id;
6308 Call : Node_Id;
6309 Block : Node_Id;
6311 begin
6312 -- If the accept statement is not part of a list, then its parent must
6313 -- be an accept alternative, and, as described above, we do not do any
6314 -- expansion for such accept statements at this level.
6316 if not Is_List_Member (N) then
6317 pragma Assert (Nkind (Parent (N)) = N_Accept_Alternative);
6318 return;
6320 -- Trivial accept case (no statement sequence, or null statements).
6321 -- If the accept statement has declarations, then just insert them
6322 -- before the procedure call.
6324 elsif Trivial_Accept_OK
6325 and then (No (Stats) or else Null_Statements (Statements (Stats)))
6326 then
6327 -- Remove declarations for renamings, because the parameter block
6328 -- will not be assigned.
6330 declare
6331 D : Node_Id;
6332 Next_D : Node_Id;
6334 begin
6335 D := First (Declarations (N));
6337 while Present (D) loop
6338 Next_D := Next (D);
6339 if Nkind (D) = N_Object_Renaming_Declaration then
6340 Remove (D);
6341 end if;
6343 D := Next_D;
6344 end loop;
6345 end;
6347 if Present (Declarations (N)) then
6348 Insert_Actions (N, Declarations (N));
6349 end if;
6351 Rewrite (N,
6352 Make_Procedure_Call_Statement (Loc,
6353 Name => New_Reference_To (RTE (RE_Accept_Trivial), Loc),
6354 Parameter_Associations => New_List (
6355 Entry_Index_Expression (Loc, Entity (Ename), Eindx, Ttyp))));
6357 Analyze (N);
6359 -- Discard Entry_Address that was created for it, so it will not be
6360 -- emitted if this accept statement is in the statement part of a
6361 -- delay alternative.
6363 if Present (Stats) then
6364 Remove_Last_Elmt (Acstack);
6365 end if;
6367 -- Case of statement sequence present
6369 else
6370 -- Construct the block, using the declarations from the accept
6371 -- statement if any to initialize the declarations of the block.
6373 Blkent := Make_Temporary (Loc, 'A');
6374 Set_Ekind (Blkent, E_Block);
6375 Set_Etype (Blkent, Standard_Void_Type);
6376 Set_Scope (Blkent, Current_Scope);
6378 Block :=
6379 Make_Block_Statement (Loc,
6380 Identifier => New_Reference_To (Blkent, Loc),
6381 Declarations => Declarations (N),
6382 Handled_Statement_Sequence => Build_Accept_Body (N));
6384 -- For the analysis of the generated declarations, the parent node
6385 -- must be properly set.
6387 Set_Parent (Block, Parent (N));
6389 -- Prepend call to Accept_Call to main statement sequence If the
6390 -- accept has exception handlers, the statement sequence is wrapped
6391 -- in a block. Insert call and renaming declarations in the
6392 -- declarations of the block, so they are elaborated before the
6393 -- handlers.
6395 Call :=
6396 Make_Procedure_Call_Statement (Loc,
6397 Name => New_Reference_To (RTE (RE_Accept_Call), Loc),
6398 Parameter_Associations => New_List (
6399 Entry_Index_Expression (Loc, Entity (Ename), Eindx, Ttyp),
6400 New_Reference_To (Ann, Loc)));
6402 if Parent (Stats) = N then
6403 Prepend (Call, Statements (Stats));
6404 else
6405 Set_Declarations (Parent (Stats), New_List (Call));
6406 end if;
6408 Analyze (Call);
6410 Push_Scope (Blkent);
6412 declare
6413 D : Node_Id;
6414 Next_D : Node_Id;
6415 Typ : Entity_Id;
6417 begin
6418 D := First (Declarations (N));
6419 while Present (D) loop
6420 Next_D := Next (D);
6422 if Nkind (D) = N_Object_Renaming_Declaration then
6424 -- The renaming declarations for the formals were created
6425 -- during analysis of the accept statement, and attached to
6426 -- the list of declarations. Place them now in the context
6427 -- of the accept block or subprogram.
6429 Remove (D);
6430 Typ := Entity (Subtype_Mark (D));
6431 Insert_After (Call, D);
6432 Analyze (D);
6434 -- If the formal is class_wide, it does not have an actual
6435 -- subtype. The analysis of the renaming declaration creates
6436 -- one, but we need to retain the class-wide nature of the
6437 -- entity.
6439 if Is_Class_Wide_Type (Typ) then
6440 Set_Etype (Defining_Identifier (D), Typ);
6441 end if;
6443 end if;
6445 D := Next_D;
6446 end loop;
6447 end;
6449 End_Scope;
6451 -- Replace the accept statement by the new block
6453 Rewrite (N, Block);
6454 Analyze (N);
6456 -- Last step is to unstack the Accept_Address value
6458 Remove_Last_Elmt (Acstack);
6459 end if;
6460 end Expand_N_Accept_Statement;
6462 ----------------------------------
6463 -- Expand_N_Asynchronous_Select --
6464 ----------------------------------
6466 -- This procedure assumes that the trigger statement is an entry call or
6467 -- a dispatching procedure call. A delay alternative should already have
6468 -- been expanded into an entry call to the appropriate delay object Wait
6469 -- entry.
6471 -- If the trigger is a task entry call, the select is implemented with
6472 -- a Task_Entry_Call:
6474 -- declare
6475 -- B : Boolean;
6476 -- C : Boolean;
6477 -- P : parms := (parm, parm, parm);
6479 -- -- Clean is added by Exp_Ch7.Expand_Cleanup_Actions
6481 -- procedure _clean is
6482 -- begin
6483 -- ...
6484 -- Cancel_Task_Entry_Call (C);
6485 -- ...
6486 -- end _clean;
6488 -- begin
6489 -- Abort_Defer;
6490 -- Task_Entry_Call
6491 -- (<acceptor-task>, -- Acceptor
6492 -- <entry-index>, -- E
6493 -- P'Address, -- Uninterpreted_Data
6494 -- Asynchronous_Call, -- Mode
6495 -- B); -- Rendezvous_Successful
6497 -- begin
6498 -- begin
6499 -- Abort_Undefer;
6500 -- <abortable-part>
6501 -- at end
6502 -- _clean; -- Added by Exp_Ch7.Expand_Cleanup_Actions
6503 -- end;
6504 -- exception
6505 -- when Abort_Signal => Abort_Undefer;
6506 -- end;
6508 -- parm := P.param;
6509 -- parm := P.param;
6510 -- ...
6511 -- if not C then
6512 -- <triggered-statements>
6513 -- end if;
6514 -- end;
6516 -- Note that Build_Simple_Entry_Call is used to expand the entry of the
6517 -- asynchronous entry call (by Expand_N_Entry_Call_Statement procedure)
6518 -- as follows:
6520 -- declare
6521 -- P : parms := (parm, parm, parm);
6522 -- begin
6523 -- Call_Simple (acceptor-task, entry-index, P'Address);
6524 -- parm := P.param;
6525 -- parm := P.param;
6526 -- ...
6527 -- end;
6529 -- so the task at hand is to convert the latter expansion into the former
6531 -- If the trigger is a protected entry call, the select is implemented
6532 -- with Protected_Entry_Call:
6534 -- declare
6535 -- P : E1_Params := (param, param, param);
6536 -- Bnn : Communications_Block;
6538 -- begin
6539 -- declare
6541 -- -- Clean is added by Exp_Ch7.Expand_Cleanup_Actions
6543 -- procedure _clean is
6544 -- begin
6545 -- ...
6546 -- if Enqueued (Bnn) then
6547 -- Cancel_Protected_Entry_Call (Bnn);
6548 -- end if;
6549 -- ...
6550 -- end _clean;
6552 -- begin
6553 -- begin
6554 -- Protected_Entry_Call
6555 -- (po._object'Access, -- Object
6556 -- <entry index>, -- E
6557 -- P'Address, -- Uninterpreted_Data
6558 -- Asynchronous_Call, -- Mode
6559 -- Bnn); -- Block
6561 -- if Enqueued (Bnn) then
6562 -- <abortable-part>
6563 -- end if;
6564 -- at end
6565 -- _clean; -- Added by Exp_Ch7.Expand_Cleanup_Actions
6566 -- end;
6567 -- exception
6568 -- when Abort_Signal => Abort_Undefer;
6569 -- end;
6571 -- if not Cancelled (Bnn) then
6572 -- <triggered-statements>
6573 -- end if;
6574 -- end;
6576 -- Build_Simple_Entry_Call is used to expand the all to a simple protected
6577 -- entry call:
6579 -- declare
6580 -- P : E1_Params := (param, param, param);
6581 -- Bnn : Communications_Block;
6583 -- begin
6584 -- Protected_Entry_Call
6585 -- (po._object'Access, -- Object
6586 -- <entry index>, -- E
6587 -- P'Address, -- Uninterpreted_Data
6588 -- Simple_Call, -- Mode
6589 -- Bnn); -- Block
6590 -- parm := P.param;
6591 -- parm := P.param;
6592 -- ...
6593 -- end;
6595 -- Ada 2005 (AI-345): If the trigger is a dispatching call, the select is
6596 -- expanded into:
6598 -- declare
6599 -- B : Boolean := False;
6600 -- Bnn : Communication_Block;
6601 -- C : Ada.Tags.Prim_Op_Kind;
6602 -- D : System.Storage_Elements.Dummy_Communication_Block;
6603 -- K : Ada.Tags.Tagged_Kind :=
6604 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
6605 -- P : Parameters := (Param1 .. ParamN);
6606 -- S : Integer;
6607 -- U : Boolean;
6609 -- begin
6610 -- if K = Ada.Tags.TK_Limited_Tagged then
6611 -- <dispatching-call>;
6612 -- <triggering-statements>;
6614 -- else
6615 -- S :=
6616 -- Ada.Tags.Get_Offset_Index
6617 -- (Ada.Tags.Tag (<object>), DT_Position (<dispatching-call>));
6619 -- _Disp_Get_Prim_Op_Kind (<object>, S, C);
6621 -- if C = POK_Protected_Entry then
6622 -- declare
6623 -- procedure _clean is
6624 -- begin
6625 -- if Enqueued (Bnn) then
6626 -- Cancel_Protected_Entry_Call (Bnn);
6627 -- end if;
6628 -- end _clean;
6630 -- begin
6631 -- begin
6632 -- _Disp_Asynchronous_Select
6633 -- (<object>, S, P'Address, D, B);
6634 -- Bnn := Communication_Block (D);
6636 -- Param1 := P.Param1;
6637 -- ...
6638 -- ParamN := P.ParamN;
6640 -- if Enqueued (Bnn) then
6641 -- <abortable-statements>
6642 -- end if;
6643 -- at end
6644 -- _clean; -- Added by Exp_Ch7.Expand_Cleanup_Actions
6645 -- end;
6646 -- exception
6647 -- when Abort_Signal => Abort_Undefer;
6648 -- end;
6650 -- if not Cancelled (Bnn) then
6651 -- <triggering-statements>
6652 -- end if;
6654 -- elsif C = POK_Task_Entry then
6655 -- declare
6656 -- procedure _clean is
6657 -- begin
6658 -- Cancel_Task_Entry_Call (U);
6659 -- end _clean;
6661 -- begin
6662 -- Abort_Defer;
6664 -- _Disp_Asynchronous_Select
6665 -- (<object>, S, P'Address, D, B);
6666 -- Bnn := Communication_Bloc (D);
6668 -- Param1 := P.Param1;
6669 -- ...
6670 -- ParamN := P.ParamN;
6672 -- begin
6673 -- begin
6674 -- Abort_Undefer;
6675 -- <abortable-statements>
6676 -- at end
6677 -- _clean; -- Added by Exp_Ch7.Expand_Cleanup_Actions
6678 -- end;
6679 -- exception
6680 -- when Abort_Signal => Abort_Undefer;
6681 -- end;
6683 -- if not U then
6684 -- <triggering-statements>
6685 -- end if;
6686 -- end;
6688 -- else
6689 -- <dispatching-call>;
6690 -- <triggering-statements>
6691 -- end if;
6692 -- end if;
6693 -- end;
6695 -- The job is to convert this to the asynchronous form
6697 -- If the trigger is a delay statement, it will have been expanded into a
6698 -- call to one of the GNARL delay procedures. This routine will convert
6699 -- this into a protected entry call on a delay object and then continue
6700 -- processing as for a protected entry call trigger. This requires
6701 -- declaring a Delay_Block object and adding a pointer to this object to
6702 -- the parameter list of the delay procedure to form the parameter list of
6703 -- the entry call. This object is used by the runtime to queue the delay
6704 -- request.
6706 -- For a description of the use of P and the assignments after the call,
6707 -- see Expand_N_Entry_Call_Statement.
6709 procedure Expand_N_Asynchronous_Select (N : Node_Id) is
6710 Loc : constant Source_Ptr := Sloc (N);
6711 Abrt : constant Node_Id := Abortable_Part (N);
6712 Trig : constant Node_Id := Triggering_Alternative (N);
6714 Abort_Block_Ent : Entity_Id;
6715 Abortable_Block : Node_Id;
6716 Actuals : List_Id;
6717 Astats : List_Id;
6718 Blk_Ent : constant Entity_Id := Make_Temporary (Loc, 'A');
6719 Blk_Typ : Entity_Id;
6720 Call : Node_Id;
6721 Call_Ent : Entity_Id;
6722 Cancel_Param : Entity_Id;
6723 Cleanup_Block : Node_Id;
6724 Cleanup_Block_Ent : Entity_Id;
6725 Cleanup_Stmts : List_Id;
6726 Conc_Typ_Stmts : List_Id;
6727 Concval : Node_Id;
6728 Dblock_Ent : Entity_Id;
6729 Decl : Node_Id;
6730 Decls : List_Id;
6731 Ecall : Node_Id;
6732 Ename : Node_Id;
6733 Enqueue_Call : Node_Id;
6734 Formals : List_Id;
6735 Hdle : List_Id;
6736 Handler_Stmt : Node_Id;
6737 Index : Node_Id;
6738 Lim_Typ_Stmts : List_Id;
6739 N_Orig : Node_Id;
6740 Obj : Entity_Id;
6741 Param : Node_Id;
6742 Params : List_Id;
6743 Pdef : Entity_Id;
6744 ProtE_Stmts : List_Id;
6745 ProtP_Stmts : List_Id;
6746 Stmt : Node_Id;
6747 Stmts : List_Id;
6748 TaskE_Stmts : List_Id;
6749 Tstats : List_Id;
6751 B : Entity_Id; -- Call status flag
6752 Bnn : Entity_Id; -- Communication block
6753 C : Entity_Id; -- Call kind
6754 K : Entity_Id; -- Tagged kind
6755 P : Entity_Id; -- Parameter block
6756 S : Entity_Id; -- Primitive operation slot
6757 T : Entity_Id; -- Additional status flag
6759 procedure Rewrite_Abortable_Part;
6760 -- If the trigger is a dispatching call, the expansion inserts multiple
6761 -- copies of the abortable part. This is both inefficient, and may lead
6762 -- to duplicate definitions that the back-end will reject, when the
6763 -- abortable part includes loops. This procedure rewrites the abortable
6764 -- part into a call to a generated procedure.
6766 ----------------------------
6767 -- Rewrite_Abortable_Part --
6768 ----------------------------
6770 procedure Rewrite_Abortable_Part is
6771 Proc : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uA);
6772 Decl : Node_Id;
6774 begin
6775 Decl :=
6776 Make_Subprogram_Body (Loc,
6777 Specification =>
6778 Make_Procedure_Specification (Loc, Defining_Unit_Name => Proc),
6779 Declarations => New_List,
6780 Handled_Statement_Sequence =>
6781 Make_Handled_Sequence_Of_Statements (Loc, Astats));
6782 Insert_Before (N, Decl);
6783 Analyze (Decl);
6785 -- Rewrite abortable part into a call to this procedure.
6787 Astats :=
6788 New_List (
6789 Make_Procedure_Call_Statement (Loc,
6790 Name => New_Occurrence_Of (Proc, Loc)));
6791 end Rewrite_Abortable_Part;
6793 begin
6794 Process_Statements_For_Controlled_Objects (Trig);
6795 Process_Statements_For_Controlled_Objects (Abrt);
6797 Ecall := Triggering_Statement (Trig);
6799 Ensure_Statement_Present (Sloc (Ecall), Trig);
6801 -- Retrieve Astats and Tstats now because the finalization machinery may
6802 -- wrap them in blocks.
6804 Astats := Statements (Abrt);
6805 Tstats := Statements (Trig);
6807 -- The arguments in the call may require dynamic allocation, and the
6808 -- call statement may have been transformed into a block. The block
6809 -- may contain additional declarations for internal entities, and the
6810 -- original call is found by sequential search.
6812 if Nkind (Ecall) = N_Block_Statement then
6813 Ecall := First (Statements (Handled_Statement_Sequence (Ecall)));
6814 while not Nkind_In (Ecall, N_Procedure_Call_Statement,
6815 N_Entry_Call_Statement)
6816 loop
6817 Next (Ecall);
6818 end loop;
6819 end if;
6821 -- This is either a dispatching call or a delay statement used as a
6822 -- trigger which was expanded into a procedure call.
6824 if Nkind (Ecall) = N_Procedure_Call_Statement then
6825 if Ada_Version >= Ada_2005
6826 and then
6827 (No (Original_Node (Ecall))
6828 or else not Nkind_In (Original_Node (Ecall),
6829 N_Delay_Relative_Statement,
6830 N_Delay_Until_Statement))
6831 then
6832 Extract_Dispatching_Call (Ecall, Call_Ent, Obj, Actuals, Formals);
6834 Rewrite_Abortable_Part;
6835 Decls := New_List;
6836 Stmts := New_List;
6838 -- Call status flag processing, generate:
6839 -- B : Boolean := False;
6841 B := Build_B (Loc, Decls);
6843 -- Communication block processing, generate:
6844 -- Bnn : Communication_Block;
6846 Bnn := Make_Temporary (Loc, 'B');
6847 Append_To (Decls,
6848 Make_Object_Declaration (Loc,
6849 Defining_Identifier => Bnn,
6850 Object_Definition =>
6851 New_Reference_To (RTE (RE_Communication_Block), Loc)));
6853 -- Call kind processing, generate:
6854 -- C : Ada.Tags.Prim_Op_Kind;
6856 C := Build_C (Loc, Decls);
6858 -- Tagged kind processing, generate:
6859 -- K : Ada.Tags.Tagged_Kind :=
6860 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
6862 -- Dummy communication block, generate:
6863 -- D : Dummy_Communication_Block;
6865 Append_To (Decls,
6866 Make_Object_Declaration (Loc,
6867 Defining_Identifier =>
6868 Make_Defining_Identifier (Loc, Name_uD),
6869 Object_Definition =>
6870 New_Reference_To
6871 (RTE (RE_Dummy_Communication_Block), Loc)));
6873 K := Build_K (Loc, Decls, Obj);
6875 -- Parameter block processing
6877 Blk_Typ := Build_Parameter_Block
6878 (Loc, Actuals, Formals, Decls);
6879 P := Parameter_Block_Pack
6880 (Loc, Blk_Typ, Actuals, Formals, Decls, Stmts);
6882 -- Dispatch table slot processing, generate:
6883 -- S : Integer;
6885 S := Build_S (Loc, Decls);
6887 -- Additional status flag processing, generate:
6888 -- Tnn : Boolean;
6890 T := Make_Temporary (Loc, 'T');
6891 Append_To (Decls,
6892 Make_Object_Declaration (Loc,
6893 Defining_Identifier => T,
6894 Object_Definition =>
6895 New_Reference_To (Standard_Boolean, Loc)));
6897 ------------------------------
6898 -- Protected entry handling --
6899 ------------------------------
6901 -- Generate:
6902 -- Param1 := P.Param1;
6903 -- ...
6904 -- ParamN := P.ParamN;
6906 Cleanup_Stmts := Parameter_Block_Unpack (Loc, P, Actuals, Formals);
6908 -- Generate:
6909 -- Bnn := Communication_Block (D);
6911 Prepend_To (Cleanup_Stmts,
6912 Make_Assignment_Statement (Loc,
6913 Name => New_Reference_To (Bnn, Loc),
6914 Expression =>
6915 Make_Unchecked_Type_Conversion (Loc,
6916 Subtype_Mark =>
6917 New_Reference_To (RTE (RE_Communication_Block), Loc),
6918 Expression => Make_Identifier (Loc, Name_uD))));
6920 -- Generate:
6921 -- _Disp_Asynchronous_Select (<object>, S, P'Address, D, B);
6923 Prepend_To (Cleanup_Stmts,
6924 Make_Procedure_Call_Statement (Loc,
6925 Name =>
6926 New_Reference_To
6927 (Find_Prim_Op
6928 (Etype (Etype (Obj)), Name_uDisp_Asynchronous_Select),
6929 Loc),
6930 Parameter_Associations =>
6931 New_List (
6932 New_Copy_Tree (Obj), -- <object>
6933 New_Reference_To (S, Loc), -- S
6934 Make_Attribute_Reference (Loc, -- P'Address
6935 Prefix => New_Reference_To (P, Loc),
6936 Attribute_Name => Name_Address),
6937 Make_Identifier (Loc, Name_uD), -- D
6938 New_Reference_To (B, Loc)))); -- B
6940 -- Generate:
6941 -- if Enqueued (Bnn) then
6942 -- <abortable-statements>
6943 -- end if;
6945 Append_To (Cleanup_Stmts,
6946 Make_Implicit_If_Statement (N,
6947 Condition =>
6948 Make_Function_Call (Loc,
6949 Name =>
6950 New_Reference_To (RTE (RE_Enqueued), Loc),
6951 Parameter_Associations =>
6952 New_List (New_Reference_To (Bnn, Loc))),
6954 Then_Statements =>
6955 New_Copy_List_Tree (Astats)));
6957 -- Wrap the statements in a block. Exp_Ch7.Expand_Cleanup_Actions
6958 -- will then generate a _clean for the communication block Bnn.
6960 -- Generate:
6961 -- declare
6962 -- procedure _clean is
6963 -- begin
6964 -- if Enqueued (Bnn) then
6965 -- Cancel_Protected_Entry_Call (Bnn);
6966 -- end if;
6967 -- end _clean;
6968 -- begin
6969 -- Cleanup_Stmts
6970 -- at end
6971 -- _clean;
6972 -- end;
6974 Cleanup_Block_Ent := Make_Temporary (Loc, 'C');
6975 Cleanup_Block :=
6976 Build_Cleanup_Block (Loc, Cleanup_Block_Ent, Cleanup_Stmts, Bnn);
6978 -- Wrap the cleanup block in an exception handling block
6980 -- Generate:
6981 -- begin
6982 -- Cleanup_Block
6983 -- exception
6984 -- when Abort_Signal => Abort_Undefer;
6985 -- end;
6987 Abort_Block_Ent := Make_Temporary (Loc, 'A');
6988 ProtE_Stmts :=
6989 New_List (
6990 Make_Implicit_Label_Declaration (Loc,
6991 Defining_Identifier => Abort_Block_Ent),
6993 Build_Abort_Block
6994 (Loc, Abort_Block_Ent, Cleanup_Block_Ent, Cleanup_Block));
6996 -- Generate:
6997 -- if not Cancelled (Bnn) then
6998 -- <triggering-statements>
6999 -- end if;
7001 Append_To (ProtE_Stmts,
7002 Make_Implicit_If_Statement (N,
7003 Condition =>
7004 Make_Op_Not (Loc,
7005 Right_Opnd =>
7006 Make_Function_Call (Loc,
7007 Name =>
7008 New_Reference_To (RTE (RE_Cancelled), Loc),
7009 Parameter_Associations =>
7010 New_List (New_Reference_To (Bnn, Loc)))),
7012 Then_Statements =>
7013 New_Copy_List_Tree (Tstats)));
7015 -------------------------
7016 -- Task entry handling --
7017 -------------------------
7019 -- Generate:
7020 -- Param1 := P.Param1;
7021 -- ...
7022 -- ParamN := P.ParamN;
7024 TaskE_Stmts := Parameter_Block_Unpack (Loc, P, Actuals, Formals);
7026 -- Generate:
7027 -- Bnn := Communication_Block (D);
7029 Append_To (TaskE_Stmts,
7030 Make_Assignment_Statement (Loc,
7031 Name =>
7032 New_Reference_To (Bnn, Loc),
7033 Expression =>
7034 Make_Unchecked_Type_Conversion (Loc,
7035 Subtype_Mark =>
7036 New_Reference_To (RTE (RE_Communication_Block), Loc),
7037 Expression => Make_Identifier (Loc, Name_uD))));
7039 -- Generate:
7040 -- _Disp_Asynchronous_Select (<object>, S, P'Address, D, B);
7042 Prepend_To (TaskE_Stmts,
7043 Make_Procedure_Call_Statement (Loc,
7044 Name =>
7045 New_Reference_To (
7046 Find_Prim_Op (Etype (Etype (Obj)),
7047 Name_uDisp_Asynchronous_Select),
7048 Loc),
7050 Parameter_Associations =>
7051 New_List (
7052 New_Copy_Tree (Obj), -- <object>
7053 New_Reference_To (S, Loc), -- S
7054 Make_Attribute_Reference (Loc, -- P'Address
7055 Prefix => New_Reference_To (P, Loc),
7056 Attribute_Name => Name_Address),
7057 Make_Identifier (Loc, Name_uD), -- D
7058 New_Reference_To (B, Loc)))); -- B
7060 -- Generate:
7061 -- Abort_Defer;
7063 Prepend_To (TaskE_Stmts,
7064 Make_Procedure_Call_Statement (Loc,
7065 Name => New_Reference_To (RTE (RE_Abort_Defer), Loc),
7066 Parameter_Associations => No_List));
7068 -- Generate:
7069 -- Abort_Undefer;
7070 -- <abortable-statements>
7072 Cleanup_Stmts := New_Copy_List_Tree (Astats);
7074 Prepend_To (Cleanup_Stmts,
7075 Make_Procedure_Call_Statement (Loc,
7076 Name => New_Reference_To (RTE (RE_Abort_Undefer), Loc),
7077 Parameter_Associations => No_List));
7079 -- Wrap the statements in a block. Exp_Ch7.Expand_Cleanup_Actions
7080 -- will generate a _clean for the additional status flag.
7082 -- Generate:
7083 -- declare
7084 -- procedure _clean is
7085 -- begin
7086 -- Cancel_Task_Entry_Call (U);
7087 -- end _clean;
7088 -- begin
7089 -- Cleanup_Stmts
7090 -- at end
7091 -- _clean;
7092 -- end;
7094 Cleanup_Block_Ent := Make_Temporary (Loc, 'C');
7095 Cleanup_Block :=
7096 Build_Cleanup_Block (Loc, Cleanup_Block_Ent, Cleanup_Stmts, T);
7098 -- Wrap the cleanup block in an exception handling block
7100 -- Generate:
7101 -- begin
7102 -- Cleanup_Block
7103 -- exception
7104 -- when Abort_Signal => Abort_Undefer;
7105 -- end;
7107 Abort_Block_Ent := Make_Temporary (Loc, 'A');
7109 Append_To (TaskE_Stmts,
7110 Make_Implicit_Label_Declaration (Loc,
7111 Defining_Identifier => Abort_Block_Ent));
7113 Append_To (TaskE_Stmts,
7114 Build_Abort_Block
7115 (Loc, Abort_Block_Ent, Cleanup_Block_Ent, Cleanup_Block));
7117 -- Generate:
7118 -- if not T then
7119 -- <triggering-statements>
7120 -- end if;
7122 Append_To (TaskE_Stmts,
7123 Make_Implicit_If_Statement (N,
7124 Condition =>
7125 Make_Op_Not (Loc, Right_Opnd => New_Reference_To (T, Loc)),
7127 Then_Statements =>
7128 New_Copy_List_Tree (Tstats)));
7130 ----------------------------------
7131 -- Protected procedure handling --
7132 ----------------------------------
7134 -- Generate:
7135 -- <dispatching-call>;
7136 -- <triggering-statements>
7138 ProtP_Stmts := New_Copy_List_Tree (Tstats);
7139 Prepend_To (ProtP_Stmts, New_Copy_Tree (Ecall));
7141 -- Generate:
7142 -- S := Ada.Tags.Get_Offset_Index
7143 -- (Ada.Tags.Tag (<object>), DT_Position (Call_Ent));
7145 Conc_Typ_Stmts :=
7146 New_List (Build_S_Assignment (Loc, S, Obj, Call_Ent));
7148 -- Generate:
7149 -- _Disp_Get_Prim_Op_Kind (<object>, S, C);
7151 Append_To (Conc_Typ_Stmts,
7152 Make_Procedure_Call_Statement (Loc,
7153 Name =>
7154 New_Reference_To
7155 (Find_Prim_Op (Etype (Etype (Obj)),
7156 Name_uDisp_Get_Prim_Op_Kind),
7157 Loc),
7158 Parameter_Associations =>
7159 New_List (
7160 New_Copy_Tree (Obj),
7161 New_Reference_To (S, Loc),
7162 New_Reference_To (C, Loc))));
7164 -- Generate:
7165 -- if C = POK_Procedure_Entry then
7166 -- ProtE_Stmts
7167 -- elsif C = POK_Task_Entry then
7168 -- TaskE_Stmts
7169 -- else
7170 -- ProtP_Stmts
7171 -- end if;
7173 Append_To (Conc_Typ_Stmts,
7174 Make_Implicit_If_Statement (N,
7175 Condition =>
7176 Make_Op_Eq (Loc,
7177 Left_Opnd =>
7178 New_Reference_To (C, Loc),
7179 Right_Opnd =>
7180 New_Reference_To (RTE (RE_POK_Protected_Entry), Loc)),
7182 Then_Statements =>
7183 ProtE_Stmts,
7185 Elsif_Parts =>
7186 New_List (
7187 Make_Elsif_Part (Loc,
7188 Condition =>
7189 Make_Op_Eq (Loc,
7190 Left_Opnd =>
7191 New_Reference_To (C, Loc),
7192 Right_Opnd =>
7193 New_Reference_To (RTE (RE_POK_Task_Entry), Loc)),
7195 Then_Statements =>
7196 TaskE_Stmts)),
7198 Else_Statements =>
7199 ProtP_Stmts));
7201 -- Generate:
7202 -- <dispatching-call>;
7203 -- <triggering-statements>
7205 Lim_Typ_Stmts := New_Copy_List_Tree (Tstats);
7206 Prepend_To (Lim_Typ_Stmts, New_Copy_Tree (Ecall));
7208 -- Generate:
7209 -- if K = Ada.Tags.TK_Limited_Tagged then
7210 -- Lim_Typ_Stmts
7211 -- else
7212 -- Conc_Typ_Stmts
7213 -- end if;
7215 Append_To (Stmts,
7216 Make_Implicit_If_Statement (N,
7217 Condition =>
7218 Make_Op_Eq (Loc,
7219 Left_Opnd =>
7220 New_Reference_To (K, Loc),
7221 Right_Opnd =>
7222 New_Reference_To (RTE (RE_TK_Limited_Tagged), Loc)),
7224 Then_Statements =>
7225 Lim_Typ_Stmts,
7227 Else_Statements =>
7228 Conc_Typ_Stmts));
7230 Rewrite (N,
7231 Make_Block_Statement (Loc,
7232 Declarations =>
7233 Decls,
7234 Handled_Statement_Sequence =>
7235 Make_Handled_Sequence_Of_Statements (Loc, Stmts)));
7237 Analyze (N);
7238 return;
7240 -- Delay triggering statement processing
7242 else
7243 -- Add a Delay_Block object to the parameter list of the delay
7244 -- procedure to form the parameter list of the Wait entry call.
7246 Dblock_Ent := Make_Temporary (Loc, 'D');
7248 Pdef := Entity (Name (Ecall));
7250 if Is_RTE (Pdef, RO_CA_Delay_For) then
7251 Enqueue_Call :=
7252 New_Reference_To (RTE (RE_Enqueue_Duration), Loc);
7254 elsif Is_RTE (Pdef, RO_CA_Delay_Until) then
7255 Enqueue_Call :=
7256 New_Reference_To (RTE (RE_Enqueue_Calendar), Loc);
7258 else pragma Assert (Is_RTE (Pdef, RO_RT_Delay_Until));
7259 Enqueue_Call := New_Reference_To (RTE (RE_Enqueue_RT), Loc);
7260 end if;
7262 Append_To (Parameter_Associations (Ecall),
7263 Make_Attribute_Reference (Loc,
7264 Prefix => New_Reference_To (Dblock_Ent, Loc),
7265 Attribute_Name => Name_Unchecked_Access));
7267 -- Create the inner block to protect the abortable part
7269 Hdle := New_List (Build_Abort_Block_Handler (Loc));
7271 Prepend_To (Astats,
7272 Make_Procedure_Call_Statement (Loc,
7273 Name => New_Reference_To (RTE (RE_Abort_Undefer), Loc)));
7275 Abortable_Block :=
7276 Make_Block_Statement (Loc,
7277 Identifier => New_Reference_To (Blk_Ent, Loc),
7278 Handled_Statement_Sequence =>
7279 Make_Handled_Sequence_Of_Statements (Loc,
7280 Statements => Astats),
7281 Has_Created_Identifier => True,
7282 Is_Asynchronous_Call_Block => True);
7284 -- Append call to if Enqueue (When, DB'Unchecked_Access) then
7286 Rewrite (Ecall,
7287 Make_Implicit_If_Statement (N,
7288 Condition =>
7289 Make_Function_Call (Loc,
7290 Name => Enqueue_Call,
7291 Parameter_Associations => Parameter_Associations (Ecall)),
7292 Then_Statements =>
7293 New_List (Make_Block_Statement (Loc,
7294 Handled_Statement_Sequence =>
7295 Make_Handled_Sequence_Of_Statements (Loc,
7296 Statements => New_List (
7297 Make_Implicit_Label_Declaration (Loc,
7298 Defining_Identifier => Blk_Ent,
7299 Label_Construct => Abortable_Block),
7300 Abortable_Block),
7301 Exception_Handlers => Hdle)))));
7303 Stmts := New_List (Ecall);
7305 -- Construct statement sequence for new block
7307 Append_To (Stmts,
7308 Make_Implicit_If_Statement (N,
7309 Condition =>
7310 Make_Function_Call (Loc,
7311 Name => New_Reference_To (
7312 RTE (RE_Timed_Out), Loc),
7313 Parameter_Associations => New_List (
7314 Make_Attribute_Reference (Loc,
7315 Prefix => New_Reference_To (Dblock_Ent, Loc),
7316 Attribute_Name => Name_Unchecked_Access))),
7317 Then_Statements => Tstats));
7319 -- The result is the new block
7321 Set_Entry_Cancel_Parameter (Blk_Ent, Dblock_Ent);
7323 Rewrite (N,
7324 Make_Block_Statement (Loc,
7325 Declarations => New_List (
7326 Make_Object_Declaration (Loc,
7327 Defining_Identifier => Dblock_Ent,
7328 Aliased_Present => True,
7329 Object_Definition =>
7330 New_Reference_To (RTE (RE_Delay_Block), Loc))),
7332 Handled_Statement_Sequence =>
7333 Make_Handled_Sequence_Of_Statements (Loc, Stmts)));
7335 Analyze (N);
7336 return;
7337 end if;
7339 else
7340 N_Orig := N;
7341 end if;
7343 Extract_Entry (Ecall, Concval, Ename, Index);
7344 Build_Simple_Entry_Call (Ecall, Concval, Ename, Index);
7346 Stmts := Statements (Handled_Statement_Sequence (Ecall));
7347 Decls := Declarations (Ecall);
7349 if Is_Protected_Type (Etype (Concval)) then
7351 -- Get the declarations of the block expanded from the entry call
7353 Decl := First (Decls);
7354 while Present (Decl)
7355 and then (Nkind (Decl) /= N_Object_Declaration
7356 or else not Is_RTE (Etype (Object_Definition (Decl)),
7357 RE_Communication_Block))
7358 loop
7359 Next (Decl);
7360 end loop;
7362 pragma Assert (Present (Decl));
7363 Cancel_Param := Defining_Identifier (Decl);
7365 -- Change the mode of the Protected_Entry_Call call
7367 -- Protected_Entry_Call (
7368 -- Object => po._object'Access,
7369 -- E => <entry index>;
7370 -- Uninterpreted_Data => P'Address;
7371 -- Mode => Asynchronous_Call;
7372 -- Block => Bnn);
7374 -- Skip assignments to temporaries created for in-out parameters
7376 -- This makes unwarranted assumptions about the shape of the expanded
7377 -- tree for the call, and should be cleaned up ???
7379 Stmt := First (Stmts);
7380 while Nkind (Stmt) /= N_Procedure_Call_Statement loop
7381 Next (Stmt);
7382 end loop;
7384 Call := Stmt;
7386 Param := First (Parameter_Associations (Call));
7387 while Present (Param)
7388 and then not Is_RTE (Etype (Param), RE_Call_Modes)
7389 loop
7390 Next (Param);
7391 end loop;
7393 pragma Assert (Present (Param));
7394 Rewrite (Param, New_Reference_To (RTE (RE_Asynchronous_Call), Loc));
7395 Analyze (Param);
7397 -- Append an if statement to execute the abortable part
7399 -- Generate:
7400 -- if Enqueued (Bnn) then
7402 Append_To (Stmts,
7403 Make_Implicit_If_Statement (N,
7404 Condition =>
7405 Make_Function_Call (Loc,
7406 Name => New_Reference_To (RTE (RE_Enqueued), Loc),
7407 Parameter_Associations => New_List (
7408 New_Reference_To (Cancel_Param, Loc))),
7409 Then_Statements => Astats));
7411 Abortable_Block :=
7412 Make_Block_Statement (Loc,
7413 Identifier => New_Reference_To (Blk_Ent, Loc),
7414 Handled_Statement_Sequence =>
7415 Make_Handled_Sequence_Of_Statements (Loc, Statements => Stmts),
7416 Has_Created_Identifier => True,
7417 Is_Asynchronous_Call_Block => True);
7419 -- For the VM call Update_Exception instead of Abort_Undefer.
7420 -- See 4jexcept.ads for an explanation.
7422 if VM_Target = No_VM then
7423 if Exception_Mechanism = Back_End_Exceptions then
7425 -- Aborts are not deferred at beginning of exception handlers
7426 -- in ZCX.
7428 Handler_Stmt := Make_Null_Statement (Loc);
7430 else
7431 Handler_Stmt := Make_Procedure_Call_Statement (Loc,
7432 Name => New_Reference_To (RTE (RE_Abort_Undefer), Loc),
7433 Parameter_Associations => No_List);
7434 end if;
7435 else
7436 Handler_Stmt := Make_Procedure_Call_Statement (Loc,
7437 Name => New_Reference_To (RTE (RE_Update_Exception), Loc),
7438 Parameter_Associations => New_List (
7439 Make_Function_Call (Loc,
7440 Name => New_Occurrence_Of
7441 (RTE (RE_Current_Target_Exception), Loc))));
7442 end if;
7444 Stmts := New_List (
7445 Make_Block_Statement (Loc,
7446 Handled_Statement_Sequence =>
7447 Make_Handled_Sequence_Of_Statements (Loc,
7448 Statements => New_List (
7449 Make_Implicit_Label_Declaration (Loc,
7450 Defining_Identifier => Blk_Ent,
7451 Label_Construct => Abortable_Block),
7452 Abortable_Block),
7454 -- exception
7456 Exception_Handlers => New_List (
7457 Make_Implicit_Exception_Handler (Loc,
7459 -- when Abort_Signal =>
7460 -- Abort_Undefer.all;
7462 Exception_Choices =>
7463 New_List (New_Reference_To (Stand.Abort_Signal, Loc)),
7464 Statements => New_List (Handler_Stmt))))),
7466 -- if not Cancelled (Bnn) then
7467 -- triggered statements
7468 -- end if;
7470 Make_Implicit_If_Statement (N,
7471 Condition => Make_Op_Not (Loc,
7472 Right_Opnd =>
7473 Make_Function_Call (Loc,
7474 Name => New_Occurrence_Of (RTE (RE_Cancelled), Loc),
7475 Parameter_Associations => New_List (
7476 New_Occurrence_Of (Cancel_Param, Loc)))),
7477 Then_Statements => Tstats));
7479 -- Asynchronous task entry call
7481 else
7482 if No (Decls) then
7483 Decls := New_List;
7484 end if;
7486 B := Make_Defining_Identifier (Loc, Name_uB);
7488 -- Insert declaration of B in declarations of existing block
7490 Prepend_To (Decls,
7491 Make_Object_Declaration (Loc,
7492 Defining_Identifier => B,
7493 Object_Definition => New_Reference_To (Standard_Boolean, Loc)));
7495 Cancel_Param := Make_Defining_Identifier (Loc, Name_uC);
7497 -- Insert declaration of C in declarations of existing block
7499 Prepend_To (Decls,
7500 Make_Object_Declaration (Loc,
7501 Defining_Identifier => Cancel_Param,
7502 Object_Definition => New_Reference_To (Standard_Boolean, Loc)));
7504 -- Remove and save the call to Call_Simple
7506 Stmt := First (Stmts);
7508 -- Skip assignments to temporaries created for in-out parameters.
7509 -- This makes unwarranted assumptions about the shape of the expanded
7510 -- tree for the call, and should be cleaned up ???
7512 while Nkind (Stmt) /= N_Procedure_Call_Statement loop
7513 Next (Stmt);
7514 end loop;
7516 Call := Stmt;
7518 -- Create the inner block to protect the abortable part
7520 Hdle := New_List (Build_Abort_Block_Handler (Loc));
7522 Prepend_To (Astats,
7523 Make_Procedure_Call_Statement (Loc,
7524 Name => New_Reference_To (RTE (RE_Abort_Undefer), Loc)));
7526 Abortable_Block :=
7527 Make_Block_Statement (Loc,
7528 Identifier => New_Reference_To (Blk_Ent, Loc),
7529 Handled_Statement_Sequence =>
7530 Make_Handled_Sequence_Of_Statements (Loc, Statements => Astats),
7531 Has_Created_Identifier => True,
7532 Is_Asynchronous_Call_Block => True);
7534 Insert_After (Call,
7535 Make_Block_Statement (Loc,
7536 Handled_Statement_Sequence =>
7537 Make_Handled_Sequence_Of_Statements (Loc,
7538 Statements => New_List (
7539 Make_Implicit_Label_Declaration (Loc,
7540 Defining_Identifier => Blk_Ent,
7541 Label_Construct => Abortable_Block),
7542 Abortable_Block),
7543 Exception_Handlers => Hdle)));
7545 -- Create new call statement
7547 Params := Parameter_Associations (Call);
7549 Append_To (Params,
7550 New_Reference_To (RTE (RE_Asynchronous_Call), Loc));
7551 Append_To (Params, New_Reference_To (B, Loc));
7553 Rewrite (Call,
7554 Make_Procedure_Call_Statement (Loc,
7555 Name => New_Reference_To (RTE (RE_Task_Entry_Call), Loc),
7556 Parameter_Associations => Params));
7558 -- Construct statement sequence for new block
7560 Append_To (Stmts,
7561 Make_Implicit_If_Statement (N,
7562 Condition =>
7563 Make_Op_Not (Loc, New_Reference_To (Cancel_Param, Loc)),
7564 Then_Statements => Tstats));
7566 -- Protected the call against abort
7568 Prepend_To (Stmts,
7569 Make_Procedure_Call_Statement (Loc,
7570 Name => New_Reference_To (RTE (RE_Abort_Defer), Loc),
7571 Parameter_Associations => Empty_List));
7572 end if;
7574 Set_Entry_Cancel_Parameter (Blk_Ent, Cancel_Param);
7576 -- The result is the new block
7578 Rewrite (N_Orig,
7579 Make_Block_Statement (Loc,
7580 Declarations => Decls,
7581 Handled_Statement_Sequence =>
7582 Make_Handled_Sequence_Of_Statements (Loc, Stmts)));
7584 Analyze (N_Orig);
7585 end Expand_N_Asynchronous_Select;
7587 -------------------------------------
7588 -- Expand_N_Conditional_Entry_Call --
7589 -------------------------------------
7591 -- The conditional task entry call is converted to a call to
7592 -- Task_Entry_Call:
7594 -- declare
7595 -- B : Boolean;
7596 -- P : parms := (parm, parm, parm);
7598 -- begin
7599 -- Task_Entry_Call
7600 -- (<acceptor-task>, -- Acceptor
7601 -- <entry-index>, -- E
7602 -- P'Address, -- Uninterpreted_Data
7603 -- Conditional_Call, -- Mode
7604 -- B); -- Rendezvous_Successful
7605 -- parm := P.param;
7606 -- parm := P.param;
7607 -- ...
7608 -- if B then
7609 -- normal-statements
7610 -- else
7611 -- else-statements
7612 -- end if;
7613 -- end;
7615 -- For a description of the use of P and the assignments after the call,
7616 -- see Expand_N_Entry_Call_Statement. Note that the entry call of the
7617 -- conditional entry call has already been expanded (by the Expand_N_Entry
7618 -- _Call_Statement procedure) as follows:
7620 -- declare
7621 -- P : parms := (parm, parm, parm);
7622 -- begin
7623 -- ... info for in-out parameters
7624 -- Call_Simple (acceptor-task, entry-index, P'Address);
7625 -- parm := P.param;
7626 -- parm := P.param;
7627 -- ...
7628 -- end;
7630 -- so the task at hand is to convert the latter expansion into the former
7632 -- The conditional protected entry call is converted to a call to
7633 -- Protected_Entry_Call:
7635 -- declare
7636 -- P : parms := (parm, parm, parm);
7637 -- Bnn : Communications_Block;
7639 -- begin
7640 -- Protected_Entry_Call
7641 -- (po._object'Access, -- Object
7642 -- <entry index>, -- E
7643 -- P'Address, -- Uninterpreted_Data
7644 -- Conditional_Call, -- Mode
7645 -- Bnn); -- Block
7646 -- parm := P.param;
7647 -- parm := P.param;
7648 -- ...
7649 -- if Cancelled (Bnn) then
7650 -- else-statements
7651 -- else
7652 -- normal-statements
7653 -- end if;
7654 -- end;
7656 -- Ada 2005 (AI-345): A dispatching conditional entry call is converted
7657 -- into:
7659 -- declare
7660 -- B : Boolean := False;
7661 -- C : Ada.Tags.Prim_Op_Kind;
7662 -- K : Ada.Tags.Tagged_Kind :=
7663 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
7664 -- P : Parameters := (Param1 .. ParamN);
7665 -- S : Integer;
7667 -- begin
7668 -- if K = Ada.Tags.TK_Limited_Tagged then
7669 -- <dispatching-call>;
7670 -- <triggering-statements>
7672 -- else
7673 -- S :=
7674 -- Ada.Tags.Get_Offset_Index
7675 -- (Ada.Tags.Tag (<object>), DT_Position (<dispatching-call>));
7677 -- _Disp_Conditional_Select (<object>, S, P'Address, C, B);
7679 -- if C = POK_Protected_Entry
7680 -- or else C = POK_Task_Entry
7681 -- then
7682 -- Param1 := P.Param1;
7683 -- ...
7684 -- ParamN := P.ParamN;
7685 -- end if;
7687 -- if B then
7688 -- if C = POK_Procedure
7689 -- or else C = POK_Protected_Procedure
7690 -- or else C = POK_Task_Procedure
7691 -- then
7692 -- <dispatching-call>;
7693 -- end if;
7695 -- <triggering-statements>
7696 -- else
7697 -- <else-statements>
7698 -- end if;
7699 -- end if;
7700 -- end;
7702 procedure Expand_N_Conditional_Entry_Call (N : Node_Id) is
7703 Loc : constant Source_Ptr := Sloc (N);
7704 Alt : constant Node_Id := Entry_Call_Alternative (N);
7705 Blk : Node_Id := Entry_Call_Statement (Alt);
7707 Actuals : List_Id;
7708 Blk_Typ : Entity_Id;
7709 Call : Node_Id;
7710 Call_Ent : Entity_Id;
7711 Conc_Typ_Stmts : List_Id;
7712 Decl : Node_Id;
7713 Decls : List_Id;
7714 Formals : List_Id;
7715 Lim_Typ_Stmts : List_Id;
7716 N_Stats : List_Id;
7717 Obj : Entity_Id;
7718 Param : Node_Id;
7719 Params : List_Id;
7720 Stmt : Node_Id;
7721 Stmts : List_Id;
7722 Transient_Blk : Node_Id;
7723 Unpack : List_Id;
7725 B : Entity_Id; -- Call status flag
7726 C : Entity_Id; -- Call kind
7727 K : Entity_Id; -- Tagged kind
7728 P : Entity_Id; -- Parameter block
7729 S : Entity_Id; -- Primitive operation slot
7731 begin
7732 Process_Statements_For_Controlled_Objects (N);
7734 if Ada_Version >= Ada_2005
7735 and then Nkind (Blk) = N_Procedure_Call_Statement
7736 then
7737 Extract_Dispatching_Call (Blk, Call_Ent, Obj, Actuals, Formals);
7739 Decls := New_List;
7740 Stmts := New_List;
7742 -- Call status flag processing, generate:
7743 -- B : Boolean := False;
7745 B := Build_B (Loc, Decls);
7747 -- Call kind processing, generate:
7748 -- C : Ada.Tags.Prim_Op_Kind;
7750 C := Build_C (Loc, Decls);
7752 -- Tagged kind processing, generate:
7753 -- K : Ada.Tags.Tagged_Kind :=
7754 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
7756 K := Build_K (Loc, Decls, Obj);
7758 -- Parameter block processing
7760 Blk_Typ := Build_Parameter_Block (Loc, Actuals, Formals, Decls);
7761 P := Parameter_Block_Pack
7762 (Loc, Blk_Typ, Actuals, Formals, Decls, Stmts);
7764 -- Dispatch table slot processing, generate:
7765 -- S : Integer;
7767 S := Build_S (Loc, Decls);
7769 -- Generate:
7770 -- S := Ada.Tags.Get_Offset_Index
7771 -- (Ada.Tags.Tag (<object>), DT_Position (Call_Ent));
7773 Conc_Typ_Stmts :=
7774 New_List (Build_S_Assignment (Loc, S, Obj, Call_Ent));
7776 -- Generate:
7777 -- _Disp_Conditional_Select (<object>, S, P'Address, C, B);
7779 Append_To (Conc_Typ_Stmts,
7780 Make_Procedure_Call_Statement (Loc,
7781 Name =>
7782 New_Reference_To (
7783 Find_Prim_Op (Etype (Etype (Obj)),
7784 Name_uDisp_Conditional_Select),
7785 Loc),
7786 Parameter_Associations =>
7787 New_List (
7788 New_Copy_Tree (Obj), -- <object>
7789 New_Reference_To (S, Loc), -- S
7790 Make_Attribute_Reference (Loc, -- P'Address
7791 Prefix => New_Reference_To (P, Loc),
7792 Attribute_Name => Name_Address),
7793 New_Reference_To (C, Loc), -- C
7794 New_Reference_To (B, Loc)))); -- B
7796 -- Generate:
7797 -- if C = POK_Protected_Entry
7798 -- or else C = POK_Task_Entry
7799 -- then
7800 -- Param1 := P.Param1;
7801 -- ...
7802 -- ParamN := P.ParamN;
7803 -- end if;
7805 Unpack := Parameter_Block_Unpack (Loc, P, Actuals, Formals);
7807 -- Generate the if statement only when the packed parameters need
7808 -- explicit assignments to their corresponding actuals.
7810 if Present (Unpack) then
7811 Append_To (Conc_Typ_Stmts,
7812 Make_Implicit_If_Statement (N,
7813 Condition =>
7814 Make_Or_Else (Loc,
7815 Left_Opnd =>
7816 Make_Op_Eq (Loc,
7817 Left_Opnd =>
7818 New_Reference_To (C, Loc),
7819 Right_Opnd =>
7820 New_Reference_To (RTE (
7821 RE_POK_Protected_Entry), Loc)),
7823 Right_Opnd =>
7824 Make_Op_Eq (Loc,
7825 Left_Opnd =>
7826 New_Reference_To (C, Loc),
7827 Right_Opnd =>
7828 New_Reference_To (RTE (RE_POK_Task_Entry), Loc))),
7830 Then_Statements => Unpack));
7831 end if;
7833 -- Generate:
7834 -- if B then
7835 -- if C = POK_Procedure
7836 -- or else C = POK_Protected_Procedure
7837 -- or else C = POK_Task_Procedure
7838 -- then
7839 -- <dispatching-call>
7840 -- end if;
7841 -- <normal-statements>
7842 -- else
7843 -- <else-statements>
7844 -- end if;
7846 N_Stats := New_Copy_List_Tree (Statements (Alt));
7848 Prepend_To (N_Stats,
7849 Make_Implicit_If_Statement (N,
7850 Condition =>
7851 Make_Or_Else (Loc,
7852 Left_Opnd =>
7853 Make_Op_Eq (Loc,
7854 Left_Opnd =>
7855 New_Reference_To (C, Loc),
7856 Right_Opnd =>
7857 New_Reference_To (RTE (RE_POK_Procedure), Loc)),
7859 Right_Opnd =>
7860 Make_Or_Else (Loc,
7861 Left_Opnd =>
7862 Make_Op_Eq (Loc,
7863 Left_Opnd =>
7864 New_Reference_To (C, Loc),
7865 Right_Opnd =>
7866 New_Reference_To (RTE (
7867 RE_POK_Protected_Procedure), Loc)),
7869 Right_Opnd =>
7870 Make_Op_Eq (Loc,
7871 Left_Opnd =>
7872 New_Reference_To (C, Loc),
7873 Right_Opnd =>
7874 New_Reference_To (RTE (
7875 RE_POK_Task_Procedure), Loc)))),
7877 Then_Statements =>
7878 New_List (Blk)));
7880 Append_To (Conc_Typ_Stmts,
7881 Make_Implicit_If_Statement (N,
7882 Condition => New_Reference_To (B, Loc),
7883 Then_Statements => N_Stats,
7884 Else_Statements => Else_Statements (N)));
7886 -- Generate:
7887 -- <dispatching-call>;
7888 -- <triggering-statements>
7890 Lim_Typ_Stmts := New_Copy_List_Tree (Statements (Alt));
7891 Prepend_To (Lim_Typ_Stmts, New_Copy_Tree (Blk));
7893 -- Generate:
7894 -- if K = Ada.Tags.TK_Limited_Tagged then
7895 -- Lim_Typ_Stmts
7896 -- else
7897 -- Conc_Typ_Stmts
7898 -- end if;
7900 Append_To (Stmts,
7901 Make_Implicit_If_Statement (N,
7902 Condition =>
7903 Make_Op_Eq (Loc,
7904 Left_Opnd =>
7905 New_Reference_To (K, Loc),
7906 Right_Opnd =>
7907 New_Reference_To (RTE (RE_TK_Limited_Tagged), Loc)),
7909 Then_Statements =>
7910 Lim_Typ_Stmts,
7912 Else_Statements =>
7913 Conc_Typ_Stmts));
7915 Rewrite (N,
7916 Make_Block_Statement (Loc,
7917 Declarations =>
7918 Decls,
7919 Handled_Statement_Sequence =>
7920 Make_Handled_Sequence_Of_Statements (Loc, Stmts)));
7922 -- As described above, the entry alternative is transformed into a
7923 -- block that contains the gnulli call, and possibly assignment
7924 -- statements for in-out parameters. The gnulli call may itself be
7925 -- rewritten into a transient block if some unconstrained parameters
7926 -- require it. We need to retrieve the call to complete its parameter
7927 -- list.
7929 else
7930 Transient_Blk :=
7931 First_Real_Statement (Handled_Statement_Sequence (Blk));
7933 if Present (Transient_Blk)
7934 and then Nkind (Transient_Blk) = N_Block_Statement
7935 then
7936 Blk := Transient_Blk;
7937 end if;
7939 Stmts := Statements (Handled_Statement_Sequence (Blk));
7940 Stmt := First (Stmts);
7941 while Nkind (Stmt) /= N_Procedure_Call_Statement loop
7942 Next (Stmt);
7943 end loop;
7945 Call := Stmt;
7946 Params := Parameter_Associations (Call);
7948 if Is_RTE (Entity (Name (Call)), RE_Protected_Entry_Call) then
7950 -- Substitute Conditional_Entry_Call for Simple_Call parameter
7952 Param := First (Params);
7953 while Present (Param)
7954 and then not Is_RTE (Etype (Param), RE_Call_Modes)
7955 loop
7956 Next (Param);
7957 end loop;
7959 pragma Assert (Present (Param));
7960 Rewrite (Param, New_Reference_To (RTE (RE_Conditional_Call), Loc));
7962 Analyze (Param);
7964 -- Find the Communication_Block parameter for the call to the
7965 -- Cancelled function.
7967 Decl := First (Declarations (Blk));
7968 while Present (Decl)
7969 and then not Is_RTE (Etype (Object_Definition (Decl)),
7970 RE_Communication_Block)
7971 loop
7972 Next (Decl);
7973 end loop;
7975 -- Add an if statement to execute the else part if the call
7976 -- does not succeed (as indicated by the Cancelled predicate).
7978 Append_To (Stmts,
7979 Make_Implicit_If_Statement (N,
7980 Condition => Make_Function_Call (Loc,
7981 Name => New_Reference_To (RTE (RE_Cancelled), Loc),
7982 Parameter_Associations => New_List (
7983 New_Reference_To (Defining_Identifier (Decl), Loc))),
7984 Then_Statements => Else_Statements (N),
7985 Else_Statements => Statements (Alt)));
7987 else
7988 B := Make_Defining_Identifier (Loc, Name_uB);
7990 -- Insert declaration of B in declarations of existing block
7992 if No (Declarations (Blk)) then
7993 Set_Declarations (Blk, New_List);
7994 end if;
7996 Prepend_To (Declarations (Blk),
7997 Make_Object_Declaration (Loc,
7998 Defining_Identifier => B,
7999 Object_Definition =>
8000 New_Reference_To (Standard_Boolean, Loc)));
8002 -- Create new call statement
8004 Append_To (Params,
8005 New_Reference_To (RTE (RE_Conditional_Call), Loc));
8006 Append_To (Params, New_Reference_To (B, Loc));
8008 Rewrite (Call,
8009 Make_Procedure_Call_Statement (Loc,
8010 Name => New_Reference_To (RTE (RE_Task_Entry_Call), Loc),
8011 Parameter_Associations => Params));
8013 -- Construct statement sequence for new block
8015 Append_To (Stmts,
8016 Make_Implicit_If_Statement (N,
8017 Condition => New_Reference_To (B, Loc),
8018 Then_Statements => Statements (Alt),
8019 Else_Statements => Else_Statements (N)));
8020 end if;
8022 -- The result is the new block
8024 Rewrite (N,
8025 Make_Block_Statement (Loc,
8026 Declarations => Declarations (Blk),
8027 Handled_Statement_Sequence =>
8028 Make_Handled_Sequence_Of_Statements (Loc, Stmts)));
8029 end if;
8031 Analyze (N);
8032 end Expand_N_Conditional_Entry_Call;
8034 ---------------------------------------
8035 -- Expand_N_Delay_Relative_Statement --
8036 ---------------------------------------
8038 -- Delay statement is implemented as a procedure call to Delay_For
8039 -- defined in Ada.Calendar.Delays in order to reduce the overhead of
8040 -- simple delays imposed by the use of Protected Objects.
8042 procedure Expand_N_Delay_Relative_Statement (N : Node_Id) is
8043 Loc : constant Source_Ptr := Sloc (N);
8044 begin
8045 Rewrite (N,
8046 Make_Procedure_Call_Statement (Loc,
8047 Name => New_Reference_To (RTE (RO_CA_Delay_For), Loc),
8048 Parameter_Associations => New_List (Expression (N))));
8049 Analyze (N);
8050 end Expand_N_Delay_Relative_Statement;
8052 ------------------------------------
8053 -- Expand_N_Delay_Until_Statement --
8054 ------------------------------------
8056 -- Delay Until statement is implemented as a procedure call to
8057 -- Delay_Until defined in Ada.Calendar.Delays and Ada.Real_Time.Delays.
8059 procedure Expand_N_Delay_Until_Statement (N : Node_Id) is
8060 Loc : constant Source_Ptr := Sloc (N);
8061 Typ : Entity_Id;
8063 begin
8064 if Is_RTE (Base_Type (Etype (Expression (N))), RO_CA_Time) then
8065 Typ := RTE (RO_CA_Delay_Until);
8066 else
8067 Typ := RTE (RO_RT_Delay_Until);
8068 end if;
8070 Rewrite (N,
8071 Make_Procedure_Call_Statement (Loc,
8072 Name => New_Reference_To (Typ, Loc),
8073 Parameter_Associations => New_List (Expression (N))));
8075 Analyze (N);
8076 end Expand_N_Delay_Until_Statement;
8078 -------------------------
8079 -- Expand_N_Entry_Body --
8080 -------------------------
8082 procedure Expand_N_Entry_Body (N : Node_Id) is
8083 begin
8084 -- Associate discriminals with the next protected operation body to be
8085 -- expanded.
8087 if Present (Next_Protected_Operation (N)) then
8088 Set_Discriminals (Parent (Current_Scope));
8089 end if;
8090 end Expand_N_Entry_Body;
8092 -----------------------------------
8093 -- Expand_N_Entry_Call_Statement --
8094 -----------------------------------
8096 -- An entry call is expanded into GNARLI calls to implement a simple entry
8097 -- call (see Build_Simple_Entry_Call).
8099 procedure Expand_N_Entry_Call_Statement (N : Node_Id) is
8100 Concval : Node_Id;
8101 Ename : Node_Id;
8102 Index : Node_Id;
8104 begin
8105 if No_Run_Time_Mode then
8106 Error_Msg_CRT ("entry call", N);
8107 return;
8108 end if;
8110 -- If this entry call is part of an asynchronous select, don't expand it
8111 -- here; it will be expanded with the select statement. Don't expand
8112 -- timed entry calls either, as they are translated into asynchronous
8113 -- entry calls.
8115 -- ??? This whole approach is questionable; it may be better to go back
8116 -- to allowing the expansion to take place and then attempting to fix it
8117 -- up in Expand_N_Asynchronous_Select. The tricky part is figuring out
8118 -- whether the expanded call is on a task or protected entry.
8120 if (Nkind (Parent (N)) /= N_Triggering_Alternative
8121 or else N /= Triggering_Statement (Parent (N)))
8122 and then (Nkind (Parent (N)) /= N_Entry_Call_Alternative
8123 or else N /= Entry_Call_Statement (Parent (N))
8124 or else Nkind (Parent (Parent (N))) /= N_Timed_Entry_Call)
8125 then
8126 Extract_Entry (N, Concval, Ename, Index);
8127 Build_Simple_Entry_Call (N, Concval, Ename, Index);
8128 end if;
8129 end Expand_N_Entry_Call_Statement;
8131 --------------------------------
8132 -- Expand_N_Entry_Declaration --
8133 --------------------------------
8135 -- If there are parameters, then first, each of the formals is marked by
8136 -- setting Is_Entry_Formal. Next a record type is built which is used to
8137 -- hold the parameter values. The name of this record type is entryP where
8138 -- entry is the name of the entry, with an additional corresponding access
8139 -- type called entryPA. The record type has matching components for each
8140 -- formal (the component names are the same as the formal names). For
8141 -- elementary types, the component type matches the formal type. For
8142 -- composite types, an access type is declared (with the name formalA)
8143 -- which designates the formal type, and the type of the component is this
8144 -- access type. Finally the Entry_Component of each formal is set to
8145 -- reference the corresponding record component.
8147 procedure Expand_N_Entry_Declaration (N : Node_Id) is
8148 Loc : constant Source_Ptr := Sloc (N);
8149 Entry_Ent : constant Entity_Id := Defining_Identifier (N);
8150 Components : List_Id;
8151 Formal : Node_Id;
8152 Ftype : Entity_Id;
8153 Last_Decl : Node_Id;
8154 Component : Entity_Id;
8155 Ctype : Entity_Id;
8156 Decl : Node_Id;
8157 Rec_Ent : Entity_Id;
8158 Acc_Ent : Entity_Id;
8160 begin
8161 Formal := First_Formal (Entry_Ent);
8162 Last_Decl := N;
8164 -- Most processing is done only if parameters are present
8166 if Present (Formal) then
8167 Components := New_List;
8169 -- Loop through formals
8171 while Present (Formal) loop
8172 Set_Is_Entry_Formal (Formal);
8173 Component :=
8174 Make_Defining_Identifier (Sloc (Formal), Chars (Formal));
8175 Set_Entry_Component (Formal, Component);
8176 Set_Entry_Formal (Component, Formal);
8177 Ftype := Etype (Formal);
8179 -- Declare new access type and then append
8181 Ctype := Make_Temporary (Loc, 'A');
8183 Decl :=
8184 Make_Full_Type_Declaration (Loc,
8185 Defining_Identifier => Ctype,
8186 Type_Definition =>
8187 Make_Access_To_Object_Definition (Loc,
8188 All_Present => True,
8189 Constant_Present => Ekind (Formal) = E_In_Parameter,
8190 Subtype_Indication => New_Reference_To (Ftype, Loc)));
8192 Insert_After (Last_Decl, Decl);
8193 Last_Decl := Decl;
8195 Append_To (Components,
8196 Make_Component_Declaration (Loc,
8197 Defining_Identifier => Component,
8198 Component_Definition =>
8199 Make_Component_Definition (Loc,
8200 Aliased_Present => False,
8201 Subtype_Indication => New_Reference_To (Ctype, Loc))));
8203 Next_Formal_With_Extras (Formal);
8204 end loop;
8206 -- Create the Entry_Parameter_Record declaration
8208 Rec_Ent := Make_Temporary (Loc, 'P');
8210 Decl :=
8211 Make_Full_Type_Declaration (Loc,
8212 Defining_Identifier => Rec_Ent,
8213 Type_Definition =>
8214 Make_Record_Definition (Loc,
8215 Component_List =>
8216 Make_Component_List (Loc,
8217 Component_Items => Components)));
8219 Insert_After (Last_Decl, Decl);
8220 Last_Decl := Decl;
8222 -- Construct and link in the corresponding access type
8224 Acc_Ent := Make_Temporary (Loc, 'A');
8226 Set_Entry_Parameters_Type (Entry_Ent, Acc_Ent);
8228 Decl :=
8229 Make_Full_Type_Declaration (Loc,
8230 Defining_Identifier => Acc_Ent,
8231 Type_Definition =>
8232 Make_Access_To_Object_Definition (Loc,
8233 All_Present => True,
8234 Subtype_Indication => New_Reference_To (Rec_Ent, Loc)));
8236 Insert_After (Last_Decl, Decl);
8237 end if;
8238 end Expand_N_Entry_Declaration;
8240 -----------------------------
8241 -- Expand_N_Protected_Body --
8242 -----------------------------
8244 -- Protected bodies are expanded to the completion of the subprograms
8245 -- created for the corresponding protected type. These are a protected and
8246 -- unprotected version of each protected subprogram in the object, a
8247 -- function to calculate each entry barrier, and a procedure to execute the
8248 -- sequence of statements of each protected entry body. For example, for
8249 -- protected type ptype:
8251 -- function entB
8252 -- (O : System.Address;
8253 -- E : Protected_Entry_Index)
8254 -- return Boolean
8255 -- is
8256 -- <discriminant renamings>
8257 -- <private object renamings>
8258 -- begin
8259 -- return <barrier expression>;
8260 -- end entB;
8262 -- procedure pprocN (_object : in out poV;...) is
8263 -- <discriminant renamings>
8264 -- <private object renamings>
8265 -- begin
8266 -- <sequence of statements>
8267 -- end pprocN;
8269 -- procedure pprocP (_object : in out poV;...) is
8270 -- procedure _clean is
8271 -- Pn : Boolean;
8272 -- begin
8273 -- ptypeS (_object, Pn);
8274 -- Unlock (_object._object'Access);
8275 -- Abort_Undefer.all;
8276 -- end _clean;
8278 -- begin
8279 -- Abort_Defer.all;
8280 -- Lock (_object._object'Access);
8281 -- pprocN (_object;...);
8282 -- at end
8283 -- _clean;
8284 -- end pproc;
8286 -- function pfuncN (_object : poV;...) return Return_Type is
8287 -- <discriminant renamings>
8288 -- <private object renamings>
8289 -- begin
8290 -- <sequence of statements>
8291 -- end pfuncN;
8293 -- function pfuncP (_object : poV) return Return_Type is
8294 -- procedure _clean is
8295 -- begin
8296 -- Unlock (_object._object'Access);
8297 -- Abort_Undefer.all;
8298 -- end _clean;
8300 -- begin
8301 -- Abort_Defer.all;
8302 -- Lock (_object._object'Access);
8303 -- return pfuncN (_object);
8305 -- at end
8306 -- _clean;
8307 -- end pfunc;
8309 -- procedure entE
8310 -- (O : System.Address;
8311 -- P : System.Address;
8312 -- E : Protected_Entry_Index)
8313 -- is
8314 -- <discriminant renamings>
8315 -- <private object renamings>
8316 -- type poVP is access poV;
8317 -- _Object : ptVP := ptVP!(O);
8319 -- begin
8320 -- begin
8321 -- <statement sequence>
8322 -- Complete_Entry_Body (_Object._Object);
8323 -- exception
8324 -- when all others =>
8325 -- Exceptional_Complete_Entry_Body (
8326 -- _Object._Object, Get_GNAT_Exception);
8327 -- end;
8328 -- end entE;
8330 -- The type poV is the record created for the protected type to hold
8331 -- the state of the protected object.
8333 procedure Expand_N_Protected_Body (N : Node_Id) is
8334 Loc : constant Source_Ptr := Sloc (N);
8335 Pid : constant Entity_Id := Corresponding_Spec (N);
8337 Lock_Free_Active : constant Boolean := Uses_Lock_Free (Pid);
8338 -- This flag indicates whether the lock free implementation is active
8340 Current_Node : Node_Id;
8341 Disp_Op_Body : Node_Id;
8342 New_Op_Body : Node_Id;
8343 Num_Entries : Natural := 0;
8344 Op_Body : Node_Id;
8345 Op_Id : Entity_Id;
8347 function Build_Dispatching_Subprogram_Body
8348 (N : Node_Id;
8349 Pid : Node_Id;
8350 Prot_Bod : Node_Id) return Node_Id;
8351 -- Build a dispatching version of the protected subprogram body. The
8352 -- newly generated subprogram contains a call to the original protected
8353 -- body. The following code is generated:
8355 -- function <protected-function-name> (Param1 .. ParamN) return
8356 -- <return-type> is
8357 -- begin
8358 -- return <protected-function-name>P (Param1 .. ParamN);
8359 -- end <protected-function-name>;
8361 -- or
8363 -- procedure <protected-procedure-name> (Param1 .. ParamN) is
8364 -- begin
8365 -- <protected-procedure-name>P (Param1 .. ParamN);
8366 -- end <protected-procedure-name>
8368 ---------------------------------------
8369 -- Build_Dispatching_Subprogram_Body --
8370 ---------------------------------------
8372 function Build_Dispatching_Subprogram_Body
8373 (N : Node_Id;
8374 Pid : Node_Id;
8375 Prot_Bod : Node_Id) return Node_Id
8377 Loc : constant Source_Ptr := Sloc (N);
8378 Actuals : List_Id;
8379 Formal : Node_Id;
8380 Spec : Node_Id;
8381 Stmts : List_Id;
8383 begin
8384 -- Generate a specification without a letter suffix in order to
8385 -- override an interface function or procedure.
8387 Spec := Build_Protected_Sub_Specification (N, Pid, Dispatching_Mode);
8389 -- The formal parameters become the actuals of the protected function
8390 -- or procedure call.
8392 Actuals := New_List;
8393 Formal := First (Parameter_Specifications (Spec));
8394 while Present (Formal) loop
8395 Append_To (Actuals,
8396 Make_Identifier (Loc, Chars (Defining_Identifier (Formal))));
8397 Next (Formal);
8398 end loop;
8400 if Nkind (Spec) = N_Procedure_Specification then
8401 Stmts :=
8402 New_List (
8403 Make_Procedure_Call_Statement (Loc,
8404 Name =>
8405 New_Reference_To (Corresponding_Spec (Prot_Bod), Loc),
8406 Parameter_Associations => Actuals));
8408 else
8409 pragma Assert (Nkind (Spec) = N_Function_Specification);
8411 Stmts :=
8412 New_List (
8413 Make_Simple_Return_Statement (Loc,
8414 Expression =>
8415 Make_Function_Call (Loc,
8416 Name =>
8417 New_Reference_To (Corresponding_Spec (Prot_Bod), Loc),
8418 Parameter_Associations => Actuals)));
8419 end if;
8421 return
8422 Make_Subprogram_Body (Loc,
8423 Declarations => Empty_List,
8424 Specification => Spec,
8425 Handled_Statement_Sequence =>
8426 Make_Handled_Sequence_Of_Statements (Loc, Stmts));
8427 end Build_Dispatching_Subprogram_Body;
8429 -- Start of processing for Expand_N_Protected_Body
8431 begin
8432 if No_Run_Time_Mode then
8433 Error_Msg_CRT ("protected body", N);
8434 return;
8435 end if;
8437 -- This is the proper body corresponding to a stub. The declarations
8438 -- must be inserted at the point of the stub, which in turn is in the
8439 -- declarative part of the parent unit.
8441 if Nkind (Parent (N)) = N_Subunit then
8442 Current_Node := Corresponding_Stub (Parent (N));
8443 else
8444 Current_Node := N;
8445 end if;
8447 Op_Body := First (Declarations (N));
8449 -- The protected body is replaced with the bodies of its
8450 -- protected operations, and the declarations for internal objects
8451 -- that may have been created for entry family bounds.
8453 Rewrite (N, Make_Null_Statement (Sloc (N)));
8454 Analyze (N);
8456 while Present (Op_Body) loop
8457 case Nkind (Op_Body) is
8458 when N_Subprogram_Declaration =>
8459 null;
8461 when N_Subprogram_Body =>
8463 -- Do not create bodies for eliminated operations
8465 if not Is_Eliminated (Defining_Entity (Op_Body))
8466 and then not Is_Eliminated (Corresponding_Spec (Op_Body))
8467 then
8468 if Lock_Free_Active then
8469 New_Op_Body :=
8470 Build_Lock_Free_Unprotected_Subprogram_Body
8471 (Op_Body, Pid);
8472 else
8473 New_Op_Body :=
8474 Build_Unprotected_Subprogram_Body (Op_Body, Pid);
8475 end if;
8477 Insert_After (Current_Node, New_Op_Body);
8478 Current_Node := New_Op_Body;
8479 Analyze (New_Op_Body);
8481 -- Build the corresponding protected operation. It may
8482 -- appear that this is needed only if this is a visible
8483 -- operation of the type, or if it is an interrupt handler,
8484 -- and this was the strategy used previously in GNAT.
8486 -- However, the operation may be exported through a 'Access
8487 -- to an external caller. This is the common idiom in code
8488 -- that uses the Ada 2005 Timing_Events package. As a result
8489 -- we need to produce the protected body for both visible
8490 -- and private operations, as well as operations that only
8491 -- have a body in the source, and for which we create a
8492 -- declaration in the protected body itself.
8494 if Present (Corresponding_Spec (Op_Body)) then
8495 if Lock_Free_Active then
8496 New_Op_Body :=
8497 Build_Lock_Free_Protected_Subprogram_Body
8498 (Op_Body, Pid, Specification (New_Op_Body));
8499 else
8500 New_Op_Body :=
8501 Build_Protected_Subprogram_Body
8502 (Op_Body, Pid, Specification (New_Op_Body));
8503 end if;
8505 Insert_After (Current_Node, New_Op_Body);
8506 Analyze (New_Op_Body);
8508 Current_Node := New_Op_Body;
8510 -- Generate an overriding primitive operation body for
8511 -- this subprogram if the protected type implements an
8512 -- interface.
8514 if Ada_Version >= Ada_2005
8515 and then
8516 Present (Interfaces (Corresponding_Record_Type (Pid)))
8517 then
8518 Disp_Op_Body :=
8519 Build_Dispatching_Subprogram_Body
8520 (Op_Body, Pid, New_Op_Body);
8522 Insert_After (Current_Node, Disp_Op_Body);
8523 Analyze (Disp_Op_Body);
8525 Current_Node := Disp_Op_Body;
8526 end if;
8527 end if;
8528 end if;
8530 when N_Entry_Body =>
8531 Op_Id := Defining_Identifier (Op_Body);
8532 Num_Entries := Num_Entries + 1;
8534 New_Op_Body := Build_Protected_Entry (Op_Body, Op_Id, Pid);
8536 Insert_After (Current_Node, New_Op_Body);
8537 Current_Node := New_Op_Body;
8538 Analyze (New_Op_Body);
8540 when N_Implicit_Label_Declaration =>
8541 null;
8543 when N_Itype_Reference =>
8544 Insert_After (Current_Node, New_Copy (Op_Body));
8546 when N_Freeze_Entity =>
8547 New_Op_Body := New_Copy (Op_Body);
8549 if Present (Entity (Op_Body))
8550 and then Freeze_Node (Entity (Op_Body)) = Op_Body
8551 then
8552 Set_Freeze_Node (Entity (Op_Body), New_Op_Body);
8553 end if;
8555 Insert_After (Current_Node, New_Op_Body);
8556 Current_Node := New_Op_Body;
8557 Analyze (New_Op_Body);
8559 when N_Pragma =>
8560 New_Op_Body := New_Copy (Op_Body);
8561 Insert_After (Current_Node, New_Op_Body);
8562 Current_Node := New_Op_Body;
8563 Analyze (New_Op_Body);
8565 when N_Object_Declaration =>
8566 pragma Assert (not Comes_From_Source (Op_Body));
8567 New_Op_Body := New_Copy (Op_Body);
8568 Insert_After (Current_Node, New_Op_Body);
8569 Current_Node := New_Op_Body;
8570 Analyze (New_Op_Body);
8572 when others =>
8573 raise Program_Error;
8575 end case;
8577 Next (Op_Body);
8578 end loop;
8580 -- Finally, create the body of the function that maps an entry index
8581 -- into the corresponding body index, except when there is no entry, or
8582 -- in a Ravenscar-like profile.
8584 if Corresponding_Runtime_Package (Pid) =
8585 System_Tasking_Protected_Objects_Entries
8586 then
8587 New_Op_Body := Build_Find_Body_Index (Pid);
8588 Insert_After (Current_Node, New_Op_Body);
8589 Current_Node := New_Op_Body;
8590 Analyze (New_Op_Body);
8591 end if;
8593 -- Ada 2005 (AI-345): Construct the primitive wrapper bodies after the
8594 -- protected body. At this point all wrapper specs have been created,
8595 -- frozen and included in the dispatch table for the protected type.
8597 if Ada_Version >= Ada_2005 then
8598 Build_Wrapper_Bodies (Loc, Pid, Current_Node);
8599 end if;
8600 end Expand_N_Protected_Body;
8602 -----------------------------------------
8603 -- Expand_N_Protected_Type_Declaration --
8604 -----------------------------------------
8606 -- First we create a corresponding record type declaration used to
8607 -- represent values of this protected type.
8608 -- The general form of this type declaration is
8610 -- type poV (discriminants) is record
8611 -- _Object : aliased <kind>Protection
8612 -- [(<entry count> [, <handler count>])];
8613 -- [entry_family : array (bounds) of Void;]
8614 -- <private data fields>
8615 -- end record;
8617 -- The discriminants are present only if the corresponding protected type
8618 -- has discriminants, and they exactly mirror the protected type
8619 -- discriminants. The private data fields similarly mirror the private
8620 -- declarations of the protected type.
8622 -- The Object field is always present. It contains RTS specific data used
8623 -- to control the protected object. It is declared as Aliased so that it
8624 -- can be passed as a pointer to the RTS. This allows the protected record
8625 -- to be referenced within RTS data structures. An appropriate Protection
8626 -- type and discriminant are generated.
8628 -- The Service field is present for protected objects with entries. It
8629 -- contains sufficient information to allow the entry service procedure for
8630 -- this object to be called when the object is not known till runtime.
8632 -- One entry_family component is present for each entry family in the
8633 -- task definition (see Expand_N_Task_Type_Declaration).
8635 -- When a protected object is declared, an instance of the protected type
8636 -- value record is created. The elaboration of this declaration creates the
8637 -- correct bounds for the entry families, and also evaluates the priority
8638 -- expression if needed. The initialization routine for the protected type
8639 -- itself then calls Initialize_Protection with appropriate parameters to
8640 -- initialize the value of the Task_Id field. Install_Handlers may be also
8641 -- called if a pragma Attach_Handler applies.
8643 -- Note: this record is passed to the subprograms created by the expansion
8644 -- of protected subprograms and entries. It is an in parameter to protected
8645 -- functions and an in out parameter to procedures and entry bodies. The
8646 -- Entity_Id for this created record type is placed in the
8647 -- Corresponding_Record_Type field of the associated protected type entity.
8649 -- Next we create a procedure specifications for protected subprograms and
8650 -- entry bodies. For each protected subprograms two subprograms are
8651 -- created, an unprotected and a protected version. The unprotected version
8652 -- is called from within other operations of the same protected object.
8654 -- We also build the call to register the procedure if a pragma
8655 -- Interrupt_Handler applies.
8657 -- A single subprogram is created to service all entry bodies; it has an
8658 -- additional boolean out parameter indicating that the previous entry call
8659 -- made by the current task was serviced immediately, i.e. not by proxy.
8660 -- The O parameter contains a pointer to a record object of the type
8661 -- described above. An untyped interface is used here to allow this
8662 -- procedure to be called in places where the type of the object to be
8663 -- serviced is not known. This must be done, for example, when a call that
8664 -- may have been requeued is cancelled; the corresponding object must be
8665 -- serviced, but which object that is not known till runtime.
8667 -- procedure ptypeS
8668 -- (O : System.Address; P : out Boolean);
8669 -- procedure pprocN (_object : in out poV);
8670 -- procedure pproc (_object : in out poV);
8671 -- function pfuncN (_object : poV);
8672 -- function pfunc (_object : poV);
8673 -- ...
8675 -- Note that this must come after the record type declaration, since
8676 -- the specs refer to this type.
8678 procedure Expand_N_Protected_Type_Declaration (N : Node_Id) is
8679 Loc : constant Source_Ptr := Sloc (N);
8680 Prot_Typ : constant Entity_Id := Defining_Identifier (N);
8682 Lock_Free_Active : constant Boolean := Uses_Lock_Free (Prot_Typ);
8683 -- This flag indicates whether the lock free implementation is active
8685 Pdef : constant Node_Id := Protected_Definition (N);
8686 -- This contains two lists; one for visible and one for private decls
8688 Rec_Decl : Node_Id;
8689 Cdecls : List_Id;
8690 Discr_Map : constant Elist_Id := New_Elmt_List;
8691 Priv : Node_Id;
8692 New_Priv : Node_Id;
8693 Comp : Node_Id;
8694 Comp_Id : Entity_Id;
8695 Sub : Node_Id;
8696 Current_Node : Node_Id := N;
8697 Bdef : Entity_Id := Empty; -- avoid uninit warning
8698 Edef : Entity_Id := Empty; -- avoid uninit warning
8699 Entries_Aggr : Node_Id;
8700 Body_Id : Entity_Id;
8701 Body_Arr : Node_Id;
8702 E_Count : Int;
8703 Object_Comp : Node_Id;
8705 procedure Check_Inlining (Subp : Entity_Id);
8706 -- If the original operation has a pragma Inline, propagate the flag
8707 -- to the internal body, for possible inlining later on. The source
8708 -- operation is invisible to the back-end and is never actually called.
8710 function Static_Component_Size (Comp : Entity_Id) return Boolean;
8711 -- When compiling under the Ravenscar profile, private components must
8712 -- have a static size, or else a protected object will require heap
8713 -- allocation, violating the corresponding restriction. It is preferable
8714 -- to make this check here, because it provides a better error message
8715 -- than the back-end, which refers to the object as a whole.
8717 procedure Register_Handler;
8718 -- For a protected operation that is an interrupt handler, add the
8719 -- freeze action that will register it as such.
8721 --------------------
8722 -- Check_Inlining --
8723 --------------------
8725 procedure Check_Inlining (Subp : Entity_Id) is
8726 begin
8727 if Is_Inlined (Subp) then
8728 Set_Is_Inlined (Protected_Body_Subprogram (Subp));
8729 Set_Is_Inlined (Subp, False);
8730 end if;
8731 end Check_Inlining;
8733 ---------------------------------
8734 -- Check_Static_Component_Size --
8735 ---------------------------------
8737 function Static_Component_Size (Comp : Entity_Id) return Boolean is
8738 Typ : constant Entity_Id := Etype (Comp);
8739 C : Entity_Id;
8741 begin
8742 if Is_Scalar_Type (Typ) then
8743 return True;
8745 elsif Is_Array_Type (Typ) then
8746 return Compile_Time_Known_Bounds (Typ);
8748 elsif Is_Record_Type (Typ) then
8749 C := First_Component (Typ);
8750 while Present (C) loop
8751 if not Static_Component_Size (C) then
8752 return False;
8753 end if;
8755 Next_Component (C);
8756 end loop;
8758 return True;
8760 -- Any other type will be checked by the back-end
8762 else
8763 return True;
8764 end if;
8765 end Static_Component_Size;
8767 ----------------------
8768 -- Register_Handler --
8769 ----------------------
8771 procedure Register_Handler is
8773 -- All semantic checks already done in Sem_Prag
8775 Prot_Proc : constant Entity_Id :=
8776 Defining_Unit_Name (Specification (Current_Node));
8778 Proc_Address : constant Node_Id :=
8779 Make_Attribute_Reference (Loc,
8780 Prefix =>
8781 New_Reference_To (Prot_Proc, Loc),
8782 Attribute_Name => Name_Address);
8784 RTS_Call : constant Entity_Id :=
8785 Make_Procedure_Call_Statement (Loc,
8786 Name =>
8787 New_Reference_To
8788 (RTE (RE_Register_Interrupt_Handler), Loc),
8789 Parameter_Associations => New_List (Proc_Address));
8790 begin
8791 Append_Freeze_Action (Prot_Proc, RTS_Call);
8792 end Register_Handler;
8794 -- Start of processing for Expand_N_Protected_Type_Declaration
8796 begin
8797 if Present (Corresponding_Record_Type (Prot_Typ)) then
8798 return;
8799 else
8800 Rec_Decl := Build_Corresponding_Record (N, Prot_Typ, Loc);
8801 end if;
8803 Cdecls := Component_Items (Component_List (Type_Definition (Rec_Decl)));
8805 Qualify_Entity_Names (N);
8807 -- If the type has discriminants, their occurrences in the declaration
8808 -- have been replaced by the corresponding discriminals. For components
8809 -- that are constrained by discriminants, their homologues in the
8810 -- corresponding record type must refer to the discriminants of that
8811 -- record, so we must apply a new renaming to subtypes_indications:
8813 -- protected discriminant => discriminal => record discriminant
8815 -- This replacement is not applied to default expressions, for which
8816 -- the discriminal is correct.
8818 if Has_Discriminants (Prot_Typ) then
8819 declare
8820 Disc : Entity_Id;
8821 Decl : Node_Id;
8823 begin
8824 Disc := First_Discriminant (Prot_Typ);
8825 Decl := First (Discriminant_Specifications (Rec_Decl));
8826 while Present (Disc) loop
8827 Append_Elmt (Discriminal (Disc), Discr_Map);
8828 Append_Elmt (Defining_Identifier (Decl), Discr_Map);
8829 Next_Discriminant (Disc);
8830 Next (Decl);
8831 end loop;
8832 end;
8833 end if;
8835 -- Fill in the component declarations
8837 -- Add components for entry families. For each entry family, create an
8838 -- anonymous type declaration with the same size, and analyze the type.
8840 Collect_Entry_Families (Loc, Cdecls, Current_Node, Prot_Typ);
8842 pragma Assert (Present (Pdef));
8844 -- Add private field components
8846 if Present (Private_Declarations (Pdef)) then
8847 Priv := First (Private_Declarations (Pdef));
8848 while Present (Priv) loop
8849 if Nkind (Priv) = N_Component_Declaration then
8850 if not Static_Component_Size (Defining_Identifier (Priv)) then
8852 -- When compiling for a restricted profile, the private
8853 -- components must have a static size. If not, this is an
8854 -- error for a single protected declaration, and rates a
8855 -- warning on a protected type declaration.
8857 if not Comes_From_Source (Prot_Typ) then
8858 Check_Restriction (No_Implicit_Heap_Allocations, Priv);
8860 elsif Restriction_Active (No_Implicit_Heap_Allocations) then
8861 Error_Msg_N ("component has non-static size??", Priv);
8862 Error_Msg_NE
8863 ("\creation of protected object of type& will violate"
8864 & " restriction No_Implicit_Heap_Allocations??",
8865 Priv, Prot_Typ);
8866 end if;
8867 end if;
8869 -- The component definition consists of a subtype indication,
8870 -- or (in Ada 2005) an access definition. Make a copy of the
8871 -- proper definition.
8873 declare
8874 Old_Comp : constant Node_Id := Component_Definition (Priv);
8875 Oent : constant Entity_Id := Defining_Identifier (Priv);
8876 New_Comp : Node_Id;
8877 Nent : constant Entity_Id :=
8878 Make_Defining_Identifier (Sloc (Oent),
8879 Chars => Chars (Oent));
8881 begin
8882 if Present (Subtype_Indication (Old_Comp)) then
8883 New_Comp :=
8884 Make_Component_Definition (Sloc (Oent),
8885 Aliased_Present => False,
8886 Subtype_Indication =>
8887 New_Copy_Tree (Subtype_Indication (Old_Comp),
8888 Discr_Map));
8889 else
8890 New_Comp :=
8891 Make_Component_Definition (Sloc (Oent),
8892 Aliased_Present => False,
8893 Access_Definition =>
8894 New_Copy_Tree (Access_Definition (Old_Comp),
8895 Discr_Map));
8896 end if;
8898 New_Priv :=
8899 Make_Component_Declaration (Loc,
8900 Defining_Identifier => Nent,
8901 Component_Definition => New_Comp,
8902 Expression => Expression (Priv));
8904 Set_Has_Per_Object_Constraint (Nent,
8905 Has_Per_Object_Constraint (Oent));
8907 Append_To (Cdecls, New_Priv);
8908 end;
8910 elsif Nkind (Priv) = N_Subprogram_Declaration then
8912 -- Make the unprotected version of the subprogram available
8913 -- for expansion of intra object calls. There is need for
8914 -- a protected version only if the subprogram is an interrupt
8915 -- handler, otherwise this operation can only be called from
8916 -- within the body.
8918 Sub :=
8919 Make_Subprogram_Declaration (Loc,
8920 Specification =>
8921 Build_Protected_Sub_Specification
8922 (Priv, Prot_Typ, Unprotected_Mode));
8924 Insert_After (Current_Node, Sub);
8925 Analyze (Sub);
8927 Set_Protected_Body_Subprogram
8928 (Defining_Unit_Name (Specification (Priv)),
8929 Defining_Unit_Name (Specification (Sub)));
8930 Check_Inlining (Defining_Unit_Name (Specification (Priv)));
8931 Current_Node := Sub;
8933 Sub :=
8934 Make_Subprogram_Declaration (Loc,
8935 Specification =>
8936 Build_Protected_Sub_Specification
8937 (Priv, Prot_Typ, Protected_Mode));
8939 Insert_After (Current_Node, Sub);
8940 Analyze (Sub);
8941 Current_Node := Sub;
8943 if Is_Interrupt_Handler
8944 (Defining_Unit_Name (Specification (Priv)))
8945 then
8946 if not Restricted_Profile then
8947 Register_Handler;
8948 end if;
8949 end if;
8950 end if;
8952 Next (Priv);
8953 end loop;
8954 end if;
8956 -- Except for the lock-free implementation, prepend the _Object field
8957 -- with the right type to the component list. We need to compute the
8958 -- number of entries, and in some cases the number of Attach_Handler
8959 -- pragmas.
8961 if not Lock_Free_Active then
8962 declare
8963 Ritem : Node_Id;
8964 Num_Attach_Handler : Int := 0;
8965 Protection_Subtype : Node_Id;
8966 Entry_Count_Expr : constant Node_Id :=
8967 Build_Entry_Count_Expression
8968 (Prot_Typ, Cdecls, Loc);
8970 begin
8971 -- Could this be simplified using Corresponding_Runtime_Package???
8973 if Has_Attach_Handler (Prot_Typ) then
8974 Ritem := First_Rep_Item (Prot_Typ);
8975 while Present (Ritem) loop
8976 if Nkind (Ritem) = N_Pragma
8977 and then Pragma_Name (Ritem) = Name_Attach_Handler
8978 then
8979 Num_Attach_Handler := Num_Attach_Handler + 1;
8980 end if;
8982 Next_Rep_Item (Ritem);
8983 end loop;
8985 if Restricted_Profile then
8986 if Has_Entries (Prot_Typ) then
8987 Protection_Subtype :=
8988 New_Reference_To (RTE (RE_Protection_Entry), Loc);
8989 else
8990 Protection_Subtype :=
8991 New_Reference_To (RTE (RE_Protection), Loc);
8992 end if;
8994 else
8995 Protection_Subtype :=
8996 Make_Subtype_Indication (Loc,
8997 Subtype_Mark =>
8998 New_Reference_To
8999 (RTE (RE_Static_Interrupt_Protection), Loc),
9000 Constraint =>
9001 Make_Index_Or_Discriminant_Constraint (Loc,
9002 Constraints => New_List (
9003 Entry_Count_Expr,
9004 Make_Integer_Literal (Loc, Num_Attach_Handler))));
9005 end if;
9007 elsif Has_Interrupt_Handler (Prot_Typ)
9008 and then not Restriction_Active (No_Dynamic_Attachment)
9009 then
9010 Protection_Subtype :=
9011 Make_Subtype_Indication (Loc,
9012 Subtype_Mark =>
9013 New_Reference_To
9014 (RTE (RE_Dynamic_Interrupt_Protection), Loc),
9015 Constraint =>
9016 Make_Index_Or_Discriminant_Constraint (Loc,
9017 Constraints => New_List (Entry_Count_Expr)));
9019 -- Type has explicit entries or generated primitive entry wrappers
9021 elsif Has_Entries (Prot_Typ)
9022 or else (Ada_Version >= Ada_2005
9023 and then Present (Interface_List (N)))
9024 then
9025 case Corresponding_Runtime_Package (Prot_Typ) is
9026 when System_Tasking_Protected_Objects_Entries =>
9027 Protection_Subtype :=
9028 Make_Subtype_Indication (Loc,
9029 Subtype_Mark =>
9030 New_Reference_To
9031 (RTE (RE_Protection_Entries), Loc),
9032 Constraint =>
9033 Make_Index_Or_Discriminant_Constraint (Loc,
9034 Constraints => New_List (Entry_Count_Expr)));
9036 when System_Tasking_Protected_Objects_Single_Entry =>
9037 Protection_Subtype :=
9038 New_Reference_To (RTE (RE_Protection_Entry), Loc);
9040 when others =>
9041 raise Program_Error;
9042 end case;
9044 else
9045 Protection_Subtype :=
9046 New_Reference_To (RTE (RE_Protection), Loc);
9047 end if;
9049 Object_Comp :=
9050 Make_Component_Declaration (Loc,
9051 Defining_Identifier =>
9052 Make_Defining_Identifier (Loc, Name_uObject),
9053 Component_Definition =>
9054 Make_Component_Definition (Loc,
9055 Aliased_Present => True,
9056 Subtype_Indication => Protection_Subtype));
9057 end;
9059 -- Put the _Object component after the private component so that it
9060 -- be finalized early as required by 9.4 (20)
9062 Append_To (Cdecls, Object_Comp);
9063 end if;
9065 Insert_After (Current_Node, Rec_Decl);
9066 Current_Node := Rec_Decl;
9068 -- Analyze the record declaration immediately after construction,
9069 -- because the initialization procedure is needed for single object
9070 -- declarations before the next entity is analyzed (the freeze call
9071 -- that generates this initialization procedure is found below).
9073 Analyze (Rec_Decl, Suppress => All_Checks);
9075 -- Ada 2005 (AI-345): Construct the primitive entry wrappers before
9076 -- the corresponding record is frozen. If any wrappers are generated,
9077 -- Current_Node is updated accordingly.
9079 if Ada_Version >= Ada_2005 then
9080 Build_Wrapper_Specs (Loc, Prot_Typ, Current_Node);
9081 end if;
9083 -- Collect pointers to entry bodies and their barriers, to be placed
9084 -- in the Entry_Bodies_Array for the type. For each entry/family we
9085 -- add an expression to the aggregate which is the initial value of
9086 -- this array. The array is declared after all protected subprograms.
9088 if Has_Entries (Prot_Typ) then
9089 Entries_Aggr := Make_Aggregate (Loc, Expressions => New_List);
9090 else
9091 Entries_Aggr := Empty;
9092 end if;
9094 -- Build two new procedure specifications for each protected subprogram;
9095 -- one to call from outside the object and one to call from inside.
9096 -- Build a barrier function and an entry body action procedure
9097 -- specification for each protected entry. Initialize the entry body
9098 -- array. If subprogram is flagged as eliminated, do not generate any
9099 -- internal operations.
9101 E_Count := 0;
9102 Comp := First (Visible_Declarations (Pdef));
9103 while Present (Comp) loop
9104 if Nkind (Comp) = N_Subprogram_Declaration then
9105 Sub :=
9106 Make_Subprogram_Declaration (Loc,
9107 Specification =>
9108 Build_Protected_Sub_Specification
9109 (Comp, Prot_Typ, Unprotected_Mode));
9111 Insert_After (Current_Node, Sub);
9112 Analyze (Sub);
9114 Set_Protected_Body_Subprogram
9115 (Defining_Unit_Name (Specification (Comp)),
9116 Defining_Unit_Name (Specification (Sub)));
9117 Check_Inlining (Defining_Unit_Name (Specification (Comp)));
9119 -- Make the protected version of the subprogram available for
9120 -- expansion of external calls.
9122 Current_Node := Sub;
9124 Sub :=
9125 Make_Subprogram_Declaration (Loc,
9126 Specification =>
9127 Build_Protected_Sub_Specification
9128 (Comp, Prot_Typ, Protected_Mode));
9130 Insert_After (Current_Node, Sub);
9131 Analyze (Sub);
9133 Current_Node := Sub;
9135 -- Generate an overriding primitive operation specification for
9136 -- this subprogram if the protected type implements an interface.
9138 if Ada_Version >= Ada_2005
9139 and then
9140 Present (Interfaces (Corresponding_Record_Type (Prot_Typ)))
9141 then
9142 Sub :=
9143 Make_Subprogram_Declaration (Loc,
9144 Specification =>
9145 Build_Protected_Sub_Specification
9146 (Comp, Prot_Typ, Dispatching_Mode));
9148 Insert_After (Current_Node, Sub);
9149 Analyze (Sub);
9151 Current_Node := Sub;
9152 end if;
9154 -- If a pragma Interrupt_Handler applies, build and add a call to
9155 -- Register_Interrupt_Handler to the freezing actions of the
9156 -- protected version (Current_Node) of the subprogram:
9158 -- system.interrupts.register_interrupt_handler
9159 -- (prot_procP'address);
9161 if not Restricted_Profile
9162 and then Is_Interrupt_Handler
9163 (Defining_Unit_Name (Specification (Comp)))
9164 then
9165 Register_Handler;
9166 end if;
9168 elsif Nkind (Comp) = N_Entry_Declaration then
9169 E_Count := E_Count + 1;
9170 Comp_Id := Defining_Identifier (Comp);
9172 Edef :=
9173 Make_Defining_Identifier (Loc,
9174 Build_Selected_Name (Prot_Typ, Comp_Id, 'E'));
9175 Sub :=
9176 Make_Subprogram_Declaration (Loc,
9177 Specification =>
9178 Build_Protected_Entry_Specification (Loc, Edef, Comp_Id));
9180 Insert_After (Current_Node, Sub);
9181 Analyze (Sub);
9183 -- Build wrapper procedure for pre/postconditions
9185 Build_PPC_Wrapper (Comp_Id, N);
9187 Set_Protected_Body_Subprogram
9188 (Defining_Identifier (Comp),
9189 Defining_Unit_Name (Specification (Sub)));
9191 Current_Node := Sub;
9193 Bdef :=
9194 Make_Defining_Identifier (Loc,
9195 Chars => Build_Selected_Name (Prot_Typ, Comp_Id, 'B'));
9196 Sub :=
9197 Make_Subprogram_Declaration (Loc,
9198 Specification =>
9199 Build_Barrier_Function_Specification (Loc, Bdef));
9201 Insert_After (Current_Node, Sub);
9202 Analyze (Sub);
9203 Set_Protected_Body_Subprogram (Bdef, Bdef);
9204 Set_Barrier_Function (Comp_Id, Bdef);
9205 Set_Scope (Bdef, Scope (Comp_Id));
9206 Current_Node := Sub;
9208 -- Collect pointers to the protected subprogram and the barrier
9209 -- of the current entry, for insertion into Entry_Bodies_Array.
9211 Append_To (Expressions (Entries_Aggr),
9212 Make_Aggregate (Loc,
9213 Expressions => New_List (
9214 Make_Attribute_Reference (Loc,
9215 Prefix => New_Reference_To (Bdef, Loc),
9216 Attribute_Name => Name_Unrestricted_Access),
9217 Make_Attribute_Reference (Loc,
9218 Prefix => New_Reference_To (Edef, Loc),
9219 Attribute_Name => Name_Unrestricted_Access))));
9220 end if;
9222 Next (Comp);
9223 end loop;
9225 -- If there are some private entry declarations, expand it as if they
9226 -- were visible entries.
9228 if Present (Private_Declarations (Pdef)) then
9229 Comp := First (Private_Declarations (Pdef));
9230 while Present (Comp) loop
9231 if Nkind (Comp) = N_Entry_Declaration then
9232 E_Count := E_Count + 1;
9233 Comp_Id := Defining_Identifier (Comp);
9235 Edef :=
9236 Make_Defining_Identifier (Loc,
9237 Build_Selected_Name (Prot_Typ, Comp_Id, 'E'));
9238 Sub :=
9239 Make_Subprogram_Declaration (Loc,
9240 Specification =>
9241 Build_Protected_Entry_Specification (Loc, Edef, Comp_Id));
9243 Insert_After (Current_Node, Sub);
9244 Analyze (Sub);
9246 Set_Protected_Body_Subprogram
9247 (Defining_Identifier (Comp),
9248 Defining_Unit_Name (Specification (Sub)));
9250 Current_Node := Sub;
9252 Bdef :=
9253 Make_Defining_Identifier (Loc,
9254 Chars => Build_Selected_Name (Prot_Typ, Comp_Id, 'E'));
9256 Sub :=
9257 Make_Subprogram_Declaration (Loc,
9258 Specification =>
9259 Build_Barrier_Function_Specification (Loc, Bdef));
9261 Insert_After (Current_Node, Sub);
9262 Analyze (Sub);
9263 Set_Protected_Body_Subprogram (Bdef, Bdef);
9264 Set_Barrier_Function (Comp_Id, Bdef);
9265 Set_Scope (Bdef, Scope (Comp_Id));
9266 Current_Node := Sub;
9268 -- Collect pointers to the protected subprogram and the barrier
9269 -- of the current entry, for insertion into Entry_Bodies_Array.
9271 Append_To (Expressions (Entries_Aggr),
9272 Make_Aggregate (Loc,
9273 Expressions => New_List (
9274 Make_Attribute_Reference (Loc,
9275 Prefix => New_Reference_To (Bdef, Loc),
9276 Attribute_Name => Name_Unrestricted_Access),
9277 Make_Attribute_Reference (Loc,
9278 Prefix => New_Reference_To (Edef, Loc),
9279 Attribute_Name => Name_Unrestricted_Access))));
9280 end if;
9282 Next (Comp);
9283 end loop;
9284 end if;
9286 -- Emit declaration for Entry_Bodies_Array, now that the addresses of
9287 -- all protected subprograms have been collected.
9289 if Has_Entries (Prot_Typ) then
9290 Body_Id :=
9291 Make_Defining_Identifier (Sloc (Prot_Typ),
9292 Chars => New_External_Name (Chars (Prot_Typ), 'A'));
9294 case Corresponding_Runtime_Package (Prot_Typ) is
9295 when System_Tasking_Protected_Objects_Entries =>
9296 Body_Arr := Make_Object_Declaration (Loc,
9297 Defining_Identifier => Body_Id,
9298 Aliased_Present => True,
9299 Object_Definition =>
9300 Make_Subtype_Indication (Loc,
9301 Subtype_Mark => New_Reference_To (
9302 RTE (RE_Protected_Entry_Body_Array), Loc),
9303 Constraint =>
9304 Make_Index_Or_Discriminant_Constraint (Loc,
9305 Constraints => New_List (
9306 Make_Range (Loc,
9307 Make_Integer_Literal (Loc, 1),
9308 Make_Integer_Literal (Loc, E_Count))))),
9309 Expression => Entries_Aggr);
9311 when System_Tasking_Protected_Objects_Single_Entry =>
9312 Body_Arr := Make_Object_Declaration (Loc,
9313 Defining_Identifier => Body_Id,
9314 Aliased_Present => True,
9315 Object_Definition => New_Reference_To
9316 (RTE (RE_Entry_Body), Loc),
9317 Expression =>
9318 Make_Aggregate (Loc,
9319 Expressions => New_List (
9320 Make_Attribute_Reference (Loc,
9321 Prefix => New_Reference_To (Bdef, Loc),
9322 Attribute_Name => Name_Unrestricted_Access),
9323 Make_Attribute_Reference (Loc,
9324 Prefix => New_Reference_To (Edef, Loc),
9325 Attribute_Name => Name_Unrestricted_Access))));
9327 when others =>
9328 raise Program_Error;
9329 end case;
9331 -- A pointer to this array will be placed in the corresponding record
9332 -- by its initialization procedure so this needs to be analyzed here.
9334 Insert_After (Current_Node, Body_Arr);
9335 Current_Node := Body_Arr;
9336 Analyze (Body_Arr);
9338 Set_Entry_Bodies_Array (Prot_Typ, Body_Id);
9340 -- Finally, build the function that maps an entry index into the
9341 -- corresponding body. A pointer to this function is placed in each
9342 -- object of the type. Except for a ravenscar-like profile (no abort,
9343 -- no entry queue, 1 entry)
9345 if Corresponding_Runtime_Package (Prot_Typ) =
9346 System_Tasking_Protected_Objects_Entries
9347 then
9348 Sub :=
9349 Make_Subprogram_Declaration (Loc,
9350 Specification => Build_Find_Body_Index_Spec (Prot_Typ));
9351 Insert_After (Current_Node, Sub);
9352 Analyze (Sub);
9353 end if;
9354 end if;
9355 end Expand_N_Protected_Type_Declaration;
9357 --------------------------------
9358 -- Expand_N_Requeue_Statement --
9359 --------------------------------
9361 -- A non-dispatching requeue statement is expanded into one of four GNARLI
9362 -- operations, depending on the source and destination (task or protected
9363 -- object). A dispatching requeue statement is expanded into a call to the
9364 -- predefined primitive _Disp_Requeue. In addition, code is generated to
9365 -- jump around the remainder of processing for the original entry and, if
9366 -- the destination is (different) protected object, to attempt to service
9367 -- it. The following illustrates the various cases:
9369 -- procedure entE
9370 -- (O : System.Address;
9371 -- P : System.Address;
9372 -- E : Protected_Entry_Index)
9373 -- is
9374 -- <discriminant renamings>
9375 -- <private object renamings>
9376 -- type poVP is access poV;
9377 -- _object : ptVP := ptVP!(O);
9379 -- begin
9380 -- begin
9381 -- <start of statement sequence for entry>
9383 -- -- Requeue from one protected entry body to another protected
9384 -- -- entry.
9386 -- Requeue_Protected_Entry (
9387 -- _object._object'Access,
9388 -- new._object'Access,
9389 -- E,
9390 -- Abort_Present);
9391 -- return;
9393 -- <some more of the statement sequence for entry>
9395 -- -- Requeue from an entry body to a task entry
9397 -- Requeue_Protected_To_Task_Entry (
9398 -- New._task_id,
9399 -- E,
9400 -- Abort_Present);
9401 -- return;
9403 -- <rest of statement sequence for entry>
9404 -- Complete_Entry_Body (_object._object);
9406 -- exception
9407 -- when all others =>
9408 -- Exceptional_Complete_Entry_Body (
9409 -- _object._object, Get_GNAT_Exception);
9410 -- end;
9411 -- end entE;
9413 -- Requeue of a task entry call to a task entry
9415 -- Accept_Call (E, Ann);
9416 -- <start of statement sequence for accept statement>
9417 -- Requeue_Task_Entry (New._task_id, E, Abort_Present);
9418 -- goto Lnn;
9419 -- <rest of statement sequence for accept statement>
9420 -- <<Lnn>>
9421 -- Complete_Rendezvous;
9423 -- exception
9424 -- when all others =>
9425 -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
9427 -- Requeue of a task entry call to a protected entry
9429 -- Accept_Call (E, Ann);
9430 -- <start of statement sequence for accept statement>
9431 -- Requeue_Task_To_Protected_Entry (
9432 -- new._object'Access,
9433 -- E,
9434 -- Abort_Present);
9435 -- newS (new, Pnn);
9436 -- goto Lnn;
9437 -- <rest of statement sequence for accept statement>
9438 -- <<Lnn>>
9439 -- Complete_Rendezvous;
9441 -- exception
9442 -- when all others =>
9443 -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
9445 -- Ada 2012 (AI05-0030): Dispatching requeue to an interface primitive
9446 -- marked by pragma Implemented (XXX, By_Entry).
9448 -- The requeue is inside a protected entry:
9450 -- procedure entE
9451 -- (O : System.Address;
9452 -- P : System.Address;
9453 -- E : Protected_Entry_Index)
9454 -- is
9455 -- <discriminant renamings>
9456 -- <private object renamings>
9457 -- type poVP is access poV;
9458 -- _object : ptVP := ptVP!(O);
9460 -- begin
9461 -- begin
9462 -- <start of statement sequence for entry>
9464 -- _Disp_Requeue
9465 -- (<interface class-wide object>,
9466 -- True,
9467 -- _object'Address,
9468 -- Ada.Tags.Get_Offset_Index
9469 -- (Tag (_object),
9470 -- <interface dispatch table index of target entry>),
9471 -- Abort_Present);
9472 -- return;
9474 -- <rest of statement sequence for entry>
9475 -- Complete_Entry_Body (_object._object);
9477 -- exception
9478 -- when all others =>
9479 -- Exceptional_Complete_Entry_Body (
9480 -- _object._object, Get_GNAT_Exception);
9481 -- end;
9482 -- end entE;
9484 -- The requeue is inside a task entry:
9486 -- Accept_Call (E, Ann);
9487 -- <start of statement sequence for accept statement>
9488 -- _Disp_Requeue
9489 -- (<interface class-wide object>,
9490 -- False,
9491 -- null,
9492 -- Ada.Tags.Get_Offset_Index
9493 -- (Tag (_object),
9494 -- <interface dispatch table index of target entrt>),
9495 -- Abort_Present);
9496 -- newS (new, Pnn);
9497 -- goto Lnn;
9498 -- <rest of statement sequence for accept statement>
9499 -- <<Lnn>>
9500 -- Complete_Rendezvous;
9502 -- exception
9503 -- when all others =>
9504 -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
9506 -- Ada 2012 (AI05-0030): Dispatching requeue to an interface primitive
9507 -- marked by pragma Implemented (XXX, By_Protected_Procedure). The requeue
9508 -- statement is replaced by a dispatching call with actual parameters taken
9509 -- from the inner-most accept statement or entry body.
9511 -- Target.Primitive (Param1, ..., ParamN);
9513 -- Ada 2012 (AI05-0030): Dispatching requeue to an interface primitive
9514 -- marked by pragma Implemented (XXX, By_Any | Optional) or not marked
9515 -- at all.
9517 -- declare
9518 -- S : constant Offset_Index :=
9519 -- Get_Offset_Index (Tag (Concval), DT_Position (Ename));
9520 -- C : constant Prim_Op_Kind := Get_Prim_Op_Kind (Tag (Concval), S);
9522 -- begin
9523 -- if C = POK_Protected_Entry
9524 -- or else C = POK_Task_Entry
9525 -- then
9526 -- <statements for dispatching requeue>
9528 -- elsif C = POK_Protected_Procedure then
9529 -- <dispatching call equivalent>
9531 -- else
9532 -- raise Program_Error;
9533 -- end if;
9534 -- end;
9536 procedure Expand_N_Requeue_Statement (N : Node_Id) is
9537 Loc : constant Source_Ptr := Sloc (N);
9538 Conc_Typ : Entity_Id;
9539 Concval : Node_Id;
9540 Ename : Node_Id;
9541 Index : Node_Id;
9542 Old_Typ : Entity_Id;
9544 function Build_Dispatching_Call_Equivalent return Node_Id;
9545 -- Ada 2012 (AI05-0030): N denotes a dispatching requeue statement of
9546 -- the form Concval.Ename. It is statically known that Ename is allowed
9547 -- to be implemented by a protected procedure. Create a dispatching call
9548 -- equivalent of Concval.Ename taking the actual parameters from the
9549 -- inner-most accept statement or entry body.
9551 function Build_Dispatching_Requeue return Node_Id;
9552 -- Ada 2012 (AI05-0030): N denotes a dispatching requeue statement of
9553 -- the form Concval.Ename. It is statically known that Ename is allowed
9554 -- to be implemented by a protected or a task entry. Create a call to
9555 -- primitive _Disp_Requeue which handles the low-level actions.
9557 function Build_Dispatching_Requeue_To_Any return Node_Id;
9558 -- Ada 2012 (AI05-0030): N denotes a dispatching requeue statement of
9559 -- the form Concval.Ename. Ename is either marked by pragma Implemented
9560 -- (XXX, By_Any | Optional) or not marked at all. Create a block which
9561 -- determines at runtime whether Ename denotes an entry or a procedure
9562 -- and perform the appropriate kind of dispatching select.
9564 function Build_Normal_Requeue return Node_Id;
9565 -- N denotes a non-dispatching requeue statement to either a task or a
9566 -- protected entry. Build the appropriate runtime call to perform the
9567 -- action.
9569 function Build_Skip_Statement (Search : Node_Id) return Node_Id;
9570 -- For a protected entry, create a return statement to skip the rest of
9571 -- the entry body. Otherwise, create a goto statement to skip the rest
9572 -- of a task accept statement. The lookup for the enclosing entry body
9573 -- or accept statement starts from Search.
9575 ---------------------------------------
9576 -- Build_Dispatching_Call_Equivalent --
9577 ---------------------------------------
9579 function Build_Dispatching_Call_Equivalent return Node_Id is
9580 Call_Ent : constant Entity_Id := Entity (Ename);
9581 Obj : constant Node_Id := Original_Node (Concval);
9582 Acc_Ent : Node_Id;
9583 Actuals : List_Id;
9584 Formal : Node_Id;
9585 Formals : List_Id;
9587 begin
9588 -- Climb the parent chain looking for the inner-most entry body or
9589 -- accept statement.
9591 Acc_Ent := N;
9592 while Present (Acc_Ent)
9593 and then not Nkind_In (Acc_Ent, N_Accept_Statement,
9594 N_Entry_Body)
9595 loop
9596 Acc_Ent := Parent (Acc_Ent);
9597 end loop;
9599 -- A requeue statement should be housed inside an entry body or an
9600 -- accept statement at some level. If this is not the case, then the
9601 -- tree is malformed.
9603 pragma Assert (Present (Acc_Ent));
9605 -- Recover the list of formal parameters
9607 if Nkind (Acc_Ent) = N_Entry_Body then
9608 Acc_Ent := Entry_Body_Formal_Part (Acc_Ent);
9609 end if;
9611 Formals := Parameter_Specifications (Acc_Ent);
9613 -- Create the actual parameters for the dispatching call. These are
9614 -- simply copies of the entry body or accept statement formals in the
9615 -- same order as they appear.
9617 Actuals := No_List;
9619 if Present (Formals) then
9620 Actuals := New_List;
9621 Formal := First (Formals);
9622 while Present (Formal) loop
9623 Append_To (Actuals,
9624 Make_Identifier (Loc, Chars (Defining_Identifier (Formal))));
9625 Next (Formal);
9626 end loop;
9627 end if;
9629 -- Generate:
9630 -- Obj.Call_Ent (Actuals);
9632 return
9633 Make_Procedure_Call_Statement (Loc,
9634 Name =>
9635 Make_Selected_Component (Loc,
9636 Prefix => Make_Identifier (Loc, Chars (Obj)),
9637 Selector_Name => Make_Identifier (Loc, Chars (Call_Ent))),
9639 Parameter_Associations => Actuals);
9640 end Build_Dispatching_Call_Equivalent;
9642 -------------------------------
9643 -- Build_Dispatching_Requeue --
9644 -------------------------------
9646 function Build_Dispatching_Requeue return Node_Id is
9647 Params : constant List_Id := New_List;
9649 begin
9650 -- Process the "with abort" parameter
9652 Prepend_To (Params,
9653 New_Reference_To (Boolean_Literals (Abort_Present (N)), Loc));
9655 -- Process the entry wrapper's position in the primary dispatch
9656 -- table parameter. Generate:
9658 -- Ada.Tags.Get_Entry_Index
9659 -- (T => To_Tag_Ptr (Obj'Address).all,
9660 -- Position =>
9661 -- Ada.Tags.Get_Offset_Index
9662 -- (Ada.Tags.Tag (Concval),
9663 -- <interface dispatch table position of Ename>));
9665 -- Note that Obj'Address is recursively expanded into a call to
9666 -- Base_Address (Obj).
9668 if Tagged_Type_Expansion then
9669 Prepend_To (Params,
9670 Make_Function_Call (Loc,
9671 Name => New_Reference_To (RTE (RE_Get_Entry_Index), Loc),
9672 Parameter_Associations => New_List (
9674 Make_Explicit_Dereference (Loc,
9675 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
9676 Make_Attribute_Reference (Loc,
9677 Prefix => New_Copy_Tree (Concval),
9678 Attribute_Name => Name_Address))),
9680 Make_Function_Call (Loc,
9681 Name => New_Reference_To (RTE (RE_Get_Offset_Index), Loc),
9682 Parameter_Associations => New_List (
9683 Unchecked_Convert_To (RTE (RE_Tag), Concval),
9684 Make_Integer_Literal (Loc,
9685 DT_Position (Entity (Ename))))))));
9687 -- VM targets
9689 else
9690 Prepend_To (Params,
9691 Make_Function_Call (Loc,
9692 Name => New_Reference_To (RTE (RE_Get_Entry_Index), Loc),
9693 Parameter_Associations => New_List (
9695 Make_Attribute_Reference (Loc,
9696 Prefix => Concval,
9697 Attribute_Name => Name_Tag),
9699 Make_Function_Call (Loc,
9700 Name => New_Reference_To (RTE (RE_Get_Offset_Index), Loc),
9702 Parameter_Associations => New_List (
9704 -- Obj_Tag
9706 Make_Attribute_Reference (Loc,
9707 Prefix => Concval,
9708 Attribute_Name => Name_Tag),
9710 -- Tag_Typ
9712 Make_Attribute_Reference (Loc,
9713 Prefix => New_Reference_To (Etype (Concval), Loc),
9714 Attribute_Name => Name_Tag),
9716 -- Position
9718 Make_Integer_Literal (Loc,
9719 DT_Position (Entity (Ename))))))));
9720 end if;
9722 -- Specific actuals for protected to XXX requeue
9724 if Is_Protected_Type (Old_Typ) then
9725 Prepend_To (Params,
9726 Make_Attribute_Reference (Loc, -- _object'Address
9727 Prefix =>
9728 Concurrent_Ref (New_Occurrence_Of (Old_Typ, Loc)),
9729 Attribute_Name => Name_Address));
9731 Prepend_To (Params, -- True
9732 New_Reference_To (Standard_True, Loc));
9734 -- Specific actuals for task to XXX requeue
9736 else
9737 pragma Assert (Is_Task_Type (Old_Typ));
9739 Prepend_To (Params, -- null
9740 New_Reference_To (RTE (RE_Null_Address), Loc));
9742 Prepend_To (Params, -- False
9743 New_Reference_To (Standard_False, Loc));
9744 end if;
9746 -- Add the object parameter
9748 Prepend_To (Params, New_Copy_Tree (Concval));
9750 -- Generate:
9751 -- _Disp_Requeue (<Params>);
9753 -- Find entity for Disp_Requeue operation, which belongs to
9754 -- the type and may not be directly visible.
9756 declare
9757 Elmt : Elmt_Id;
9758 Op : Entity_Id;
9760 begin
9761 Elmt := First_Elmt (Primitive_Operations (Etype (Conc_Typ)));
9762 while Present (Elmt) loop
9763 Op := Node (Elmt);
9764 exit when Chars (Op) = Name_uDisp_Requeue;
9765 Next_Elmt (Elmt);
9766 end loop;
9768 return
9769 Make_Procedure_Call_Statement (Loc,
9770 Name => New_Occurrence_Of (Op, Loc),
9771 Parameter_Associations => Params);
9772 end;
9773 end Build_Dispatching_Requeue;
9775 --------------------------------------
9776 -- Build_Dispatching_Requeue_To_Any --
9777 --------------------------------------
9779 function Build_Dispatching_Requeue_To_Any return Node_Id is
9780 Call_Ent : constant Entity_Id := Entity (Ename);
9781 Obj : constant Node_Id := Original_Node (Concval);
9782 Skip : constant Node_Id := Build_Skip_Statement (N);
9783 C : Entity_Id;
9784 Decls : List_Id;
9785 S : Entity_Id;
9786 Stmts : List_Id;
9788 begin
9789 Decls := New_List;
9790 Stmts := New_List;
9792 -- Dispatch table slot processing, generate:
9793 -- S : Integer;
9795 S := Build_S (Loc, Decls);
9797 -- Call kind processing, generate:
9798 -- C : Ada.Tags.Prim_Op_Kind;
9800 C := Build_C (Loc, Decls);
9802 -- Generate:
9803 -- S := Ada.Tags.Get_Offset_Index
9804 -- (Ada.Tags.Tag (Obj), DT_Position (Call_Ent));
9806 Append_To (Stmts, Build_S_Assignment (Loc, S, Obj, Call_Ent));
9808 -- Generate:
9809 -- _Disp_Get_Prim_Op_Kind (Obj, S, C);
9811 Append_To (Stmts,
9812 Make_Procedure_Call_Statement (Loc,
9813 Name =>
9814 New_Reference_To (
9815 Find_Prim_Op (Etype (Etype (Obj)),
9816 Name_uDisp_Get_Prim_Op_Kind),
9817 Loc),
9818 Parameter_Associations => New_List (
9819 New_Copy_Tree (Obj),
9820 New_Reference_To (S, Loc),
9821 New_Reference_To (C, Loc))));
9823 Append_To (Stmts,
9825 -- if C = POK_Protected_Entry
9826 -- or else C = POK_Task_Entry
9827 -- then
9829 Make_Implicit_If_Statement (N,
9830 Condition =>
9831 Make_Op_Or (Loc,
9832 Left_Opnd =>
9833 Make_Op_Eq (Loc,
9834 Left_Opnd =>
9835 New_Reference_To (C, Loc),
9836 Right_Opnd =>
9837 New_Reference_To (RTE (RE_POK_Protected_Entry), Loc)),
9839 Right_Opnd =>
9840 Make_Op_Eq (Loc,
9841 Left_Opnd =>
9842 New_Reference_To (C, Loc),
9843 Right_Opnd =>
9844 New_Reference_To (RTE (RE_POK_Task_Entry), Loc))),
9846 -- Dispatching requeue equivalent
9848 Then_Statements => New_List (
9849 Build_Dispatching_Requeue,
9850 Skip),
9852 -- elsif C = POK_Protected_Procedure then
9854 Elsif_Parts => New_List (
9855 Make_Elsif_Part (Loc,
9856 Condition =>
9857 Make_Op_Eq (Loc,
9858 Left_Opnd =>
9859 New_Reference_To (C, Loc),
9860 Right_Opnd =>
9861 New_Reference_To (
9862 RTE (RE_POK_Protected_Procedure), Loc)),
9864 -- Dispatching call equivalent
9866 Then_Statements => New_List (
9867 Build_Dispatching_Call_Equivalent))),
9869 -- else
9870 -- raise Program_Error;
9871 -- end if;
9873 Else_Statements => New_List (
9874 Make_Raise_Program_Error (Loc,
9875 Reason => PE_Explicit_Raise))));
9877 -- Wrap everything into a block
9879 return
9880 Make_Block_Statement (Loc,
9881 Declarations => Decls,
9882 Handled_Statement_Sequence =>
9883 Make_Handled_Sequence_Of_Statements (Loc,
9884 Statements => Stmts));
9885 end Build_Dispatching_Requeue_To_Any;
9887 --------------------------
9888 -- Build_Normal_Requeue --
9889 --------------------------
9891 function Build_Normal_Requeue return Node_Id is
9892 Params : constant List_Id := New_List;
9893 Param : Node_Id;
9894 RT_Call : Node_Id;
9896 begin
9897 -- Process the "with abort" parameter
9899 Prepend_To (Params,
9900 New_Reference_To (Boolean_Literals (Abort_Present (N)), Loc));
9902 -- Add the index expression to the parameters. It is common among all
9903 -- four cases.
9905 Prepend_To (Params,
9906 Entry_Index_Expression (Loc, Entity (Ename), Index, Conc_Typ));
9908 if Is_Protected_Type (Old_Typ) then
9909 declare
9910 Self_Param : Node_Id;
9912 begin
9913 Self_Param :=
9914 Make_Attribute_Reference (Loc,
9915 Prefix =>
9916 Concurrent_Ref (New_Occurrence_Of (Old_Typ, Loc)),
9917 Attribute_Name =>
9918 Name_Unchecked_Access);
9920 -- Protected to protected requeue
9922 if Is_Protected_Type (Conc_Typ) then
9923 RT_Call :=
9924 New_Reference_To (
9925 RTE (RE_Requeue_Protected_Entry), Loc);
9927 Param :=
9928 Make_Attribute_Reference (Loc,
9929 Prefix =>
9930 Concurrent_Ref (Concval),
9931 Attribute_Name =>
9932 Name_Unchecked_Access);
9934 -- Protected to task requeue
9936 else pragma Assert (Is_Task_Type (Conc_Typ));
9937 RT_Call :=
9938 New_Reference_To (
9939 RTE (RE_Requeue_Protected_To_Task_Entry), Loc);
9941 Param := Concurrent_Ref (Concval);
9942 end if;
9944 Prepend_To (Params, Param);
9945 Prepend_To (Params, Self_Param);
9946 end;
9948 else pragma Assert (Is_Task_Type (Old_Typ));
9950 -- Task to protected requeue
9952 if Is_Protected_Type (Conc_Typ) then
9953 RT_Call :=
9954 New_Reference_To (
9955 RTE (RE_Requeue_Task_To_Protected_Entry), Loc);
9957 Param :=
9958 Make_Attribute_Reference (Loc,
9959 Prefix =>
9960 Concurrent_Ref (Concval),
9961 Attribute_Name =>
9962 Name_Unchecked_Access);
9964 -- Task to task requeue
9966 else pragma Assert (Is_Task_Type (Conc_Typ));
9967 RT_Call :=
9968 New_Reference_To (RTE (RE_Requeue_Task_Entry), Loc);
9970 Param := Concurrent_Ref (Concval);
9971 end if;
9973 Prepend_To (Params, Param);
9974 end if;
9976 return
9977 Make_Procedure_Call_Statement (Loc,
9978 Name => RT_Call,
9979 Parameter_Associations => Params);
9980 end Build_Normal_Requeue;
9982 --------------------------
9983 -- Build_Skip_Statement --
9984 --------------------------
9986 function Build_Skip_Statement (Search : Node_Id) return Node_Id is
9987 Skip_Stmt : Node_Id;
9989 begin
9990 -- Build a return statement to skip the rest of the entire body
9992 if Is_Protected_Type (Old_Typ) then
9993 Skip_Stmt := Make_Simple_Return_Statement (Loc);
9995 -- If the requeue is within a task, find the end label of the
9996 -- enclosing accept statement and create a goto statement to it.
9998 else
9999 declare
10000 Acc : Node_Id;
10001 Label : Node_Id;
10003 begin
10004 -- Climb the parent chain looking for the enclosing accept
10005 -- statement.
10007 Acc := Parent (Search);
10008 while Present (Acc)
10009 and then Nkind (Acc) /= N_Accept_Statement
10010 loop
10011 Acc := Parent (Acc);
10012 end loop;
10014 -- The last statement is the second label used for completing
10015 -- the rendezvous the usual way. The label we are looking for
10016 -- is right before it.
10018 Label :=
10019 Prev (Last (Statements (Handled_Statement_Sequence (Acc))));
10021 pragma Assert (Nkind (Label) = N_Label);
10023 -- Generate a goto statement to skip the rest of the accept
10025 Skip_Stmt :=
10026 Make_Goto_Statement (Loc,
10027 Name =>
10028 New_Occurrence_Of (Entity (Identifier (Label)), Loc));
10029 end;
10030 end if;
10032 Set_Analyzed (Skip_Stmt);
10034 return Skip_Stmt;
10035 end Build_Skip_Statement;
10037 -- Start of processing for Expand_N_Requeue_Statement
10039 begin
10040 -- Extract the components of the entry call
10042 Extract_Entry (N, Concval, Ename, Index);
10043 Conc_Typ := Etype (Concval);
10045 -- If the prefix is an access to class-wide type, dereference to get
10046 -- object and entry type.
10048 if Is_Access_Type (Conc_Typ) then
10049 Conc_Typ := Designated_Type (Conc_Typ);
10050 Rewrite (Concval,
10051 Make_Explicit_Dereference (Loc, Relocate_Node (Concval)));
10052 Analyze_And_Resolve (Concval, Conc_Typ);
10053 end if;
10055 -- Examine the scope stack in order to find nearest enclosing protected
10056 -- or task type. This will constitute our invocation source.
10058 Old_Typ := Current_Scope;
10059 while Present (Old_Typ)
10060 and then not Is_Protected_Type (Old_Typ)
10061 and then not Is_Task_Type (Old_Typ)
10062 loop
10063 Old_Typ := Scope (Old_Typ);
10064 end loop;
10066 -- Ada 2012 (AI05-0030): We have a dispatching requeue of the form
10067 -- Concval.Ename where the type of Concval is class-wide concurrent
10068 -- interface.
10070 if Ada_Version >= Ada_2012
10071 and then Present (Concval)
10072 and then Is_Class_Wide_Type (Conc_Typ)
10073 and then Is_Concurrent_Interface (Conc_Typ)
10074 then
10075 declare
10076 Has_Impl : Boolean := False;
10077 Impl_Kind : Name_Id := No_Name;
10079 begin
10080 -- Check whether the Ename is flagged by pragma Implemented
10082 if Has_Rep_Pragma (Entity (Ename), Name_Implemented) then
10083 Has_Impl := True;
10084 Impl_Kind := Implementation_Kind (Entity (Ename));
10085 end if;
10087 -- The procedure_or_entry_NAME is guaranteed to be overridden by
10088 -- an entry. Create a call to predefined primitive _Disp_Requeue.
10090 if Has_Impl
10091 and then Impl_Kind = Name_By_Entry
10092 then
10093 Rewrite (N, Build_Dispatching_Requeue);
10094 Analyze (N);
10095 Insert_After (N, Build_Skip_Statement (N));
10097 -- The procedure_or_entry_NAME is guaranteed to be overridden by
10098 -- a protected procedure. In this case the requeue is transformed
10099 -- into a dispatching call.
10101 elsif Has_Impl
10102 and then Impl_Kind = Name_By_Protected_Procedure
10103 then
10104 Rewrite (N, Build_Dispatching_Call_Equivalent);
10105 Analyze (N);
10107 -- The procedure_or_entry_NAME's implementation kind is either
10108 -- By_Any, Optional, or pragma Implemented was not applied at all.
10109 -- In this case a runtime test determines whether Ename denotes an
10110 -- entry or a protected procedure and performs the appropriate
10111 -- call.
10113 else
10114 Rewrite (N, Build_Dispatching_Requeue_To_Any);
10115 Analyze (N);
10116 end if;
10117 end;
10119 -- Processing for regular (non-dispatching) requeues
10121 else
10122 Rewrite (N, Build_Normal_Requeue);
10123 Analyze (N);
10124 Insert_After (N, Build_Skip_Statement (N));
10125 end if;
10126 end Expand_N_Requeue_Statement;
10128 -------------------------------
10129 -- Expand_N_Selective_Accept --
10130 -------------------------------
10132 procedure Expand_N_Selective_Accept (N : Node_Id) is
10133 Loc : constant Source_Ptr := Sloc (N);
10134 Alts : constant List_Id := Select_Alternatives (N);
10136 -- Note: in the below declarations a lot of new lists are allocated
10137 -- unconditionally which may well not end up being used. That's not
10138 -- a good idea since it wastes space gratuitously ???
10140 Accept_Case : List_Id;
10141 Accept_List : constant List_Id := New_List;
10143 Alt : Node_Id;
10144 Alt_List : constant List_Id := New_List;
10145 Alt_Stats : List_Id;
10146 Ann : Entity_Id := Empty;
10148 Check_Guard : Boolean := True;
10150 Decls : constant List_Id := New_List;
10151 Stats : constant List_Id := New_List;
10152 Body_List : constant List_Id := New_List;
10153 Trailing_List : constant List_Id := New_List;
10155 Choices : List_Id;
10156 Else_Present : Boolean := False;
10157 Terminate_Alt : Node_Id := Empty;
10158 Select_Mode : Node_Id;
10160 Delay_Case : List_Id;
10161 Delay_Count : Integer := 0;
10162 Delay_Val : Entity_Id;
10163 Delay_Index : Entity_Id;
10164 Delay_Min : Entity_Id;
10165 Delay_Num : Int := 1;
10166 Delay_Alt_List : List_Id := New_List;
10167 Delay_List : constant List_Id := New_List;
10168 D : Entity_Id;
10169 M : Entity_Id;
10171 First_Delay : Boolean := True;
10172 Guard_Open : Entity_Id;
10174 End_Lab : Node_Id;
10175 Index : Int := 1;
10176 Lab : Node_Id;
10177 Num_Alts : Int;
10178 Num_Accept : Nat := 0;
10179 Proc : Node_Id;
10180 Time_Type : Entity_Id;
10181 Select_Call : Node_Id;
10183 Qnam : constant Entity_Id :=
10184 Make_Defining_Identifier (Loc, New_External_Name ('S', 0));
10186 Xnam : constant Entity_Id :=
10187 Make_Defining_Identifier (Loc, New_External_Name ('J', 1));
10189 -----------------------
10190 -- Local subprograms --
10191 -----------------------
10193 function Accept_Or_Raise return List_Id;
10194 -- For the rare case where delay alternatives all have guards, and
10195 -- all of them are closed, it is still possible that there were open
10196 -- accept alternatives with no callers. We must reexamine the
10197 -- Accept_List, and execute a selective wait with no else if some
10198 -- accept is open. If none, we raise program_error.
10200 procedure Add_Accept (Alt : Node_Id);
10201 -- Process a single accept statement in a select alternative. Build
10202 -- procedure for body of accept, and add entry to dispatch table with
10203 -- expression for guard, in preparation for call to run time select.
10205 function Make_And_Declare_Label (Num : Int) return Node_Id;
10206 -- Manufacture a label using Num as a serial number and declare it.
10207 -- The declaration is appended to Decls. The label marks the trailing
10208 -- statements of an accept or delay alternative.
10210 function Make_Select_Call (Select_Mode : Entity_Id) return Node_Id;
10211 -- Build call to Selective_Wait runtime routine
10213 procedure Process_Delay_Alternative (Alt : Node_Id; Index : Int);
10214 -- Add code to compare value of delay with previous values, and
10215 -- generate case entry for trailing statements.
10217 procedure Process_Accept_Alternative
10218 (Alt : Node_Id;
10219 Index : Int;
10220 Proc : Node_Id);
10221 -- Add code to call corresponding procedure, and branch to
10222 -- trailing statements, if any.
10224 ---------------------
10225 -- Accept_Or_Raise --
10226 ---------------------
10228 function Accept_Or_Raise return List_Id is
10229 Cond : Node_Id;
10230 Stats : List_Id;
10231 J : constant Entity_Id := Make_Temporary (Loc, 'J');
10233 begin
10234 -- We generate the following:
10236 -- for J in q'range loop
10237 -- if q(J).S /=null_task_entry then
10238 -- selective_wait (simple_mode,...);
10239 -- done := True;
10240 -- exit;
10241 -- end if;
10242 -- end loop;
10244 -- if no rendez_vous then
10245 -- raise program_error;
10246 -- end if;
10248 -- Note that the code needs to know that the selector name
10249 -- in an Accept_Alternative is named S.
10251 Cond := Make_Op_Ne (Loc,
10252 Left_Opnd =>
10253 Make_Selected_Component (Loc,
10254 Prefix =>
10255 Make_Indexed_Component (Loc,
10256 Prefix => New_Reference_To (Qnam, Loc),
10257 Expressions => New_List (New_Reference_To (J, Loc))),
10258 Selector_Name => Make_Identifier (Loc, Name_S)),
10259 Right_Opnd =>
10260 New_Reference_To (RTE (RE_Null_Task_Entry), Loc));
10262 Stats := New_List (
10263 Make_Implicit_Loop_Statement (N,
10264 Iteration_Scheme =>
10265 Make_Iteration_Scheme (Loc,
10266 Loop_Parameter_Specification =>
10267 Make_Loop_Parameter_Specification (Loc,
10268 Defining_Identifier => J,
10269 Discrete_Subtype_Definition =>
10270 Make_Attribute_Reference (Loc,
10271 Prefix => New_Reference_To (Qnam, Loc),
10272 Attribute_Name => Name_Range,
10273 Expressions => New_List (
10274 Make_Integer_Literal (Loc, 1))))),
10276 Statements => New_List (
10277 Make_Implicit_If_Statement (N,
10278 Condition => Cond,
10279 Then_Statements => New_List (
10280 Make_Select_Call (
10281 New_Reference_To (RTE (RE_Simple_Mode), Loc)),
10282 Make_Exit_Statement (Loc))))));
10284 Append_To (Stats,
10285 Make_Raise_Program_Error (Loc,
10286 Condition => Make_Op_Eq (Loc,
10287 Left_Opnd => New_Reference_To (Xnam, Loc),
10288 Right_Opnd =>
10289 New_Reference_To (RTE (RE_No_Rendezvous), Loc)),
10290 Reason => PE_All_Guards_Closed));
10292 return Stats;
10293 end Accept_Or_Raise;
10295 ----------------
10296 -- Add_Accept --
10297 ----------------
10299 procedure Add_Accept (Alt : Node_Id) is
10300 Acc_Stm : constant Node_Id := Accept_Statement (Alt);
10301 Ename : constant Node_Id := Entry_Direct_Name (Acc_Stm);
10302 Eloc : constant Source_Ptr := Sloc (Ename);
10303 Eent : constant Entity_Id := Entity (Ename);
10304 Index : constant Node_Id := Entry_Index (Acc_Stm);
10305 Null_Body : Node_Id;
10306 Proc_Body : Node_Id;
10307 PB_Ent : Entity_Id;
10308 Expr : Node_Id;
10309 Call : Node_Id;
10311 begin
10312 if No (Ann) then
10313 Ann := Node (Last_Elmt (Accept_Address (Eent)));
10314 end if;
10316 if Present (Condition (Alt)) then
10317 Expr :=
10318 Make_If_Expression (Eloc, New_List (
10319 Condition (Alt),
10320 Entry_Index_Expression (Eloc, Eent, Index, Scope (Eent)),
10321 New_Reference_To (RTE (RE_Null_Task_Entry), Eloc)));
10322 else
10323 Expr :=
10324 Entry_Index_Expression
10325 (Eloc, Eent, Index, Scope (Eent));
10326 end if;
10328 if Present (Handled_Statement_Sequence (Accept_Statement (Alt))) then
10329 Null_Body := New_Reference_To (Standard_False, Eloc);
10331 if Abort_Allowed then
10332 Call := Make_Procedure_Call_Statement (Eloc,
10333 Name => New_Reference_To (RTE (RE_Abort_Undefer), Eloc));
10334 Insert_Before (First (Statements (Handled_Statement_Sequence (
10335 Accept_Statement (Alt)))), Call);
10336 Analyze (Call);
10337 end if;
10339 PB_Ent :=
10340 Make_Defining_Identifier (Eloc,
10341 New_External_Name (Chars (Ename), 'A', Num_Accept));
10343 if Comes_From_Source (Alt) then
10344 Set_Debug_Info_Needed (PB_Ent);
10345 end if;
10347 Proc_Body :=
10348 Make_Subprogram_Body (Eloc,
10349 Specification =>
10350 Make_Procedure_Specification (Eloc,
10351 Defining_Unit_Name => PB_Ent),
10352 Declarations => Declarations (Acc_Stm),
10353 Handled_Statement_Sequence =>
10354 Build_Accept_Body (Accept_Statement (Alt)));
10356 -- During the analysis of the body of the accept statement, any
10357 -- zero cost exception handler records were collected in the
10358 -- Accept_Handler_Records field of the N_Accept_Alternative node.
10359 -- This is where we move them to where they belong, namely the
10360 -- newly created procedure.
10362 Set_Handler_Records (PB_Ent, Accept_Handler_Records (Alt));
10363 Append (Proc_Body, Body_List);
10365 else
10366 Null_Body := New_Reference_To (Standard_True, Eloc);
10368 -- if accept statement has declarations, insert above, given that
10369 -- we are not creating a body for the accept.
10371 if Present (Declarations (Acc_Stm)) then
10372 Insert_Actions (N, Declarations (Acc_Stm));
10373 end if;
10374 end if;
10376 Append_To (Accept_List,
10377 Make_Aggregate (Eloc, Expressions => New_List (Null_Body, Expr)));
10379 Num_Accept := Num_Accept + 1;
10380 end Add_Accept;
10382 ----------------------------
10383 -- Make_And_Declare_Label --
10384 ----------------------------
10386 function Make_And_Declare_Label (Num : Int) return Node_Id is
10387 Lab_Id : Node_Id;
10389 begin
10390 Lab_Id := Make_Identifier (Loc, New_External_Name ('L', Num));
10391 Lab :=
10392 Make_Label (Loc, Lab_Id);
10394 Append_To (Decls,
10395 Make_Implicit_Label_Declaration (Loc,
10396 Defining_Identifier =>
10397 Make_Defining_Identifier (Loc, Chars (Lab_Id)),
10398 Label_Construct => Lab));
10400 return Lab;
10401 end Make_And_Declare_Label;
10403 ----------------------
10404 -- Make_Select_Call --
10405 ----------------------
10407 function Make_Select_Call (Select_Mode : Entity_Id) return Node_Id is
10408 Params : constant List_Id := New_List;
10410 begin
10411 Append (
10412 Make_Attribute_Reference (Loc,
10413 Prefix => New_Reference_To (Qnam, Loc),
10414 Attribute_Name => Name_Unchecked_Access),
10415 Params);
10416 Append (Select_Mode, Params);
10417 Append (New_Reference_To (Ann, Loc), Params);
10418 Append (New_Reference_To (Xnam, Loc), Params);
10420 return
10421 Make_Procedure_Call_Statement (Loc,
10422 Name => New_Reference_To (RTE (RE_Selective_Wait), Loc),
10423 Parameter_Associations => Params);
10424 end Make_Select_Call;
10426 --------------------------------
10427 -- Process_Accept_Alternative --
10428 --------------------------------
10430 procedure Process_Accept_Alternative
10431 (Alt : Node_Id;
10432 Index : Int;
10433 Proc : Node_Id)
10435 Astmt : constant Node_Id := Accept_Statement (Alt);
10436 Alt_Stats : List_Id;
10438 begin
10439 Adjust_Condition (Condition (Alt));
10441 -- Accept with body
10443 if Present (Handled_Statement_Sequence (Astmt)) then
10444 Alt_Stats :=
10445 New_List (
10446 Make_Procedure_Call_Statement (Sloc (Proc),
10447 Name =>
10448 New_Reference_To
10449 (Defining_Unit_Name (Specification (Proc)),
10450 Sloc (Proc))));
10452 -- Accept with no body (followed by trailing statements)
10454 else
10455 Alt_Stats := Empty_List;
10456 end if;
10458 Ensure_Statement_Present (Sloc (Astmt), Alt);
10460 -- After the call, if any, branch to trailing statements, if any.
10461 -- We create a label for each, as well as the corresponding label
10462 -- declaration.
10464 if not Is_Empty_List (Statements (Alt)) then
10465 Lab := Make_And_Declare_Label (Index);
10466 Append (Lab, Trailing_List);
10467 Append_List (Statements (Alt), Trailing_List);
10468 Append_To (Trailing_List,
10469 Make_Goto_Statement (Loc,
10470 Name => New_Copy (Identifier (End_Lab))));
10472 else
10473 Lab := End_Lab;
10474 end if;
10476 Append_To (Alt_Stats,
10477 Make_Goto_Statement (Loc, Name => New_Copy (Identifier (Lab))));
10479 Append_To (Alt_List,
10480 Make_Case_Statement_Alternative (Loc,
10481 Discrete_Choices => New_List (Make_Integer_Literal (Loc, Index)),
10482 Statements => Alt_Stats));
10483 end Process_Accept_Alternative;
10485 -------------------------------
10486 -- Process_Delay_Alternative --
10487 -------------------------------
10489 procedure Process_Delay_Alternative (Alt : Node_Id; Index : Int) is
10490 Dloc : constant Source_Ptr := Sloc (Delay_Statement (Alt));
10491 Cond : Node_Id;
10492 Delay_Alt : List_Id;
10494 begin
10495 -- Deal with C/Fortran boolean as delay condition
10497 Adjust_Condition (Condition (Alt));
10499 -- Determine the smallest specified delay
10501 -- for each delay alternative generate:
10503 -- if guard-expression then
10504 -- Delay_Val := delay-expression;
10505 -- Guard_Open := True;
10506 -- if Delay_Val < Delay_Min then
10507 -- Delay_Min := Delay_Val;
10508 -- Delay_Index := Index;
10509 -- end if;
10510 -- end if;
10512 -- The enclosing if-statement is omitted if there is no guard
10514 if Delay_Count = 1 or else First_Delay then
10515 First_Delay := False;
10517 Delay_Alt := New_List (
10518 Make_Assignment_Statement (Loc,
10519 Name => New_Reference_To (Delay_Min, Loc),
10520 Expression => Expression (Delay_Statement (Alt))));
10522 if Delay_Count > 1 then
10523 Append_To (Delay_Alt,
10524 Make_Assignment_Statement (Loc,
10525 Name => New_Reference_To (Delay_Index, Loc),
10526 Expression => Make_Integer_Literal (Loc, Index)));
10527 end if;
10529 else
10530 Delay_Alt := New_List (
10531 Make_Assignment_Statement (Loc,
10532 Name => New_Reference_To (Delay_Val, Loc),
10533 Expression => Expression (Delay_Statement (Alt))));
10535 if Time_Type = Standard_Duration then
10536 Cond :=
10537 Make_Op_Lt (Loc,
10538 Left_Opnd => New_Reference_To (Delay_Val, Loc),
10539 Right_Opnd => New_Reference_To (Delay_Min, Loc));
10541 else
10542 -- The scope of the time type must define a comparison
10543 -- operator. The scope itself may not be visible, so we
10544 -- construct a node with entity information to insure that
10545 -- semantic analysis can find the proper operator.
10547 Cond :=
10548 Make_Function_Call (Loc,
10549 Name => Make_Selected_Component (Loc,
10550 Prefix =>
10551 New_Reference_To (Scope (Time_Type), Loc),
10552 Selector_Name =>
10553 Make_Operator_Symbol (Loc,
10554 Chars => Name_Op_Lt,
10555 Strval => No_String)),
10556 Parameter_Associations =>
10557 New_List (
10558 New_Reference_To (Delay_Val, Loc),
10559 New_Reference_To (Delay_Min, Loc)));
10561 Set_Entity (Prefix (Name (Cond)), Scope (Time_Type));
10562 end if;
10564 Append_To (Delay_Alt,
10565 Make_Implicit_If_Statement (N,
10566 Condition => Cond,
10567 Then_Statements => New_List (
10568 Make_Assignment_Statement (Loc,
10569 Name => New_Reference_To (Delay_Min, Loc),
10570 Expression => New_Reference_To (Delay_Val, Loc)),
10572 Make_Assignment_Statement (Loc,
10573 Name => New_Reference_To (Delay_Index, Loc),
10574 Expression => Make_Integer_Literal (Loc, Index)))));
10575 end if;
10577 if Check_Guard then
10578 Append_To (Delay_Alt,
10579 Make_Assignment_Statement (Loc,
10580 Name => New_Reference_To (Guard_Open, Loc),
10581 Expression => New_Reference_To (Standard_True, Loc)));
10582 end if;
10584 if Present (Condition (Alt)) then
10585 Delay_Alt := New_List (
10586 Make_Implicit_If_Statement (N,
10587 Condition => Condition (Alt),
10588 Then_Statements => Delay_Alt));
10589 end if;
10591 Append_List (Delay_Alt, Delay_List);
10593 Ensure_Statement_Present (Dloc, Alt);
10595 -- If the delay alternative has a statement part, add choice to the
10596 -- case statements for delays.
10598 if not Is_Empty_List (Statements (Alt)) then
10600 if Delay_Count = 1 then
10601 Append_List (Statements (Alt), Delay_Alt_List);
10603 else
10604 Append_To (Delay_Alt_List,
10605 Make_Case_Statement_Alternative (Loc,
10606 Discrete_Choices => New_List (
10607 Make_Integer_Literal (Loc, Index)),
10608 Statements => Statements (Alt)));
10609 end if;
10611 elsif Delay_Count = 1 then
10613 -- If the single delay has no trailing statements, add a branch
10614 -- to the exit label to the selective wait.
10616 Delay_Alt_List := New_List (
10617 Make_Goto_Statement (Loc,
10618 Name => New_Copy (Identifier (End_Lab))));
10620 end if;
10621 end Process_Delay_Alternative;
10623 -- Start of processing for Expand_N_Selective_Accept
10625 begin
10626 Process_Statements_For_Controlled_Objects (N);
10628 -- First insert some declarations before the select. The first is:
10630 -- Ann : Address
10632 -- This variable holds the parameters passed to the accept body. This
10633 -- declaration has already been inserted by the time we get here by
10634 -- a call to Expand_Accept_Declarations made from the semantics when
10635 -- processing the first accept statement contained in the select. We
10636 -- can find this entity as Accept_Address (E), where E is any of the
10637 -- entries references by contained accept statements.
10639 -- The first step is to scan the list of Selective_Accept_Statements
10640 -- to find this entity, and also count the number of accepts, and
10641 -- determine if terminated, delay or else is present:
10643 Num_Alts := 0;
10645 Alt := First (Alts);
10646 while Present (Alt) loop
10647 Process_Statements_For_Controlled_Objects (Alt);
10649 if Nkind (Alt) = N_Accept_Alternative then
10650 Add_Accept (Alt);
10652 elsif Nkind (Alt) = N_Delay_Alternative then
10653 Delay_Count := Delay_Count + 1;
10655 -- If the delays are relative delays, the delay expressions have
10656 -- type Standard_Duration. Otherwise they must have some time type
10657 -- recognized by GNAT.
10659 if Nkind (Delay_Statement (Alt)) = N_Delay_Relative_Statement then
10660 Time_Type := Standard_Duration;
10661 else
10662 Time_Type := Etype (Expression (Delay_Statement (Alt)));
10664 if Is_RTE (Base_Type (Etype (Time_Type)), RO_CA_Time)
10665 or else Is_RTE (Base_Type (Etype (Time_Type)), RO_RT_Time)
10666 then
10667 null;
10668 else
10669 Error_Msg_NE (
10670 "& is not a time type (RM 9.6(6))",
10671 Expression (Delay_Statement (Alt)), Time_Type);
10672 Time_Type := Standard_Duration;
10673 Set_Etype (Expression (Delay_Statement (Alt)), Any_Type);
10674 end if;
10675 end if;
10677 if No (Condition (Alt)) then
10679 -- This guard will always be open
10681 Check_Guard := False;
10682 end if;
10684 elsif Nkind (Alt) = N_Terminate_Alternative then
10685 Adjust_Condition (Condition (Alt));
10686 Terminate_Alt := Alt;
10687 end if;
10689 Num_Alts := Num_Alts + 1;
10690 Next (Alt);
10691 end loop;
10693 Else_Present := Present (Else_Statements (N));
10695 -- At the same time (see procedure Add_Accept) we build the accept list:
10697 -- Qnn : Accept_List (1 .. num-select) := (
10698 -- (null-body, entry-index),
10699 -- (null-body, entry-index),
10700 -- ..
10701 -- (null_body, entry-index));
10703 -- In the above declaration, null-body is True if the corresponding
10704 -- accept has no body, and false otherwise. The entry is either the
10705 -- entry index expression if there is no guard, or if a guard is
10706 -- present, then an if expression of the form:
10708 -- (if guard then entry-index else Null_Task_Entry)
10710 -- If a guard is statically known to be false, the entry can simply
10711 -- be omitted from the accept list.
10713 Append_To (Decls,
10714 Make_Object_Declaration (Loc,
10715 Defining_Identifier => Qnam,
10716 Object_Definition => New_Reference_To (RTE (RE_Accept_List), Loc),
10717 Aliased_Present => True,
10718 Expression =>
10719 Make_Qualified_Expression (Loc,
10720 Subtype_Mark =>
10721 New_Reference_To (RTE (RE_Accept_List), Loc),
10722 Expression =>
10723 Make_Aggregate (Loc, Expressions => Accept_List))));
10725 -- Then we declare the variable that holds the index for the accept
10726 -- that will be selected for service:
10728 -- Xnn : Select_Index;
10730 Append_To (Decls,
10731 Make_Object_Declaration (Loc,
10732 Defining_Identifier => Xnam,
10733 Object_Definition =>
10734 New_Reference_To (RTE (RE_Select_Index), Loc),
10735 Expression =>
10736 New_Reference_To (RTE (RE_No_Rendezvous), Loc)));
10738 -- After this follow procedure declarations for each accept body
10740 -- procedure Pnn is
10741 -- begin
10742 -- ...
10743 -- end;
10745 -- where the ... are statements from the corresponding procedure body.
10746 -- No parameters are involved, since the parameters are passed via Ann
10747 -- and the parameter references have already been expanded to be direct
10748 -- references to Ann (see Exp_Ch2.Expand_Entry_Parameter). Furthermore,
10749 -- any embedded tasking statements (which would normally be illegal in
10750 -- procedures), have been converted to calls to the tasking runtime so
10751 -- there is no problem in putting them into procedures.
10753 -- The original accept statement has been expanded into a block in
10754 -- the same fashion as for simple accepts (see Build_Accept_Body).
10756 -- Note: we don't really need to build these procedures for the case
10757 -- where no delay statement is present, but it is just as easy to
10758 -- build them unconditionally, and not significantly inefficient,
10759 -- since if they are short they will be inlined anyway.
10761 -- The procedure declarations have been assembled in Body_List
10763 -- If delays are present, we must compute the required delay.
10764 -- We first generate the declarations:
10766 -- Delay_Index : Boolean := 0;
10767 -- Delay_Min : Some_Time_Type.Time;
10768 -- Delay_Val : Some_Time_Type.Time;
10770 -- Delay_Index will be set to the index of the minimum delay, i.e. the
10771 -- active delay that is actually chosen as the basis for the possible
10772 -- delay if an immediate rendez-vous is not possible.
10774 -- In the most common case there is a single delay statement, and this
10775 -- is handled specially.
10777 if Delay_Count > 0 then
10779 -- Generate the required declarations
10781 Delay_Val :=
10782 Make_Defining_Identifier (Loc, New_External_Name ('D', 1));
10783 Delay_Index :=
10784 Make_Defining_Identifier (Loc, New_External_Name ('D', 2));
10785 Delay_Min :=
10786 Make_Defining_Identifier (Loc, New_External_Name ('D', 3));
10788 Append_To (Decls,
10789 Make_Object_Declaration (Loc,
10790 Defining_Identifier => Delay_Val,
10791 Object_Definition => New_Reference_To (Time_Type, Loc)));
10793 Append_To (Decls,
10794 Make_Object_Declaration (Loc,
10795 Defining_Identifier => Delay_Index,
10796 Object_Definition => New_Reference_To (Standard_Integer, Loc),
10797 Expression => Make_Integer_Literal (Loc, 0)));
10799 Append_To (Decls,
10800 Make_Object_Declaration (Loc,
10801 Defining_Identifier => Delay_Min,
10802 Object_Definition => New_Reference_To (Time_Type, Loc),
10803 Expression =>
10804 Unchecked_Convert_To (Time_Type,
10805 Make_Attribute_Reference (Loc,
10806 Prefix =>
10807 New_Occurrence_Of (Underlying_Type (Time_Type), Loc),
10808 Attribute_Name => Name_Last))));
10810 -- Create Duration and Delay_Mode objects used for passing a delay
10811 -- value to RTS
10813 D := Make_Temporary (Loc, 'D');
10814 M := Make_Temporary (Loc, 'M');
10816 declare
10817 Discr : Entity_Id;
10819 begin
10820 -- Note that these values are defined in s-osprim.ads and must
10821 -- be kept in sync:
10823 -- Relative : constant := 0;
10824 -- Absolute_Calendar : constant := 1;
10825 -- Absolute_RT : constant := 2;
10827 if Time_Type = Standard_Duration then
10828 Discr := Make_Integer_Literal (Loc, 0);
10830 elsif Is_RTE (Base_Type (Etype (Time_Type)), RO_CA_Time) then
10831 Discr := Make_Integer_Literal (Loc, 1);
10833 else
10834 pragma Assert
10835 (Is_RTE (Base_Type (Etype (Time_Type)), RO_RT_Time));
10836 Discr := Make_Integer_Literal (Loc, 2);
10837 end if;
10839 Append_To (Decls,
10840 Make_Object_Declaration (Loc,
10841 Defining_Identifier => D,
10842 Object_Definition =>
10843 New_Reference_To (Standard_Duration, Loc)));
10845 Append_To (Decls,
10846 Make_Object_Declaration (Loc,
10847 Defining_Identifier => M,
10848 Object_Definition =>
10849 New_Reference_To (Standard_Integer, Loc),
10850 Expression => Discr));
10851 end;
10853 if Check_Guard then
10854 Guard_Open :=
10855 Make_Defining_Identifier (Loc, New_External_Name ('G', 1));
10857 Append_To (Decls,
10858 Make_Object_Declaration (Loc,
10859 Defining_Identifier => Guard_Open,
10860 Object_Definition => New_Reference_To (Standard_Boolean, Loc),
10861 Expression => New_Reference_To (Standard_False, Loc)));
10862 end if;
10864 -- Delay_Count is zero, don't need M and D set (suppress warning)
10866 else
10867 M := Empty;
10868 D := Empty;
10869 end if;
10871 if Present (Terminate_Alt) then
10873 -- If the terminate alternative guard is False, use
10874 -- Simple_Mode; otherwise use Terminate_Mode.
10876 if Present (Condition (Terminate_Alt)) then
10877 Select_Mode := Make_If_Expression (Loc,
10878 New_List (Condition (Terminate_Alt),
10879 New_Reference_To (RTE (RE_Terminate_Mode), Loc),
10880 New_Reference_To (RTE (RE_Simple_Mode), Loc)));
10881 else
10882 Select_Mode := New_Reference_To (RTE (RE_Terminate_Mode), Loc);
10883 end if;
10885 elsif Else_Present or Delay_Count > 0 then
10886 Select_Mode := New_Reference_To (RTE (RE_Else_Mode), Loc);
10888 else
10889 Select_Mode := New_Reference_To (RTE (RE_Simple_Mode), Loc);
10890 end if;
10892 Select_Call := Make_Select_Call (Select_Mode);
10893 Append (Select_Call, Stats);
10895 -- Now generate code to act on the result. There is an entry
10896 -- in this case for each accept statement with a non-null body,
10897 -- followed by a branch to the statements that follow the Accept.
10898 -- In the absence of delay alternatives, we generate:
10900 -- case X is
10901 -- when No_Rendezvous => -- omitted if simple mode
10902 -- goto Lab0;
10904 -- when 1 =>
10905 -- P1n;
10906 -- goto Lab1;
10908 -- when 2 =>
10909 -- P2n;
10910 -- goto Lab2;
10912 -- when others =>
10913 -- goto Exit;
10914 -- end case;
10916 -- Lab0: Else_Statements;
10917 -- goto exit;
10919 -- Lab1: Trailing_Statements1;
10920 -- goto Exit;
10922 -- Lab2: Trailing_Statements2;
10923 -- goto Exit;
10924 -- ...
10925 -- Exit:
10927 -- Generate label for common exit
10929 End_Lab := Make_And_Declare_Label (Num_Alts + 1);
10931 -- First entry is the default case, when no rendezvous is possible
10933 Choices := New_List (New_Reference_To (RTE (RE_No_Rendezvous), Loc));
10935 if Else_Present then
10937 -- If no rendezvous is possible, the else part is executed
10939 Lab := Make_And_Declare_Label (0);
10940 Alt_Stats := New_List (
10941 Make_Goto_Statement (Loc,
10942 Name => New_Copy (Identifier (Lab))));
10944 Append (Lab, Trailing_List);
10945 Append_List (Else_Statements (N), Trailing_List);
10946 Append_To (Trailing_List,
10947 Make_Goto_Statement (Loc,
10948 Name => New_Copy (Identifier (End_Lab))));
10949 else
10950 Alt_Stats := New_List (
10951 Make_Goto_Statement (Loc,
10952 Name => New_Copy (Identifier (End_Lab))));
10953 end if;
10955 Append_To (Alt_List,
10956 Make_Case_Statement_Alternative (Loc,
10957 Discrete_Choices => Choices,
10958 Statements => Alt_Stats));
10960 -- We make use of the fact that Accept_Index is an integer type, and
10961 -- generate successive literals for entries for each accept. Only those
10962 -- for which there is a body or trailing statements get a case entry.
10964 Alt := First (Select_Alternatives (N));
10965 Proc := First (Body_List);
10966 while Present (Alt) loop
10968 if Nkind (Alt) = N_Accept_Alternative then
10969 Process_Accept_Alternative (Alt, Index, Proc);
10970 Index := Index + 1;
10972 if Present
10973 (Handled_Statement_Sequence (Accept_Statement (Alt)))
10974 then
10975 Next (Proc);
10976 end if;
10978 elsif Nkind (Alt) = N_Delay_Alternative then
10979 Process_Delay_Alternative (Alt, Delay_Num);
10980 Delay_Num := Delay_Num + 1;
10981 end if;
10983 Next (Alt);
10984 end loop;
10986 -- An others choice is always added to the main case, as well
10987 -- as the delay case (to satisfy the compiler).
10989 Append_To (Alt_List,
10990 Make_Case_Statement_Alternative (Loc,
10991 Discrete_Choices =>
10992 New_List (Make_Others_Choice (Loc)),
10993 Statements =>
10994 New_List (Make_Goto_Statement (Loc,
10995 Name => New_Copy (Identifier (End_Lab))))));
10997 Accept_Case := New_List (
10998 Make_Case_Statement (Loc,
10999 Expression => New_Reference_To (Xnam, Loc),
11000 Alternatives => Alt_List));
11002 Append_List (Trailing_List, Accept_Case);
11003 Append_List (Body_List, Decls);
11005 -- Construct case statement for trailing statements of delay
11006 -- alternatives, if there are several of them.
11008 if Delay_Count > 1 then
11009 Append_To (Delay_Alt_List,
11010 Make_Case_Statement_Alternative (Loc,
11011 Discrete_Choices =>
11012 New_List (Make_Others_Choice (Loc)),
11013 Statements =>
11014 New_List (Make_Null_Statement (Loc))));
11016 Delay_Case := New_List (
11017 Make_Case_Statement (Loc,
11018 Expression => New_Reference_To (Delay_Index, Loc),
11019 Alternatives => Delay_Alt_List));
11020 else
11021 Delay_Case := Delay_Alt_List;
11022 end if;
11024 -- If there are no delay alternatives, we append the case statement
11025 -- to the statement list.
11027 if Delay_Count = 0 then
11028 Append_List (Accept_Case, Stats);
11030 -- Delay alternatives present
11032 else
11033 -- If delay alternatives are present we generate:
11035 -- find minimum delay.
11036 -- DX := minimum delay;
11037 -- M := <delay mode>;
11038 -- Timed_Selective_Wait (Q'Unchecked_Access, Delay_Mode, P,
11039 -- DX, MX, X);
11041 -- if X = No_Rendezvous then
11042 -- case statement for delay statements.
11043 -- else
11044 -- case statement for accept alternatives.
11045 -- end if;
11047 declare
11048 Cases : Node_Id;
11049 Stmt : Node_Id;
11050 Parms : List_Id;
11051 Parm : Node_Id;
11052 Conv : Node_Id;
11054 begin
11055 -- The type of the delay expression is known to be legal
11057 if Time_Type = Standard_Duration then
11058 Conv := New_Reference_To (Delay_Min, Loc);
11060 elsif Is_RTE (Base_Type (Etype (Time_Type)), RO_CA_Time) then
11061 Conv := Make_Function_Call (Loc,
11062 New_Reference_To (RTE (RO_CA_To_Duration), Loc),
11063 New_List (New_Reference_To (Delay_Min, Loc)));
11065 else
11066 pragma Assert
11067 (Is_RTE (Base_Type (Etype (Time_Type)), RO_RT_Time));
11069 Conv := Make_Function_Call (Loc,
11070 New_Reference_To (RTE (RO_RT_To_Duration), Loc),
11071 New_List (New_Reference_To (Delay_Min, Loc)));
11072 end if;
11074 Stmt := Make_Assignment_Statement (Loc,
11075 Name => New_Reference_To (D, Loc),
11076 Expression => Conv);
11078 -- Change the value for Accept_Modes. (Else_Mode -> Delay_Mode)
11080 Parms := Parameter_Associations (Select_Call);
11081 Parm := First (Parms);
11083 while Present (Parm) and then Parm /= Select_Mode loop
11084 Next (Parm);
11085 end loop;
11087 pragma Assert (Present (Parm));
11088 Rewrite (Parm, New_Reference_To (RTE (RE_Delay_Mode), Loc));
11089 Analyze (Parm);
11091 -- Prepare two new parameters of Duration and Delay_Mode type
11092 -- which represent the value and the mode of the minimum delay.
11094 Next (Parm);
11095 Insert_After (Parm, New_Reference_To (M, Loc));
11096 Insert_After (Parm, New_Reference_To (D, Loc));
11098 -- Create a call to RTS
11100 Rewrite (Select_Call,
11101 Make_Procedure_Call_Statement (Loc,
11102 Name => New_Reference_To (RTE (RE_Timed_Selective_Wait), Loc),
11103 Parameter_Associations => Parms));
11105 -- This new call should follow the calculation of the minimum
11106 -- delay.
11108 Insert_List_Before (Select_Call, Delay_List);
11110 if Check_Guard then
11111 Stmt :=
11112 Make_Implicit_If_Statement (N,
11113 Condition => New_Reference_To (Guard_Open, Loc),
11114 Then_Statements => New_List (
11115 New_Copy_Tree (Stmt),
11116 New_Copy_Tree (Select_Call)),
11117 Else_Statements => Accept_Or_Raise);
11118 Rewrite (Select_Call, Stmt);
11119 else
11120 Insert_Before (Select_Call, Stmt);
11121 end if;
11123 Cases :=
11124 Make_Implicit_If_Statement (N,
11125 Condition => Make_Op_Eq (Loc,
11126 Left_Opnd => New_Reference_To (Xnam, Loc),
11127 Right_Opnd =>
11128 New_Reference_To (RTE (RE_No_Rendezvous), Loc)),
11130 Then_Statements => Delay_Case,
11131 Else_Statements => Accept_Case);
11133 Append (Cases, Stats);
11134 end;
11135 end if;
11136 Append (End_Lab, Stats);
11138 -- Replace accept statement with appropriate block
11140 Rewrite (N,
11141 Make_Block_Statement (Loc,
11142 Declarations => Decls,
11143 Handled_Statement_Sequence =>
11144 Make_Handled_Sequence_Of_Statements (Loc, Statements => Stats)));
11145 Analyze (N);
11147 -- Note: have to worry more about abort deferral in above code ???
11149 -- Final step is to unstack the Accept_Address entries for all accept
11150 -- statements appearing in accept alternatives in the select statement
11152 Alt := First (Alts);
11153 while Present (Alt) loop
11154 if Nkind (Alt) = N_Accept_Alternative then
11155 Remove_Last_Elmt (Accept_Address
11156 (Entity (Entry_Direct_Name (Accept_Statement (Alt)))));
11157 end if;
11159 Next (Alt);
11160 end loop;
11161 end Expand_N_Selective_Accept;
11163 --------------------------------------
11164 -- Expand_N_Single_Task_Declaration --
11165 --------------------------------------
11167 -- Single task declarations should never be present after semantic
11168 -- analysis, since we expect them to be replaced by a declaration of an
11169 -- anonymous task type, followed by a declaration of the task object. We
11170 -- include this routine to make sure that is happening!
11172 procedure Expand_N_Single_Task_Declaration (N : Node_Id) is
11173 begin
11174 raise Program_Error;
11175 end Expand_N_Single_Task_Declaration;
11177 ------------------------
11178 -- Expand_N_Task_Body --
11179 ------------------------
11181 -- Given a task body
11183 -- task body tname is
11184 -- <declarations>
11185 -- begin
11186 -- <statements>
11187 -- end x;
11189 -- This expansion routine converts it into a procedure and sets the
11190 -- elaboration flag for the procedure to true, to represent the fact
11191 -- that the task body is now elaborated:
11193 -- procedure tnameB (_Task : access tnameV) is
11194 -- discriminal : dtype renames _Task.discriminant;
11196 -- procedure _clean is
11197 -- begin
11198 -- Abort_Defer.all;
11199 -- Complete_Task;
11200 -- Abort_Undefer.all;
11201 -- return;
11202 -- end _clean;
11204 -- begin
11205 -- Abort_Undefer.all;
11206 -- <declarations>
11207 -- System.Task_Stages.Complete_Activation;
11208 -- <statements>
11209 -- at end
11210 -- _clean;
11211 -- end tnameB;
11213 -- tnameE := True;
11215 -- In addition, if the task body is an activator, then a call to activate
11216 -- tasks is added at the start of the statements, before the call to
11217 -- Complete_Activation, and if in addition the task is a master then it
11218 -- must be established as a master. These calls are inserted and analyzed
11219 -- in Expand_Cleanup_Actions, when the Handled_Sequence_Of_Statements is
11220 -- expanded.
11222 -- There is one discriminal declaration line generated for each
11223 -- discriminant that is present to provide an easy reference point for
11224 -- discriminant references inside the body (see Exp_Ch2.Expand_Name).
11226 -- Note on relationship to GNARLI definition. In the GNARLI definition,
11227 -- task body procedures have a profile (Arg : System.Address). That is
11228 -- needed because GNARLI has to use the same access-to-subprogram type
11229 -- for all task types. We depend here on knowing that in GNAT, passing
11230 -- an address argument by value is identical to passing a record value
11231 -- by access (in either case a single pointer is passed), so even though
11232 -- this procedure has the wrong profile. In fact it's all OK, since the
11233 -- callings sequence is identical.
11235 procedure Expand_N_Task_Body (N : Node_Id) is
11236 Loc : constant Source_Ptr := Sloc (N);
11237 Ttyp : constant Entity_Id := Corresponding_Spec (N);
11238 Call : Node_Id;
11239 New_N : Node_Id;
11241 Insert_Nod : Node_Id;
11242 -- Used to determine the proper location of wrapper body insertions
11244 begin
11245 -- Add renaming declarations for discriminals and a declaration for the
11246 -- entry family index (if applicable).
11248 Install_Private_Data_Declarations
11249 (Loc, Task_Body_Procedure (Ttyp), Ttyp, N, Declarations (N));
11251 -- Add a call to Abort_Undefer at the very beginning of the task
11252 -- body since this body is called with abort still deferred.
11254 if Abort_Allowed then
11255 Call := Build_Runtime_Call (Loc, RE_Abort_Undefer);
11256 Insert_Before
11257 (First (Statements (Handled_Statement_Sequence (N))), Call);
11258 Analyze (Call);
11259 end if;
11261 -- The statement part has already been protected with an at_end and
11262 -- cleanup actions. The call to Complete_Activation must be placed
11263 -- at the head of the sequence of statements of that block. The
11264 -- declarations have been merged in this sequence of statements but
11265 -- the first real statement is accessible from the First_Real_Statement
11266 -- field (which was set for exactly this purpose).
11268 if Restricted_Profile then
11269 Call := Build_Runtime_Call (Loc, RE_Complete_Restricted_Activation);
11270 else
11271 Call := Build_Runtime_Call (Loc, RE_Complete_Activation);
11272 end if;
11274 Insert_Before
11275 (First_Real_Statement (Handled_Statement_Sequence (N)), Call);
11276 Analyze (Call);
11278 New_N :=
11279 Make_Subprogram_Body (Loc,
11280 Specification => Build_Task_Proc_Specification (Ttyp),
11281 Declarations => Declarations (N),
11282 Handled_Statement_Sequence => Handled_Statement_Sequence (N));
11284 -- If the task contains generic instantiations, cleanup actions are
11285 -- delayed until after instantiation. Transfer the activation chain to
11286 -- the subprogram, to insure that the activation call is properly
11287 -- generated. It the task body contains inner tasks, indicate that the
11288 -- subprogram is a task master.
11290 if Delay_Cleanups (Ttyp) then
11291 Set_Activation_Chain_Entity (New_N, Activation_Chain_Entity (N));
11292 Set_Is_Task_Master (New_N, Is_Task_Master (N));
11293 end if;
11295 Rewrite (N, New_N);
11296 Analyze (N);
11298 -- Set elaboration flag immediately after task body. If the body is a
11299 -- subunit, the flag is set in the declarative part containing the stub.
11301 if Nkind (Parent (N)) /= N_Subunit then
11302 Insert_After (N,
11303 Make_Assignment_Statement (Loc,
11304 Name =>
11305 Make_Identifier (Loc, New_External_Name (Chars (Ttyp), 'E')),
11306 Expression => New_Reference_To (Standard_True, Loc)));
11307 end if;
11309 -- Ada 2005 (AI-345): Construct the primitive entry wrapper bodies after
11310 -- the task body. At this point all wrapper specs have been created,
11311 -- frozen and included in the dispatch table for the task type.
11313 if Ada_Version >= Ada_2005 then
11314 if Nkind (Parent (N)) = N_Subunit then
11315 Insert_Nod := Corresponding_Stub (Parent (N));
11316 else
11317 Insert_Nod := N;
11318 end if;
11320 Build_Wrapper_Bodies (Loc, Ttyp, Insert_Nod);
11321 end if;
11322 end Expand_N_Task_Body;
11324 ------------------------------------
11325 -- Expand_N_Task_Type_Declaration --
11326 ------------------------------------
11328 -- We have several things to do. First we must create a Boolean flag used
11329 -- to mark if the body is elaborated yet. This variable gets set to True
11330 -- when the body of the task is elaborated (we can't rely on the normal
11331 -- ABE mechanism for the task body, since we need to pass an access to
11332 -- this elaboration boolean to the runtime routines).
11334 -- taskE : aliased Boolean := False;
11336 -- Next a variable is declared to hold the task stack size (either the
11337 -- default : Unspecified_Size, or a value that is set by a pragma
11338 -- Storage_Size). If the value of the pragma Storage_Size is static, then
11339 -- the variable is initialized with this value:
11341 -- taskZ : Size_Type := Unspecified_Size;
11342 -- or
11343 -- taskZ : Size_Type := Size_Type (size_expression);
11345 -- Note: No variable is needed to hold the task relative deadline since
11346 -- its value would never be static because the parameter is of a private
11347 -- type (Ada.Real_Time.Time_Span).
11349 -- Next we create a corresponding record type declaration used to represent
11350 -- values of this task. The general form of this type declaration is
11352 -- type taskV (discriminants) is record
11353 -- _Task_Id : Task_Id;
11354 -- entry_family : array (bounds) of Void;
11355 -- _Priority : Integer := priority_expression;
11356 -- _Size : Size_Type := size_expression;
11357 -- _Task_Info : Task_Info_Type := task_info_expression;
11358 -- _CPU : Integer := cpu_range_expression;
11359 -- _Relative_Deadline : Time_Span := time_span_expression;
11360 -- _Domain : Dispatching_Domain := dd_expression;
11361 -- end record;
11363 -- The discriminants are present only if the corresponding task type has
11364 -- discriminants, and they exactly mirror the task type discriminants.
11366 -- The Id field is always present. It contains the Task_Id value, as set by
11367 -- the call to Create_Task. Note that although the task is limited, the
11368 -- task value record type is not limited, so there is no problem in passing
11369 -- this field as an out parameter to Create_Task.
11371 -- One entry_family component is present for each entry family in the task
11372 -- definition. The bounds correspond to the bounds of the entry family
11373 -- (which may depend on discriminants). The element type is void, since we
11374 -- only need the bounds information for determining the entry index. Note
11375 -- that the use of an anonymous array would normally be illegal in this
11376 -- context, but this is a parser check, and the semantics is quite prepared
11377 -- to handle such a case.
11379 -- The _Size field is present only if a Storage_Size pragma appears in the
11380 -- task definition. The expression captures the argument that was present
11381 -- in the pragma, and is used to override the task stack size otherwise
11382 -- associated with the task type.
11384 -- The _Priority field is present only if the task entity has a Priority or
11385 -- Interrupt_Priority rep item (pragma, aspect specification or attribute
11386 -- definition clause). It will be filled at the freeze point, when the
11387 -- record init proc is built, to capture the expression of the rep item
11388 -- (see Build_Record_Init_Proc in Exp_Ch3). Note that it cannot be filled
11389 -- here since aspect evaluations are delayed till the freeze point.
11391 -- The _Task_Info field is present only if a Task_Info pragma appears in
11392 -- the task definition. The expression captures the argument that was
11393 -- present in the pragma, and is used to provide the Task_Image parameter
11394 -- to the call to Create_Task.
11396 -- The _CPU field is present only if the task entity has a CPU rep item
11397 -- (pragma, aspect specification or attribute definition clause). It will
11398 -- be filled at the freeze point, when the record init proc is built, to
11399 -- capture the expression of the rep item (see Build_Record_Init_Proc in
11400 -- Exp_Ch3). Note that it cannot be filled here since aspect evaluations
11401 -- are delayed till the freeze point.
11403 -- The _Relative_Deadline field is present only if a Relative_Deadline
11404 -- pragma appears in the task definition. The expression captures the
11405 -- argument that was present in the pragma, and is used to provide the
11406 -- Relative_Deadline parameter to the call to Create_Task.
11408 -- The _Domain field is present only if the task entity has a
11409 -- Dispatching_Domain rep item (pragma, aspect specification or attribute
11410 -- definition clause). It will be filled at the freeze point, when the
11411 -- record init proc is built, to capture the expression of the rep item
11412 -- (see Build_Record_Init_Proc in Exp_Ch3). Note that it cannot be filled
11413 -- here since aspect evaluations are delayed till the freeze point.
11415 -- When a task is declared, an instance of the task value record is
11416 -- created. The elaboration of this declaration creates the correct bounds
11417 -- for the entry families, and also evaluates the size, priority, and
11418 -- task_Info expressions if needed. The initialization routine for the task
11419 -- type itself then calls Create_Task with appropriate parameters to
11420 -- initialize the value of the Task_Id field.
11422 -- Note: the address of this record is passed as the "Discriminants"
11423 -- parameter for Create_Task. Since Create_Task merely passes this onto the
11424 -- body procedure, it does not matter that it does not quite match the
11425 -- GNARLI model of what is being passed (the record contains more than just
11426 -- the discriminants, but the discriminants can be found from the record
11427 -- value).
11429 -- The Entity_Id for this created record type is placed in the
11430 -- Corresponding_Record_Type field of the associated task type entity.
11432 -- Next we create a procedure specification for the task body procedure:
11434 -- procedure taskB (_Task : access taskV);
11436 -- Note that this must come after the record type declaration, since
11437 -- the spec refers to this type. It turns out that the initialization
11438 -- procedure for the value type references the task body spec, but that's
11439 -- fine, since it won't be generated till the freeze point for the type,
11440 -- which is certainly after the task body spec declaration.
11442 -- Finally, we set the task index value field of the entry attribute in
11443 -- the case of a simple entry.
11445 procedure Expand_N_Task_Type_Declaration (N : Node_Id) is
11446 Loc : constant Source_Ptr := Sloc (N);
11447 TaskId : constant Entity_Id := Defining_Identifier (N);
11448 Tasktyp : constant Entity_Id := Etype (Defining_Identifier (N));
11449 Tasknm : constant Name_Id := Chars (Tasktyp);
11450 Taskdef : constant Node_Id := Task_Definition (N);
11452 Body_Decl : Node_Id;
11453 Cdecls : List_Id;
11454 Decl_Stack : Node_Id;
11455 Elab_Decl : Node_Id;
11456 Ent_Stack : Entity_Id;
11457 Proc_Spec : Node_Id;
11458 Rec_Decl : Node_Id;
11459 Rec_Ent : Entity_Id;
11460 Size_Decl : Entity_Id;
11461 Task_Size : Node_Id;
11463 function Get_Relative_Deadline_Pragma (T : Node_Id) return Node_Id;
11464 -- Searches the task definition T for the first occurrence of the pragma
11465 -- Relative Deadline. The caller has ensured that the pragma is present
11466 -- in the task definition. Note that this routine cannot be implemented
11467 -- with the Rep Item chain mechanism since Relative_Deadline pragmas are
11468 -- not chained because their expansion into a procedure call statement
11469 -- would cause a break in the chain.
11471 ----------------------------------
11472 -- Get_Relative_Deadline_Pragma --
11473 ----------------------------------
11475 function Get_Relative_Deadline_Pragma (T : Node_Id) return Node_Id is
11476 N : Node_Id;
11478 begin
11479 N := First (Visible_Declarations (T));
11480 while Present (N) loop
11481 if Nkind (N) = N_Pragma
11482 and then Pragma_Name (N) = Name_Relative_Deadline
11483 then
11484 return N;
11485 end if;
11487 Next (N);
11488 end loop;
11490 N := First (Private_Declarations (T));
11491 while Present (N) loop
11492 if Nkind (N) = N_Pragma
11493 and then Pragma_Name (N) = Name_Relative_Deadline
11494 then
11495 return N;
11496 end if;
11498 Next (N);
11499 end loop;
11501 raise Program_Error;
11502 end Get_Relative_Deadline_Pragma;
11504 -- Start of processing for Expand_N_Task_Type_Declaration
11506 begin
11507 -- If already expanded, nothing to do
11509 if Present (Corresponding_Record_Type (Tasktyp)) then
11510 return;
11511 end if;
11513 -- Here we will do the expansion
11515 Rec_Decl := Build_Corresponding_Record (N, Tasktyp, Loc);
11517 Rec_Ent := Defining_Identifier (Rec_Decl);
11518 Cdecls := Component_Items (Component_List
11519 (Type_Definition (Rec_Decl)));
11521 Qualify_Entity_Names (N);
11523 -- First create the elaboration variable
11525 Elab_Decl :=
11526 Make_Object_Declaration (Loc,
11527 Defining_Identifier =>
11528 Make_Defining_Identifier (Sloc (Tasktyp),
11529 Chars => New_External_Name (Tasknm, 'E')),
11530 Aliased_Present => True,
11531 Object_Definition => New_Reference_To (Standard_Boolean, Loc),
11532 Expression => New_Reference_To (Standard_False, Loc));
11534 Insert_After (N, Elab_Decl);
11536 -- Next create the declaration of the size variable (tasknmZ)
11538 Set_Storage_Size_Variable (Tasktyp,
11539 Make_Defining_Identifier (Sloc (Tasktyp),
11540 Chars => New_External_Name (Tasknm, 'Z')));
11542 if Present (Taskdef)
11543 and then Has_Storage_Size_Pragma (Taskdef)
11544 and then
11545 Is_Static_Expression
11546 (Expression
11547 (First (Pragma_Argument_Associations
11548 (Get_Rep_Pragma (TaskId, Name_Storage_Size)))))
11549 then
11550 Size_Decl :=
11551 Make_Object_Declaration (Loc,
11552 Defining_Identifier => Storage_Size_Variable (Tasktyp),
11553 Object_Definition => New_Reference_To (RTE (RE_Size_Type), Loc),
11554 Expression =>
11555 Convert_To (RTE (RE_Size_Type),
11556 Relocate_Node
11557 (Expression (First (Pragma_Argument_Associations
11558 (Get_Rep_Pragma
11559 (TaskId, Name_Storage_Size)))))));
11561 else
11562 Size_Decl :=
11563 Make_Object_Declaration (Loc,
11564 Defining_Identifier => Storage_Size_Variable (Tasktyp),
11565 Object_Definition =>
11566 New_Reference_To (RTE (RE_Size_Type), Loc),
11567 Expression =>
11568 New_Reference_To (RTE (RE_Unspecified_Size), Loc));
11569 end if;
11571 Insert_After (Elab_Decl, Size_Decl);
11573 -- Next build the rest of the corresponding record declaration. This is
11574 -- done last, since the corresponding record initialization procedure
11575 -- will reference the previously created entities.
11577 -- Fill in the component declarations -- first the _Task_Id field
11579 Append_To (Cdecls,
11580 Make_Component_Declaration (Loc,
11581 Defining_Identifier =>
11582 Make_Defining_Identifier (Loc, Name_uTask_Id),
11583 Component_Definition =>
11584 Make_Component_Definition (Loc,
11585 Aliased_Present => False,
11586 Subtype_Indication => New_Reference_To (RTE (RO_ST_Task_Id),
11587 Loc))));
11589 -- Declare static ATCB (that is, created by the expander) if we are
11590 -- using the Restricted run time.
11592 if Restricted_Profile then
11593 Append_To (Cdecls,
11594 Make_Component_Declaration (Loc,
11595 Defining_Identifier =>
11596 Make_Defining_Identifier (Loc, Name_uATCB),
11598 Component_Definition =>
11599 Make_Component_Definition (Loc,
11600 Aliased_Present => True,
11601 Subtype_Indication => Make_Subtype_Indication (Loc,
11602 Subtype_Mark =>
11603 New_Occurrence_Of (RTE (RE_Ada_Task_Control_Block), Loc),
11605 Constraint =>
11606 Make_Index_Or_Discriminant_Constraint (Loc,
11607 Constraints =>
11608 New_List (Make_Integer_Literal (Loc, 0)))))));
11610 end if;
11612 -- Declare static stack (that is, created by the expander) if we are
11613 -- using the Restricted run time on a bare board configuration.
11615 if Restricted_Profile
11616 and then Preallocated_Stacks_On_Target
11617 then
11618 -- First we need to extract the appropriate stack size
11620 Ent_Stack := Make_Defining_Identifier (Loc, Name_uStack);
11622 if Present (Taskdef) and then Has_Storage_Size_Pragma (Taskdef) then
11623 declare
11624 Expr_N : constant Node_Id :=
11625 Expression (First (
11626 Pragma_Argument_Associations (
11627 Get_Rep_Pragma (TaskId, Name_Storage_Size))));
11628 Etyp : constant Entity_Id := Etype (Expr_N);
11629 P : constant Node_Id := Parent (Expr_N);
11631 begin
11632 -- The stack is defined inside the corresponding record.
11633 -- Therefore if the size of the stack is set by means of
11634 -- a discriminant, we must reference the discriminant of the
11635 -- corresponding record type.
11637 if Nkind (Expr_N) in N_Has_Entity
11638 and then Present (Discriminal_Link (Entity (Expr_N)))
11639 then
11640 Task_Size :=
11641 New_Reference_To
11642 (CR_Discriminant (Discriminal_Link (Entity (Expr_N))),
11643 Loc);
11644 Set_Parent (Task_Size, P);
11645 Set_Etype (Task_Size, Etyp);
11646 Set_Analyzed (Task_Size);
11648 else
11649 Task_Size := Relocate_Node (Expr_N);
11650 end if;
11651 end;
11653 else
11654 Task_Size :=
11655 New_Reference_To (RTE (RE_Default_Stack_Size), Loc);
11656 end if;
11658 Decl_Stack := Make_Component_Declaration (Loc,
11659 Defining_Identifier => Ent_Stack,
11661 Component_Definition =>
11662 Make_Component_Definition (Loc,
11663 Aliased_Present => True,
11664 Subtype_Indication => Make_Subtype_Indication (Loc,
11665 Subtype_Mark =>
11666 New_Occurrence_Of (RTE (RE_Storage_Array), Loc),
11668 Constraint =>
11669 Make_Index_Or_Discriminant_Constraint (Loc,
11670 Constraints => New_List (Make_Range (Loc,
11671 Low_Bound => Make_Integer_Literal (Loc, 1),
11672 High_Bound => Convert_To (RTE (RE_Storage_Offset),
11673 Task_Size)))))));
11675 Append_To (Cdecls, Decl_Stack);
11677 -- The appropriate alignment for the stack is ensured by the run-time
11678 -- code in charge of task creation.
11680 end if;
11682 -- Add components for entry families
11684 Collect_Entry_Families (Loc, Cdecls, Size_Decl, Tasktyp);
11686 -- Add the _Priority component if a Interrupt_Priority or Priority rep
11687 -- item is present.
11689 if Has_Rep_Item (TaskId, Name_Priority, Check_Parents => False) then
11690 Append_To (Cdecls,
11691 Make_Component_Declaration (Loc,
11692 Defining_Identifier =>
11693 Make_Defining_Identifier (Loc, Name_uPriority),
11694 Component_Definition =>
11695 Make_Component_Definition (Loc,
11696 Aliased_Present => False,
11697 Subtype_Indication =>
11698 New_Reference_To (Standard_Integer, Loc))));
11699 end if;
11701 -- Add the _Size component if a Storage_Size pragma is present
11703 if Present (Taskdef)
11704 and then Has_Storage_Size_Pragma (Taskdef)
11705 then
11706 Append_To (Cdecls,
11707 Make_Component_Declaration (Loc,
11708 Defining_Identifier =>
11709 Make_Defining_Identifier (Loc, Name_uSize),
11711 Component_Definition =>
11712 Make_Component_Definition (Loc,
11713 Aliased_Present => False,
11714 Subtype_Indication =>
11715 New_Reference_To (RTE (RE_Size_Type), Loc)),
11717 Expression =>
11718 Convert_To (RTE (RE_Size_Type),
11719 Relocate_Node (
11720 Expression (First (
11721 Pragma_Argument_Associations (
11722 Get_Rep_Pragma (TaskId, Name_Storage_Size))))))));
11723 end if;
11725 -- Add the _Task_Info component if a Task_Info pragma is present
11727 if Has_Rep_Pragma (TaskId, Name_Task_Info, Check_Parents => False) then
11728 Append_To (Cdecls,
11729 Make_Component_Declaration (Loc,
11730 Defining_Identifier =>
11731 Make_Defining_Identifier (Loc, Name_uTask_Info),
11733 Component_Definition =>
11734 Make_Component_Definition (Loc,
11735 Aliased_Present => False,
11736 Subtype_Indication =>
11737 New_Reference_To (RTE (RE_Task_Info_Type), Loc)),
11739 Expression => New_Copy (
11740 Expression (First (
11741 Pragma_Argument_Associations (
11742 Get_Rep_Pragma
11743 (TaskId, Name_Task_Info, Check_Parents => False)))))));
11744 end if;
11746 -- Add the _CPU component if a CPU rep item is present
11748 if Has_Rep_Item (TaskId, Name_CPU, Check_Parents => False) then
11749 Append_To (Cdecls,
11750 Make_Component_Declaration (Loc,
11751 Defining_Identifier =>
11752 Make_Defining_Identifier (Loc, Name_uCPU),
11754 Component_Definition =>
11755 Make_Component_Definition (Loc,
11756 Aliased_Present => False,
11757 Subtype_Indication =>
11758 New_Reference_To (RTE (RE_CPU_Range), Loc))));
11759 end if;
11761 -- Add the _Relative_Deadline component if a Relative_Deadline pragma is
11762 -- present. If we are using a restricted run time this component will
11763 -- not be added (deadlines are not allowed by the Ravenscar profile).
11765 if not Restricted_Profile
11766 and then Present (Taskdef)
11767 and then Has_Relative_Deadline_Pragma (Taskdef)
11768 then
11769 Append_To (Cdecls,
11770 Make_Component_Declaration (Loc,
11771 Defining_Identifier =>
11772 Make_Defining_Identifier (Loc, Name_uRelative_Deadline),
11774 Component_Definition =>
11775 Make_Component_Definition (Loc,
11776 Aliased_Present => False,
11777 Subtype_Indication =>
11778 New_Reference_To (RTE (RE_Time_Span), Loc)),
11780 Expression =>
11781 Convert_To (RTE (RE_Time_Span),
11782 Relocate_Node (
11783 Expression (First (
11784 Pragma_Argument_Associations (
11785 Get_Relative_Deadline_Pragma (Taskdef))))))));
11786 end if;
11788 -- Add the _Dispatching_Domain component if a Dispatching_Domain rep
11789 -- item is present. If we are using a restricted run time this component
11790 -- will not be added (dispatching domains are not allowed by the
11791 -- Ravenscar profile).
11793 if not Restricted_Profile
11794 and then
11795 Has_Rep_Item
11796 (TaskId, Name_Dispatching_Domain, Check_Parents => False)
11797 then
11798 Append_To (Cdecls,
11799 Make_Component_Declaration (Loc,
11800 Defining_Identifier =>
11801 Make_Defining_Identifier (Loc, Name_uDispatching_Domain),
11803 Component_Definition =>
11804 Make_Component_Definition (Loc,
11805 Aliased_Present => False,
11806 Subtype_Indication =>
11807 New_Reference_To
11808 (RTE (RE_Dispatching_Domain_Access), Loc))));
11809 end if;
11811 Insert_After (Size_Decl, Rec_Decl);
11813 -- Analyze the record declaration immediately after construction,
11814 -- because the initialization procedure is needed for single task
11815 -- declarations before the next entity is analyzed.
11817 Analyze (Rec_Decl);
11819 -- Create the declaration of the task body procedure
11821 Proc_Spec := Build_Task_Proc_Specification (Tasktyp);
11822 Body_Decl :=
11823 Make_Subprogram_Declaration (Loc,
11824 Specification => Proc_Spec);
11826 Insert_After (Rec_Decl, Body_Decl);
11828 -- The subprogram does not comes from source, so we have to indicate the
11829 -- need for debugging information explicitly.
11831 if Comes_From_Source (Original_Node (N)) then
11832 Set_Debug_Info_Needed (Defining_Entity (Proc_Spec));
11833 end if;
11835 -- Ada 2005 (AI-345): Construct the primitive entry wrapper specs before
11836 -- the corresponding record has been frozen.
11838 if Ada_Version >= Ada_2005 then
11839 Build_Wrapper_Specs (Loc, Tasktyp, Rec_Decl);
11840 end if;
11842 -- Ada 2005 (AI-345): We must defer freezing to allow further
11843 -- declaration of primitive subprograms covering task interfaces
11845 if Ada_Version <= Ada_95 then
11847 -- Now we can freeze the corresponding record. This needs manually
11848 -- freezing, since it is really part of the task type, and the task
11849 -- type is frozen at this stage. We of course need the initialization
11850 -- procedure for this corresponding record type and we won't get it
11851 -- in time if we don't freeze now.
11853 declare
11854 L : constant List_Id := Freeze_Entity (Rec_Ent, N);
11855 begin
11856 if Is_Non_Empty_List (L) then
11857 Insert_List_After (Body_Decl, L);
11858 end if;
11859 end;
11860 end if;
11862 -- Complete the expansion of access types to the current task type, if
11863 -- any were declared.
11865 Expand_Previous_Access_Type (Tasktyp);
11867 -- Create wrappers for entries that have pre/postconditions
11869 declare
11870 Ent : Entity_Id;
11872 begin
11873 Ent := First_Entity (Tasktyp);
11874 while Present (Ent) loop
11875 if Ekind_In (Ent, E_Entry, E_Entry_Family)
11876 and then Present (Pre_Post_Conditions (Contract (Ent)))
11877 then
11878 Build_PPC_Wrapper (Ent, N);
11879 end if;
11881 Next_Entity (Ent);
11882 end loop;
11883 end;
11884 end Expand_N_Task_Type_Declaration;
11886 -------------------------------
11887 -- Expand_N_Timed_Entry_Call --
11888 -------------------------------
11890 -- A timed entry call in normal case is not implemented using ATC mechanism
11891 -- anymore for efficiency reason.
11893 -- select
11894 -- T.E;
11895 -- S1;
11896 -- or
11897 -- delay D;
11898 -- S2;
11899 -- end select;
11901 -- is expanded as follows:
11903 -- 1) When T.E is a task entry_call;
11905 -- declare
11906 -- B : Boolean;
11907 -- X : Task_Entry_Index := <entry index>;
11908 -- DX : Duration := To_Duration (D);
11909 -- M : Delay_Mode := <discriminant>;
11910 -- P : parms := (parm, parm, parm);
11912 -- begin
11913 -- Timed_Protected_Entry_Call
11914 -- (<acceptor-task>, X, P'Address, DX, M, B);
11915 -- if B then
11916 -- S1;
11917 -- else
11918 -- S2;
11919 -- end if;
11920 -- end;
11922 -- 2) When T.E is a protected entry_call;
11924 -- declare
11925 -- B : Boolean;
11926 -- X : Protected_Entry_Index := <entry index>;
11927 -- DX : Duration := To_Duration (D);
11928 -- M : Delay_Mode := <discriminant>;
11929 -- P : parms := (parm, parm, parm);
11931 -- begin
11932 -- Timed_Protected_Entry_Call
11933 -- (<object>'unchecked_access, X, P'Address, DX, M, B);
11934 -- if B then
11935 -- S1;
11936 -- else
11937 -- S2;
11938 -- end if;
11939 -- end;
11941 -- 3) Ada 2005 (AI-345): When T.E is a dispatching procedure call;
11943 -- declare
11944 -- B : Boolean := False;
11945 -- C : Ada.Tags.Prim_Op_Kind;
11946 -- DX : Duration := To_Duration (D)
11947 -- K : Ada.Tags.Tagged_Kind :=
11948 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
11949 -- M : Integer :=...;
11950 -- P : Parameters := (Param1 .. ParamN);
11951 -- S : Integer;
11953 -- begin
11954 -- if K = Ada.Tags.TK_Limited_Tagged then
11955 -- <dispatching-call>;
11956 -- <triggering-statements>
11958 -- else
11959 -- S :=
11960 -- Ada.Tags.Get_Offset_Index
11961 -- (Ada.Tags.Tag (<object>), DT_Position (<dispatching-call>));
11963 -- _Disp_Timed_Select (<object>, S, P'Address, DX, M, C, B);
11965 -- if C = POK_Protected_Entry
11966 -- or else C = POK_Task_Entry
11967 -- then
11968 -- Param1 := P.Param1;
11969 -- ...
11970 -- ParamN := P.ParamN;
11971 -- end if;
11973 -- if B then
11974 -- if C = POK_Procedure
11975 -- or else C = POK_Protected_Procedure
11976 -- or else C = POK_Task_Procedure
11977 -- then
11978 -- <dispatching-call>;
11979 -- end if;
11981 -- <triggering-statements>
11982 -- else
11983 -- <timed-statements>
11984 -- end if;
11985 -- end if;
11986 -- end;
11988 -- The triggering statement and the sequence of timed statements have not
11989 -- been analyzed yet (see Analyzed_Timed_Entry_Call). They may contain
11990 -- local declarations, and therefore the copies that are made during
11991 -- expansion must be disjoint, as for any other inlining.
11993 procedure Expand_N_Timed_Entry_Call (N : Node_Id) is
11994 Loc : constant Source_Ptr := Sloc (N);
11996 Actuals : List_Id;
11997 Blk_Typ : Entity_Id;
11998 Call : Node_Id;
11999 Call_Ent : Entity_Id;
12000 Conc_Typ_Stmts : List_Id;
12001 Concval : Node_Id;
12002 D_Alt : constant Node_Id := Delay_Alternative (N);
12003 D_Conv : Node_Id;
12004 D_Disc : Node_Id;
12005 D_Stat : Node_Id := Delay_Statement (D_Alt);
12006 D_Stats : List_Id;
12007 D_Type : Entity_Id;
12008 Decls : List_Id;
12009 Dummy : Node_Id;
12010 E_Alt : constant Node_Id := Entry_Call_Alternative (N);
12011 E_Call : Node_Id := Entry_Call_Statement (E_Alt);
12012 E_Stats : List_Id;
12013 Ename : Node_Id;
12014 Formals : List_Id;
12015 Index : Node_Id;
12016 Is_Disp_Select : Boolean;
12017 Lim_Typ_Stmts : List_Id;
12018 N_Stats : List_Id;
12019 Obj : Entity_Id;
12020 Param : Node_Id;
12021 Params : List_Id;
12022 Stmt : Node_Id;
12023 Stmts : List_Id;
12024 Unpack : List_Id;
12026 B : Entity_Id; -- Call status flag
12027 C : Entity_Id; -- Call kind
12028 D : Entity_Id; -- Delay
12029 K : Entity_Id; -- Tagged kind
12030 M : Entity_Id; -- Delay mode
12031 P : Entity_Id; -- Parameter block
12032 S : Entity_Id; -- Primitive operation slot
12034 begin
12035 -- Under the Ravenscar profile, timed entry calls are excluded. An error
12036 -- was already reported on spec, so do not attempt to expand the call.
12038 if Restriction_Active (No_Select_Statements) then
12039 return;
12040 end if;
12042 Process_Statements_For_Controlled_Objects (E_Alt);
12043 Process_Statements_For_Controlled_Objects (D_Alt);
12045 Ensure_Statement_Present (Sloc (D_Stat), D_Alt);
12047 -- Retrieve E_Stats and D_Stats now because the finalization machinery
12048 -- may wrap them in blocks.
12050 E_Stats := Statements (E_Alt);
12051 D_Stats := Statements (D_Alt);
12053 -- The arguments in the call may require dynamic allocation, and the
12054 -- call statement may have been transformed into a block. The block
12055 -- may contain additional declarations for internal entities, and the
12056 -- original call is found by sequential search.
12058 if Nkind (E_Call) = N_Block_Statement then
12059 E_Call := First (Statements (Handled_Statement_Sequence (E_Call)));
12060 while not Nkind_In (E_Call, N_Procedure_Call_Statement,
12061 N_Entry_Call_Statement)
12062 loop
12063 Next (E_Call);
12064 end loop;
12065 end if;
12067 Is_Disp_Select :=
12068 Ada_Version >= Ada_2005
12069 and then Nkind (E_Call) = N_Procedure_Call_Statement;
12071 if Is_Disp_Select then
12072 Extract_Dispatching_Call (E_Call, Call_Ent, Obj, Actuals, Formals);
12074 Decls := New_List;
12075 Stmts := New_List;
12077 -- Generate:
12078 -- B : Boolean := False;
12080 B := Build_B (Loc, Decls);
12082 -- Generate:
12083 -- C : Ada.Tags.Prim_Op_Kind;
12085 C := Build_C (Loc, Decls);
12087 -- Because the analysis of all statements was disabled, manually
12088 -- analyze the delay statement.
12090 Analyze (D_Stat);
12091 D_Stat := Original_Node (D_Stat);
12093 else
12094 -- Build an entry call using Simple_Entry_Call
12096 Extract_Entry (E_Call, Concval, Ename, Index);
12097 Build_Simple_Entry_Call (E_Call, Concval, Ename, Index);
12099 Decls := Declarations (E_Call);
12100 Stmts := Statements (Handled_Statement_Sequence (E_Call));
12102 if No (Decls) then
12103 Decls := New_List;
12104 end if;
12106 -- Generate:
12107 -- B : Boolean;
12109 B := Make_Defining_Identifier (Loc, Name_uB);
12111 Prepend_To (Decls,
12112 Make_Object_Declaration (Loc,
12113 Defining_Identifier => B,
12114 Object_Definition => New_Reference_To (Standard_Boolean, Loc)));
12115 end if;
12117 -- Duration and mode processing
12119 D_Type := Base_Type (Etype (Expression (D_Stat)));
12121 -- Use the type of the delay expression (Calendar or Real_Time) to
12122 -- generate the appropriate conversion.
12124 if Nkind (D_Stat) = N_Delay_Relative_Statement then
12125 D_Disc := Make_Integer_Literal (Loc, 0);
12126 D_Conv := Relocate_Node (Expression (D_Stat));
12128 elsif Is_RTE (D_Type, RO_CA_Time) then
12129 D_Disc := Make_Integer_Literal (Loc, 1);
12130 D_Conv :=
12131 Make_Function_Call (Loc,
12132 Name => New_Reference_To (RTE (RO_CA_To_Duration), Loc),
12133 Parameter_Associations =>
12134 New_List (New_Copy (Expression (D_Stat))));
12136 else pragma Assert (Is_RTE (D_Type, RO_RT_Time));
12137 D_Disc := Make_Integer_Literal (Loc, 2);
12138 D_Conv :=
12139 Make_Function_Call (Loc,
12140 Name => New_Reference_To (RTE (RO_RT_To_Duration), Loc),
12141 Parameter_Associations =>
12142 New_List (New_Copy (Expression (D_Stat))));
12143 end if;
12145 D := Make_Temporary (Loc, 'D');
12147 -- Generate:
12148 -- D : Duration;
12150 Append_To (Decls,
12151 Make_Object_Declaration (Loc,
12152 Defining_Identifier => D,
12153 Object_Definition => New_Reference_To (Standard_Duration, Loc)));
12155 M := Make_Temporary (Loc, 'M');
12157 -- Generate:
12158 -- M : Integer := (0 | 1 | 2);
12160 Append_To (Decls,
12161 Make_Object_Declaration (Loc,
12162 Defining_Identifier => M,
12163 Object_Definition => New_Reference_To (Standard_Integer, Loc),
12164 Expression => D_Disc));
12166 -- Do the assignment at this stage only because the evaluation of the
12167 -- expression must not occur before (see ACVC C97302A).
12169 Append_To (Stmts,
12170 Make_Assignment_Statement (Loc,
12171 Name => New_Reference_To (D, Loc),
12172 Expression => D_Conv));
12174 -- Parameter block processing
12176 -- Manually create the parameter block for dispatching calls. In the
12177 -- case of entries, the block has already been created during the call
12178 -- to Build_Simple_Entry_Call.
12180 if Is_Disp_Select then
12182 -- Tagged kind processing, generate:
12183 -- K : Ada.Tags.Tagged_Kind :=
12184 -- Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag <object>));
12186 K := Build_K (Loc, Decls, Obj);
12188 Blk_Typ := Build_Parameter_Block (Loc, Actuals, Formals, Decls);
12189 P :=
12190 Parameter_Block_Pack (Loc, Blk_Typ, Actuals, Formals, Decls, Stmts);
12192 -- Dispatch table slot processing, generate:
12193 -- S : Integer;
12195 S := Build_S (Loc, Decls);
12197 -- Generate:
12198 -- S := Ada.Tags.Get_Offset_Index
12199 -- (Ada.Tags.Tag (<object>), DT_Position (Call_Ent));
12201 Conc_Typ_Stmts :=
12202 New_List (Build_S_Assignment (Loc, S, Obj, Call_Ent));
12204 -- Generate:
12205 -- _Disp_Timed_Select (<object>, S, P'Address, D, M, C, B);
12207 -- where Obj is the controlling formal parameter, S is the dispatch
12208 -- table slot number of the dispatching operation, P is the wrapped
12209 -- parameter block, D is the duration, M is the duration mode, C is
12210 -- the call kind and B is the call status.
12212 Params := New_List;
12214 Append_To (Params, New_Copy_Tree (Obj));
12215 Append_To (Params, New_Reference_To (S, Loc));
12216 Append_To (Params,
12217 Make_Attribute_Reference (Loc,
12218 Prefix => New_Reference_To (P, Loc),
12219 Attribute_Name => Name_Address));
12220 Append_To (Params, New_Reference_To (D, Loc));
12221 Append_To (Params, New_Reference_To (M, Loc));
12222 Append_To (Params, New_Reference_To (C, Loc));
12223 Append_To (Params, New_Reference_To (B, Loc));
12225 Append_To (Conc_Typ_Stmts,
12226 Make_Procedure_Call_Statement (Loc,
12227 Name =>
12228 New_Reference_To
12229 (Find_Prim_Op
12230 (Etype (Etype (Obj)), Name_uDisp_Timed_Select), Loc),
12231 Parameter_Associations => Params));
12233 -- Generate:
12234 -- if C = POK_Protected_Entry
12235 -- or else C = POK_Task_Entry
12236 -- then
12237 -- Param1 := P.Param1;
12238 -- ...
12239 -- ParamN := P.ParamN;
12240 -- end if;
12242 Unpack := Parameter_Block_Unpack (Loc, P, Actuals, Formals);
12244 -- Generate the if statement only when the packed parameters need
12245 -- explicit assignments to their corresponding actuals.
12247 if Present (Unpack) then
12248 Append_To (Conc_Typ_Stmts,
12249 Make_Implicit_If_Statement (N,
12251 Condition =>
12252 Make_Or_Else (Loc,
12253 Left_Opnd =>
12254 Make_Op_Eq (Loc,
12255 Left_Opnd => New_Reference_To (C, Loc),
12256 Right_Opnd =>
12257 New_Reference_To
12258 (RTE (RE_POK_Protected_Entry), Loc)),
12260 Right_Opnd =>
12261 Make_Op_Eq (Loc,
12262 Left_Opnd => New_Reference_To (C, Loc),
12263 Right_Opnd =>
12264 New_Reference_To (RTE (RE_POK_Task_Entry), Loc))),
12266 Then_Statements => Unpack));
12267 end if;
12269 -- Generate:
12271 -- if B then
12272 -- if C = POK_Procedure
12273 -- or else C = POK_Protected_Procedure
12274 -- or else C = POK_Task_Procedure
12275 -- then
12276 -- <dispatching-call>
12277 -- end if;
12278 -- <triggering-statements>
12279 -- else
12280 -- <timed-statements>
12281 -- end if;
12283 N_Stats := Copy_Separate_List (E_Stats);
12285 Prepend_To (N_Stats,
12286 Make_Implicit_If_Statement (N,
12288 Condition =>
12289 Make_Or_Else (Loc,
12290 Left_Opnd =>
12291 Make_Op_Eq (Loc,
12292 Left_Opnd => New_Reference_To (C, Loc),
12293 Right_Opnd =>
12294 New_Reference_To (RTE (RE_POK_Procedure), Loc)),
12296 Right_Opnd =>
12297 Make_Or_Else (Loc,
12298 Left_Opnd =>
12299 Make_Op_Eq (Loc,
12300 Left_Opnd => New_Reference_To (C, Loc),
12301 Right_Opnd =>
12302 New_Reference_To (RTE (
12303 RE_POK_Protected_Procedure), Loc)),
12304 Right_Opnd =>
12305 Make_Op_Eq (Loc,
12306 Left_Opnd => New_Reference_To (C, Loc),
12307 Right_Opnd =>
12308 New_Reference_To
12309 (RTE (RE_POK_Task_Procedure), Loc)))),
12311 Then_Statements => New_List (E_Call)));
12313 Append_To (Conc_Typ_Stmts,
12314 Make_Implicit_If_Statement (N,
12315 Condition => New_Reference_To (B, Loc),
12316 Then_Statements => N_Stats,
12317 Else_Statements => D_Stats));
12319 -- Generate:
12320 -- <dispatching-call>;
12321 -- <triggering-statements>
12323 Lim_Typ_Stmts := Copy_Separate_List (E_Stats);
12324 Prepend_To (Lim_Typ_Stmts, New_Copy_Tree (E_Call));
12326 -- Generate:
12327 -- if K = Ada.Tags.TK_Limited_Tagged then
12328 -- Lim_Typ_Stmts
12329 -- else
12330 -- Conc_Typ_Stmts
12331 -- end if;
12333 Append_To (Stmts,
12334 Make_Implicit_If_Statement (N,
12335 Condition =>
12336 Make_Op_Eq (Loc,
12337 Left_Opnd => New_Reference_To (K, Loc),
12338 Right_Opnd =>
12339 New_Reference_To (RTE (RE_TK_Limited_Tagged), Loc)),
12340 Then_Statements => Lim_Typ_Stmts,
12341 Else_Statements => Conc_Typ_Stmts));
12343 else
12344 -- Skip assignments to temporaries created for in-out parameters.
12345 -- This makes unwarranted assumptions about the shape of the expanded
12346 -- tree for the call, and should be cleaned up ???
12348 Stmt := First (Stmts);
12349 while Nkind (Stmt) /= N_Procedure_Call_Statement loop
12350 Next (Stmt);
12351 end loop;
12353 -- Do the assignment at this stage only because the evaluation
12354 -- of the expression must not occur before (see ACVC C97302A).
12356 Insert_Before (Stmt,
12357 Make_Assignment_Statement (Loc,
12358 Name => New_Reference_To (D, Loc),
12359 Expression => D_Conv));
12361 Call := Stmt;
12362 Params := Parameter_Associations (Call);
12364 -- For a protected type, we build a Timed_Protected_Entry_Call
12366 if Is_Protected_Type (Etype (Concval)) then
12368 -- Create a new call statement
12370 Param := First (Params);
12371 while Present (Param)
12372 and then not Is_RTE (Etype (Param), RE_Call_Modes)
12373 loop
12374 Next (Param);
12375 end loop;
12377 Dummy := Remove_Next (Next (Param));
12379 -- Remove garbage is following the Cancel_Param if present
12381 Dummy := Next (Param);
12383 -- Remove the mode of the Protected_Entry_Call call, then remove
12384 -- the Communication_Block of the Protected_Entry_Call call, and
12385 -- finally add Duration and a Delay_Mode parameter
12387 pragma Assert (Present (Param));
12388 Rewrite (Param, New_Reference_To (D, Loc));
12390 Rewrite (Dummy, New_Reference_To (M, Loc));
12392 -- Add a Boolean flag for successful entry call
12394 Append_To (Params, New_Reference_To (B, Loc));
12396 case Corresponding_Runtime_Package (Etype (Concval)) is
12397 when System_Tasking_Protected_Objects_Entries =>
12398 Rewrite (Call,
12399 Make_Procedure_Call_Statement (Loc,
12400 Name =>
12401 New_Reference_To
12402 (RTE (RE_Timed_Protected_Entry_Call), Loc),
12403 Parameter_Associations => Params));
12405 when System_Tasking_Protected_Objects_Single_Entry =>
12406 Param := First (Params);
12407 while Present (Param)
12408 and then not
12409 Is_RTE (Etype (Param), RE_Protected_Entry_Index)
12410 loop
12411 Next (Param);
12412 end loop;
12414 Remove (Param);
12416 Rewrite (Call,
12417 Make_Procedure_Call_Statement (Loc,
12418 Name =>
12419 New_Reference_To
12420 (RTE (RE_Timed_Protected_Single_Entry_Call), Loc),
12421 Parameter_Associations => Params));
12423 when others =>
12424 raise Program_Error;
12425 end case;
12427 -- For the task case, build a Timed_Task_Entry_Call
12429 else
12430 -- Create a new call statement
12432 Append_To (Params, New_Reference_To (D, Loc));
12433 Append_To (Params, New_Reference_To (M, Loc));
12434 Append_To (Params, New_Reference_To (B, Loc));
12436 Rewrite (Call,
12437 Make_Procedure_Call_Statement (Loc,
12438 Name =>
12439 New_Reference_To (RTE (RE_Timed_Task_Entry_Call), Loc),
12440 Parameter_Associations => Params));
12441 end if;
12443 Append_To (Stmts,
12444 Make_Implicit_If_Statement (N,
12445 Condition => New_Reference_To (B, Loc),
12446 Then_Statements => E_Stats,
12447 Else_Statements => D_Stats));
12448 end if;
12450 Rewrite (N,
12451 Make_Block_Statement (Loc,
12452 Declarations => Decls,
12453 Handled_Statement_Sequence =>
12454 Make_Handled_Sequence_Of_Statements (Loc, Stmts)));
12456 Analyze (N);
12457 end Expand_N_Timed_Entry_Call;
12459 ----------------------------------------
12460 -- Expand_Protected_Body_Declarations --
12461 ----------------------------------------
12463 procedure Expand_Protected_Body_Declarations
12464 (N : Node_Id;
12465 Spec_Id : Entity_Id)
12467 begin
12468 if No_Run_Time_Mode then
12469 Error_Msg_CRT ("protected body", N);
12470 return;
12472 elsif Full_Expander_Active then
12474 -- Associate discriminals with the first subprogram or entry body to
12475 -- be expanded.
12477 if Present (First_Protected_Operation (Declarations (N))) then
12478 Set_Discriminals (Parent (Spec_Id));
12479 end if;
12480 end if;
12481 end Expand_Protected_Body_Declarations;
12483 -------------------------
12484 -- External_Subprogram --
12485 -------------------------
12487 function External_Subprogram (E : Entity_Id) return Entity_Id is
12488 Subp : constant Entity_Id := Protected_Body_Subprogram (E);
12490 begin
12491 -- The internal and external subprograms follow each other on the entity
12492 -- chain. Note that previously private operations had no separate
12493 -- external subprogram. We now create one in all cases, because a
12494 -- private operation may actually appear in an external call, through
12495 -- a 'Access reference used for a callback.
12497 -- If the operation is a function that returns an anonymous access type,
12498 -- the corresponding itype appears before the operation, and must be
12499 -- skipped.
12501 -- This mechanism is fragile, there should be a real link between the
12502 -- two versions of the operation, but there is no place to put it ???
12504 if Is_Access_Type (Next_Entity (Subp)) then
12505 return Next_Entity (Next_Entity (Subp));
12506 else
12507 return Next_Entity (Subp);
12508 end if;
12509 end External_Subprogram;
12511 ------------------------------
12512 -- Extract_Dispatching_Call --
12513 ------------------------------
12515 procedure Extract_Dispatching_Call
12516 (N : Node_Id;
12517 Call_Ent : out Entity_Id;
12518 Object : out Entity_Id;
12519 Actuals : out List_Id;
12520 Formals : out List_Id)
12522 Call_Nam : Node_Id;
12524 begin
12525 pragma Assert (Nkind (N) = N_Procedure_Call_Statement);
12527 if Present (Original_Node (N)) then
12528 Call_Nam := Name (Original_Node (N));
12529 else
12530 Call_Nam := Name (N);
12531 end if;
12533 -- Retrieve the name of the dispatching procedure. It contains the
12534 -- dispatch table slot number.
12536 loop
12537 case Nkind (Call_Nam) is
12538 when N_Identifier =>
12539 exit;
12541 when N_Selected_Component =>
12542 Call_Nam := Selector_Name (Call_Nam);
12544 when others =>
12545 raise Program_Error;
12547 end case;
12548 end loop;
12550 Actuals := Parameter_Associations (N);
12551 Call_Ent := Entity (Call_Nam);
12552 Formals := Parameter_Specifications (Parent (Call_Ent));
12553 Object := First (Actuals);
12555 if Present (Original_Node (Object)) then
12556 Object := Original_Node (Object);
12557 end if;
12559 -- If the type of the dispatching object is an access type then return
12560 -- an explicit dereference.
12562 if Is_Access_Type (Etype (Object)) then
12563 Object := Make_Explicit_Dereference (Sloc (N), Object);
12564 Analyze (Object);
12565 end if;
12566 end Extract_Dispatching_Call;
12568 -------------------
12569 -- Extract_Entry --
12570 -------------------
12572 procedure Extract_Entry
12573 (N : Node_Id;
12574 Concval : out Node_Id;
12575 Ename : out Node_Id;
12576 Index : out Node_Id)
12578 Nam : constant Node_Id := Name (N);
12580 begin
12581 -- For a simple entry, the name is a selected component, with the
12582 -- prefix being the task value, and the selector being the entry.
12584 if Nkind (Nam) = N_Selected_Component then
12585 Concval := Prefix (Nam);
12586 Ename := Selector_Name (Nam);
12587 Index := Empty;
12589 -- For a member of an entry family, the name is an indexed component
12590 -- where the prefix is a selected component, whose prefix in turn is
12591 -- the task value, and whose selector is the entry family. The single
12592 -- expression in the expressions list of the indexed component is the
12593 -- subscript for the family.
12595 else pragma Assert (Nkind (Nam) = N_Indexed_Component);
12596 Concval := Prefix (Prefix (Nam));
12597 Ename := Selector_Name (Prefix (Nam));
12598 Index := First (Expressions (Nam));
12599 end if;
12600 end Extract_Entry;
12602 -------------------
12603 -- Family_Offset --
12604 -------------------
12606 function Family_Offset
12607 (Loc : Source_Ptr;
12608 Hi : Node_Id;
12609 Lo : Node_Id;
12610 Ttyp : Entity_Id;
12611 Cap : Boolean) return Node_Id
12613 Ityp : Entity_Id;
12614 Real_Hi : Node_Id;
12615 Real_Lo : Node_Id;
12617 function Convert_Discriminant_Ref (Bound : Node_Id) return Node_Id;
12618 -- If one of the bounds is a reference to a discriminant, replace with
12619 -- corresponding discriminal of type. Within the body of a task retrieve
12620 -- the renamed discriminant by simple visibility, using its generated
12621 -- name. Within a protected object, find the original discriminant and
12622 -- replace it with the discriminal of the current protected operation.
12624 ------------------------------
12625 -- Convert_Discriminant_Ref --
12626 ------------------------------
12628 function Convert_Discriminant_Ref (Bound : Node_Id) return Node_Id is
12629 Loc : constant Source_Ptr := Sloc (Bound);
12630 B : Node_Id;
12631 D : Entity_Id;
12633 begin
12634 if Is_Entity_Name (Bound)
12635 and then Ekind (Entity (Bound)) = E_Discriminant
12636 then
12637 if Is_Task_Type (Ttyp)
12638 and then Has_Completion (Ttyp)
12639 then
12640 B := Make_Identifier (Loc, Chars (Entity (Bound)));
12641 Find_Direct_Name (B);
12643 elsif Is_Protected_Type (Ttyp) then
12644 D := First_Discriminant (Ttyp);
12645 while Chars (D) /= Chars (Entity (Bound)) loop
12646 Next_Discriminant (D);
12647 end loop;
12649 B := New_Reference_To (Discriminal (D), Loc);
12651 else
12652 B := New_Reference_To (Discriminal (Entity (Bound)), Loc);
12653 end if;
12655 elsif Nkind (Bound) = N_Attribute_Reference then
12656 return Bound;
12658 else
12659 B := New_Copy_Tree (Bound);
12660 end if;
12662 return
12663 Make_Attribute_Reference (Loc,
12664 Attribute_Name => Name_Pos,
12665 Prefix => New_Occurrence_Of (Etype (Bound), Loc),
12666 Expressions => New_List (B));
12667 end Convert_Discriminant_Ref;
12669 -- Start of processing for Family_Offset
12671 begin
12672 Real_Hi := Convert_Discriminant_Ref (Hi);
12673 Real_Lo := Convert_Discriminant_Ref (Lo);
12675 if Cap then
12676 if Is_Task_Type (Ttyp) then
12677 Ityp := RTE (RE_Task_Entry_Index);
12678 else
12679 Ityp := RTE (RE_Protected_Entry_Index);
12680 end if;
12682 Real_Hi :=
12683 Make_Attribute_Reference (Loc,
12684 Prefix => New_Reference_To (Ityp, Loc),
12685 Attribute_Name => Name_Min,
12686 Expressions => New_List (
12687 Real_Hi,
12688 Make_Integer_Literal (Loc, Entry_Family_Bound - 1)));
12690 Real_Lo :=
12691 Make_Attribute_Reference (Loc,
12692 Prefix => New_Reference_To (Ityp, Loc),
12693 Attribute_Name => Name_Max,
12694 Expressions => New_List (
12695 Real_Lo,
12696 Make_Integer_Literal (Loc, -Entry_Family_Bound)));
12697 end if;
12699 return Make_Op_Subtract (Loc, Real_Hi, Real_Lo);
12700 end Family_Offset;
12702 -----------------
12703 -- Family_Size --
12704 -----------------
12706 function Family_Size
12707 (Loc : Source_Ptr;
12708 Hi : Node_Id;
12709 Lo : Node_Id;
12710 Ttyp : Entity_Id;
12711 Cap : Boolean) return Node_Id
12713 Ityp : Entity_Id;
12715 begin
12716 if Is_Task_Type (Ttyp) then
12717 Ityp := RTE (RE_Task_Entry_Index);
12718 else
12719 Ityp := RTE (RE_Protected_Entry_Index);
12720 end if;
12722 return
12723 Make_Attribute_Reference (Loc,
12724 Prefix => New_Reference_To (Ityp, Loc),
12725 Attribute_Name => Name_Max,
12726 Expressions => New_List (
12727 Make_Op_Add (Loc,
12728 Left_Opnd =>
12729 Family_Offset (Loc, Hi, Lo, Ttyp, Cap),
12730 Right_Opnd =>
12731 Make_Integer_Literal (Loc, 1)),
12732 Make_Integer_Literal (Loc, 0)));
12733 end Family_Size;
12735 ----------------------------
12736 -- Find_Enclosing_Context --
12737 ----------------------------
12739 procedure Find_Enclosing_Context
12740 (N : Node_Id;
12741 Context : out Node_Id;
12742 Context_Id : out Entity_Id;
12743 Context_Decls : out List_Id)
12745 begin
12746 -- Traverse the parent chain looking for an enclosing body, block,
12747 -- package or return statement.
12749 Context := Parent (N);
12750 while not Nkind_In (Context, N_Block_Statement,
12751 N_Entry_Body,
12752 N_Extended_Return_Statement,
12753 N_Package_Body,
12754 N_Package_Declaration,
12755 N_Subprogram_Body,
12756 N_Task_Body)
12757 loop
12758 Context := Parent (Context);
12759 end loop;
12761 -- Extract the constituents of the context
12763 if Nkind (Context) = N_Extended_Return_Statement then
12764 Context_Decls := Return_Object_Declarations (Context);
12765 Context_Id := Return_Statement_Entity (Context);
12767 -- Package declarations and bodies use a common library-level activation
12768 -- chain or task master, therefore return the package declaration as the
12769 -- proper carrier for the appropriate flag.
12771 elsif Nkind (Context) = N_Package_Body then
12772 Context_Decls := Declarations (Context);
12773 Context_Id := Corresponding_Spec (Context);
12774 Context := Parent (Context_Id);
12776 if Nkind (Context) = N_Defining_Program_Unit_Name then
12777 Context := Parent (Parent (Context));
12778 else
12779 Context := Parent (Context);
12780 end if;
12782 elsif Nkind (Context) = N_Package_Declaration then
12783 Context_Decls := Visible_Declarations (Specification (Context));
12784 Context_Id := Defining_Unit_Name (Specification (Context));
12786 if Nkind (Context_Id) = N_Defining_Program_Unit_Name then
12787 Context_Id := Defining_Identifier (Context_Id);
12788 end if;
12790 else
12791 Context_Decls := Declarations (Context);
12793 if Nkind (Context) = N_Block_Statement then
12794 Context_Id := Entity (Identifier (Context));
12796 elsif Nkind (Context) = N_Entry_Body then
12797 Context_Id := Defining_Identifier (Context);
12799 elsif Nkind (Context) = N_Subprogram_Body then
12800 if Present (Corresponding_Spec (Context)) then
12801 Context_Id := Corresponding_Spec (Context);
12802 else
12803 Context_Id := Defining_Unit_Name (Specification (Context));
12805 if Nkind (Context_Id) = N_Defining_Program_Unit_Name then
12806 Context_Id := Defining_Identifier (Context_Id);
12807 end if;
12808 end if;
12810 elsif Nkind (Context) = N_Task_Body then
12811 Context_Id := Corresponding_Spec (Context);
12813 else
12814 raise Program_Error;
12815 end if;
12816 end if;
12818 pragma Assert (Present (Context));
12819 pragma Assert (Present (Context_Id));
12820 pragma Assert (Present (Context_Decls));
12821 end Find_Enclosing_Context;
12823 -----------------------
12824 -- Find_Master_Scope --
12825 -----------------------
12827 function Find_Master_Scope (E : Entity_Id) return Entity_Id is
12828 S : Entity_Id;
12830 begin
12831 -- In Ada 2005, the master is the innermost enclosing scope that is not
12832 -- transient. If the enclosing block is the rewriting of a call or the
12833 -- scope is an extended return statement this is valid master. The
12834 -- master in an extended return is only used within the return, and is
12835 -- subsequently overwritten in Move_Activation_Chain, but it must exist
12836 -- now before that overwriting occurs.
12838 S := Scope (E);
12840 if Ada_Version >= Ada_2005 then
12841 while Is_Internal (S) loop
12842 if Nkind (Parent (S)) = N_Block_Statement
12843 and then
12844 Nkind (Original_Node (Parent (S))) = N_Procedure_Call_Statement
12845 then
12846 exit;
12848 elsif Ekind (S) = E_Return_Statement then
12849 exit;
12851 else
12852 S := Scope (S);
12853 end if;
12854 end loop;
12855 end if;
12857 return S;
12858 end Find_Master_Scope;
12860 -------------------------------
12861 -- First_Protected_Operation --
12862 -------------------------------
12864 function First_Protected_Operation (D : List_Id) return Node_Id is
12865 First_Op : Node_Id;
12867 begin
12868 First_Op := First (D);
12869 while Present (First_Op)
12870 and then not Nkind_In (First_Op, N_Subprogram_Body, N_Entry_Body)
12871 loop
12872 Next (First_Op);
12873 end loop;
12875 return First_Op;
12876 end First_Protected_Operation;
12878 ---------------------------------------
12879 -- Install_Private_Data_Declarations --
12880 ---------------------------------------
12882 procedure Install_Private_Data_Declarations
12883 (Loc : Source_Ptr;
12884 Spec_Id : Entity_Id;
12885 Conc_Typ : Entity_Id;
12886 Body_Nod : Node_Id;
12887 Decls : List_Id;
12888 Barrier : Boolean := False;
12889 Family : Boolean := False)
12891 Is_Protected : constant Boolean := Is_Protected_Type (Conc_Typ);
12892 Decl : Node_Id;
12893 Def : Node_Id;
12894 Insert_Node : Node_Id := Empty;
12895 Obj_Ent : Entity_Id;
12897 procedure Add (Decl : Node_Id);
12898 -- Add a single declaration after Insert_Node. If this is the first
12899 -- addition, Decl is added to the front of Decls and it becomes the
12900 -- insertion node.
12902 function Replace_Bound (Bound : Node_Id) return Node_Id;
12903 -- The bounds of an entry index may depend on discriminants, create a
12904 -- reference to the corresponding prival. Otherwise return a duplicate
12905 -- of the original bound.
12907 ---------
12908 -- Add --
12909 ---------
12911 procedure Add (Decl : Node_Id) is
12912 begin
12913 if No (Insert_Node) then
12914 Prepend_To (Decls, Decl);
12915 else
12916 Insert_After (Insert_Node, Decl);
12917 end if;
12919 Insert_Node := Decl;
12920 end Add;
12922 --------------------------
12923 -- Replace_Discriminant --
12924 --------------------------
12926 function Replace_Bound (Bound : Node_Id) return Node_Id is
12927 begin
12928 if Nkind (Bound) = N_Identifier
12929 and then Is_Discriminal (Entity (Bound))
12930 then
12931 return Make_Identifier (Loc, Chars (Entity (Bound)));
12932 else
12933 return Duplicate_Subexpr (Bound);
12934 end if;
12935 end Replace_Bound;
12937 -- Start of processing for Install_Private_Data_Declarations
12939 begin
12940 -- Step 1: Retrieve the concurrent object entity. Obj_Ent can denote
12941 -- formal parameter _O, _object or _task depending on the context.
12943 Obj_Ent := Concurrent_Object (Spec_Id, Conc_Typ);
12945 -- Special processing of _O for barrier functions, protected entries
12946 -- and families.
12948 if Barrier
12949 or else
12950 (Is_Protected
12951 and then
12952 (Ekind (Spec_Id) = E_Entry
12953 or else Ekind (Spec_Id) = E_Entry_Family))
12954 then
12955 declare
12956 Conc_Rec : constant Entity_Id :=
12957 Corresponding_Record_Type (Conc_Typ);
12958 Typ_Id : constant Entity_Id :=
12959 Make_Defining_Identifier (Loc,
12960 New_External_Name (Chars (Conc_Rec), 'P'));
12961 begin
12962 -- Generate:
12963 -- type prot_typVP is access prot_typV;
12965 Decl :=
12966 Make_Full_Type_Declaration (Loc,
12967 Defining_Identifier => Typ_Id,
12968 Type_Definition =>
12969 Make_Access_To_Object_Definition (Loc,
12970 Subtype_Indication =>
12971 New_Reference_To (Conc_Rec, Loc)));
12972 Add (Decl);
12974 -- Generate:
12975 -- _object : prot_typVP := prot_typV (_O);
12977 Decl :=
12978 Make_Object_Declaration (Loc,
12979 Defining_Identifier =>
12980 Make_Defining_Identifier (Loc, Name_uObject),
12981 Object_Definition => New_Reference_To (Typ_Id, Loc),
12982 Expression =>
12983 Unchecked_Convert_To (Typ_Id,
12984 New_Reference_To (Obj_Ent, Loc)));
12985 Add (Decl);
12987 -- Set the reference to the concurrent object
12989 Obj_Ent := Defining_Identifier (Decl);
12990 end;
12991 end if;
12993 -- Step 2: Create the Protection object and build its declaration for
12994 -- any protected entry (family) of subprogram. Note for the lock-free
12995 -- implementation, the Protection object is not needed anymore.
12997 if Is_Protected and then not Uses_Lock_Free (Conc_Typ) then
12998 declare
12999 Prot_Ent : constant Entity_Id := Make_Temporary (Loc, 'R');
13000 Prot_Typ : RE_Id;
13002 begin
13003 Set_Protection_Object (Spec_Id, Prot_Ent);
13005 -- Determine the proper protection type
13007 if Has_Attach_Handler (Conc_Typ)
13008 and then not Restricted_Profile
13009 and then not Restriction_Active (No_Dynamic_Attachment)
13010 then
13011 Prot_Typ := RE_Static_Interrupt_Protection;
13013 elsif Has_Interrupt_Handler (Conc_Typ)
13014 and then not Restriction_Active (No_Dynamic_Attachment)
13015 then
13016 Prot_Typ := RE_Dynamic_Interrupt_Protection;
13018 -- The type has explicit entries or generated primitive entry
13019 -- wrappers.
13021 elsif Has_Entries (Conc_Typ)
13022 or else
13023 (Ada_Version >= Ada_2005
13024 and then Present (Interface_List (Parent (Conc_Typ))))
13025 then
13026 case Corresponding_Runtime_Package (Conc_Typ) is
13027 when System_Tasking_Protected_Objects_Entries =>
13028 Prot_Typ := RE_Protection_Entries;
13030 when System_Tasking_Protected_Objects_Single_Entry =>
13031 Prot_Typ := RE_Protection_Entry;
13033 when others =>
13034 raise Program_Error;
13035 end case;
13037 else
13038 Prot_Typ := RE_Protection;
13039 end if;
13041 -- Generate:
13042 -- conc_typR : protection_typ renames _object._object;
13044 Decl :=
13045 Make_Object_Renaming_Declaration (Loc,
13046 Defining_Identifier => Prot_Ent,
13047 Subtype_Mark =>
13048 New_Reference_To (RTE (Prot_Typ), Loc),
13049 Name =>
13050 Make_Selected_Component (Loc,
13051 Prefix => New_Reference_To (Obj_Ent, Loc),
13052 Selector_Name => Make_Identifier (Loc, Name_uObject)));
13053 Add (Decl);
13054 end;
13055 end if;
13057 -- Step 3: Add discriminant renamings (if any)
13059 if Has_Discriminants (Conc_Typ) then
13060 declare
13061 D : Entity_Id;
13063 begin
13064 D := First_Discriminant (Conc_Typ);
13065 while Present (D) loop
13067 -- Adjust the source location
13069 Set_Sloc (Discriminal (D), Loc);
13071 -- Generate:
13072 -- discr_name : discr_typ renames _object.discr_name;
13073 -- or
13074 -- discr_name : discr_typ renames _task.discr_name;
13076 Decl :=
13077 Make_Object_Renaming_Declaration (Loc,
13078 Defining_Identifier => Discriminal (D),
13079 Subtype_Mark => New_Reference_To (Etype (D), Loc),
13080 Name =>
13081 Make_Selected_Component (Loc,
13082 Prefix => New_Reference_To (Obj_Ent, Loc),
13083 Selector_Name => Make_Identifier (Loc, Chars (D))));
13084 Add (Decl);
13086 Next_Discriminant (D);
13087 end loop;
13088 end;
13089 end if;
13091 -- Step 4: Add private component renamings (if any)
13093 if Is_Protected then
13094 Def := Protected_Definition (Parent (Conc_Typ));
13096 if Present (Private_Declarations (Def)) then
13097 declare
13098 Comp : Node_Id;
13099 Comp_Id : Entity_Id;
13100 Decl_Id : Entity_Id;
13102 begin
13103 Comp := First (Private_Declarations (Def));
13104 while Present (Comp) loop
13105 if Nkind (Comp) = N_Component_Declaration then
13106 Comp_Id := Defining_Identifier (Comp);
13107 Decl_Id :=
13108 Make_Defining_Identifier (Loc, Chars (Comp_Id));
13110 -- Minimal decoration
13112 if Ekind (Spec_Id) = E_Function then
13113 Set_Ekind (Decl_Id, E_Constant);
13114 else
13115 Set_Ekind (Decl_Id, E_Variable);
13116 end if;
13118 Set_Prival (Comp_Id, Decl_Id);
13119 Set_Prival_Link (Decl_Id, Comp_Id);
13120 Set_Is_Aliased (Decl_Id, Is_Aliased (Comp_Id));
13122 -- Generate:
13123 -- comp_name : comp_typ renames _object.comp_name;
13125 Decl :=
13126 Make_Object_Renaming_Declaration (Loc,
13127 Defining_Identifier => Decl_Id,
13128 Subtype_Mark =>
13129 New_Reference_To (Etype (Comp_Id), Loc),
13130 Name =>
13131 Make_Selected_Component (Loc,
13132 Prefix =>
13133 New_Reference_To (Obj_Ent, Loc),
13134 Selector_Name =>
13135 Make_Identifier (Loc, Chars (Comp_Id))));
13136 Add (Decl);
13137 end if;
13139 Next (Comp);
13140 end loop;
13141 end;
13142 end if;
13143 end if;
13145 -- Step 5: Add the declaration of the entry index and the associated
13146 -- type for barrier functions and entry families.
13148 if (Barrier and then Family)
13149 or else Ekind (Spec_Id) = E_Entry_Family
13150 then
13151 declare
13152 E : constant Entity_Id := Index_Object (Spec_Id);
13153 Index : constant Entity_Id :=
13154 Defining_Identifier (
13155 Entry_Index_Specification (
13156 Entry_Body_Formal_Part (Body_Nod)));
13157 Index_Con : constant Entity_Id :=
13158 Make_Defining_Identifier (Loc, Chars (Index));
13159 High : Node_Id;
13160 Index_Typ : Entity_Id;
13161 Low : Node_Id;
13163 begin
13164 -- Minimal decoration
13166 Set_Ekind (Index_Con, E_Constant);
13167 Set_Entry_Index_Constant (Index, Index_Con);
13168 Set_Discriminal_Link (Index_Con, Index);
13170 -- Retrieve the bounds of the entry family
13172 High := Type_High_Bound (Etype (Index));
13173 Low := Type_Low_Bound (Etype (Index));
13175 -- In the simple case the entry family is given by a subtype
13176 -- mark and the index constant has the same type.
13178 if Is_Entity_Name (Original_Node (
13179 Discrete_Subtype_Definition (Parent (Index))))
13180 then
13181 Index_Typ := Etype (Index);
13183 -- Otherwise a new subtype declaration is required
13185 else
13186 High := Replace_Bound (High);
13187 Low := Replace_Bound (Low);
13189 Index_Typ := Make_Temporary (Loc, 'J');
13191 -- Generate:
13192 -- subtype Jnn is <Etype of Index> range Low .. High;
13194 Decl :=
13195 Make_Subtype_Declaration (Loc,
13196 Defining_Identifier => Index_Typ,
13197 Subtype_Indication =>
13198 Make_Subtype_Indication (Loc,
13199 Subtype_Mark =>
13200 New_Reference_To (Base_Type (Etype (Index)), Loc),
13201 Constraint =>
13202 Make_Range_Constraint (Loc,
13203 Range_Expression =>
13204 Make_Range (Loc, Low, High))));
13205 Add (Decl);
13206 end if;
13208 Set_Etype (Index_Con, Index_Typ);
13210 -- Create the object which designates the index:
13211 -- J : constant Jnn :=
13212 -- Jnn'Val (_E - <index expr> + Jnn'Pos (Jnn'First));
13214 -- where Jnn is the subtype created above or the original type of
13215 -- the index, _E is a formal of the protected body subprogram and
13216 -- <index expr> is the index of the first family member.
13218 Decl :=
13219 Make_Object_Declaration (Loc,
13220 Defining_Identifier => Index_Con,
13221 Constant_Present => True,
13222 Object_Definition =>
13223 New_Reference_To (Index_Typ, Loc),
13225 Expression =>
13226 Make_Attribute_Reference (Loc,
13227 Prefix =>
13228 New_Reference_To (Index_Typ, Loc),
13229 Attribute_Name => Name_Val,
13231 Expressions => New_List (
13233 Make_Op_Add (Loc,
13234 Left_Opnd =>
13235 Make_Op_Subtract (Loc,
13236 Left_Opnd =>
13237 New_Reference_To (E, Loc),
13238 Right_Opnd =>
13239 Entry_Index_Expression (Loc,
13240 Defining_Identifier (Body_Nod),
13241 Empty, Conc_Typ)),
13243 Right_Opnd =>
13244 Make_Attribute_Reference (Loc,
13245 Prefix =>
13246 New_Reference_To (Index_Typ, Loc),
13247 Attribute_Name => Name_Pos,
13248 Expressions => New_List (
13249 Make_Attribute_Reference (Loc,
13250 Prefix =>
13251 New_Reference_To (Index_Typ, Loc),
13252 Attribute_Name => Name_First)))))));
13253 Add (Decl);
13254 end;
13255 end if;
13256 end Install_Private_Data_Declarations;
13258 -----------------------
13259 -- Is_Exception_Safe --
13260 -----------------------
13262 function Is_Exception_Safe (Subprogram : Node_Id) return Boolean is
13264 function Has_Side_Effect (N : Node_Id) return Boolean;
13265 -- Return True whenever encountering a subprogram call or raise
13266 -- statement of any kind in the sequence of statements
13268 ---------------------
13269 -- Has_Side_Effect --
13270 ---------------------
13272 -- What is this doing buried two levels down in exp_ch9. It seems like a
13273 -- generally useful function, and indeed there may be code duplication
13274 -- going on here ???
13276 function Has_Side_Effect (N : Node_Id) return Boolean is
13277 Stmt : Node_Id;
13278 Expr : Node_Id;
13280 function Is_Call_Or_Raise (N : Node_Id) return Boolean;
13281 -- Indicate whether N is a subprogram call or a raise statement
13283 ----------------------
13284 -- Is_Call_Or_Raise --
13285 ----------------------
13287 function Is_Call_Or_Raise (N : Node_Id) return Boolean is
13288 begin
13289 return Nkind_In (N, N_Procedure_Call_Statement,
13290 N_Function_Call,
13291 N_Raise_Statement,
13292 N_Raise_Constraint_Error,
13293 N_Raise_Program_Error,
13294 N_Raise_Storage_Error);
13295 end Is_Call_Or_Raise;
13297 -- Start of processing for Has_Side_Effect
13299 begin
13300 Stmt := N;
13301 while Present (Stmt) loop
13302 if Is_Call_Or_Raise (Stmt) then
13303 return True;
13304 end if;
13306 -- An object declaration can also contain a function call or a
13307 -- raise statement.
13309 if Nkind (Stmt) = N_Object_Declaration then
13310 Expr := Expression (Stmt);
13312 if Present (Expr) and then Is_Call_Or_Raise (Expr) then
13313 return True;
13314 end if;
13315 end if;
13317 Next (Stmt);
13318 end loop;
13320 return False;
13321 end Has_Side_Effect;
13323 -- Start of processing for Is_Exception_Safe
13325 begin
13326 -- If the checks handled by the back end are not disabled, we cannot
13327 -- ensure that no exception will be raised.
13329 if not Access_Checks_Suppressed (Empty)
13330 or else not Discriminant_Checks_Suppressed (Empty)
13331 or else not Range_Checks_Suppressed (Empty)
13332 or else not Index_Checks_Suppressed (Empty)
13333 or else Opt.Stack_Checking_Enabled
13334 then
13335 return False;
13336 end if;
13338 if Has_Side_Effect (First (Declarations (Subprogram)))
13339 or else
13340 Has_Side_Effect
13341 (First (Statements (Handled_Statement_Sequence (Subprogram))))
13342 then
13343 return False;
13344 else
13345 return True;
13346 end if;
13347 end Is_Exception_Safe;
13349 ---------------------------------
13350 -- Is_Potentially_Large_Family --
13351 ---------------------------------
13353 function Is_Potentially_Large_Family
13354 (Base_Index : Entity_Id;
13355 Conctyp : Entity_Id;
13356 Lo : Node_Id;
13357 Hi : Node_Id) return Boolean
13359 begin
13360 return Scope (Base_Index) = Standard_Standard
13361 and then Base_Index = Base_Type (Standard_Integer)
13362 and then Has_Discriminants (Conctyp)
13363 and then
13364 Present (Discriminant_Default_Value (First_Discriminant (Conctyp)))
13365 and then
13366 (Denotes_Discriminant (Lo, True)
13367 or else
13368 Denotes_Discriminant (Hi, True));
13369 end Is_Potentially_Large_Family;
13371 -------------------------------------
13372 -- Is_Private_Primitive_Subprogram --
13373 -------------------------------------
13375 function Is_Private_Primitive_Subprogram (Id : Entity_Id) return Boolean is
13376 begin
13377 return
13378 (Ekind (Id) = E_Function or else Ekind (Id) = E_Procedure)
13379 and then Is_Private_Primitive (Id);
13380 end Is_Private_Primitive_Subprogram;
13382 ------------------
13383 -- Index_Object --
13384 ------------------
13386 function Index_Object (Spec_Id : Entity_Id) return Entity_Id is
13387 Bod_Subp : constant Entity_Id := Protected_Body_Subprogram (Spec_Id);
13388 Formal : Entity_Id;
13390 begin
13391 Formal := First_Formal (Bod_Subp);
13392 while Present (Formal) loop
13394 -- Look for formal parameter _E
13396 if Chars (Formal) = Name_uE then
13397 return Formal;
13398 end if;
13400 Next_Formal (Formal);
13401 end loop;
13403 -- A protected body subprogram should always have the parameter in
13404 -- question.
13406 raise Program_Error;
13407 end Index_Object;
13409 --------------------------------
13410 -- Make_Initialize_Protection --
13411 --------------------------------
13413 function Make_Initialize_Protection
13414 (Protect_Rec : Entity_Id) return List_Id
13416 Loc : constant Source_Ptr := Sloc (Protect_Rec);
13417 P_Arr : Entity_Id;
13418 Pdec : Node_Id;
13419 Ptyp : constant Node_Id :=
13420 Corresponding_Concurrent_Type (Protect_Rec);
13421 Args : List_Id;
13422 L : constant List_Id := New_List;
13423 Has_Entry : constant Boolean := Has_Entries (Ptyp);
13424 Prio_Type : Entity_Id;
13425 Restricted : constant Boolean := Restricted_Profile;
13427 begin
13428 -- We may need two calls to properly initialize the object, one to
13429 -- Initialize_Protection, and possibly one to Install_Handlers if we
13430 -- have a pragma Attach_Handler.
13432 -- Get protected declaration. In the case of a task type declaration,
13433 -- this is simply the parent of the protected type entity. In the single
13434 -- protected object declaration, this parent will be the implicit type,
13435 -- and we can find the corresponding single protected object declaration
13436 -- by searching forward in the declaration list in the tree.
13438 -- Is the test for N_Single_Protected_Declaration needed here??? Nodes
13439 -- of this type should have been removed during semantic analysis.
13441 Pdec := Parent (Ptyp);
13442 while not Nkind_In (Pdec, N_Protected_Type_Declaration,
13443 N_Single_Protected_Declaration)
13444 loop
13445 Next (Pdec);
13446 end loop;
13448 -- Build the parameter list for the call. Note that _Init is the name
13449 -- of the formal for the object to be initialized, which is the task
13450 -- value record itself.
13452 Args := New_List;
13454 -- For lock-free implementation, skip initializations of the Protection
13455 -- object.
13457 if not Uses_Lock_Free (Defining_Identifier (Pdec)) then
13458 -- Object parameter. This is a pointer to the object of type
13459 -- Protection used by the GNARL to control the protected object.
13461 Append_To (Args,
13462 Make_Attribute_Reference (Loc,
13463 Prefix =>
13464 Make_Selected_Component (Loc,
13465 Prefix => Make_Identifier (Loc, Name_uInit),
13466 Selector_Name => Make_Identifier (Loc, Name_uObject)),
13467 Attribute_Name => Name_Unchecked_Access));
13469 -- Priority parameter. Set to Unspecified_Priority unless there is a
13470 -- Priority rep item, in which case we take the value from the pragma
13471 -- or attribute definition clause, or there is an Interrupt_Priority
13472 -- rep item and no Priority rep item, and we set the ceiling to
13473 -- Interrupt_Priority'Last, an implementation-defined value, see
13474 -- (RM D.3(10)).
13476 if Has_Rep_Item (Ptyp, Name_Priority, Check_Parents => False) then
13477 declare
13478 Prio_Clause : constant Node_Id :=
13479 Get_Rep_Item
13480 (Ptyp, Name_Priority, Check_Parents => False);
13482 Prio : Node_Id;
13483 Temp : Entity_Id;
13485 begin
13486 -- Pragma Priority
13488 if Nkind (Prio_Clause) = N_Pragma then
13489 Prio :=
13490 Expression
13491 (First (Pragma_Argument_Associations (Prio_Clause)));
13493 -- Get_Rep_Item returns either priority pragma.
13495 if Pragma_Name (Prio_Clause) = Name_Priority then
13496 Prio_Type := RTE (RE_Any_Priority);
13497 else
13498 Prio_Type := RTE (RE_Interrupt_Priority);
13499 end if;
13501 -- Attribute definition clause Priority
13503 else
13504 if Chars (Prio_Clause) = Name_Priority then
13505 Prio_Type := RTE (RE_Any_Priority);
13506 else
13507 Prio_Type := RTE (RE_Interrupt_Priority);
13508 end if;
13510 Prio := Expression (Prio_Clause);
13511 end if;
13513 -- If priority is a static expression, then we can duplicate it
13514 -- with no problem and simply append it to the argument list.
13515 -- However, it has only be pre-analyzed, so we need to check
13516 -- now that it is in the bounds of the priority type.
13518 if Is_Static_Expression (Prio) then
13519 Set_Analyzed (Prio, False);
13520 Append_To (Args,
13521 Make_Type_Conversion (Loc,
13522 Subtype_Mark => New_Occurrence_Of (Prio_Type, Loc),
13523 Expression => Duplicate_Subexpr (Prio)));
13525 -- Otherwise, the priority may be a per-object expression, if
13526 -- it depends on a discriminant of the type. In this case,
13527 -- create local variable to capture the expression. Note that
13528 -- it is really necessary to create this variable explicitly.
13529 -- It might be thought that removing side effects would the
13530 -- appropriate approach, but that could generate declarations
13531 -- improperly placed in the enclosing scope.
13533 else
13534 Temp := Make_Temporary (Loc, 'R', Prio);
13535 Append_To (L,
13536 Make_Object_Declaration (Loc,
13537 Defining_Identifier => Temp,
13538 Object_Definition =>
13539 New_Occurrence_Of (Prio_Type, Loc),
13540 Expression => Relocate_Node (Prio)));
13542 Append_To (Args, New_Occurrence_Of (Temp, Loc));
13543 end if;
13544 end;
13546 -- When no priority is specified but an xx_Handler pragma is, we
13547 -- default to System.Interrupts.Default_Interrupt_Priority, see
13548 -- D.3(10).
13550 elsif Has_Attach_Handler (Ptyp)
13551 or else Has_Interrupt_Handler (Ptyp)
13552 then
13553 Append_To (Args,
13554 New_Reference_To (RTE (RE_Default_Interrupt_Priority), Loc));
13556 -- Normal case, no priority or xx_Handler specified, default priority
13558 else
13559 Append_To (Args,
13560 New_Reference_To (RTE (RE_Unspecified_Priority), Loc));
13561 end if;
13563 -- Test for Compiler_Info parameter. This parameter allows entry body
13564 -- procedures and barrier functions to be called from the runtime. It
13565 -- is a pointer to the record generated by the compiler to represent
13566 -- the protected object.
13568 -- A protected type without entries that covers an interface and
13569 -- overrides the abstract routines with protected procedures is
13570 -- considered equivalent to a protected type with entries in the
13571 -- context of dispatching select statements.
13573 if Has_Entry
13574 or else Has_Interfaces (Protect_Rec)
13575 or else
13576 ((Has_Attach_Handler (Ptyp) or else Has_Interrupt_Handler (Ptyp))
13577 and then not Restriction_Active (No_Dynamic_Attachment))
13578 then
13579 declare
13580 Pkg_Id : constant RTU_Id :=
13581 Corresponding_Runtime_Package (Ptyp);
13583 Called_Subp : RE_Id;
13585 begin
13586 case Pkg_Id is
13587 when System_Tasking_Protected_Objects_Entries =>
13588 Called_Subp := RE_Initialize_Protection_Entries;
13590 when System_Tasking_Protected_Objects =>
13591 Called_Subp := RE_Initialize_Protection;
13593 when System_Tasking_Protected_Objects_Single_Entry =>
13594 Called_Subp := RE_Initialize_Protection_Entry;
13596 when others =>
13597 raise Program_Error;
13598 end case;
13600 if Has_Entry
13601 or else not Restricted
13602 or else Has_Interfaces (Protect_Rec)
13603 then
13604 Append_To (Args,
13605 Make_Attribute_Reference (Loc,
13606 Prefix => Make_Identifier (Loc, Name_uInit),
13607 Attribute_Name => Name_Address));
13608 end if;
13610 -- Entry_Bodies parameter. This is a pointer to an array of
13611 -- pointers to the entry body procedures and barrier functions
13612 -- of the object. If the protected type has no entries this
13613 -- object will not exist, in this case, pass a null.
13615 if Has_Entry then
13616 P_Arr := Entry_Bodies_Array (Ptyp);
13618 Append_To (Args,
13619 Make_Attribute_Reference (Loc,
13620 Prefix => New_Reference_To (P_Arr, Loc),
13621 Attribute_Name => Name_Unrestricted_Access));
13623 if Pkg_Id = System_Tasking_Protected_Objects_Entries then
13625 -- Find index mapping function (clumsy but ok for now)
13627 while Ekind (P_Arr) /= E_Function loop
13628 Next_Entity (P_Arr);
13629 end loop;
13631 Append_To (Args,
13632 Make_Attribute_Reference (Loc,
13633 Prefix => New_Reference_To (P_Arr, Loc),
13634 Attribute_Name => Name_Unrestricted_Access));
13635 end if;
13637 elsif Pkg_Id =
13638 System_Tasking_Protected_Objects_Single_Entry
13639 then
13640 Append_To (Args, Make_Null (Loc));
13642 elsif Pkg_Id = System_Tasking_Protected_Objects_Entries then
13643 Append_To (Args, Make_Null (Loc));
13644 Append_To (Args, Make_Null (Loc));
13645 end if;
13647 Append_To (L,
13648 Make_Procedure_Call_Statement (Loc,
13649 Name => New_Reference_To (RTE (Called_Subp), Loc),
13650 Parameter_Associations => Args));
13651 end;
13652 else
13653 Append_To (L,
13654 Make_Procedure_Call_Statement (Loc,
13655 Name => New_Reference_To (RTE (RE_Initialize_Protection), Loc),
13656 Parameter_Associations => Args));
13657 end if;
13658 end if;
13660 if Has_Attach_Handler (Ptyp) then
13662 -- We have a list of N Attach_Handler (ProcI, ExprI), and we have to
13663 -- make the following call:
13665 -- Install_Handlers (_object,
13666 -- ((Expr1, Proc1'access), ...., (ExprN, ProcN'access));
13668 -- or, in the case of Ravenscar:
13670 -- Install_Restricted_Handlers
13671 -- ((Expr1, Proc1'access), ...., (ExprN, ProcN'access));
13673 declare
13674 Args : constant List_Id := New_List;
13675 Table : constant List_Id := New_List;
13676 Ritem : Node_Id := First_Rep_Item (Ptyp);
13678 begin
13679 -- Build the Attach_Handler table argument
13681 while Present (Ritem) loop
13682 if Nkind (Ritem) = N_Pragma
13683 and then Pragma_Name (Ritem) = Name_Attach_Handler
13684 then
13685 declare
13686 Handler : constant Node_Id :=
13687 First (Pragma_Argument_Associations (Ritem));
13689 Interrupt : constant Node_Id := Next (Handler);
13690 Expr : constant Node_Id := Expression (Interrupt);
13692 begin
13693 Append_To (Table,
13694 Make_Aggregate (Loc, Expressions => New_List (
13695 Unchecked_Convert_To
13696 (RTE (RE_System_Interrupt_Id), Expr),
13697 Make_Attribute_Reference (Loc,
13698 Prefix => Make_Selected_Component (Loc,
13699 Make_Identifier (Loc, Name_uInit),
13700 Duplicate_Subexpr_No_Checks
13701 (Expression (Handler))),
13702 Attribute_Name => Name_Access))));
13703 end;
13704 end if;
13706 Next_Rep_Item (Ritem);
13707 end loop;
13709 -- Append the table argument we just built
13711 Append_To (Args, Make_Aggregate (Loc, Table));
13713 -- Append the Install_Handlers (or Install_Restricted_Handlers)
13714 -- call to the statements.
13716 if Restricted then
13717 -- Call a simplified version of Install_Handlers to be used
13718 -- when the Ravenscar restrictions are in effect
13719 -- (Install_Restricted_Handlers).
13721 Append_To (L,
13722 Make_Procedure_Call_Statement (Loc,
13723 Name =>
13724 New_Reference_To
13725 (RTE (RE_Install_Restricted_Handlers), Loc),
13726 Parameter_Associations => Args));
13728 else
13729 if not Uses_Lock_Free (Defining_Identifier (Pdec)) then
13730 -- First, prepends the _object argument
13732 Prepend_To (Args,
13733 Make_Attribute_Reference (Loc,
13734 Prefix =>
13735 Make_Selected_Component (Loc,
13736 Prefix => Make_Identifier (Loc, Name_uInit),
13737 Selector_Name =>
13738 Make_Identifier (Loc, Name_uObject)),
13739 Attribute_Name => Name_Unchecked_Access));
13740 end if;
13742 -- Then, insert call to Install_Handlers
13744 Append_To (L,
13745 Make_Procedure_Call_Statement (Loc,
13746 Name => New_Reference_To (RTE (RE_Install_Handlers), Loc),
13747 Parameter_Associations => Args));
13748 end if;
13749 end;
13750 end if;
13752 return L;
13753 end Make_Initialize_Protection;
13755 ---------------------------
13756 -- Make_Task_Create_Call --
13757 ---------------------------
13759 function Make_Task_Create_Call (Task_Rec : Entity_Id) return Node_Id is
13760 Loc : constant Source_Ptr := Sloc (Task_Rec);
13761 Args : List_Id;
13762 Ecount : Node_Id;
13763 Name : Node_Id;
13764 Tdec : Node_Id;
13765 Tdef : Node_Id;
13766 Tnam : Name_Id;
13767 Ttyp : Node_Id;
13769 begin
13770 Ttyp := Corresponding_Concurrent_Type (Task_Rec);
13771 Tnam := Chars (Ttyp);
13773 -- Get task declaration. In the case of a task type declaration, this is
13774 -- simply the parent of the task type entity. In the single task
13775 -- declaration, this parent will be the implicit type, and we can find
13776 -- the corresponding single task declaration by searching forward in the
13777 -- declaration list in the tree.
13779 -- Is the test for N_Single_Task_Declaration needed here??? Nodes of
13780 -- this type should have been removed during semantic analysis.
13782 Tdec := Parent (Ttyp);
13783 while not Nkind_In (Tdec, N_Task_Type_Declaration,
13784 N_Single_Task_Declaration)
13785 loop
13786 Next (Tdec);
13787 end loop;
13789 -- Now we can find the task definition from this declaration
13791 Tdef := Task_Definition (Tdec);
13793 -- Build the parameter list for the call. Note that _Init is the name
13794 -- of the formal for the object to be initialized, which is the task
13795 -- value record itself.
13797 Args := New_List;
13799 -- Priority parameter. Set to Unspecified_Priority unless there is a
13800 -- Priority rep item, in which case we take the value from the rep item.
13802 if Has_Rep_Item (Ttyp, Name_Priority, Check_Parents => False) then
13803 Append_To (Args,
13804 Make_Selected_Component (Loc,
13805 Prefix => Make_Identifier (Loc, Name_uInit),
13806 Selector_Name => Make_Identifier (Loc, Name_uPriority)));
13807 else
13808 Append_To (Args,
13809 New_Reference_To (RTE (RE_Unspecified_Priority), Loc));
13810 end if;
13812 -- Optional Stack parameter
13814 if Restricted_Profile then
13816 -- If the stack has been preallocated by the expander then
13817 -- pass its address. Otherwise, pass a null address.
13819 if Preallocated_Stacks_On_Target then
13820 Append_To (Args,
13821 Make_Attribute_Reference (Loc,
13822 Prefix =>
13823 Make_Selected_Component (Loc,
13824 Prefix => Make_Identifier (Loc, Name_uInit),
13825 Selector_Name => Make_Identifier (Loc, Name_uStack)),
13826 Attribute_Name => Name_Address));
13828 else
13829 Append_To (Args,
13830 New_Reference_To (RTE (RE_Null_Address), Loc));
13831 end if;
13832 end if;
13834 -- Size parameter. If no Storage_Size pragma is present, then
13835 -- the size is taken from the taskZ variable for the type, which
13836 -- is either Unspecified_Size, or has been reset by the use of
13837 -- a Storage_Size attribute definition clause. If a pragma is
13838 -- present, then the size is taken from the _Size field of the
13839 -- task value record, which was set from the pragma value.
13841 if Present (Tdef)
13842 and then Has_Storage_Size_Pragma (Tdef)
13843 then
13844 Append_To (Args,
13845 Make_Selected_Component (Loc,
13846 Prefix => Make_Identifier (Loc, Name_uInit),
13847 Selector_Name => Make_Identifier (Loc, Name_uSize)));
13849 else
13850 Append_To (Args,
13851 New_Reference_To (Storage_Size_Variable (Ttyp), Loc));
13852 end if;
13854 -- Task_Info parameter. Set to Unspecified_Task_Info unless there is a
13855 -- Task_Info pragma, in which case we take the value from the pragma.
13857 if Has_Rep_Pragma (Ttyp, Name_Task_Info, Check_Parents => False) then
13858 Append_To (Args,
13859 Make_Selected_Component (Loc,
13860 Prefix => Make_Identifier (Loc, Name_uInit),
13861 Selector_Name => Make_Identifier (Loc, Name_uTask_Info)));
13863 else
13864 Append_To (Args,
13865 New_Reference_To (RTE (RE_Unspecified_Task_Info), Loc));
13866 end if;
13868 -- CPU parameter. Set to Unspecified_CPU unless there is a CPU rep item,
13869 -- in which case we take the value from the rep item. The parameter is
13870 -- passed as an Integer because in the case of unspecified CPU the
13871 -- value is not in the range of CPU_Range.
13873 if Has_Rep_Item (Ttyp, Name_CPU, Check_Parents => False) then
13874 Append_To (Args,
13875 Convert_To (Standard_Integer,
13876 Make_Selected_Component (Loc,
13877 Prefix => Make_Identifier (Loc, Name_uInit),
13878 Selector_Name => Make_Identifier (Loc, Name_uCPU))));
13879 else
13880 Append_To (Args,
13881 New_Reference_To (RTE (RE_Unspecified_CPU), Loc));
13882 end if;
13884 if not Restricted_Profile then
13886 -- Deadline parameter. If no Relative_Deadline pragma is present,
13887 -- then the deadline is Time_Span_Zero. If a pragma is present, then
13888 -- the deadline is taken from the _Relative_Deadline field of the
13889 -- task value record, which was set from the pragma value. Note that
13890 -- this parameter must not be generated for the restricted profiles
13891 -- since Ravenscar does not allow deadlines.
13893 -- Case where pragma Relative_Deadline applies: use given value
13895 if Present (Tdef)
13896 and then Has_Relative_Deadline_Pragma (Tdef)
13897 then
13898 Append_To (Args,
13899 Make_Selected_Component (Loc,
13900 Prefix =>
13901 Make_Identifier (Loc, Name_uInit),
13902 Selector_Name =>
13903 Make_Identifier (Loc, Name_uRelative_Deadline)));
13905 -- No pragma Relative_Deadline apply to the task
13907 else
13908 Append_To (Args,
13909 New_Reference_To (RTE (RE_Time_Span_Zero), Loc));
13910 end if;
13912 -- Dispatching_Domain parameter. If no Dispatching_Domain rep item is
13913 -- present, then the dispatching domain is null. If a rep item is
13914 -- present, then the dispatching domain is taken from the
13915 -- _Dispatching_Domain field of the task value record, which was set
13916 -- from the rep item value. Note that this parameter must not be
13917 -- generated for the restricted profiles since Ravenscar does not
13918 -- allow dispatching domains.
13920 -- Case where Dispatching_Domain rep item applies: use given value
13922 if Has_Rep_Item
13923 (Ttyp, Name_Dispatching_Domain, Check_Parents => False)
13924 then
13925 Append_To (Args,
13926 Make_Selected_Component (Loc,
13927 Prefix =>
13928 Make_Identifier (Loc, Name_uInit),
13929 Selector_Name =>
13930 Make_Identifier (Loc, Name_uDispatching_Domain)));
13932 -- No pragma or aspect Dispatching_Domain apply to the task
13934 else
13935 Append_To (Args, Make_Null (Loc));
13936 end if;
13938 -- Number of entries. This is an expression of the form:
13940 -- n + _Init.a'Length + _Init.a'B'Length + ...
13942 -- where a,b... are the entry family names for the task definition
13944 Ecount :=
13945 Build_Entry_Count_Expression
13946 (Ttyp,
13947 Component_Items
13948 (Component_List
13949 (Type_Definition
13950 (Parent (Corresponding_Record_Type (Ttyp))))),
13951 Loc);
13952 Append_To (Args, Ecount);
13954 -- Master parameter. This is a reference to the _Master parameter of
13955 -- the initialization procedure, except in the case of the pragma
13956 -- Restrictions (No_Task_Hierarchy) where the value is fixed to
13957 -- System.Tasking.Library_Task_Level.
13959 if Restriction_Active (No_Task_Hierarchy) = False then
13960 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
13961 else
13962 Append_To (Args,
13963 New_Occurrence_Of (RTE (RE_Library_Task_Level), Loc));
13964 end if;
13965 end if;
13967 -- State parameter. This is a pointer to the task body procedure. The
13968 -- required value is obtained by taking 'Unrestricted_Access of the task
13969 -- body procedure and converting it (with an unchecked conversion) to
13970 -- the type required by the task kernel. For further details, see the
13971 -- description of Expand_N_Task_Body. We use 'Unrestricted_Access rather
13972 -- than 'Address in order to avoid creating trampolines.
13974 declare
13975 Body_Proc : constant Node_Id := Get_Task_Body_Procedure (Ttyp);
13976 Subp_Ptr_Typ : constant Node_Id :=
13977 Create_Itype (E_Access_Subprogram_Type, Tdec);
13978 Ref : constant Node_Id := Make_Itype_Reference (Loc);
13980 begin
13981 Set_Directly_Designated_Type (Subp_Ptr_Typ, Body_Proc);
13982 Set_Etype (Subp_Ptr_Typ, Subp_Ptr_Typ);
13984 -- Be sure to freeze a reference to the access-to-subprogram type,
13985 -- otherwise gigi will complain that it's in the wrong scope, because
13986 -- it's actually inside the init procedure for the record type that
13987 -- corresponds to the task type.
13989 -- This processing is causing a crash in the .NET/JVM back ends that
13990 -- is not yet understood, so skip it in these cases ???
13992 if VM_Target = No_VM then
13993 Set_Itype (Ref, Subp_Ptr_Typ);
13994 Append_Freeze_Action (Task_Rec, Ref);
13996 Append_To (Args,
13997 Unchecked_Convert_To (RTE (RE_Task_Procedure_Access),
13998 Make_Qualified_Expression (Loc,
13999 Subtype_Mark => New_Reference_To (Subp_Ptr_Typ, Loc),
14000 Expression =>
14001 Make_Attribute_Reference (Loc,
14002 Prefix =>
14003 New_Occurrence_Of (Body_Proc, Loc),
14004 Attribute_Name => Name_Unrestricted_Access))));
14006 -- For the .NET/JVM cases revert to the original code below ???
14008 else
14009 Append_To (Args,
14010 Unchecked_Convert_To (RTE (RE_Task_Procedure_Access),
14011 Make_Attribute_Reference (Loc,
14012 Prefix =>
14013 New_Occurrence_Of (Body_Proc, Loc),
14014 Attribute_Name => Name_Address)));
14015 end if;
14016 end;
14018 -- Discriminants parameter. This is just the address of the task
14019 -- value record itself (which contains the discriminant values
14021 Append_To (Args,
14022 Make_Attribute_Reference (Loc,
14023 Prefix => Make_Identifier (Loc, Name_uInit),
14024 Attribute_Name => Name_Address));
14026 -- Elaborated parameter. This is an access to the elaboration Boolean
14028 Append_To (Args,
14029 Make_Attribute_Reference (Loc,
14030 Prefix => Make_Identifier (Loc, New_External_Name (Tnam, 'E')),
14031 Attribute_Name => Name_Unchecked_Access));
14033 -- Add Chain parameter (not done for sequential elaboration policy, see
14034 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
14036 if Partition_Elaboration_Policy /= 'S' then
14037 Append_To (Args, Make_Identifier (Loc, Name_uChain));
14038 end if;
14040 -- Task name parameter. Take this from the _Task_Id parameter to the
14041 -- init call unless there is a Task_Name pragma, in which case we take
14042 -- the value from the pragma.
14044 if Has_Rep_Pragma (Ttyp, Name_Task_Name, Check_Parents => False) then
14045 -- Copy expression in full, because it may be dynamic and have
14046 -- side effects.
14048 Append_To (Args,
14049 New_Copy_Tree
14050 (Expression
14051 (First
14052 (Pragma_Argument_Associations
14053 (Get_Rep_Pragma
14054 (Ttyp, Name_Task_Name, Check_Parents => False))))));
14056 else
14057 Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
14058 end if;
14060 -- Created_Task parameter. This is the _Task_Id field of the task
14061 -- record value
14063 Append_To (Args,
14064 Make_Selected_Component (Loc,
14065 Prefix => Make_Identifier (Loc, Name_uInit),
14066 Selector_Name => Make_Identifier (Loc, Name_uTask_Id)));
14068 declare
14069 Create_RE : RE_Id;
14071 begin
14072 if Restricted_Profile then
14073 if Partition_Elaboration_Policy = 'S' then
14074 Create_RE := RE_Create_Restricted_Task_Sequential;
14075 else
14076 Create_RE := RE_Create_Restricted_Task;
14077 end if;
14078 else
14079 Create_RE := RE_Create_Task;
14080 end if;
14082 Name := New_Reference_To (RTE (Create_RE), Loc);
14083 end;
14085 return
14086 Make_Procedure_Call_Statement (Loc,
14087 Name => Name,
14088 Parameter_Associations => Args);
14089 end Make_Task_Create_Call;
14091 ------------------------------
14092 -- Next_Protected_Operation --
14093 ------------------------------
14095 function Next_Protected_Operation (N : Node_Id) return Node_Id is
14096 Next_Op : Node_Id;
14098 begin
14099 Next_Op := Next (N);
14100 while Present (Next_Op)
14101 and then not Nkind_In (Next_Op, N_Subprogram_Body, N_Entry_Body)
14102 loop
14103 Next (Next_Op);
14104 end loop;
14106 return Next_Op;
14107 end Next_Protected_Operation;
14109 ---------------------
14110 -- Null_Statements --
14111 ---------------------
14113 function Null_Statements (Stats : List_Id) return Boolean is
14114 Stmt : Node_Id;
14116 begin
14117 Stmt := First (Stats);
14118 while Nkind (Stmt) /= N_Empty
14119 and then (Nkind_In (Stmt, N_Null_Statement, N_Label)
14120 or else
14121 (Nkind (Stmt) = N_Pragma
14122 and then
14123 Nam_In (Pragma_Name (Stmt), Name_Unreferenced,
14124 Name_Unmodified,
14125 Name_Warnings)))
14126 loop
14127 Next (Stmt);
14128 end loop;
14130 return Nkind (Stmt) = N_Empty;
14131 end Null_Statements;
14133 --------------------------
14134 -- Parameter_Block_Pack --
14135 --------------------------
14137 function Parameter_Block_Pack
14138 (Loc : Source_Ptr;
14139 Blk_Typ : Entity_Id;
14140 Actuals : List_Id;
14141 Formals : List_Id;
14142 Decls : List_Id;
14143 Stmts : List_Id) return Node_Id
14145 Actual : Entity_Id;
14146 Expr : Node_Id := Empty;
14147 Formal : Entity_Id;
14148 Has_Param : Boolean := False;
14149 P : Entity_Id;
14150 Params : List_Id;
14151 Temp_Asn : Node_Id;
14152 Temp_Nam : Node_Id;
14154 begin
14155 Actual := First (Actuals);
14156 Formal := Defining_Identifier (First (Formals));
14157 Params := New_List;
14159 while Present (Actual) loop
14160 if Is_By_Copy_Type (Etype (Actual)) then
14161 -- Generate:
14162 -- Jnn : aliased <formal-type>
14164 Temp_Nam := Make_Temporary (Loc, 'J');
14166 Append_To (Decls,
14167 Make_Object_Declaration (Loc,
14168 Aliased_Present =>
14169 True,
14170 Defining_Identifier =>
14171 Temp_Nam,
14172 Object_Definition =>
14173 New_Reference_To (Etype (Formal), Loc)));
14175 if Ekind (Formal) /= E_Out_Parameter then
14177 -- Generate:
14178 -- Jnn := <actual>
14180 Temp_Asn :=
14181 New_Reference_To (Temp_Nam, Loc);
14183 Set_Assignment_OK (Temp_Asn);
14185 Append_To (Stmts,
14186 Make_Assignment_Statement (Loc,
14187 Name =>
14188 Temp_Asn,
14189 Expression =>
14190 New_Copy_Tree (Actual)));
14191 end if;
14193 -- Generate:
14194 -- Jnn'unchecked_access
14196 Append_To (Params,
14197 Make_Attribute_Reference (Loc,
14198 Attribute_Name =>
14199 Name_Unchecked_Access,
14200 Prefix =>
14201 New_Reference_To (Temp_Nam, Loc)));
14203 Has_Param := True;
14205 -- The controlling parameter is omitted
14207 else
14208 if not Is_Controlling_Actual (Actual) then
14209 Append_To (Params,
14210 Make_Reference (Loc, New_Copy_Tree (Actual)));
14212 Has_Param := True;
14213 end if;
14214 end if;
14216 Next_Actual (Actual);
14217 Next_Formal_With_Extras (Formal);
14218 end loop;
14220 if Has_Param then
14221 Expr := Make_Aggregate (Loc, Params);
14222 end if;
14224 -- Generate:
14225 -- P : Ann := (
14226 -- J1'unchecked_access;
14227 -- <actual2>'reference;
14228 -- ...);
14230 P := Make_Temporary (Loc, 'P');
14232 Append_To (Decls,
14233 Make_Object_Declaration (Loc,
14234 Defining_Identifier =>
14236 Object_Definition =>
14237 New_Reference_To (Blk_Typ, Loc),
14238 Expression =>
14239 Expr));
14241 return P;
14242 end Parameter_Block_Pack;
14244 ----------------------------
14245 -- Parameter_Block_Unpack --
14246 ----------------------------
14248 function Parameter_Block_Unpack
14249 (Loc : Source_Ptr;
14250 P : Entity_Id;
14251 Actuals : List_Id;
14252 Formals : List_Id) return List_Id
14254 Actual : Entity_Id;
14255 Asnmt : Node_Id;
14256 Formal : Entity_Id;
14257 Has_Asnmt : Boolean := False;
14258 Result : constant List_Id := New_List;
14260 begin
14261 Actual := First (Actuals);
14262 Formal := Defining_Identifier (First (Formals));
14263 while Present (Actual) loop
14264 if Is_By_Copy_Type (Etype (Actual))
14265 and then Ekind (Formal) /= E_In_Parameter
14266 then
14267 -- Generate:
14268 -- <actual> := P.<formal>;
14270 Asnmt :=
14271 Make_Assignment_Statement (Loc,
14272 Name =>
14273 New_Copy (Actual),
14274 Expression =>
14275 Make_Explicit_Dereference (Loc,
14276 Make_Selected_Component (Loc,
14277 Prefix =>
14278 New_Reference_To (P, Loc),
14279 Selector_Name =>
14280 Make_Identifier (Loc, Chars (Formal)))));
14282 Set_Assignment_OK (Name (Asnmt));
14283 Append_To (Result, Asnmt);
14285 Has_Asnmt := True;
14286 end if;
14288 Next_Actual (Actual);
14289 Next_Formal_With_Extras (Formal);
14290 end loop;
14292 if Has_Asnmt then
14293 return Result;
14294 else
14295 return New_List (Make_Null_Statement (Loc));
14296 end if;
14297 end Parameter_Block_Unpack;
14299 ----------------------
14300 -- Set_Discriminals --
14301 ----------------------
14303 procedure Set_Discriminals (Dec : Node_Id) is
14304 D : Entity_Id;
14305 Pdef : Entity_Id;
14306 D_Minal : Entity_Id;
14308 begin
14309 pragma Assert (Nkind (Dec) = N_Protected_Type_Declaration);
14310 Pdef := Defining_Identifier (Dec);
14312 if Has_Discriminants (Pdef) then
14313 D := First_Discriminant (Pdef);
14314 while Present (D) loop
14315 D_Minal :=
14316 Make_Defining_Identifier (Sloc (D),
14317 Chars => New_External_Name (Chars (D), 'D'));
14319 Set_Ekind (D_Minal, E_Constant);
14320 Set_Etype (D_Minal, Etype (D));
14321 Set_Scope (D_Minal, Pdef);
14322 Set_Discriminal (D, D_Minal);
14323 Set_Discriminal_Link (D_Minal, D);
14325 Next_Discriminant (D);
14326 end loop;
14327 end if;
14328 end Set_Discriminals;
14330 -----------------------
14331 -- Trivial_Accept_OK --
14332 -----------------------
14334 function Trivial_Accept_OK return Boolean is
14335 begin
14336 case Opt.Task_Dispatching_Policy is
14338 -- If we have the default task dispatching policy in effect, we can
14339 -- definitely do the optimization (one way of looking at this is to
14340 -- think of the formal definition of the default policy being allowed
14341 -- to run any task it likes after a rendezvous, so even if notionally
14342 -- a full rescheduling occurs, we can say that our dispatching policy
14343 -- (i.e. the default dispatching policy) reorders the queue to be the
14344 -- same as just before the call.
14346 when ' ' =>
14347 return True;
14349 -- FIFO_Within_Priorities certainly does not permit this
14350 -- optimization since the Rendezvous is a scheduling action that may
14351 -- require some other task to be run.
14353 when 'F' =>
14354 return False;
14356 -- For now, disallow the optimization for all other policies. This
14357 -- may be over-conservative, but it is certainly not incorrect.
14359 when others =>
14360 return False;
14362 end case;
14363 end Trivial_Accept_OK;
14365 end Exp_Ch9;