OSDN Git Service

Minor reformatting.
[pf3gnuchains/gcc-fork.git] / gcc / ada / exp_ch9.adb
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-2010, 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 ------------------------------------------------------------------------------
25
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_Ch11; use Sem_Ch11;
55 with Sem_Elab; use Sem_Elab;
56 with Sem_Eval; use Sem_Eval;
57 with Sem_Res;  use Sem_Res;
58 with Sem_Util; use Sem_Util;
59 with Sinfo;    use Sinfo;
60 with Snames;   use Snames;
61 with Stand;    use Stand;
62 with Stringt;  use Stringt;
63 with Targparm; use Targparm;
64 with Tbuild;   use Tbuild;
65 with Uintp;    use Uintp;
66
67 package body Exp_Ch9 is
68
69    --  The following constant establishes the upper bound for the index of
70    --  an entry family. It is used to limit the allocated size of protected
71    --  types with defaulted discriminant of an integer type, when the bound
72    --  of some entry family depends on a discriminant. The limitation to
73    --  entry families of 128K should be reasonable in all cases, and is a
74    --  documented implementation restriction. It will be lifted when protected
75    --  entry families are re-implemented as a single ordered queue.
76
77    Entry_Family_Bound : constant Int := 2**16;
78
79    -----------------------
80    -- Local Subprograms --
81    -----------------------
82
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.
91
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.
100
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.
112
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.
117
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.
124
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.
130
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).
138
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.
147
148    function Build_Parameter_Block
149      (Loc     : Source_Ptr;
150       Actuals : List_Id;
151       Formals : List_Id;
152       Decls   : List_Id) return Entity_Id;
153    --  Generate an access type for each actual parameter in the list Actuals.
154    --  Create an encapsulating record that contains all the actuals and return
155    --  its type. Generate:
156    --    type Ann1 is access all <actual1-type>
157    --    ...
158    --    type AnnN is access all <actualN-type>
159    --    type Pnn is record
160    --       <formal1> : Ann1;
161    --       ...
162    --       <formalN> : AnnN;
163    --    end record;
164
165    procedure Build_PPC_Wrapper (E : Entity_Id; Decl : Node_Id);
166    --  Build body of wrapper procedure for an entry or entry family that has
167    --  pre/postconditions. The body gathers the PPC's and expands them in the
168    --  usual way, and performs the entry call itself. This way preconditions
169    --  are evaluated before the call is queued. E is the entry in question,
170    --  and Decl is the enclosing synchronized type declaration at whose
171    --  freeze point the generated body is analyzed.
172
173    procedure Build_Wrapper_Bodies
174      (Loc : Source_Ptr;
175       Typ : Entity_Id;
176       N   : Node_Id);
177    --  Ada 2005 (AI-345): Typ is either a concurrent type or the corresponding
178    --  record of a concurrent type. N is the insertion node where all bodies
179    --  will be placed. This routine builds the bodies of the subprograms which
180    --  serve as an indirection mechanism to overriding primitives of concurrent
181    --  types, entries and protected procedures. Any new body is analyzed.
182
183    procedure Build_Wrapper_Specs
184      (Loc : Source_Ptr;
185       Typ : Entity_Id;
186       N   : in out Node_Id);
187    --  Ada 2005 (AI-345): Typ is either a concurrent type or the corresponding
188    --  record of a concurrent type. N is the insertion node where all specs
189    --  will be placed. This routine builds the specs of the subprograms which
190    --  serve as an indirection mechanism to overriding primitives of concurrent
191    --  types, entries and protected procedures. Any new spec is analyzed.
192
193    function Build_Find_Body_Index (Typ : Entity_Id) return Node_Id;
194    --  Build the function that translates the entry index in the call
195    --  (which depends on the size of entry families) into an index into the
196    --  Entry_Bodies_Array, to determine the body and barrier function used
197    --  in a protected entry call. A pointer to this function appears in every
198    --  protected object.
199
200    function Build_Find_Body_Index_Spec (Typ : Entity_Id) return Node_Id;
201    --  Build subprogram declaration for previous one
202
203    function Build_Protected_Entry
204      (N   : Node_Id;
205       Ent : Entity_Id;
206       Pid : Node_Id) return Node_Id;
207    --  Build the procedure implementing the statement sequence of the specified
208    --  entry body.
209
210    function Build_Protected_Entry_Specification
211      (Loc    : Source_Ptr;
212       Def_Id : Entity_Id;
213       Ent_Id : Entity_Id) return Node_Id;
214    --  Build a specification for the procedure implementing the statements of
215    --  the specified entry body. Add attributes associating it with the entry
216    --  defining identifier Ent_Id.
217
218    function Build_Protected_Spec
219      (N           : Node_Id;
220       Obj_Type    : Entity_Id;
221       Ident       : Entity_Id;
222       Unprotected : Boolean := False) return List_Id;
223    --  Utility shared by Build_Protected_Sub_Spec and Expand_Access_Protected_
224    --  Subprogram_Type. Builds signature of protected subprogram, adding the
225    --  formal that corresponds to the object itself. For an access to protected
226    --  subprogram, there is no object type to specify, so the parameter has
227    --  type Address and mode In. An indirect call through such a pointer will
228    --  convert the address to a reference to the actual object. The object is
229    --  a limited record and therefore a by_reference type.
230
231    function Build_Protected_Subprogram_Body
232      (N         : Node_Id;
233       Pid       : Node_Id;
234       N_Op_Spec : Node_Id) return Node_Id;
235    --  This function is used to construct the protected version of a protected
236    --  subprogram. Its statement sequence first defers abort, then locks
237    --  the associated protected object, and then enters a block that contains
238    --  a call to the unprotected version of the subprogram (for details, see
239    --  Build_Unprotected_Subprogram_Body). This block statement requires
240    --  a cleanup handler that unlocks the object in all cases.
241    --  (see Exp_Ch7.Expand_Cleanup_Actions).
242
243    function Build_Selected_Name
244      (Prefix      : Entity_Id;
245       Selector    : Entity_Id;
246       Append_Char : Character := ' ') return Name_Id;
247    --  Build a name in the form of Prefix__Selector, with an optional
248    --  character appended. This is used for internal subprograms generated
249    --  for operations of protected types, including barrier functions.
250    --  For the subprograms generated for entry bodies and entry barriers,
251    --  the generated name includes a sequence number that makes names
252    --  unique in the presence of entry overloading. This is necessary
253    --  because entry body procedures and barrier functions all have the
254    --  same signature.
255
256    procedure Build_Simple_Entry_Call
257      (N       : Node_Id;
258       Concval : Node_Id;
259       Ename   : Node_Id;
260       Index   : Node_Id);
261    --  Some comments here would be useful ???
262
263    function Build_Task_Proc_Specification (T : Entity_Id) return Node_Id;
264    --  This routine constructs a specification for the procedure that we will
265    --  build for the task body for task type T. The spec has the form:
266    --
267    --    procedure tnameB (_Task : access tnameV);
268    --
269    --  where name is the character name taken from the task type entity that
270    --  is passed as the argument to the procedure, and tnameV is the task
271    --  value type that is associated with the task type.
272
273    function Build_Unprotected_Subprogram_Body
274      (N   : Node_Id;
275       Pid : Node_Id) return Node_Id;
276    --  This routine constructs the unprotected version of a protected
277    --  subprogram body, which is contains all of the code in the
278    --  original, unexpanded body. This is the version of the protected
279    --  subprogram that is called from all protected operations on the same
280    --  object, including the protected version of the same subprogram.
281
282    procedure Collect_Entry_Families
283      (Loc          : Source_Ptr;
284       Cdecls       : List_Id;
285       Current_Node : in out Node_Id;
286       Conctyp      : Entity_Id);
287    --  For each entry family in a concurrent type, create an anonymous array
288    --  type of the right size, and add a component to the corresponding_record.
289
290    function Concurrent_Object
291      (Spec_Id  : Entity_Id;
292       Conc_Typ : Entity_Id) return Entity_Id;
293    --  Given a subprogram entity Spec_Id and concurrent type Conc_Typ, return
294    --  the entity associated with the concurrent object in the Protected_Body_
295    --  Subprogram or the Task_Body_Procedure of Spec_Id. The returned entity
296    --  denotes formal parameter _O, _object or _task.
297
298    function Copy_Result_Type (Res : Node_Id) return Node_Id;
299    --  Copy the result type of a function specification, when building the
300    --  internal operation corresponding to a protected function, or when
301    --  expanding an access to protected function. If the result is an anonymous
302    --  access to subprogram itself, we need to create a new signature with the
303    --  same parameter names and the same resolved types, but with new entities
304    --  for the formals.
305
306    procedure Debug_Private_Data_Declarations (Decls : List_Id);
307    --  Decls is a list which may contain the declarations created by Install_
308    --  Private_Data_Declarations. All generated entities are marked as needing
309    --  debug info and debug nodes are manually generation where necessary. This
310    --  step of the expansion must to be done after private data has been moved
311    --  to its final resting scope to ensure proper visibility of debug objects.
312
313    function Family_Offset
314      (Loc  : Source_Ptr;
315       Hi   : Node_Id;
316       Lo   : Node_Id;
317       Ttyp : Entity_Id;
318       Cap  : Boolean) return Node_Id;
319    --  Compute (Hi - Lo) for two entry family indices. Hi is the index in
320    --  an accept statement, or the upper bound in the discrete subtype of
321    --  an entry declaration. Lo is the corresponding lower bound. Ttyp is
322    --  the concurrent type of the entry. If Cap is true, the result is
323    --  capped according to Entry_Family_Bound.
324
325    function Family_Size
326      (Loc  : Source_Ptr;
327       Hi   : Node_Id;
328       Lo   : Node_Id;
329       Ttyp : Entity_Id;
330       Cap  : Boolean) return Node_Id;
331    --  Compute (Hi - Lo) + 1 Max 0, to determine the number of entries in
332    --  a family, and handle properly the superflat case. This is equivalent
333    --  to the use of 'Length on the index type, but must use Family_Offset
334    --  to handle properly the case of bounds that depend on discriminants.
335    --  If Cap is true, the result is capped according to Entry_Family_Bound.
336
337    procedure Extract_Dispatching_Call
338      (N        : Node_Id;
339       Call_Ent : out Entity_Id;
340       Object   : out Entity_Id;
341       Actuals  : out List_Id;
342       Formals  : out List_Id);
343    --  Given a dispatching call, extract the entity of the name of the call,
344    --  its object parameter, its actual parameters and the formal parameters
345    --  of the overridden interface-level version.
346
347    procedure Extract_Entry
348      (N       : Node_Id;
349       Concval : out Node_Id;
350       Ename   : out Node_Id;
351       Index   : out Node_Id);
352    --  Given an entry call, returns the associated concurrent object,
353    --  the entry name, and the entry family index.
354
355    function Find_Task_Or_Protected_Pragma
356      (T : Node_Id;
357       P : Name_Id) return Node_Id;
358    --  Searches the task or protected definition T for the first occurrence
359    --  of the pragma whose name is given by P. The caller has ensured that
360    --  the pragma is present in the task definition. A special case is that
361    --  when P is Name_uPriority, the call will also find Interrupt_Priority.
362    --  ??? Should be implemented with the rep item chain mechanism.
363
364    function Index_Object (Spec_Id : Entity_Id) return Entity_Id;
365    --  Given a subprogram identifier, return the entity which is associated
366    --  with the protection entry index in the Protected_Body_Subprogram or the
367    --  Task_Body_Procedure of Spec_Id. The returned entity denotes formal
368    --  parameter _E.
369
370    function Is_Potentially_Large_Family
371      (Base_Index : Entity_Id;
372       Conctyp    : Entity_Id;
373       Lo         : Node_Id;
374       Hi         : Node_Id) return Boolean;
375
376    function Is_Private_Primitive_Subprogram (Id : Entity_Id) return Boolean;
377    --  Determine whether Id is a function or a procedure and is marked as a
378    --  private primitive.
379
380    function Null_Statements (Stats : List_Id) return Boolean;
381    --  Used to check DO-END sequence. Checks for equivalent of DO NULL; END.
382    --  Allows labels, and pragma Warnings/Unreferenced in the sequence as
383    --  well to still count as null. Returns True for a null sequence. The
384    --  argument is the list of statements from the DO-END sequence.
385
386    function Parameter_Block_Pack
387      (Loc     : Source_Ptr;
388       Blk_Typ : Entity_Id;
389       Actuals : List_Id;
390       Formals : List_Id;
391       Decls   : List_Id;
392       Stmts   : List_Id) return Entity_Id;
393    --  Set the components of the generated parameter block with the values of
394    --  the actual parameters. Generate aliased temporaries to capture the
395    --  values for types that are passed by copy. Otherwise generate a reference
396    --  to the actual's value. Return the address of the aggregate block.
397    --  Generate:
398    --    Jnn1 : alias <formal-type1>;
399    --    Jnn1 := <actual1>;
400    --    ...
401    --    P : Blk_Typ := (
402    --      Jnn1'unchecked_access;
403    --      <actual2>'reference;
404    --      ...);
405
406    function Parameter_Block_Unpack
407      (Loc     : Source_Ptr;
408       P       : Entity_Id;
409       Actuals : List_Id;
410       Formals : List_Id) return List_Id;
411    --  Retrieve the values of the components from the parameter block and
412    --  assign then to the original actual parameters. Generate:
413    --    <actual1> := P.<formal1>;
414    --    ...
415    --    <actualN> := P.<formalN>;
416
417    function Trivial_Accept_OK return Boolean;
418    --  If there is no DO-END block for an accept, or if the DO-END block has
419    --  only null statements, then it is possible to do the Rendezvous with much
420    --  less overhead using the Accept_Trivial routine in the run-time library.
421    --  However, this is not always a valid optimization. Whether it is valid or
422    --  not depends on the Task_Dispatching_Policy. The issue is whether a full
423    --  rescheduling action is required or not. In FIFO_Within_Priorities, such
424    --  a rescheduling is required, so this optimization is not allowed. This
425    --  function returns True if the optimization is permitted.
426
427    -----------------------------
428    -- Actual_Index_Expression --
429    -----------------------------
430
431    function Actual_Index_Expression
432      (Sloc  : Source_Ptr;
433       Ent   : Entity_Id;
434       Index : Node_Id;
435       Tsk   : Entity_Id) return Node_Id
436    is
437       Ttyp : constant Entity_Id := Etype (Tsk);
438       Expr : Node_Id;
439       Num  : Node_Id;
440       Lo   : Node_Id;
441       Hi   : Node_Id;
442       Prev : Entity_Id;
443       S    : Node_Id;
444
445       function Actual_Family_Offset (Hi, Lo : Node_Id) return Node_Id;
446       --  Compute difference between bounds of entry family
447
448       --------------------------
449       -- Actual_Family_Offset --
450       --------------------------
451
452       function Actual_Family_Offset (Hi, Lo : Node_Id) return Node_Id is
453
454          function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id;
455          --  Replace a reference to a discriminant with a selected component
456          --  denoting the discriminant of the target task.
457
458          -----------------------------
459          -- Actual_Discriminant_Ref --
460          -----------------------------
461
462          function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id is
463             Typ : constant Entity_Id := Etype (Bound);
464             B   : Node_Id;
465
466          begin
467             if not Is_Entity_Name (Bound)
468               or else Ekind (Entity (Bound)) /= E_Discriminant
469             then
470                if Nkind (Bound) = N_Attribute_Reference then
471                   return Bound;
472                else
473                   B := New_Copy_Tree (Bound);
474                end if;
475
476             else
477                B :=
478                  Make_Selected_Component (Sloc,
479                    Prefix => New_Copy_Tree (Tsk),
480                    Selector_Name => New_Occurrence_Of (Entity (Bound), Sloc));
481
482                Analyze_And_Resolve (B, Typ);
483             end if;
484
485             return
486               Make_Attribute_Reference (Sloc,
487                 Attribute_Name => Name_Pos,
488                 Prefix => New_Occurrence_Of (Etype (Bound), Sloc),
489                 Expressions => New_List (B));
490          end Actual_Discriminant_Ref;
491
492       --  Start of processing for Actual_Family_Offset
493
494       begin
495          return
496            Make_Op_Subtract (Sloc,
497              Left_Opnd  => Actual_Discriminant_Ref (Hi),
498              Right_Opnd => Actual_Discriminant_Ref (Lo));
499       end Actual_Family_Offset;
500
501    --  Start of processing for Actual_Index_Expression
502
503    begin
504       --  The queues of entries and entry families appear in textual order in
505       --  the associated record. The entry index is computed as the sum of the
506       --  number of queues for all entries that precede the designated one, to
507       --  which is added the index expression, if this expression denotes a
508       --  member of a family.
509
510       --  The following is a place holder for the count of simple entries
511
512       Num := Make_Integer_Literal (Sloc, 1);
513
514       --  We construct an expression which is a series of addition operations.
515       --  See comments in Entry_Index_Expression, which is identical in
516       --  structure.
517
518       if Present (Index) then
519          S := Etype (Discrete_Subtype_Definition (Declaration_Node (Ent)));
520
521          Expr :=
522            Make_Op_Add (Sloc,
523              Left_Opnd  => Num,
524
525              Right_Opnd =>
526                Actual_Family_Offset (
527                  Make_Attribute_Reference (Sloc,
528                    Attribute_Name => Name_Pos,
529                    Prefix => New_Reference_To (Base_Type (S), Sloc),
530                    Expressions => New_List (Relocate_Node (Index))),
531                  Type_Low_Bound (S)));
532       else
533          Expr := Num;
534       end if;
535
536       --  Now add lengths of preceding entries and entry families
537
538       Prev := First_Entity (Ttyp);
539
540       while Chars (Prev) /= Chars (Ent)
541         or else (Ekind (Prev) /= Ekind (Ent))
542         or else not Sem_Ch6.Type_Conformant (Ent, Prev)
543       loop
544          if Ekind (Prev) = E_Entry then
545             Set_Intval (Num, Intval (Num) + 1);
546
547          elsif Ekind (Prev) = E_Entry_Family then
548             S :=
549               Etype (Discrete_Subtype_Definition (Declaration_Node (Prev)));
550
551             --  The need for the following full view retrieval stems from
552             --  this complex case of nested generics and tasking:
553
554             --     generic
555             --        type Formal_Index is range <>;
556             --        ...
557             --     package Outer is
558             --        type Index is private;
559             --        generic
560             --           ...
561             --        package Inner is
562             --           procedure P;
563             --        end Inner;
564             --     private
565             --        type Index is new Formal_Index range 1 .. 10;
566             --     end Outer;
567
568             --     package body Outer is
569             --        task type T is
570             --           entry Fam (Index);  --  (2)
571             --           entry E;
572             --        end T;
573             --        package body Inner is  --  (3)
574             --           procedure P is
575             --           begin
576             --              T.E;             --  (1)
577             --           end P;
578             --       end Inner;
579             --       ...
580
581             --  We are currently building the index expression for the entry
582             --  call "T.E" (1). Part of the expansion must mention the range
583             --  of the discrete type "Index" (2) of entry family "Fam".
584             --  However only the private view of type "Index" is available to
585             --  the inner generic (3) because there was no prior mention of
586             --  the type inside "Inner". This visibility requirement is
587             --  implicit and cannot be detected during the construction of
588             --  the generic trees and needs special handling.
589
590             if In_Instance_Body
591               and then Is_Private_Type (S)
592               and then Present (Full_View (S))
593             then
594                S := Full_View (S);
595             end if;
596
597             Lo := Type_Low_Bound  (S);
598             Hi := Type_High_Bound (S);
599
600             Expr :=
601               Make_Op_Add (Sloc,
602               Left_Opnd  => Expr,
603               Right_Opnd =>
604                 Make_Op_Add (Sloc,
605                   Left_Opnd =>
606                     Actual_Family_Offset (Hi, Lo),
607                   Right_Opnd =>
608                     Make_Integer_Literal (Sloc, 1)));
609
610          --  Other components are anonymous types to be ignored
611
612          else
613             null;
614          end if;
615
616          Next_Entity (Prev);
617       end loop;
618
619       return Expr;
620    end Actual_Index_Expression;
621
622    --------------------------
623    -- Add_Formal_Renamings --
624    --------------------------
625
626    procedure Add_Formal_Renamings
627      (Spec  : Node_Id;
628       Decls : List_Id;
629       Ent   : Entity_Id;
630       Loc   : Source_Ptr)
631    is
632       Ptr : constant Entity_Id :=
633               Defining_Identifier
634                 (Next (First (Parameter_Specifications (Spec))));
635       --  The name of the formal that holds the address of the parameter block
636       --  for the call.
637
638       Comp   : Entity_Id;
639       Decl   : Node_Id;
640       Formal : Entity_Id;
641       New_F  : Entity_Id;
642
643    begin
644       Formal := First_Formal (Ent);
645       while Present (Formal) loop
646          Comp := Entry_Component (Formal);
647          New_F :=
648            Make_Defining_Identifier (Sloc (Formal),
649              Chars => Chars (Formal));
650          Set_Etype (New_F, Etype (Formal));
651          Set_Scope (New_F, Ent);
652
653          --  Now we set debug info needed on New_F even though it does not
654          --  come from source, so that the debugger will get the right
655          --  information for these generated names.
656
657          Set_Debug_Info_Needed (New_F);
658
659          if Ekind (Formal) = E_In_Parameter then
660             Set_Ekind (New_F, E_Constant);
661          else
662             Set_Ekind (New_F, E_Variable);
663             Set_Extra_Constrained (New_F, Extra_Constrained (Formal));
664          end if;
665
666          Set_Actual_Subtype (New_F, Actual_Subtype (Formal));
667
668          Decl :=
669            Make_Object_Renaming_Declaration (Loc,
670            Defining_Identifier => New_F,
671            Subtype_Mark =>
672              New_Reference_To (Etype (Formal), Loc),
673            Name =>
674              Make_Explicit_Dereference (Loc,
675                Make_Selected_Component (Loc,
676                  Prefix =>
677                    Unchecked_Convert_To (Entry_Parameters_Type (Ent),
678                      Make_Identifier (Loc, Chars (Ptr))),
679                  Selector_Name =>
680                    New_Reference_To (Comp, Loc))));
681
682          Append (Decl, Decls);
683          Set_Renamed_Object (Formal, New_F);
684          Next_Formal (Formal);
685       end loop;
686    end Add_Formal_Renamings;
687
688    ------------------------
689    -- Add_Object_Pointer --
690    ------------------------
691
692    procedure Add_Object_Pointer
693      (Loc      : Source_Ptr;
694       Conc_Typ : Entity_Id;
695       Decls    : List_Id)
696    is
697       Rec_Typ : constant Entity_Id := Corresponding_Record_Type (Conc_Typ);
698       Decl    : Node_Id;
699       Obj_Ptr : Node_Id;
700
701    begin
702       --  Create the renaming declaration for the Protection object of a
703       --  protected type. _Object is used by Complete_Entry_Body.
704       --  ??? An attempt to make this a renaming was unsuccessful.
705
706       --  Build the entity for the access type
707
708       Obj_Ptr :=
709         Make_Defining_Identifier (Loc,
710           New_External_Name (Chars (Rec_Typ), 'P'));
711
712       --  Generate:
713       --    _object : poVP := poVP!O;
714
715       Decl :=
716         Make_Object_Declaration (Loc,
717           Defining_Identifier =>
718             Make_Defining_Identifier (Loc, Name_uObject),
719           Object_Definition =>
720             New_Reference_To (Obj_Ptr, Loc),
721           Expression =>
722             Unchecked_Convert_To (Obj_Ptr,
723               Make_Identifier (Loc, Name_uO)));
724       Set_Debug_Info_Needed (Defining_Identifier (Decl));
725       Prepend_To (Decls, Decl);
726
727       --  Generate:
728       --    type poVP is access poV;
729
730       Decl :=
731         Make_Full_Type_Declaration (Loc,
732           Defining_Identifier =>
733             Obj_Ptr,
734           Type_Definition =>
735             Make_Access_To_Object_Definition (Loc,
736           Subtype_Indication =>
737             New_Reference_To (Rec_Typ, Loc)));
738       Set_Debug_Info_Needed (Defining_Identifier (Decl));
739       Prepend_To (Decls, Decl);
740    end Add_Object_Pointer;
741
742    -----------------------
743    -- Build_Accept_Body --
744    -----------------------
745
746    function Build_Accept_Body (Astat : Node_Id) return  Node_Id is
747       Loc     : constant Source_Ptr := Sloc (Astat);
748       Stats   : constant Node_Id    := Handled_Statement_Sequence (Astat);
749       New_S   : Node_Id;
750       Hand    : Node_Id;
751       Call    : Node_Id;
752       Ohandle : Node_Id;
753
754    begin
755       --  At the end of the statement sequence, Complete_Rendezvous is called.
756       --  A label skipping the Complete_Rendezvous, and all other accept
757       --  processing, has already been added for the expansion of requeue
758       --  statements. The Sloc is copied from the last statement since it
759       --  is really part of this last statement.
760
761       Call :=
762         Build_Runtime_Call
763           (Sloc (Last (Statements (Stats))), RE_Complete_Rendezvous);
764       Insert_Before (Last (Statements (Stats)), Call);
765       Analyze (Call);
766
767       --  If exception handlers are present, then append Complete_Rendezvous
768       --  calls to the handlers, and construct the required outer block. As
769       --  above, the Sloc is copied from the last statement in the sequence.
770
771       if Present (Exception_Handlers (Stats)) then
772          Hand := First (Exception_Handlers (Stats));
773          while Present (Hand) loop
774             Call :=
775               Build_Runtime_Call
776                 (Sloc (Last (Statements (Hand))), RE_Complete_Rendezvous);
777             Append (Call, Statements (Hand));
778             Analyze (Call);
779             Next (Hand);
780          end loop;
781
782          New_S :=
783            Make_Handled_Sequence_Of_Statements (Loc,
784              Statements => New_List (
785                Make_Block_Statement (Loc,
786                  Handled_Statement_Sequence => Stats)));
787
788       else
789          New_S := Stats;
790       end if;
791
792       --  At this stage we know that the new statement sequence does not
793       --  have an exception handler part, so we supply one to call
794       --  Exceptional_Complete_Rendezvous. This handler is
795
796       --    when all others =>
797       --       Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
798
799       --  We handle Abort_Signal to make sure that we properly catch the abort
800       --  case and wake up the caller.
801
802       Ohandle := Make_Others_Choice (Loc);
803       Set_All_Others (Ohandle);
804
805       Set_Exception_Handlers (New_S,
806         New_List (
807           Make_Implicit_Exception_Handler (Loc,
808             Exception_Choices => New_List (Ohandle),
809
810             Statements =>  New_List (
811               Make_Procedure_Call_Statement (Sloc (Stats),
812                 Name => New_Reference_To (
813                   RTE (RE_Exceptional_Complete_Rendezvous), Sloc (Stats)),
814                 Parameter_Associations => New_List (
815                   Make_Function_Call (Sloc (Stats),
816                     Name => New_Reference_To (
817                       RTE (RE_Get_GNAT_Exception), Sloc (Stats)))))))));
818
819       Set_Parent (New_S, Astat); -- temp parent for Analyze call
820       Analyze_Exception_Handlers (Exception_Handlers (New_S));
821       Expand_Exception_Handlers (New_S);
822
823       --  Exceptional_Complete_Rendezvous must be called with abort
824       --  still deferred, which is the case for a "when all others" handler.
825
826       return New_S;
827    end Build_Accept_Body;
828
829    -----------------------------------
830    -- Build_Activation_Chain_Entity --
831    -----------------------------------
832
833    procedure Build_Activation_Chain_Entity (N : Node_Id) is
834       P     : Node_Id;
835       Decls : List_Id;
836       Chain : Entity_Id;
837
838    begin
839       --  Loop to find enclosing construct containing activation chain variable
840       --  The construct is a body, a block, or an extended return.
841
842       P := Parent (N);
843
844       while not Nkind_In (P, N_Subprogram_Body,
845                              N_Entry_Body,
846                              N_Package_Declaration,
847                              N_Package_Body,
848                              N_Block_Statement,
849                              N_Task_Body,
850                              N_Extended_Return_Statement)
851       loop
852          P := Parent (P);
853       end loop;
854
855       --  If we are in a package body, the activation chain variable is
856       --  declared in the body, but the Activation_Chain_Entity is attached
857       --  to the spec.
858
859       if Nkind (P) = N_Package_Body then
860          Decls := Declarations (P);
861          P := Unit_Declaration_Node (Corresponding_Spec (P));
862
863       elsif Nkind (P) = N_Package_Declaration then
864          Decls := Visible_Declarations (Specification (P));
865
866       elsif Nkind (P) = N_Extended_Return_Statement then
867          Decls := Return_Object_Declarations (P);
868
869       else
870          Decls := Declarations (P);
871       end if;
872
873       --  If activation chain entity not already declared, declare it
874
875       if Nkind (P) = N_Extended_Return_Statement
876         or else No (Activation_Chain_Entity (P))
877       then
878          Chain := Make_Defining_Identifier (Sloc (N), Name_uChain);
879
880          --  Note: An extended return statement is not really a task activator,
881          --  but it does have an activation chain on which to store the tasks
882          --  temporarily. On successful return, the tasks on this chain are
883          --  moved to the chain passed in by the caller. We do not build an
884          --  Activation_Chain_Entity for an N_Extended_Return_Statement,
885          --  because we do not want to build a call to Activate_Tasks. Task
886          --  activation is the responsibility of the caller.
887
888          if Nkind (P) /= N_Extended_Return_Statement then
889             Set_Activation_Chain_Entity (P, Chain);
890          end if;
891
892          Prepend_To (Decls,
893            Make_Object_Declaration (Sloc (P),
894              Defining_Identifier => Chain,
895              Aliased_Present => True,
896              Object_Definition =>
897                New_Reference_To (RTE (RE_Activation_Chain), Sloc (P))));
898
899          Analyze (First (Decls));
900       end if;
901    end Build_Activation_Chain_Entity;
902
903    ----------------------------
904    -- Build_Barrier_Function --
905    ----------------------------
906
907    function Build_Barrier_Function
908      (N   : Node_Id;
909       Ent : Entity_Id;
910       Pid : Node_Id) return Node_Id
911    is
912       Loc         : constant Source_Ptr := Sloc (N);
913       Func_Id     : constant Entity_Id  := Barrier_Function (Ent);
914       Ent_Formals : constant Node_Id    := Entry_Body_Formal_Part (N);
915       Op_Decls    : constant List_Id    := New_List;
916       Func_Body   : Node_Id;
917
918    begin
919       --  Add a declaration for the Protection object, renaming declarations
920       --  for the discriminals and privals and finally a declaration for the
921       --  entry family index (if applicable).
922
923       Install_Private_Data_Declarations
924         (Loc, Func_Id, Pid, N, Op_Decls, True, Ekind (Ent) = E_Entry_Family);
925
926       --  Note: the condition in the barrier function needs to be properly
927       --  processed for the C/Fortran boolean possibility, but this happens
928       --  automatically since the return statement does this normalization.
929
930       Func_Body :=
931         Make_Subprogram_Body (Loc,
932           Specification =>
933             Build_Barrier_Function_Specification (Loc,
934               Make_Defining_Identifier (Loc, Chars (Func_Id))),
935           Declarations => Op_Decls,
936           Handled_Statement_Sequence =>
937             Make_Handled_Sequence_Of_Statements (Loc,
938               Statements => New_List (
939                 Make_Simple_Return_Statement (Loc,
940                   Expression => Condition (Ent_Formals)))));
941       Set_Is_Entry_Barrier_Function (Func_Body);
942
943       return Func_Body;
944    end Build_Barrier_Function;
945
946    ------------------------------------------
947    -- Build_Barrier_Function_Specification --
948    ------------------------------------------
949
950    function Build_Barrier_Function_Specification
951      (Loc    : Source_Ptr;
952       Def_Id : Entity_Id) return Node_Id
953    is
954    begin
955       Set_Debug_Info_Needed (Def_Id);
956
957       return Make_Function_Specification (Loc,
958         Defining_Unit_Name => Def_Id,
959         Parameter_Specifications => New_List (
960           Make_Parameter_Specification (Loc,
961             Defining_Identifier =>
962               Make_Defining_Identifier (Loc, Name_uO),
963             Parameter_Type =>
964               New_Reference_To (RTE (RE_Address), Loc)),
965
966           Make_Parameter_Specification (Loc,
967             Defining_Identifier =>
968               Make_Defining_Identifier (Loc, Name_uE),
969             Parameter_Type =>
970               New_Reference_To (RTE (RE_Protected_Entry_Index), Loc))),
971
972         Result_Definition =>
973           New_Reference_To (Standard_Boolean, Loc));
974    end Build_Barrier_Function_Specification;
975
976    --------------------------
977    -- Build_Call_With_Task --
978    --------------------------
979
980    function Build_Call_With_Task
981      (N : Node_Id;
982       E : Entity_Id) return Node_Id
983    is
984       Loc : constant Source_Ptr := Sloc (N);
985    begin
986       return
987         Make_Function_Call (Loc,
988           Name => New_Reference_To (E, Loc),
989           Parameter_Associations => New_List (Concurrent_Ref (N)));
990    end Build_Call_With_Task;
991
992    --------------------------------
993    -- Build_Corresponding_Record --
994    --------------------------------
995
996    function Build_Corresponding_Record
997     (N    : Node_Id;
998      Ctyp : Entity_Id;
999      Loc  : Source_Ptr) return Node_Id
1000    is
1001       Rec_Ent  : constant Entity_Id :=
1002                    Make_Defining_Identifier
1003                      (Loc, New_External_Name (Chars (Ctyp), 'V'));
1004       Disc     : Entity_Id;
1005       Dlist    : List_Id;
1006       New_Disc : Entity_Id;
1007       Cdecls   : List_Id;
1008
1009    begin
1010       Set_Corresponding_Record_Type     (Ctyp, Rec_Ent);
1011       Set_Ekind                         (Rec_Ent, E_Record_Type);
1012       Set_Has_Delayed_Freeze            (Rec_Ent, Has_Delayed_Freeze (Ctyp));
1013       Set_Is_Concurrent_Record_Type     (Rec_Ent, True);
1014       Set_Corresponding_Concurrent_Type (Rec_Ent, Ctyp);
1015       Set_Stored_Constraint             (Rec_Ent, No_Elist);
1016       Cdecls := New_List;
1017
1018       --  Use discriminals to create list of discriminants for record, and
1019       --  create new discriminals for use in default expressions, etc. It is
1020       --  worth noting that a task discriminant gives rise to 5 entities;
1021
1022       --  a) The original discriminant.
1023       --  b) The discriminal for use in the task.
1024       --  c) The discriminant of the corresponding record.
1025       --  d) The discriminal for the init proc of the corresponding record.
1026       --  e) The local variable that renames the discriminant in the procedure
1027       --     for the task body.
1028
1029       --  In fact the discriminals b) are used in the renaming declarations
1030       --  for e). See details in  einfo (Handling of Discriminants).
1031
1032       if Present (Discriminant_Specifications (N)) then
1033          Dlist := New_List;
1034          Disc := First_Discriminant (Ctyp);
1035
1036          while Present (Disc) loop
1037             New_Disc := CR_Discriminant (Disc);
1038
1039             Append_To (Dlist,
1040               Make_Discriminant_Specification (Loc,
1041                 Defining_Identifier => New_Disc,
1042                 Discriminant_Type =>
1043                   New_Occurrence_Of (Etype (Disc), Loc),
1044                 Expression =>
1045                   New_Copy (Discriminant_Default_Value (Disc))));
1046
1047             Next_Discriminant (Disc);
1048          end loop;
1049
1050       else
1051          Dlist := No_List;
1052       end if;
1053
1054       --  Now we can construct the record type declaration. Note that this
1055       --  record is "limited tagged". It is "limited" to reflect the underlying
1056       --  limitedness of the task or protected object that it represents, and
1057       --  ensuring for example that it is properly passed by reference. It is
1058       --  "tagged" to give support to dispatching calls through interfaces. We
1059       --  propagate here the list of interfaces covered by the concurrent type
1060       --  (Ada 2005: AI-345).
1061
1062       return
1063         Make_Full_Type_Declaration (Loc,
1064           Defining_Identifier => Rec_Ent,
1065           Discriminant_Specifications => Dlist,
1066           Type_Definition =>
1067             Make_Record_Definition (Loc,
1068               Component_List =>
1069                 Make_Component_List (Loc,
1070                   Component_Items => Cdecls),
1071               Tagged_Present  =>
1072                  Ada_Version >= Ada_2005 and then Is_Tagged_Type (Ctyp),
1073               Interface_List  => Interface_List (N),
1074               Limited_Present => True));
1075    end Build_Corresponding_Record;
1076
1077    ----------------------------------
1078    -- Build_Entry_Count_Expression --
1079    ----------------------------------
1080
1081    function Build_Entry_Count_Expression
1082      (Concurrent_Type : Node_Id;
1083       Component_List  : List_Id;
1084       Loc             : Source_Ptr) return Node_Id
1085    is
1086       Eindx  : Nat;
1087       Ent    : Entity_Id;
1088       Ecount : Node_Id;
1089       Comp   : Node_Id;
1090       Lo     : Node_Id;
1091       Hi     : Node_Id;
1092       Typ    : Entity_Id;
1093       Large  : Boolean;
1094
1095    begin
1096       --  Count number of non-family entries
1097
1098       Eindx := 0;
1099       Ent := First_Entity (Concurrent_Type);
1100       while Present (Ent) loop
1101          if Ekind (Ent) = E_Entry then
1102             Eindx := Eindx + 1;
1103          end if;
1104
1105          Next_Entity (Ent);
1106       end loop;
1107
1108       Ecount := Make_Integer_Literal (Loc, Eindx);
1109
1110       --  Loop through entry families building the addition nodes
1111
1112       Ent := First_Entity (Concurrent_Type);
1113       Comp := First (Component_List);
1114       while Present (Ent) loop
1115          if Ekind (Ent) = E_Entry_Family then
1116             while Chars (Ent) /= Chars (Defining_Identifier (Comp)) loop
1117                Next (Comp);
1118             end loop;
1119
1120             Typ := Etype (Discrete_Subtype_Definition (Parent (Ent)));
1121             Hi := Type_High_Bound (Typ);
1122             Lo := Type_Low_Bound  (Typ);
1123             Large := Is_Potentially_Large_Family
1124                        (Base_Type (Typ), Concurrent_Type, Lo, Hi);
1125             Ecount :=
1126               Make_Op_Add (Loc,
1127                 Left_Opnd  => Ecount,
1128                 Right_Opnd => Family_Size
1129                                 (Loc, Hi, Lo, Concurrent_Type, Large));
1130          end if;
1131
1132          Next_Entity (Ent);
1133       end loop;
1134
1135       return Ecount;
1136    end Build_Entry_Count_Expression;
1137
1138    -----------------------
1139    -- Build_Entry_Names --
1140    -----------------------
1141
1142    function Build_Entry_Names (Conc_Typ : Entity_Id) return Node_Id is
1143       Loc       : constant Source_Ptr := Sloc (Conc_Typ);
1144       B_Decls   : List_Id;
1145       B_Stmts   : List_Id;
1146       Comp      : Node_Id;
1147       Index     : Entity_Id;
1148       Index_Typ : RE_Id;
1149       Typ       : Entity_Id := Conc_Typ;
1150
1151       procedure Build_Entry_Family_Name (Id : Entity_Id);
1152       --  Generate:
1153       --    for Lnn in Family_Low .. Family_High loop
1154       --       Inn := Inn + 1;
1155       --       Set_Entry_Name
1156       --         (_init._object <or> _init._task_id,
1157       --          Inn,
1158       --          new String ("<Entry name>(" & Lnn'Img & ")"));
1159       --    end loop;
1160       --  Note that the bounds of the range may reference discriminants. The
1161       --  above construct is added directly to the statements of the block.
1162
1163       procedure Build_Entry_Name (Id : Entity_Id);
1164       --  Generate:
1165       --    Inn := Inn + 1;
1166       --    Set_Entry_Name
1167       --      (_init._object <or>_init._task_id,
1168       --       Inn,
1169       --       new String ("<Entry name>");
1170       --  The above construct is added directly to the statements of the block.
1171
1172       function Build_Set_Entry_Name_Call (Arg3 : Node_Id) return Node_Id;
1173       --  Generate the call to the runtime routine Set_Entry_Name with actuals
1174       --  _init._task_id or _init._object, Inn and Arg3.
1175
1176       function Find_Protection_Type (Conc_Typ : Entity_Id) return Entity_Id;
1177       --  Given a protected type or its corresponding record, find the type of
1178       --  field _object.
1179
1180       procedure Increment_Index (Stmts : List_Id);
1181       --  Generate the following and add it to Stmts
1182       --    Inn := Inn + 1;
1183
1184       -----------------------------
1185       -- Build_Entry_Family_Name --
1186       -----------------------------
1187
1188       procedure Build_Entry_Family_Name (Id : Entity_Id) is
1189          Def     : constant Node_Id :=
1190                      Discrete_Subtype_Definition (Parent (Id));
1191          L_Id    : constant Entity_Id := Make_Temporary (Loc, 'L');
1192          L_Stmts : constant List_Id := New_List;
1193          Val     : Node_Id;
1194
1195          function Build_Range (Def : Node_Id) return Node_Id;
1196          --  Given a discrete subtype definition of an entry family, generate a
1197          --  range node which covers the range of Def's type.
1198
1199          -----------------
1200          -- Build_Range --
1201          -----------------
1202
1203          function Build_Range (Def : Node_Id) return Node_Id is
1204             High : Node_Id := Type_High_Bound (Etype (Def));
1205             Low  : Node_Id := Type_Low_Bound  (Etype (Def));
1206
1207          begin
1208             --  If a bound references a discriminant, generate an identifier
1209             --  with the same name. Resolution will map it to the formals of
1210             --  the init proc.
1211
1212             if Is_Entity_Name (Low)
1213               and then Ekind (Entity (Low)) = E_Discriminant
1214             then
1215                Low := Make_Identifier (Loc, Chars (Low));
1216             else
1217                Low := New_Copy_Tree (Low);
1218             end if;
1219
1220             if Is_Entity_Name (High)
1221               and then Ekind (Entity (High)) = E_Discriminant
1222             then
1223                High := Make_Identifier (Loc, Chars (High));
1224             else
1225                High := New_Copy_Tree (High);
1226             end if;
1227
1228             return
1229               Make_Range (Loc,
1230                 Low_Bound  => Low,
1231                 High_Bound => High);
1232          end Build_Range;
1233
1234       --  Start of processing for Build_Entry_Family_Name
1235
1236       begin
1237          Get_Name_String (Chars (Id));
1238
1239          --  Add a leading '('
1240
1241          Add_Char_To_Name_Buffer ('(');
1242
1243          --  Generate:
1244          --    new String'("<Entry name>(" & Lnn'Img & ")");
1245
1246          --  This is an implicit heap allocation, and Comes_From_Source is
1247          --  False, which ensures that it will get flagged as a violation of
1248          --  No_Implicit_Heap_Allocations when that restriction applies.
1249
1250          Val :=
1251            Make_Allocator (Loc,
1252              Make_Qualified_Expression (Loc,
1253                Subtype_Mark =>
1254                  New_Reference_To (Standard_String, Loc),
1255                Expression =>
1256                  Make_Op_Concat (Loc,
1257                    Left_Opnd =>
1258                      Make_Op_Concat (Loc,
1259                        Left_Opnd =>
1260                          Make_String_Literal (Loc,
1261                            Strval => String_From_Name_Buffer),
1262                        Right_Opnd =>
1263                          Make_Attribute_Reference (Loc,
1264                            Prefix =>
1265                              New_Reference_To (L_Id, Loc),
1266                                Attribute_Name => Name_Img)),
1267                    Right_Opnd =>
1268                      Make_String_Literal (Loc,
1269                        Strval => ")"))));
1270
1271          Increment_Index (L_Stmts);
1272          Append_To (L_Stmts, Build_Set_Entry_Name_Call (Val));
1273
1274          --  Generate:
1275          --    for Lnn in Family_Low .. Family_High loop
1276          --       Inn := Inn + 1;
1277          --       Set_Entry_Name
1278          --         (_init._object <or> _init._task_id, Inn, <Val>);
1279          --    end loop;
1280
1281          Append_To (B_Stmts,
1282            Make_Loop_Statement (Loc,
1283              Iteration_Scheme =>
1284                Make_Iteration_Scheme (Loc,
1285                  Loop_Parameter_Specification =>
1286                    Make_Loop_Parameter_Specification (Loc,
1287                     Defining_Identifier         => L_Id,
1288                     Discrete_Subtype_Definition => Build_Range (Def))),
1289              Statements => L_Stmts,
1290              End_Label => Empty));
1291       end Build_Entry_Family_Name;
1292
1293       ----------------------
1294       -- Build_Entry_Name --
1295       ----------------------
1296
1297       procedure Build_Entry_Name (Id : Entity_Id) is
1298          Val : Node_Id;
1299
1300       begin
1301          Get_Name_String (Chars (Id));
1302
1303          --  This is an implicit heap allocation, and Comes_From_Source is
1304          --  False, which ensures that it will get flagged as a violation of
1305          --  No_Implicit_Heap_Allocations when that restriction applies.
1306
1307          Val :=
1308            Make_Allocator (Loc,
1309              Make_Qualified_Expression (Loc,
1310                Subtype_Mark =>
1311                  New_Reference_To (Standard_String, Loc),
1312                Expression =>
1313                  Make_String_Literal (Loc,
1314                    String_From_Name_Buffer)));
1315
1316          Increment_Index (B_Stmts);
1317          Append_To (B_Stmts, Build_Set_Entry_Name_Call (Val));
1318       end Build_Entry_Name;
1319
1320       -------------------------------
1321       -- Build_Set_Entry_Name_Call --
1322       -------------------------------
1323
1324       function Build_Set_Entry_Name_Call (Arg3 : Node_Id) return Node_Id is
1325          Arg1 : Name_Id;
1326          Proc : RE_Id;
1327
1328       begin
1329          --  Determine the proper name for the first argument and the RTS
1330          --  routine to call.
1331
1332          if Is_Protected_Type (Typ) then
1333             Arg1 := Name_uObject;
1334             Proc := RO_PE_Set_Entry_Name;
1335
1336          else pragma Assert (Is_Task_Type (Typ));
1337             Arg1 := Name_uTask_Id;
1338             Proc := RO_TS_Set_Entry_Name;
1339          end if;
1340
1341          --  Generate:
1342          --    Set_Entry_Name (_init.Arg1, Inn, Arg3);
1343
1344          return
1345            Make_Procedure_Call_Statement (Loc,
1346              Name =>
1347                New_Reference_To (RTE (Proc), Loc),
1348              Parameter_Associations => New_List (
1349                Make_Selected_Component (Loc,              --  _init._object
1350                  Prefix =>                                --  _init._task_id
1351                    Make_Identifier (Loc, Name_uInit),
1352                  Selector_Name =>
1353                    Make_Identifier (Loc, Arg1)),
1354                New_Reference_To (Index, Loc),             --  Inn
1355                Arg3));                                    --  Val
1356       end Build_Set_Entry_Name_Call;
1357
1358       --------------------------
1359       -- Find_Protection_Type --
1360       --------------------------
1361
1362       function Find_Protection_Type (Conc_Typ : Entity_Id) return Entity_Id is
1363          Comp : Entity_Id;
1364          Typ  : Entity_Id := Conc_Typ;
1365
1366       begin
1367          if Is_Concurrent_Type (Typ) then
1368             Typ := Corresponding_Record_Type (Typ);
1369          end if;
1370
1371          Comp := First_Component (Typ);
1372          while Present (Comp) loop
1373             if Chars (Comp) = Name_uObject then
1374                return Base_Type (Etype (Comp));
1375             end if;
1376
1377             Next_Component (Comp);
1378          end loop;
1379
1380          --  The corresponding record of a protected type should always have an
1381          --  _object field.
1382
1383          raise Program_Error;
1384       end Find_Protection_Type;
1385
1386       ---------------------
1387       -- Increment_Index --
1388       ---------------------
1389
1390       procedure Increment_Index (Stmts : List_Id) is
1391       begin
1392          --  Generate:
1393          --    Inn := Inn + 1;
1394
1395          Append_To (Stmts,
1396            Make_Assignment_Statement (Loc,
1397              Name =>
1398                New_Reference_To (Index, Loc),
1399              Expression =>
1400                Make_Op_Add (Loc,
1401                  Left_Opnd =>
1402                    New_Reference_To (Index, Loc),
1403                  Right_Opnd =>
1404                    Make_Integer_Literal (Loc, 1))));
1405       end Increment_Index;
1406
1407    --  Start of processing for Build_Entry_Names
1408
1409    begin
1410       --  Retrieve the original concurrent type
1411
1412       if Is_Concurrent_Record_Type (Typ) then
1413          Typ := Corresponding_Concurrent_Type (Typ);
1414       end if;
1415
1416       pragma Assert (Is_Protected_Type (Typ) or else Is_Task_Type (Typ));
1417
1418       --  Nothing to do if the type has no entries
1419
1420       if not Has_Entries (Typ) then
1421          return Empty;
1422       end if;
1423
1424       --  Avoid generating entry names for a protected type with only one entry
1425
1426       if Is_Protected_Type (Typ)
1427         and then Find_Protection_Type (Typ) /= RTE (RE_Protection_Entries)
1428       then
1429          return Empty;
1430       end if;
1431
1432       Index := Make_Temporary (Loc, 'I');
1433
1434       --  Step 1: Generate the declaration of the index variable:
1435       --    Inn : Protected_Entry_Index := 0;
1436       --      or
1437       --    Inn : Task_Entry_Index := 0;
1438
1439       if Is_Protected_Type (Typ) then
1440          Index_Typ := RE_Protected_Entry_Index;
1441       else
1442          Index_Typ := RE_Task_Entry_Index;
1443       end if;
1444
1445       B_Decls := New_List;
1446       Append_To (B_Decls,
1447         Make_Object_Declaration (Loc,
1448           Defining_Identifier => Index,
1449           Object_Definition   => New_Reference_To (RTE (Index_Typ), Loc),
1450           Expression          => Make_Integer_Literal (Loc, 0)));
1451
1452       B_Stmts := New_List;
1453
1454       --  Step 2: Generate a call to Set_Entry_Name for each entry and entry
1455       --  family member.
1456
1457       Comp := First_Entity (Typ);
1458       while Present (Comp) loop
1459          if Ekind (Comp) = E_Entry then
1460             Build_Entry_Name (Comp);
1461
1462          elsif Ekind (Comp) = E_Entry_Family then
1463             Build_Entry_Family_Name (Comp);
1464          end if;
1465
1466          Next_Entity (Comp);
1467       end loop;
1468
1469       --  Step 3: Wrap the statements in a block
1470
1471       return
1472         Make_Block_Statement (Loc,
1473           Declarations => B_Decls,
1474           Handled_Statement_Sequence =>
1475             Make_Handled_Sequence_Of_Statements (Loc,
1476               Statements => B_Stmts));
1477    end Build_Entry_Names;
1478
1479    ---------------------------
1480    -- Build_Parameter_Block --
1481    ---------------------------
1482
1483    function Build_Parameter_Block
1484      (Loc     : Source_Ptr;
1485       Actuals : List_Id;
1486       Formals : List_Id;
1487       Decls   : List_Id) return Entity_Id
1488    is
1489       Actual   : Entity_Id;
1490       Comp_Nam : Node_Id;
1491       Comps    : List_Id;
1492       Formal   : Entity_Id;
1493       Has_Comp : Boolean := False;
1494       Rec_Nam  : Node_Id;
1495
1496    begin
1497       Actual := First (Actuals);
1498       Comps  := New_List;
1499       Formal := Defining_Identifier (First (Formals));
1500
1501       while Present (Actual) loop
1502          if not Is_Controlling_Actual (Actual) then
1503
1504             --  Generate:
1505             --    type Ann is access all <actual-type>
1506
1507             Comp_Nam := Make_Temporary (Loc, 'A');
1508
1509             Append_To (Decls,
1510               Make_Full_Type_Declaration (Loc,
1511                 Defining_Identifier => Comp_Nam,
1512                 Type_Definition     =>
1513                   Make_Access_To_Object_Definition (Loc,
1514                     All_Present        => True,
1515                     Constant_Present   => Ekind (Formal) = E_In_Parameter,
1516                     Subtype_Indication =>
1517                       New_Reference_To (Etype (Actual), Loc))));
1518
1519             --  Generate:
1520             --    Param : Ann;
1521
1522             Append_To (Comps,
1523               Make_Component_Declaration (Loc,
1524                 Defining_Identifier =>
1525                   Make_Defining_Identifier (Loc, Chars (Formal)),
1526                 Component_Definition =>
1527                   Make_Component_Definition (Loc,
1528                     Aliased_Present =>
1529                       False,
1530                     Subtype_Indication =>
1531                       New_Reference_To (Comp_Nam, Loc))));
1532
1533             Has_Comp := True;
1534          end if;
1535
1536          Next_Actual (Actual);
1537          Next_Formal_With_Extras (Formal);
1538       end loop;
1539
1540       Rec_Nam := Make_Temporary (Loc, 'P');
1541
1542       if Has_Comp then
1543
1544          --  Generate:
1545          --    type Pnn is record
1546          --       Param1 : Ann1;
1547          --       ...
1548          --       ParamN : AnnN;
1549
1550          --  where Pnn is a parameter wrapping record, Param1 .. ParamN are
1551          --  the original parameter names and Ann1 .. AnnN are the access to
1552          --  actual types.
1553
1554          Append_To (Decls,
1555            Make_Full_Type_Declaration (Loc,
1556              Defining_Identifier =>
1557                Rec_Nam,
1558              Type_Definition =>
1559                Make_Record_Definition (Loc,
1560                  Component_List =>
1561                    Make_Component_List (Loc, Comps))));
1562       else
1563          --  Generate:
1564          --    type Pnn is null record;
1565
1566          Append_To (Decls,
1567            Make_Full_Type_Declaration (Loc,
1568              Defining_Identifier =>
1569                Rec_Nam,
1570              Type_Definition =>
1571                Make_Record_Definition (Loc,
1572                  Null_Present   => True,
1573                  Component_List => Empty)));
1574       end if;
1575
1576       return Rec_Nam;
1577    end Build_Parameter_Block;
1578
1579    -----------------------
1580    -- Build_PPC_Wrapper --
1581    -----------------------
1582
1583    procedure Build_PPC_Wrapper (E : Entity_Id; Decl : Node_Id) is
1584       Loc        : constant Source_Ptr := Sloc (E);
1585       Synch_Type : constant Entity_Id := Scope (E);
1586
1587       Wrapper_Id : constant Entity_Id :=
1588                      Make_Defining_Identifier (Loc,
1589                        Chars => New_External_Name (Chars (E), 'E'));
1590       --  the wrapper procedure name
1591
1592       Wrapper_Body : Node_Id;
1593
1594       Synch_Id : constant Entity_Id :=
1595                    Make_Defining_Identifier (Loc,
1596                      Chars => New_External_Name (Chars (Scope (E)), 'A'));
1597       --  The parameter that designates the synchronized object in the call
1598
1599       Actuals : constant List_Id := New_List;
1600       --  the actuals in the entry call.
1601
1602       Decls : constant List_Id := New_List;
1603
1604       Entry_Call : Node_Id;
1605       Entry_Name : Node_Id;
1606
1607       Specs : List_Id;
1608       --  The specification of the wrapper procedure
1609
1610    begin
1611
1612       --  Only build the wrapper if entry has pre/postconditions.
1613       --  Should this be done unconditionally instead ???
1614
1615       declare
1616          P : Node_Id;
1617
1618       begin
1619          P := Spec_PPC_List (E);
1620          if No (P) then
1621             return;
1622          end if;
1623
1624          --  Transfer ppc pragmas to the declarations of the wrapper
1625
1626          while Present (P) loop
1627             if Pragma_Name (P) = Name_Precondition
1628               or else Pragma_Name (P) = Name_Postcondition
1629             then
1630                Append (Relocate_Node (P), Decls);
1631                Set_Analyzed (Last (Decls), False);
1632             end if;
1633
1634             P := Next_Pragma (P);
1635          end loop;
1636       end;
1637
1638       --  First formal is synchronized object
1639
1640       Specs := New_List (
1641         Make_Parameter_Specification (Loc,
1642           Defining_Identifier => Synch_Id,
1643           Out_Present         =>  True,
1644           In_Present          =>  True,
1645           Parameter_Type      => New_Occurrence_Of (Scope (E), Loc)));
1646
1647       Entry_Name :=
1648         Make_Selected_Component (Loc,
1649           Prefix        => New_Occurrence_Of (Synch_Id, Loc),
1650           Selector_Name => New_Occurrence_Of (E, Loc));
1651
1652       --  If entity is entry family, second formal is the corresponding index,
1653       --  and entry name is an indexed component.
1654
1655       if Ekind (E) = E_Entry_Family then
1656          declare
1657             Index : constant Entity_Id :=
1658                       Make_Defining_Identifier (Loc, Name_I);
1659          begin
1660             Append_To (Specs,
1661               Make_Parameter_Specification (Loc,
1662                 Defining_Identifier => Index,
1663                 Parameter_Type      =>
1664                   New_Occurrence_Of (Entry_Index_Type (E), Loc)));
1665
1666             Entry_Name :=
1667               Make_Indexed_Component (Loc,
1668                 Prefix      => Entry_Name,
1669                 Expressions => New_List (New_Occurrence_Of (Index, Loc)));
1670          end;
1671       end if;
1672
1673       Entry_Call :=
1674         Make_Procedure_Call_Statement (Loc,
1675           Name                   => Entry_Name,
1676           Parameter_Associations => Actuals);
1677
1678       --  Now add formals that match those of the entry, and build actuals for
1679       --  the nested entry call.
1680
1681       declare
1682          Form      : Entity_Id;
1683          New_Form  : Entity_Id;
1684          Parm_Spec : Node_Id;
1685
1686       begin
1687          Form := First_Formal (E);
1688          while Present (Form) loop
1689             New_Form := Make_Defining_Identifier (Loc, Chars (Form));
1690             Parm_Spec :=
1691               Make_Parameter_Specification (Loc,
1692                 Defining_Identifier => New_Form,
1693                 Out_Present         => Out_Present (Parent (Form)),
1694                 In_Present          => In_Present  (Parent (Form)),
1695                 Parameter_Type      => New_Occurrence_Of (Etype (Form), Loc));
1696
1697             Append (Parm_Spec, Specs);
1698             Append (New_Occurrence_Of (New_Form, Loc), Actuals);
1699             Next_Formal (Form);
1700          end loop;
1701       end;
1702
1703       --  Add renaming declarations for the discriminants of the enclosing
1704       --  type, which may be visible in the preconditions.
1705
1706       if Has_Discriminants (Synch_Type) then
1707          declare
1708             D : Entity_Id;
1709             Decl : Node_Id;
1710
1711          begin
1712             D := First_Discriminant (Synch_Type);
1713             while Present (D) loop
1714                Decl :=
1715                  Make_Object_Renaming_Declaration (Loc,
1716                    Defining_Identifier =>
1717                      Make_Defining_Identifier (Loc, Chars (D)),
1718                    Subtype_Mark        => New_Reference_To (Etype (D), Loc),
1719                    Name                =>
1720                      Make_Selected_Component (Loc,
1721                        Prefix        => New_Reference_To (Synch_Id, Loc),
1722                        Selector_Name => Make_Identifier (Loc, Chars (D))));
1723                Prepend (Decl, Decls);
1724                Next_Discriminant (D);
1725             end loop;
1726          end;
1727       end if;
1728
1729       Set_PPC_Wrapper (E, Wrapper_Id);
1730       Wrapper_Body :=
1731         Make_Subprogram_Body (Loc,
1732           Specification              =>
1733             Make_Procedure_Specification (Loc,
1734               Defining_Unit_Name       => Wrapper_Id,
1735               Parameter_Specifications => Specs),
1736           Declarations               => Decls,
1737           Handled_Statement_Sequence =>
1738             Make_Handled_Sequence_Of_Statements (Loc,
1739               Statements => New_List (Entry_Call)));
1740
1741       --  The wrapper body is analyzed when the enclosing type is frozen
1742
1743       Append_Freeze_Action (Defining_Entity (Decl), Wrapper_Body);
1744    end Build_PPC_Wrapper;
1745
1746    --------------------------
1747    -- Build_Wrapper_Bodies --
1748    --------------------------
1749
1750    procedure Build_Wrapper_Bodies
1751      (Loc : Source_Ptr;
1752       Typ : Entity_Id;
1753       N   : Node_Id)
1754    is
1755       Rec_Typ : Entity_Id;
1756
1757       function Build_Wrapper_Body
1758         (Loc     : Source_Ptr;
1759          Subp_Id : Entity_Id;
1760          Obj_Typ : Entity_Id;
1761          Formals : List_Id) return Node_Id;
1762       --  Ada 2005 (AI-345): Build the body that wraps a primitive operation
1763       --  associated with a protected or task type. Subp_Id is the subprogram
1764       --  name which will be wrapped. Obj_Typ is the type of the new formal
1765       --  parameter which handles dispatching and object notation. Formals are
1766       --  the original formals of Subp_Id which will be explicitly replicated.
1767
1768       ------------------------
1769       -- Build_Wrapper_Body --
1770       ------------------------
1771
1772       function Build_Wrapper_Body
1773         (Loc     : Source_Ptr;
1774          Subp_Id : Entity_Id;
1775          Obj_Typ : Entity_Id;
1776          Formals : List_Id) return Node_Id
1777       is
1778          Body_Spec : Node_Id;
1779
1780       begin
1781          Body_Spec := Build_Wrapper_Spec (Subp_Id, Obj_Typ, Formals);
1782
1783          --  The subprogram is not overriding or is not a primitive declared
1784          --  between two views.
1785
1786          if No (Body_Spec) then
1787             return Empty;
1788          end if;
1789
1790          declare
1791             Actuals    : List_Id := No_List;
1792             Conv_Id    : Node_Id;
1793             First_Form : Node_Id;
1794             Formal     : Node_Id;
1795             Nam        : Node_Id;
1796
1797          begin
1798             --  Map formals to actuals. Use the list built for the wrapper
1799             --  spec, skipping the object notation parameter.
1800
1801             First_Form := First (Parameter_Specifications (Body_Spec));
1802
1803             Formal := First_Form;
1804             Next (Formal);
1805
1806             if Present (Formal) then
1807                Actuals := New_List;
1808                while Present (Formal) loop
1809                   Append_To (Actuals,
1810                     Make_Identifier (Loc, Chars =>
1811                       Chars (Defining_Identifier (Formal))));
1812
1813                   Next (Formal);
1814                end loop;
1815             end if;
1816
1817             --  Special processing for primitives declared between a private
1818             --  type and its completion: the wrapper needs a properly typed
1819             --  parameter if the wrapped operation has a controlling first
1820             --  parameter. Note that this might not be the case for a function
1821             --  with a controlling result.
1822
1823             if Is_Private_Primitive_Subprogram (Subp_Id) then
1824                if No (Actuals) then
1825                   Actuals := New_List;
1826                end if;
1827
1828                if Is_Controlling_Formal (First_Formal (Subp_Id)) then
1829                   Prepend_To (Actuals,
1830                     Unchecked_Convert_To
1831                       (Corresponding_Concurrent_Type (Obj_Typ),
1832                        Make_Identifier (Loc, Name_uO)));
1833
1834                else
1835                   Prepend_To (Actuals,
1836                     Make_Identifier (Loc, Chars =>
1837                       Chars (Defining_Identifier (First_Form))));
1838                end if;
1839
1840                Nam := New_Reference_To (Subp_Id, Loc);
1841             else
1842                --  An access-to-variable object parameter requires an explicit
1843                --  dereference in the unchecked conversion. This case occurs
1844                --  when a protected entry wrapper must override an interface
1845                --  level procedure with interface access as first parameter.
1846
1847                --     O.all.Subp_Id (Formal_1, ..., Formal_N)
1848
1849                if Nkind (Parameter_Type (First_Form)) =
1850                     N_Access_Definition
1851                then
1852                   Conv_Id :=
1853                     Make_Explicit_Dereference (Loc,
1854                       Prefix => Make_Identifier (Loc, Name_uO));
1855                else
1856                   Conv_Id := Make_Identifier (Loc, Name_uO);
1857                end if;
1858
1859                Nam :=
1860                  Make_Selected_Component (Loc,
1861                    Prefix        =>
1862                      Unchecked_Convert_To
1863                        (Corresponding_Concurrent_Type (Obj_Typ), Conv_Id),
1864                    Selector_Name => New_Reference_To (Subp_Id, Loc));
1865             end if;
1866
1867             --  Create the subprogram body. For a function, the call to the
1868             --  actual subprogram has to be converted to the corresponding
1869             --  record if it is a controlling result.
1870
1871             if Ekind (Subp_Id) = E_Function then
1872                declare
1873                   Res : Node_Id;
1874
1875                begin
1876                   Res :=
1877                      Make_Function_Call (Loc,
1878                        Name                   => Nam,
1879                        Parameter_Associations => Actuals);
1880
1881                   if Has_Controlling_Result (Subp_Id) then
1882                      Res :=
1883                        Unchecked_Convert_To
1884                          (Corresponding_Record_Type (Etype (Subp_Id)), Res);
1885                   end if;
1886
1887                   return
1888                     Make_Subprogram_Body (Loc,
1889                       Specification              => Body_Spec,
1890                       Declarations               => Empty_List,
1891                       Handled_Statement_Sequence =>
1892                         Make_Handled_Sequence_Of_Statements (Loc,
1893                           Statements => New_List (
1894                             Make_Simple_Return_Statement (Loc, Res))));
1895                end;
1896
1897             else
1898                return
1899                  Make_Subprogram_Body (Loc,
1900                    Specification              => Body_Spec,
1901                    Declarations               => Empty_List,
1902                    Handled_Statement_Sequence =>
1903                      Make_Handled_Sequence_Of_Statements (Loc,
1904                        Statements => New_List (
1905                          Make_Procedure_Call_Statement (Loc,
1906                            Name                   => Nam,
1907                            Parameter_Associations => Actuals))));
1908             end if;
1909          end;
1910       end Build_Wrapper_Body;
1911
1912    --  Start of processing for Build_Wrapper_Bodies
1913
1914    begin
1915       if Is_Concurrent_Type (Typ) then
1916          Rec_Typ := Corresponding_Record_Type (Typ);
1917       else
1918          Rec_Typ := Typ;
1919       end if;
1920
1921       --  Generate wrapper bodies for a concurrent type which implements an
1922       --  interface.
1923
1924       if Present (Interfaces (Rec_Typ)) then
1925          declare
1926             Insert_Nod : Node_Id;
1927             Prim       : Entity_Id;
1928             Prim_Elmt  : Elmt_Id;
1929             Prim_Decl  : Node_Id;
1930             Subp       : Entity_Id;
1931             Wrap_Body  : Node_Id;
1932             Wrap_Id    : Entity_Id;
1933
1934          begin
1935             Insert_Nod := N;
1936
1937             --  Examine all primitive operations of the corresponding record
1938             --  type, looking for wrapper specs. Generate bodies in order to
1939             --  complete them.
1940
1941             Prim_Elmt := First_Elmt (Primitive_Operations (Rec_Typ));
1942             while Present (Prim_Elmt) loop
1943                Prim := Node (Prim_Elmt);
1944
1945                if (Ekind (Prim) = E_Function
1946                      or else Ekind (Prim) = E_Procedure)
1947                  and then Is_Primitive_Wrapper (Prim)
1948                then
1949                   Subp := Wrapped_Entity (Prim);
1950                   Prim_Decl := Parent (Parent (Prim));
1951
1952                   Wrap_Body :=
1953                     Build_Wrapper_Body (Loc,
1954                       Subp_Id => Subp,
1955                       Obj_Typ => Rec_Typ,
1956                       Formals => Parameter_Specifications (Parent (Subp)));
1957                   Wrap_Id := Defining_Unit_Name (Specification (Wrap_Body));
1958
1959                   Set_Corresponding_Spec (Wrap_Body, Prim);
1960                   Set_Corresponding_Body (Prim_Decl, Wrap_Id);
1961
1962                   Insert_After (Insert_Nod, Wrap_Body);
1963                   Insert_Nod := Wrap_Body;
1964
1965                   Analyze (Wrap_Body);
1966                end if;
1967
1968                Next_Elmt (Prim_Elmt);
1969             end loop;
1970          end;
1971       end if;
1972    end Build_Wrapper_Bodies;
1973
1974    ------------------------
1975    -- Build_Wrapper_Spec --
1976    ------------------------
1977
1978    function Build_Wrapper_Spec
1979      (Subp_Id : Entity_Id;
1980       Obj_Typ : Entity_Id;
1981       Formals : List_Id) return Node_Id
1982    is
1983       Loc           : constant Source_Ptr := Sloc (Subp_Id);
1984       First_Param   : Node_Id;
1985       Iface         : Entity_Id;
1986       Iface_Elmt    : Elmt_Id;
1987       Iface_Op      : Entity_Id;
1988       Iface_Op_Elmt : Elmt_Id;
1989
1990       function Overriding_Possible
1991         (Iface_Op : Entity_Id;
1992          Wrapper  : Entity_Id) return Boolean;
1993       --  Determine whether a primitive operation can be overridden by Wrapper.
1994       --  Iface_Op is the candidate primitive operation of an interface type,
1995       --  Wrapper is the generated entry wrapper.
1996
1997       function Replicate_Formals
1998         (Loc     : Source_Ptr;
1999          Formals : List_Id) return List_Id;
2000       --  An explicit parameter replication is required due to the Is_Entry_
2001       --  Formal flag being set for all the formals of an entry. The explicit
2002       --  replication removes the flag that would otherwise cause a different
2003       --  path of analysis.
2004
2005       -------------------------
2006       -- Overriding_Possible --
2007       -------------------------
2008
2009       function Overriding_Possible
2010         (Iface_Op : Entity_Id;
2011          Wrapper  : Entity_Id) return Boolean
2012       is
2013          Iface_Op_Spec : constant Node_Id := Parent (Iface_Op);
2014          Wrapper_Spec  : constant Node_Id := Parent (Wrapper);
2015
2016          function Type_Conformant_Parameters
2017            (Iface_Op_Params : List_Id;
2018             Wrapper_Params  : List_Id) return Boolean;
2019          --  Determine whether the parameters of the generated entry wrapper
2020          --  and those of a primitive operation are type conformant. During
2021          --  this check, the first parameter of the primitive operation is
2022          --  skipped if it is a controlling argument: protected functions
2023          --  may have a controlling result.
2024
2025          --------------------------------
2026          -- Type_Conformant_Parameters --
2027          --------------------------------
2028
2029          function Type_Conformant_Parameters
2030            (Iface_Op_Params : List_Id;
2031             Wrapper_Params  : List_Id) return Boolean
2032          is
2033             Iface_Op_Param : Node_Id;
2034             Iface_Op_Typ   : Entity_Id;
2035             Wrapper_Param  : Node_Id;
2036             Wrapper_Typ    : Entity_Id;
2037
2038          begin
2039             --  Skip the first (controlling) parameter of primitive operation
2040
2041             Iface_Op_Param := First (Iface_Op_Params);
2042
2043             if Present (First_Formal (Iface_Op))
2044               and then Is_Controlling_Formal (First_Formal (Iface_Op))
2045             then
2046                Iface_Op_Param := Next (Iface_Op_Param);
2047             end if;
2048
2049             Wrapper_Param  := First (Wrapper_Params);
2050             while Present (Iface_Op_Param)
2051               and then Present (Wrapper_Param)
2052             loop
2053                Iface_Op_Typ := Find_Parameter_Type (Iface_Op_Param);
2054                Wrapper_Typ  := Find_Parameter_Type (Wrapper_Param);
2055
2056                --  The two parameters must be mode conformant
2057
2058                if not Conforming_Types
2059                         (Iface_Op_Typ, Wrapper_Typ, Mode_Conformant)
2060                then
2061                   return False;
2062                end if;
2063
2064                Next (Iface_Op_Param);
2065                Next (Wrapper_Param);
2066             end loop;
2067
2068             --  One of the lists is longer than the other
2069
2070             if Present (Iface_Op_Param) or else Present (Wrapper_Param) then
2071                return False;
2072             end if;
2073
2074             return True;
2075          end Type_Conformant_Parameters;
2076
2077       --  Start of processing for Overriding_Possible
2078
2079       begin
2080          if Chars (Iface_Op) /= Chars (Wrapper) then
2081             return False;
2082          end if;
2083
2084          --  If an inherited subprogram is implemented by a protected procedure
2085          --  or an entry, then the first parameter of the inherited subprogram
2086          --  shall be of mode OUT or IN OUT, or access-to-variable parameter.
2087
2088          if Ekind (Iface_Op) = E_Procedure
2089            and then Present (Parameter_Specifications (Iface_Op_Spec))
2090          then
2091             declare
2092                Obj_Param : constant Node_Id :=
2093                              First (Parameter_Specifications (Iface_Op_Spec));
2094             begin
2095                if not Out_Present (Obj_Param)
2096                  and then Nkind (Parameter_Type (Obj_Param)) /=
2097                                                          N_Access_Definition
2098                then
2099                   return False;
2100                end if;
2101             end;
2102          end if;
2103
2104          return
2105            Type_Conformant_Parameters (
2106              Parameter_Specifications (Iface_Op_Spec),
2107              Parameter_Specifications (Wrapper_Spec));
2108       end Overriding_Possible;
2109
2110       -----------------------
2111       -- Replicate_Formals --
2112       -----------------------
2113
2114       function Replicate_Formals
2115         (Loc     : Source_Ptr;
2116          Formals : List_Id) return List_Id
2117       is
2118          New_Formals : constant List_Id := New_List;
2119          Formal      : Node_Id;
2120          Param_Type  : Node_Id;
2121
2122       begin
2123          Formal := First (Formals);
2124
2125          --  Skip the object parameter when dealing with primitives declared
2126          --  between two views.
2127
2128          if Is_Private_Primitive_Subprogram (Subp_Id)
2129            and then not Has_Controlling_Result (Subp_Id)
2130          then
2131             Formal := Next (Formal);
2132          end if;
2133
2134          while Present (Formal) loop
2135
2136             --  Create an explicit copy of the entry parameter
2137
2138             --  When creating the wrapper subprogram for a primitive operation
2139             --  of a protected interface we must construct an equivalent
2140             --  signature to that of the overriding operation. For regular
2141             --  parameters we can just use the type of the formal, but for
2142             --  access to subprogram parameters we need to reanalyze the
2143             --  parameter type to create local entities for the signature of
2144             --  the subprogram type. Using the entities of the overriding
2145             --  subprogram will result in out-of-scope errors in the back-end.
2146
2147             if Nkind (Parameter_Type (Formal)) = N_Access_Definition then
2148                Param_Type := Copy_Separate_Tree (Parameter_Type (Formal));
2149             else
2150                Param_Type :=
2151                  New_Reference_To (Etype (Parameter_Type (Formal)), Loc);
2152             end if;
2153
2154             Append_To (New_Formals,
2155               Make_Parameter_Specification (Loc,
2156                 Defining_Identifier =>
2157                   Make_Defining_Identifier (Loc,
2158                     Chars          => Chars (Defining_Identifier (Formal))),
2159                     In_Present     => In_Present  (Formal),
2160                     Out_Present    => Out_Present (Formal),
2161                     Parameter_Type => Param_Type));
2162
2163             Next (Formal);
2164          end loop;
2165
2166          return New_Formals;
2167       end Replicate_Formals;
2168
2169    --  Start of processing for Build_Wrapper_Spec
2170
2171    begin
2172       --  There is no point in building wrappers for non-tagged concurrent
2173       --  types.
2174
2175       pragma Assert (Is_Tagged_Type (Obj_Typ));
2176
2177       --  An entry or a protected procedure can override a routine where the
2178       --  controlling formal is either IN OUT, OUT or is of access-to-variable
2179       --  type. Since the wrapper must have the exact same signature as that of
2180       --  the overridden subprogram, we try to find the overriding candidate
2181       --  and use its controlling formal.
2182
2183       First_Param := Empty;
2184
2185       --  Check every implemented interface
2186
2187       if Present (Interfaces (Obj_Typ)) then
2188          Iface_Elmt := First_Elmt (Interfaces (Obj_Typ));
2189          Search : while Present (Iface_Elmt) loop
2190             Iface := Node (Iface_Elmt);
2191
2192             --  Check every interface primitive
2193
2194             if Present (Primitive_Operations (Iface)) then
2195                Iface_Op_Elmt := First_Elmt (Primitive_Operations (Iface));
2196                while Present (Iface_Op_Elmt) loop
2197                   Iface_Op := Node (Iface_Op_Elmt);
2198
2199                   --  Ignore predefined primitives
2200
2201                   if not Is_Predefined_Dispatching_Operation (Iface_Op) then
2202                      Iface_Op := Ultimate_Alias (Iface_Op);
2203
2204                      --  The current primitive operation can be overridden by
2205                      --  the generated entry wrapper.
2206
2207                      if Overriding_Possible (Iface_Op, Subp_Id) then
2208                         First_Param :=
2209                           First (Parameter_Specifications (Parent (Iface_Op)));
2210
2211                         exit Search;
2212                      end if;
2213                   end if;
2214
2215                   Next_Elmt (Iface_Op_Elmt);
2216                end loop;
2217             end if;
2218
2219             Next_Elmt (Iface_Elmt);
2220          end loop Search;
2221       end if;
2222
2223       --  If the subprogram to be wrapped is not overriding anything or is not
2224       --  a primitive declared between two views, do not produce anything. This
2225       --  avoids spurious errors involving overriding.
2226
2227       if No (First_Param)
2228         and then not Is_Private_Primitive_Subprogram (Subp_Id)
2229       then
2230          return Empty;
2231       end if;
2232
2233       declare
2234          Wrapper_Id    : constant Entity_Id :=
2235                            Make_Defining_Identifier (Loc, Chars (Subp_Id));
2236          New_Formals   : List_Id;
2237          Obj_Param     : Node_Id;
2238          Obj_Param_Typ : Entity_Id;
2239
2240       begin
2241          --  Minimum decoration is needed to catch the entity in
2242          --  Sem_Ch6.Override_Dispatching_Operation.
2243
2244          if Ekind (Subp_Id) = E_Function then
2245             Set_Ekind (Wrapper_Id, E_Function);
2246          else
2247             Set_Ekind (Wrapper_Id, E_Procedure);
2248          end if;
2249
2250          Set_Is_Primitive_Wrapper (Wrapper_Id);
2251          Set_Wrapped_Entity       (Wrapper_Id, Subp_Id);
2252          Set_Is_Private_Primitive (Wrapper_Id,
2253            Is_Private_Primitive_Subprogram (Subp_Id));
2254
2255          --  Process the formals
2256
2257          New_Formals := Replicate_Formals (Loc, Formals);
2258
2259          --  A function with a controlling result and no first controlling
2260          --  formal needs no additional parameter.
2261
2262          if Has_Controlling_Result (Subp_Id)
2263            and then
2264              (No (First_Formal (Subp_Id))
2265                or else not Is_Controlling_Formal (First_Formal (Subp_Id)))
2266          then
2267             null;
2268
2269          --  Routine Subp_Id has been found to override an interface primitive.
2270          --  If the interface operation has an access parameter, create a copy
2271          --  of it, with the same null exclusion indicator if present.
2272
2273          elsif Present (First_Param) then
2274             if Nkind (Parameter_Type (First_Param)) = N_Access_Definition then
2275                Obj_Param_Typ :=
2276                  Make_Access_Definition (Loc,
2277                    Subtype_Mark =>
2278                      New_Reference_To (Obj_Typ, Loc));
2279                Set_Null_Exclusion_Present (Obj_Param_Typ,
2280                  Null_Exclusion_Present (Parameter_Type (First_Param)));
2281
2282             else
2283                Obj_Param_Typ := New_Reference_To (Obj_Typ, Loc);
2284             end if;
2285
2286             Obj_Param :=
2287               Make_Parameter_Specification (Loc,
2288                 Defining_Identifier =>
2289                   Make_Defining_Identifier (Loc,
2290                     Chars => Name_uO),
2291                 In_Present          => In_Present  (First_Param),
2292                 Out_Present         => Out_Present (First_Param),
2293                 Parameter_Type      => Obj_Param_Typ);
2294
2295             Prepend_To (New_Formals, Obj_Param);
2296
2297          --  If we are dealing with a primitive declared between two views,
2298          --  implemented by a synchronized operation, we need to create
2299          --  a default parameter. The mode of the parameter must match that
2300          --  of the primitive operation.
2301
2302          else
2303             pragma Assert (Is_Private_Primitive_Subprogram (Subp_Id));
2304             Obj_Param :=
2305               Make_Parameter_Specification (Loc,
2306                 Defining_Identifier =>
2307                   Make_Defining_Identifier (Loc, Name_uO),
2308                 In_Present  => In_Present (Parent (First_Entity (Subp_Id))),
2309                 Out_Present => Ekind (Subp_Id) /= E_Function,
2310                   Parameter_Type => New_Reference_To (Obj_Typ, Loc));
2311             Prepend_To (New_Formals, Obj_Param);
2312          end if;
2313
2314          --  Build the final spec. If it is a function with a controlling
2315          --  result, it is a primitive operation of the corresponding
2316          --  record type, so mark the spec accordingly.
2317
2318          if Ekind (Subp_Id) = E_Function then
2319             declare
2320                Res_Def : Node_Id;
2321
2322             begin
2323                if Has_Controlling_Result (Subp_Id) then
2324                   Res_Def :=
2325                     New_Occurrence_Of
2326                       (Corresponding_Record_Type (Etype (Subp_Id)), Loc);
2327                else
2328                   Res_Def := New_Copy (Result_Definition (Parent (Subp_Id)));
2329                end if;
2330
2331                return
2332                  Make_Function_Specification (Loc,
2333                    Defining_Unit_Name       => Wrapper_Id,
2334                    Parameter_Specifications => New_Formals,
2335                    Result_Definition        => Res_Def);
2336             end;
2337          else
2338             return
2339               Make_Procedure_Specification (Loc,
2340                 Defining_Unit_Name       => Wrapper_Id,
2341                 Parameter_Specifications => New_Formals);
2342          end if;
2343       end;
2344    end Build_Wrapper_Spec;
2345
2346    -------------------------
2347    -- Build_Wrapper_Specs --
2348    -------------------------
2349
2350    procedure Build_Wrapper_Specs
2351      (Loc : Source_Ptr;
2352       Typ : Entity_Id;
2353       N   : in out Node_Id)
2354    is
2355       Def     : Node_Id;
2356       Rec_Typ : Entity_Id;
2357       procedure Scan_Declarations (L : List_Id);
2358       --  Common processing for visible and private declarations
2359       --  of a protected type.
2360
2361       procedure Scan_Declarations (L : List_Id) is
2362          Decl      : Node_Id;
2363          Wrap_Decl : Node_Id;
2364          Wrap_Spec : Node_Id;
2365
2366       begin
2367          if No (L) then
2368             return;
2369          end if;
2370
2371          Decl := First (L);
2372          while Present (Decl) loop
2373             Wrap_Spec := Empty;
2374
2375             if Nkind (Decl) = N_Entry_Declaration
2376               and then Ekind (Defining_Identifier (Decl)) = E_Entry
2377             then
2378                Wrap_Spec :=
2379                  Build_Wrapper_Spec
2380                    (Subp_Id => Defining_Identifier (Decl),
2381                     Obj_Typ => Rec_Typ,
2382                     Formals => Parameter_Specifications (Decl));
2383
2384             elsif Nkind (Decl) = N_Subprogram_Declaration then
2385                Wrap_Spec :=
2386                  Build_Wrapper_Spec
2387                    (Subp_Id => Defining_Unit_Name (Specification (Decl)),
2388                     Obj_Typ => Rec_Typ,
2389                     Formals =>
2390                       Parameter_Specifications (Specification (Decl)));
2391             end if;
2392
2393             if Present (Wrap_Spec) then
2394                Wrap_Decl :=
2395                  Make_Subprogram_Declaration (Loc,
2396                    Specification => Wrap_Spec);
2397
2398                Insert_After (N, Wrap_Decl);
2399                N := Wrap_Decl;
2400
2401                Analyze (Wrap_Decl);
2402             end if;
2403
2404             Next (Decl);
2405          end loop;
2406       end Scan_Declarations;
2407
2408       --  start of processing for Build_Wrapper_Specs
2409
2410    begin
2411       if Is_Protected_Type (Typ) then
2412          Def := Protected_Definition (Parent (Typ));
2413       else pragma Assert (Is_Task_Type (Typ));
2414          Def := Task_Definition (Parent (Typ));
2415       end if;
2416
2417       Rec_Typ := Corresponding_Record_Type (Typ);
2418
2419       --  Generate wrapper specs for a concurrent type which implements an
2420       --  interface. Operations in both the visible and private parts may
2421       --  implement progenitor operations.
2422
2423       if Present (Interfaces (Rec_Typ))
2424         and then Present (Def)
2425       then
2426          Scan_Declarations (Visible_Declarations (Def));
2427          Scan_Declarations (Private_Declarations (Def));
2428       end if;
2429    end Build_Wrapper_Specs;
2430
2431    ---------------------------
2432    -- Build_Find_Body_Index --
2433    ---------------------------
2434
2435    function Build_Find_Body_Index (Typ : Entity_Id) return Node_Id is
2436       Loc   : constant Source_Ptr := Sloc (Typ);
2437       Ent   : Entity_Id;
2438       E_Typ : Entity_Id;
2439       Has_F : Boolean := False;
2440       Index : Nat;
2441       If_St : Node_Id := Empty;
2442       Lo    : Node_Id;
2443       Hi    : Node_Id;
2444       Decls : List_Id := New_List;
2445       Ret   : Node_Id;
2446       Spec  : Node_Id;
2447       Siz   : Node_Id := Empty;
2448
2449       procedure Add_If_Clause (Expr : Node_Id);
2450       --  Add test for range of current entry
2451
2452       function Convert_Discriminant_Ref (Bound : Node_Id) return Node_Id;
2453       --  If a bound of an entry is given by a discriminant, retrieve the
2454       --  actual value of the discriminant from the enclosing object.
2455
2456       -------------------
2457       -- Add_If_Clause --
2458       -------------------
2459
2460       procedure Add_If_Clause (Expr : Node_Id) is
2461          Cond  : Node_Id;
2462          Stats : constant List_Id :=
2463                    New_List (
2464                      Make_Simple_Return_Statement (Loc,
2465                        Expression => Make_Integer_Literal (Loc, Index + 1)));
2466
2467       begin
2468          --  Index for current entry body
2469
2470          Index := Index + 1;
2471
2472          --  Compute total length of entry queues so far
2473
2474          if No (Siz) then
2475             Siz := Expr;
2476          else
2477             Siz :=
2478               Make_Op_Add (Loc,
2479                 Left_Opnd => Siz,
2480                 Right_Opnd => Expr);
2481          end if;
2482
2483          Cond :=
2484            Make_Op_Le (Loc,
2485              Left_Opnd => Make_Identifier (Loc, Name_uE),
2486              Right_Opnd => Siz);
2487
2488          --  Map entry queue indices in the range of the current family
2489          --  into the current index, that designates the entry body.
2490
2491          if No (If_St) then
2492             If_St :=
2493               Make_Implicit_If_Statement (Typ,
2494                 Condition => Cond,
2495                 Then_Statements => Stats,
2496                 Elsif_Parts   => New_List);
2497
2498             Ret := If_St;
2499
2500          else
2501             Append (
2502               Make_Elsif_Part (Loc,
2503                 Condition => Cond,
2504                 Then_Statements => Stats),
2505               Elsif_Parts (If_St));
2506          end if;
2507       end Add_If_Clause;
2508
2509       ------------------------------
2510       -- Convert_Discriminant_Ref --
2511       ------------------------------
2512
2513       function Convert_Discriminant_Ref (Bound : Node_Id) return Node_Id is
2514          B   : Node_Id;
2515
2516       begin
2517          if Is_Entity_Name (Bound)
2518            and then Ekind (Entity (Bound)) = E_Discriminant
2519          then
2520             B :=
2521               Make_Selected_Component (Loc,
2522                Prefix =>
2523                  Unchecked_Convert_To (Corresponding_Record_Type (Typ),
2524                    Make_Explicit_Dereference (Loc,
2525                      Make_Identifier (Loc, Name_uObject))),
2526                Selector_Name => Make_Identifier (Loc, Chars (Bound)));
2527             Set_Etype (B, Etype (Entity (Bound)));
2528          else
2529             B := New_Copy_Tree (Bound);
2530          end if;
2531
2532          return B;
2533       end Convert_Discriminant_Ref;
2534
2535    --  Start of processing for Build_Find_Body_Index
2536
2537    begin
2538       Spec := Build_Find_Body_Index_Spec (Typ);
2539
2540       Ent := First_Entity (Typ);
2541       while Present (Ent) loop
2542          if Ekind (Ent) = E_Entry_Family then
2543             Has_F := True;
2544             exit;
2545          end if;
2546
2547          Next_Entity (Ent);
2548       end loop;
2549
2550       if not Has_F then
2551
2552          --  If the protected type has no entry families, there is a one-one
2553          --  correspondence between entry queue and entry body.
2554
2555          Ret :=
2556            Make_Simple_Return_Statement (Loc,
2557              Expression => Make_Identifier (Loc, Name_uE));
2558
2559       else
2560          --  Suppose entries e1, e2, ... have size l1, l2, ... we generate
2561          --  the following:
2562          --
2563          --  if E <= l1 then return 1;
2564          --  elsif E <= l1 + l2 then return 2;
2565          --  ...
2566
2567          Index := 0;
2568          Siz   := Empty;
2569          Ent   := First_Entity (Typ);
2570
2571          Add_Object_Pointer (Loc, Typ, Decls);
2572
2573          while Present (Ent) loop
2574             if Ekind (Ent) = E_Entry then
2575                Add_If_Clause (Make_Integer_Literal (Loc, 1));
2576
2577             elsif Ekind (Ent) = E_Entry_Family then
2578                E_Typ := Etype (Discrete_Subtype_Definition (Parent (Ent)));
2579                Hi := Convert_Discriminant_Ref (Type_High_Bound (E_Typ));
2580                Lo := Convert_Discriminant_Ref (Type_Low_Bound  (E_Typ));
2581                Add_If_Clause (Family_Size (Loc, Hi, Lo, Typ, False));
2582             end if;
2583
2584             Next_Entity (Ent);
2585          end loop;
2586
2587          if Index = 1 then
2588             Decls := New_List;
2589             Ret :=
2590               Make_Simple_Return_Statement (Loc,
2591                 Expression => Make_Integer_Literal (Loc, 1));
2592
2593          elsif Nkind (Ret) = N_If_Statement then
2594
2595             --  Ranges are in increasing order, so last one doesn't need guard
2596
2597             declare
2598                Nod : constant Node_Id := Last (Elsif_Parts (Ret));
2599             begin
2600                Remove (Nod);
2601                Set_Else_Statements (Ret, Then_Statements (Nod));
2602             end;
2603          end if;
2604       end if;
2605
2606       return
2607         Make_Subprogram_Body (Loc,
2608           Specification => Spec,
2609           Declarations  => Decls,
2610           Handled_Statement_Sequence =>
2611             Make_Handled_Sequence_Of_Statements (Loc,
2612               Statements => New_List (Ret)));
2613    end Build_Find_Body_Index;
2614
2615    --------------------------------
2616    -- Build_Find_Body_Index_Spec --
2617    --------------------------------
2618
2619    function Build_Find_Body_Index_Spec (Typ : Entity_Id) return Node_Id is
2620       Loc   : constant Source_Ptr := Sloc (Typ);
2621       Id    : constant Entity_Id :=
2622                Make_Defining_Identifier (Loc,
2623                  Chars => New_External_Name (Chars (Typ), 'F'));
2624       Parm1 : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uO);
2625       Parm2 : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uE);
2626
2627    begin
2628       return
2629         Make_Function_Specification (Loc,
2630           Defining_Unit_Name => Id,
2631           Parameter_Specifications => New_List (
2632             Make_Parameter_Specification (Loc,
2633               Defining_Identifier => Parm1,
2634               Parameter_Type =>
2635                 New_Reference_To (RTE (RE_Address), Loc)),
2636
2637             Make_Parameter_Specification (Loc,
2638               Defining_Identifier => Parm2,
2639               Parameter_Type =>
2640                 New_Reference_To (RTE (RE_Protected_Entry_Index), Loc))),
2641           Result_Definition => New_Occurrence_Of (
2642             RTE (RE_Protected_Entry_Index), Loc));
2643    end Build_Find_Body_Index_Spec;
2644
2645    -------------------------
2646    -- Build_Master_Entity --
2647    -------------------------
2648
2649    procedure Build_Master_Entity (E : Entity_Id) is
2650       Loc  : constant Source_Ptr := Sloc (E);
2651       P    : Node_Id;
2652       Decl : Node_Id;
2653       S    : Entity_Id;
2654
2655    begin
2656       S := Find_Master_Scope (E);
2657
2658       --  Nothing to do if we already built a master entity for this scope
2659       --  or if there is no task hierarchy.
2660
2661       if Has_Master_Entity (S)
2662         or else Restriction_Active (No_Task_Hierarchy)
2663       then
2664          return;
2665       end if;
2666
2667       --  Otherwise first build the master entity
2668       --    _Master : constant Master_Id := Current_Master.all;
2669       --  and insert it just before the current declaration
2670
2671       Decl :=
2672         Make_Object_Declaration (Loc,
2673           Defining_Identifier =>
2674             Make_Defining_Identifier (Loc, Name_uMaster),
2675           Constant_Present => True,
2676           Object_Definition => New_Reference_To (RTE (RE_Master_Id), Loc),
2677           Expression =>
2678             Make_Explicit_Dereference (Loc,
2679               New_Reference_To (RTE (RE_Current_Master), Loc)));
2680
2681       P := Parent (E);
2682       Insert_Before (P, Decl);
2683       Analyze (Decl);
2684
2685       Set_Has_Master_Entity (S);
2686
2687       --  Now mark the containing scope as a task master
2688
2689       while Nkind (P) /= N_Compilation_Unit loop
2690          P := Parent (P);
2691
2692          --  If we fall off the top, we are at the outer level, and the
2693          --  environment task is our effective master, so nothing to mark.
2694
2695          if Nkind_In
2696               (P, N_Task_Body, N_Block_Statement, N_Subprogram_Body)
2697          then
2698             Set_Is_Task_Master (P, True);
2699             return;
2700
2701          elsif Nkind (Parent (P)) = N_Subunit then
2702             P := Corresponding_Stub (Parent (P));
2703          end if;
2704       end loop;
2705    end Build_Master_Entity;
2706
2707    -----------------------------------------
2708    -- Build_Private_Protected_Declaration --
2709    -----------------------------------------
2710
2711    function Build_Private_Protected_Declaration
2712      (N : Node_Id) return Entity_Id
2713    is
2714       Loc      : constant Source_Ptr := Sloc (N);
2715       Body_Id  : constant Entity_Id := Defining_Entity (N);
2716       Decl     : Node_Id;
2717       Plist    : List_Id;
2718       Formal   : Entity_Id;
2719       New_Spec : Node_Id;
2720       Spec_Id  : Entity_Id;
2721
2722    begin
2723       Formal := First_Formal (Body_Id);
2724
2725       --  The protected operation always has at least one formal, namely the
2726       --  object itself, but it is only placed in the parameter list if
2727       --  expansion is enabled.
2728
2729       if Present (Formal) or else Expander_Active then
2730          Plist := Copy_Parameter_List (Body_Id);
2731       else
2732          Plist := No_List;
2733       end if;
2734
2735       if Nkind (Specification (N)) = N_Procedure_Specification then
2736          New_Spec :=
2737            Make_Procedure_Specification (Loc,
2738               Defining_Unit_Name       =>
2739                 Make_Defining_Identifier (Sloc (Body_Id),
2740                   Chars => Chars (Body_Id)),
2741               Parameter_Specifications =>
2742                 Plist);
2743       else
2744          New_Spec :=
2745            Make_Function_Specification (Loc,
2746              Defining_Unit_Name       =>
2747                Make_Defining_Identifier (Sloc (Body_Id),
2748                  Chars => Chars (Body_Id)),
2749              Parameter_Specifications => Plist,
2750              Result_Definition        =>
2751                New_Occurrence_Of (Etype (Body_Id), Loc));
2752       end if;
2753
2754       Decl := Make_Subprogram_Declaration (Loc, Specification => New_Spec);
2755       Insert_Before (N, Decl);
2756       Spec_Id := Defining_Unit_Name (New_Spec);
2757
2758       --  Indicate that the entity comes from source, to ensure that cross-
2759       --  reference information is properly generated. The body itself is
2760       --  rewritten during expansion, and the body entity will not appear in
2761       --  calls to the operation.
2762
2763       Set_Comes_From_Source (Spec_Id, True);
2764       Analyze (Decl);
2765       Set_Has_Completion (Spec_Id);
2766       Set_Convention (Spec_Id, Convention_Protected);
2767       return Spec_Id;
2768    end Build_Private_Protected_Declaration;
2769
2770    ---------------------------
2771    -- Build_Protected_Entry --
2772    ---------------------------
2773
2774    function Build_Protected_Entry
2775      (N   : Node_Id;
2776       Ent : Entity_Id;
2777       Pid : Node_Id) return Node_Id
2778    is
2779       Loc : constant Source_Ptr := Sloc (N);
2780
2781       Decls   : constant List_Id := Declarations (N);
2782       End_Lab : constant Node_Id :=
2783                   End_Label (Handled_Statement_Sequence (N));
2784       End_Loc : constant Source_Ptr :=
2785                   Sloc (Last (Statements (Handled_Statement_Sequence (N))));
2786       --  Used for the generated call to Complete_Entry_Body
2787
2788       Han_Loc : Source_Ptr;
2789       --  Used for the exception handler, inserted at end of the body
2790
2791       Op_Decls : constant List_Id := New_List;
2792       Complete : Node_Id;
2793       Edef     : Entity_Id;
2794       Espec    : Node_Id;
2795       Ohandle  : Node_Id;
2796       Op_Stats : List_Id;
2797
2798    begin
2799       --  Set the source location on the exception handler only when debugging
2800       --  the expanded code (see Make_Implicit_Exception_Handler).
2801
2802       if Debug_Generated_Code then
2803          Han_Loc := End_Loc;
2804
2805       --  Otherwise the inserted code should not be visible to the debugger
2806
2807       else
2808          Han_Loc := No_Location;
2809       end if;
2810
2811       Edef :=
2812         Make_Defining_Identifier (Loc,
2813           Chars => Chars (Protected_Body_Subprogram (Ent)));
2814       Espec :=
2815         Build_Protected_Entry_Specification (Loc, Edef, Empty);
2816
2817       --  Add the following declarations:
2818       --    type poVP is access poV;
2819       --    _object : poVP := poVP (_O);
2820       --
2821       --  where _O is the formal parameter associated with the concurrent
2822       --  object. These declarations are needed for Complete_Entry_Body.
2823
2824       Add_Object_Pointer (Loc, Pid, Op_Decls);
2825
2826       --  Add renamings for all formals, the Protection object, discriminals,
2827       --  privals and the entry index constant for use by debugger.
2828
2829       Add_Formal_Renamings (Espec, Op_Decls, Ent, Loc);
2830       Debug_Private_Data_Declarations (Decls);
2831
2832       case Corresponding_Runtime_Package (Pid) is
2833          when System_Tasking_Protected_Objects_Entries =>
2834             Complete :=
2835               New_Reference_To (RTE (RE_Complete_Entry_Body), Loc);
2836
2837          when System_Tasking_Protected_Objects_Single_Entry =>
2838             Complete :=
2839               New_Reference_To (RTE (RE_Complete_Single_Entry_Body), Loc);
2840
2841          when others =>
2842             raise Program_Error;
2843       end case;
2844
2845       Op_Stats := New_List (
2846         Make_Block_Statement (Loc,
2847           Declarations => Decls,
2848           Handled_Statement_Sequence =>
2849             Handled_Statement_Sequence (N)),
2850
2851         Make_Procedure_Call_Statement (End_Loc,
2852           Name => Complete,
2853           Parameter_Associations => New_List (
2854             Make_Attribute_Reference (End_Loc,
2855               Prefix =>
2856                 Make_Selected_Component (End_Loc,
2857                   Prefix =>
2858                     Make_Identifier (End_Loc, Name_uObject),
2859                   Selector_Name =>
2860                     Make_Identifier (End_Loc, Name_uObject)),
2861               Attribute_Name => Name_Unchecked_Access))));
2862
2863       --  When exceptions can not be propagated, we never need to call
2864       --  Exception_Complete_Entry_Body
2865
2866       if No_Exception_Handlers_Set then
2867          return
2868            Make_Subprogram_Body (Loc,
2869              Specification => Espec,
2870              Declarations => Op_Decls,
2871              Handled_Statement_Sequence =>
2872                Make_Handled_Sequence_Of_Statements (Loc,
2873                  Statements => Op_Stats,
2874                  End_Label  => End_Lab));
2875
2876       else
2877          Ohandle := Make_Others_Choice (Loc);
2878          Set_All_Others (Ohandle);
2879
2880          case Corresponding_Runtime_Package (Pid) is
2881             when System_Tasking_Protected_Objects_Entries =>
2882                Complete :=
2883                  New_Reference_To
2884                    (RTE (RE_Exceptional_Complete_Entry_Body), Loc);
2885
2886             when System_Tasking_Protected_Objects_Single_Entry =>
2887                Complete :=
2888                  New_Reference_To
2889                    (RTE (RE_Exceptional_Complete_Single_Entry_Body), Loc);
2890
2891             when others =>
2892                raise Program_Error;
2893          end case;
2894
2895          --  Establish link between subprogram body entity and source entry.
2896
2897          Set_Corresponding_Protected_Entry (Edef, Ent);
2898
2899          --  Create body of entry procedure. The renaming declarations are
2900          --  placed ahead of the block that contains the actual entry body.
2901
2902          return
2903            Make_Subprogram_Body (Loc,
2904              Specification => Espec,
2905              Declarations => Op_Decls,
2906              Handled_Statement_Sequence =>
2907                Make_Handled_Sequence_Of_Statements (Loc,
2908                  Statements => Op_Stats,
2909                  End_Label  => End_Lab,
2910                  Exception_Handlers => New_List (
2911                    Make_Implicit_Exception_Handler (Han_Loc,
2912                      Exception_Choices => New_List (Ohandle),
2913
2914                      Statements =>  New_List (
2915                        Make_Procedure_Call_Statement (Han_Loc,
2916                          Name => Complete,
2917                          Parameter_Associations => New_List (
2918                            Make_Attribute_Reference (Han_Loc,
2919                              Prefix =>
2920                                Make_Selected_Component (Han_Loc,
2921                                  Prefix =>
2922                                    Make_Identifier (Han_Loc, Name_uObject),
2923                                  Selector_Name =>
2924                                    Make_Identifier (Han_Loc, Name_uObject)),
2925                                Attribute_Name => Name_Unchecked_Access),
2926
2927                            Make_Function_Call (Han_Loc,
2928                              Name => New_Reference_To (
2929                                RTE (RE_Get_GNAT_Exception), Loc)))))))));
2930       end if;
2931    end Build_Protected_Entry;
2932
2933    -----------------------------------------
2934    -- Build_Protected_Entry_Specification --
2935    -----------------------------------------
2936
2937    function Build_Protected_Entry_Specification
2938      (Loc    : Source_Ptr;
2939       Def_Id : Entity_Id;
2940       Ent_Id : Entity_Id) return Node_Id
2941    is
2942       P : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uP);
2943
2944    begin
2945       Set_Debug_Info_Needed (Def_Id);
2946
2947       if Present (Ent_Id) then
2948          Append_Elmt (P, Accept_Address (Ent_Id));
2949       end if;
2950
2951       return
2952         Make_Procedure_Specification (Loc,
2953           Defining_Unit_Name => Def_Id,
2954           Parameter_Specifications => New_List (
2955             Make_Parameter_Specification (Loc,
2956               Defining_Identifier =>
2957                 Make_Defining_Identifier (Loc, Name_uO),
2958               Parameter_Type =>
2959                 New_Reference_To (RTE (RE_Address), Loc)),
2960
2961             Make_Parameter_Specification (Loc,
2962               Defining_Identifier => P,
2963               Parameter_Type =>
2964                 New_Reference_To (RTE (RE_Address), Loc)),
2965
2966             Make_Parameter_Specification (Loc,
2967               Defining_Identifier =>
2968                 Make_Defining_Identifier (Loc, Name_uE),
2969               Parameter_Type =>
2970                 New_Reference_To (RTE (RE_Protected_Entry_Index), Loc))));
2971    end Build_Protected_Entry_Specification;
2972
2973    --------------------------
2974    -- Build_Protected_Spec --
2975    --------------------------
2976
2977    function Build_Protected_Spec
2978      (N           : Node_Id;
2979       Obj_Type    : Entity_Id;
2980       Ident       : Entity_Id;
2981       Unprotected : Boolean := False) return List_Id
2982    is
2983       Loc       : constant Source_Ptr := Sloc (N);
2984       Decl      : Node_Id;
2985       Formal    : Entity_Id;
2986       New_Plist : List_Id;
2987       New_Param : Node_Id;
2988
2989    begin
2990       New_Plist := New_List;
2991
2992       Formal := First_Formal (Ident);
2993       while Present (Formal) loop
2994          New_Param :=
2995            Make_Parameter_Specification (Loc,
2996              Defining_Identifier =>
2997                Make_Defining_Identifier (Sloc (Formal), Chars (Formal)),
2998              In_Present          => In_Present (Parent (Formal)),
2999              Out_Present         => Out_Present (Parent (Formal)),
3000              Parameter_Type      => New_Reference_To (Etype (Formal), Loc));
3001
3002          if Unprotected then
3003             Set_Protected_Formal (Formal, Defining_Identifier (New_Param));
3004          end if;
3005
3006          Append (New_Param, New_Plist);
3007          Next_Formal (Formal);
3008       end loop;
3009
3010       --  If the subprogram is a procedure and the context is not an access
3011       --  to protected subprogram, the parameter is in-out. Otherwise it is
3012       --  an in parameter.
3013
3014       Decl :=
3015         Make_Parameter_Specification (Loc,
3016           Defining_Identifier =>
3017             Make_Defining_Identifier (Loc, Name_uObject),
3018           In_Present => True,
3019           Out_Present =>
3020             (Etype (Ident) = Standard_Void_Type
3021                and then not Is_RTE (Obj_Type, RE_Address)),
3022           Parameter_Type =>
3023             New_Reference_To (Obj_Type, Loc));
3024       Set_Debug_Info_Needed (Defining_Identifier (Decl));
3025       Prepend_To (New_Plist, Decl);
3026
3027       return New_Plist;
3028    end Build_Protected_Spec;
3029
3030    ---------------------------------------
3031    -- Build_Protected_Sub_Specification --
3032    ---------------------------------------
3033
3034    function Build_Protected_Sub_Specification
3035      (N        : Node_Id;
3036       Prot_Typ : Entity_Id;
3037       Mode     : Subprogram_Protection_Mode) return Node_Id
3038    is
3039       Loc       : constant Source_Ptr := Sloc (N);
3040       Decl      : Node_Id;
3041       Def_Id    : Entity_Id;
3042       New_Id    : Entity_Id;
3043       New_Plist : List_Id;
3044       New_Spec  : Node_Id;
3045
3046       Append_Chr : constant array (Subprogram_Protection_Mode) of Character :=
3047                      (Dispatching_Mode => ' ',
3048                       Protected_Mode   => 'P',
3049                       Unprotected_Mode => 'N');
3050
3051    begin
3052       if Ekind (Defining_Unit_Name (Specification (N))) =
3053            E_Subprogram_Body
3054       then
3055          Decl := Unit_Declaration_Node (Corresponding_Spec (N));
3056       else
3057          Decl := N;
3058       end if;
3059
3060       Def_Id := Defining_Unit_Name (Specification (Decl));
3061
3062       New_Plist :=
3063         Build_Protected_Spec
3064           (Decl, Corresponding_Record_Type (Prot_Typ), Def_Id,
3065            Mode = Unprotected_Mode);
3066       New_Id :=
3067         Make_Defining_Identifier (Loc,
3068           Chars => Build_Selected_Name (Prot_Typ, Def_Id, Append_Chr (Mode)));
3069
3070       --  The unprotected operation carries the user code, and debugging
3071       --  information must be generated for it, even though this spec does
3072       --  not come from source. It is also convenient to allow gdb to step
3073       --  into the protected operation, even though it only contains lock/
3074       --  unlock calls.
3075
3076       Set_Debug_Info_Needed (New_Id);
3077
3078       --  If a pragma Eliminate applies to the source entity, the internal
3079       --  subprograms will be eliminated as well.
3080
3081       Set_Is_Eliminated (New_Id, Is_Eliminated (Def_Id));
3082
3083       if Nkind (Specification (Decl)) = N_Procedure_Specification then
3084          New_Spec :=
3085            Make_Procedure_Specification (Loc,
3086              Defining_Unit_Name => New_Id,
3087              Parameter_Specifications => New_Plist);
3088
3089       --  Create a new specification for the anonymous subprogram type
3090
3091       else
3092          New_Spec :=
3093            Make_Function_Specification (Loc,
3094              Defining_Unit_Name => New_Id,
3095              Parameter_Specifications => New_Plist,
3096              Result_Definition =>
3097                Copy_Result_Type (Result_Definition (Specification (Decl))));
3098
3099          Set_Return_Present (Defining_Unit_Name (New_Spec));
3100       end if;
3101
3102       return New_Spec;
3103    end Build_Protected_Sub_Specification;
3104
3105    -------------------------------------
3106    -- Build_Protected_Subprogram_Body --
3107    -------------------------------------
3108
3109    function Build_Protected_Subprogram_Body
3110      (N         : Node_Id;
3111       Pid       : Node_Id;
3112       N_Op_Spec : Node_Id) return Node_Id
3113    is
3114       Loc          : constant Source_Ptr := Sloc (N);
3115       Op_Spec      : Node_Id;
3116       P_Op_Spec    : Node_Id;
3117       Uactuals     : List_Id;
3118       Pformal      : Node_Id;
3119       Unprot_Call  : Node_Id;
3120       Sub_Body     : Node_Id;
3121       Lock_Name    : Node_Id;
3122       Lock_Stmt    : Node_Id;
3123       Service_Name : Node_Id;
3124       R            : Node_Id;
3125       Return_Stmt  : Node_Id := Empty;    -- init to avoid gcc 3 warning
3126       Pre_Stmts    : List_Id := No_List;  -- init to avoid gcc 3 warning
3127       Stmts        : List_Id;
3128       Object_Parm  : Node_Id;
3129       Exc_Safe     : Boolean;
3130
3131       function Is_Exception_Safe (Subprogram : Node_Id) return Boolean;
3132       --  Tell whether a given subprogram cannot raise an exception
3133
3134       -----------------------
3135       -- Is_Exception_Safe --
3136       -----------------------
3137
3138       function Is_Exception_Safe (Subprogram : Node_Id) return Boolean is
3139
3140          function Has_Side_Effect (N : Node_Id) return Boolean;
3141          --  Return True whenever encountering a subprogram call or raise
3142          --  statement of any kind in the sequence of statements
3143
3144          ---------------------
3145          -- Has_Side_Effect --
3146          ---------------------
3147
3148          --  What is this doing buried two levels down in exp_ch9. It seems
3149          --  like a generally useful function, and indeed there may be code
3150          --  duplication going on here ???
3151
3152          function Has_Side_Effect (N : Node_Id) return Boolean is
3153             Stmt : Node_Id;
3154             Expr : Node_Id;
3155
3156             function Is_Call_Or_Raise (N : Node_Id) return Boolean;
3157             --  Indicate whether N is a subprogram call or a raise statement
3158
3159             ----------------------
3160             -- Is_Call_Or_Raise --
3161             ----------------------
3162
3163             function Is_Call_Or_Raise (N : Node_Id) return Boolean is
3164             begin
3165                return Nkind_In (N, N_Procedure_Call_Statement,
3166                                    N_Function_Call,
3167                                    N_Raise_Statement,
3168                                    N_Raise_Constraint_Error,
3169                                    N_Raise_Program_Error,
3170                                    N_Raise_Storage_Error);
3171             end Is_Call_Or_Raise;
3172
3173          --  Start of processing for Has_Side_Effect
3174
3175          begin
3176             Stmt := N;
3177             while Present (Stmt) loop
3178                if Is_Call_Or_Raise (Stmt) then
3179                   return True;
3180                end if;
3181
3182                --  An object declaration can also contain a function call
3183                --  or a raise statement
3184
3185                if Nkind (Stmt) = N_Object_Declaration then
3186                   Expr := Expression (Stmt);
3187
3188                   if Present (Expr) and then Is_Call_Or_Raise (Expr) then
3189                      return True;
3190                   end if;
3191                end if;
3192
3193                Next (Stmt);
3194             end loop;
3195
3196             return False;
3197          end Has_Side_Effect;
3198
3199       --  Start of processing for Is_Exception_Safe
3200
3201       begin
3202          --  If the checks handled by the back end are not disabled, we cannot
3203          --  ensure that no exception will be raised.
3204
3205          if not Access_Checks_Suppressed (Empty)
3206            or else not Discriminant_Checks_Suppressed (Empty)
3207            or else not Range_Checks_Suppressed (Empty)
3208            or else not Index_Checks_Suppressed (Empty)
3209            or else Opt.Stack_Checking_Enabled
3210          then
3211             return False;
3212          end if;
3213
3214          if Has_Side_Effect (First (Declarations (Subprogram)))
3215            or else
3216               Has_Side_Effect (
3217                 First (Statements (Handled_Statement_Sequence (Subprogram))))
3218          then
3219             return False;
3220          else
3221             return True;
3222          end if;
3223       end Is_Exception_Safe;
3224
3225    --  Start of processing for Build_Protected_Subprogram_Body
3226
3227    begin
3228       Op_Spec := Specification (N);
3229       Exc_Safe := Is_Exception_Safe (N);
3230
3231       P_Op_Spec :=
3232         Build_Protected_Sub_Specification (N, Pid, Protected_Mode);
3233
3234       --  Build a list of the formal parameters of the protected version of
3235       --  the subprogram to use as the actual parameters of the unprotected
3236       --  version.
3237
3238       Uactuals := New_List;
3239       Pformal := First (Parameter_Specifications (P_Op_Spec));
3240       while Present (Pformal) loop
3241          Append (
3242            Make_Identifier (Loc, Chars (Defining_Identifier (Pformal))),
3243            Uactuals);
3244          Next (Pformal);
3245       end loop;
3246
3247       --  Make a call to the unprotected version of the subprogram built above
3248       --  for use by the protected version built below.
3249
3250       if Nkind (Op_Spec) = N_Function_Specification then
3251          if Exc_Safe then
3252             R := Make_Temporary (Loc, 'R');
3253             Unprot_Call :=
3254               Make_Object_Declaration (Loc,
3255                 Defining_Identifier => R,
3256                 Constant_Present => True,
3257                 Object_Definition => New_Copy (Result_Definition (N_Op_Spec)),
3258                 Expression =>
3259                   Make_Function_Call (Loc,
3260                     Name => Make_Identifier (Loc,
3261                       Chars (Defining_Unit_Name (N_Op_Spec))),
3262                     Parameter_Associations => Uactuals));
3263
3264             Return_Stmt :=
3265               Make_Simple_Return_Statement (Loc,
3266                 Expression => New_Reference_To (R, Loc));
3267
3268          else
3269             Unprot_Call := Make_Simple_Return_Statement (Loc,
3270               Expression => Make_Function_Call (Loc,
3271                 Name =>
3272                   Make_Identifier (Loc,
3273                     Chars (Defining_Unit_Name (N_Op_Spec))),
3274                 Parameter_Associations => Uactuals));
3275          end if;
3276
3277       else
3278          Unprot_Call :=
3279            Make_Procedure_Call_Statement (Loc,
3280              Name =>
3281                Make_Identifier (Loc,
3282                  Chars (Defining_Unit_Name (N_Op_Spec))),
3283              Parameter_Associations => Uactuals);
3284       end if;
3285
3286       --  Wrap call in block that will be covered by an at_end handler
3287
3288       if not Exc_Safe then
3289          Unprot_Call := Make_Block_Statement (Loc,
3290            Handled_Statement_Sequence =>
3291              Make_Handled_Sequence_Of_Statements (Loc,
3292                Statements => New_List (Unprot_Call)));
3293       end if;
3294
3295       --  Make the protected subprogram body. This locks the protected
3296       --  object and calls the unprotected version of the subprogram.
3297
3298       case Corresponding_Runtime_Package (Pid) is
3299          when System_Tasking_Protected_Objects_Entries =>
3300             Lock_Name := New_Reference_To (RTE (RE_Lock_Entries), Loc);
3301             Service_Name := New_Reference_To (RTE (RE_Service_Entries), Loc);
3302
3303          when System_Tasking_Protected_Objects_Single_Entry =>
3304             Lock_Name := New_Reference_To (RTE (RE_Lock_Entry), Loc);
3305             Service_Name := New_Reference_To (RTE (RE_Service_Entry), Loc);
3306
3307          when System_Tasking_Protected_Objects =>
3308             Lock_Name := New_Reference_To (RTE (RE_Lock), Loc);
3309             Service_Name := New_Reference_To (RTE (RE_Unlock), Loc);
3310
3311          when others =>
3312             raise Program_Error;
3313       end case;
3314
3315       Object_Parm :=
3316         Make_Attribute_Reference (Loc,
3317            Prefix =>
3318              Make_Selected_Component (Loc,
3319                Prefix =>
3320                  Make_Identifier (Loc, Name_uObject),
3321              Selector_Name =>
3322                  Make_Identifier (Loc, Name_uObject)),
3323            Attribute_Name => Name_Unchecked_Access);
3324
3325       Lock_Stmt := Make_Procedure_Call_Statement (Loc,
3326         Name => Lock_Name,
3327         Parameter_Associations => New_List (Object_Parm));
3328
3329       if Abort_Allowed then
3330          Stmts := New_List (
3331            Make_Procedure_Call_Statement (Loc,
3332              Name => New_Reference_To (RTE (RE_Abort_Defer), Loc),
3333              Parameter_Associations => Empty_List),
3334            Lock_Stmt);
3335
3336       else
3337          Stmts := New_List (Lock_Stmt);
3338       end if;
3339
3340       if not Exc_Safe then
3341          Append (Unprot_Call, Stmts);
3342       else
3343          if Nkind (Op_Spec) = N_Function_Specification then
3344             Pre_Stmts := Stmts;
3345             Stmts     := Empty_List;
3346          else
3347             Append (Unprot_Call, Stmts);
3348          end if;
3349
3350          Append (
3351            Make_Procedure_Call_Statement (Loc,
3352              Name => Service_Name,
3353              Parameter_Associations =>
3354                New_List (New_Copy_Tree (Object_Parm))),
3355            Stmts);
3356
3357          if Abort_Allowed then
3358             Append (
3359               Make_Procedure_Call_Statement (Loc,
3360                 Name => New_Reference_To (RTE (RE_Abort_Undefer), Loc),
3361                 Parameter_Associations => Empty_List),
3362               Stmts);
3363          end if;
3364
3365          if Nkind (Op_Spec) = N_Function_Specification then
3366             Append (Return_Stmt, Stmts);
3367             Append (Make_Block_Statement (Loc,
3368               Declarations => New_List (Unprot_Call),
3369               Handled_Statement_Sequence =>
3370                 Make_Handled_Sequence_Of_Statements (Loc,
3371                   Statements => Stmts)), Pre_Stmts);
3372             Stmts := Pre_Stmts;
3373          end if;
3374       end if;
3375
3376       Sub_Body :=
3377         Make_Subprogram_Body (Loc,
3378           Declarations => Empty_List,
3379           Specification => P_Op_Spec,
3380           Handled_Statement_Sequence =>
3381             Make_Handled_Sequence_Of_Statements (Loc, Statements => Stmts));
3382
3383       if not Exc_Safe then
3384          Set_Is_Protected_Subprogram_Body (Sub_Body);
3385       end if;
3386
3387       return Sub_Body;
3388    end Build_Protected_Subprogram_Body;
3389
3390    -------------------------------------
3391    -- Build_Protected_Subprogram_Call --
3392    -------------------------------------
3393
3394    procedure Build_Protected_Subprogram_Call
3395      (N        : Node_Id;
3396       Name     : Node_Id;
3397       Rec      : Node_Id;
3398       External : Boolean := True)
3399    is
3400       Loc     : constant Source_Ptr := Sloc (N);
3401       Sub     : constant Entity_Id  := Entity (Name);
3402       New_Sub : Node_Id;
3403       Params  : List_Id;
3404
3405    begin
3406       if External then
3407          New_Sub := New_Occurrence_Of (External_Subprogram (Sub), Loc);
3408       else
3409          New_Sub :=
3410            New_Occurrence_Of (Protected_Body_Subprogram (Sub), Loc);
3411       end if;
3412
3413       if Present (Parameter_Associations (N)) then
3414          Params := New_Copy_List_Tree (Parameter_Associations (N));
3415       else
3416          Params := New_List;
3417       end if;
3418
3419       --  If the type is an untagged derived type, convert to the root type,
3420       --  which is the one on which the operations are defined.
3421
3422       if Nkind (Rec) = N_Unchecked_Type_Conversion
3423         and then not Is_Tagged_Type (Etype (Rec))
3424         and then Is_Derived_Type (Etype (Rec))
3425       then
3426          Set_Etype (Rec, Root_Type (Etype (Rec)));
3427          Set_Subtype_Mark (Rec,
3428            New_Occurrence_Of (Root_Type (Etype (Rec)), Sloc (N)));
3429       end if;
3430
3431       Prepend (Rec, Params);
3432
3433       if Ekind (Sub) = E_Procedure then
3434          Rewrite (N,
3435            Make_Procedure_Call_Statement (Loc,
3436              Name => New_Sub,
3437              Parameter_Associations => Params));
3438
3439       else
3440          pragma Assert (Ekind (Sub) = E_Function);
3441          Rewrite (N,
3442            Make_Function_Call (Loc,
3443              Name => New_Sub,
3444              Parameter_Associations => Params));
3445       end if;
3446
3447       if External
3448         and then Nkind (Rec) = N_Unchecked_Type_Conversion
3449         and then Is_Entity_Name (Expression (Rec))
3450         and then Is_Shared_Passive (Entity (Expression (Rec)))
3451       then
3452          Add_Shared_Var_Lock_Procs (N);
3453       end if;
3454    end Build_Protected_Subprogram_Call;
3455
3456    -------------------------
3457    -- Build_Selected_Name --
3458    -------------------------
3459
3460    function Build_Selected_Name
3461      (Prefix      : Entity_Id;
3462       Selector    : Entity_Id;
3463       Append_Char : Character := ' ') return Name_Id
3464    is
3465       Select_Buffer : String (1 .. Hostparm.Max_Name_Length);
3466       Select_Len    : Natural;
3467
3468    begin
3469       Get_Name_String (Chars (Selector));
3470       Select_Len := Name_Len;
3471       Select_Buffer (1 .. Select_Len) := Name_Buffer (1 .. Name_Len);
3472       Get_Name_String (Chars (Prefix));
3473
3474       --  If scope is anonymous type, discard suffix to recover name of
3475       --  single protected object. Otherwise use protected type name.
3476
3477       if Name_Buffer (Name_Len) = 'T' then
3478          Name_Len := Name_Len - 1;
3479       end if;
3480
3481       Add_Str_To_Name_Buffer ("__");
3482       for J in 1 .. Select_Len loop
3483          Add_Char_To_Name_Buffer (Select_Buffer (J));
3484       end loop;
3485
3486       --  Now add the Append_Char if specified. The encoding to follow
3487       --  depends on the type of entity. If Append_Char is either 'N' or 'P',
3488       --  then the entity is associated to a protected type subprogram.
3489       --  Otherwise, it is a protected type entry. For each case, the
3490       --  encoding to follow for the suffix is documented in exp_dbug.ads.
3491
3492       --  It would be better to encapsulate this as a routine in Exp_Dbug ???
3493
3494       if Append_Char /= ' ' then
3495          if Append_Char = 'P' or Append_Char = 'N' then
3496             Add_Char_To_Name_Buffer (Append_Char);
3497             return Name_Find;
3498          else
3499             Add_Str_To_Name_Buffer ((1 => '_', 2 => Append_Char));
3500             return New_External_Name (Name_Find, ' ', -1);
3501          end if;
3502       else
3503          return Name_Find;
3504       end if;
3505    end Build_Selected_Name;
3506
3507    -----------------------------
3508    -- Build_Simple_Entry_Call --
3509    -----------------------------
3510
3511    --  A task entry call is converted to a call to Call_Simple
3512
3513    --    declare
3514    --       P : parms := (parm, parm, parm);
3515    --    begin
3516    --       Call_Simple (acceptor-task, entry-index, P'Address);
3517    --       parm := P.param;
3518    --       parm := P.param;
3519    --       ...
3520    --    end;
3521
3522    --  Here Pnn is an aggregate of the type constructed for the entry to hold
3523    --  the parameters, and the constructed aggregate value contains either the
3524    --  parameters or, in the case of non-elementary types, references to these
3525    --  parameters. Then the address of this aggregate is passed to the runtime
3526    --  routine, along with the task id value and the task entry index value.
3527    --  Pnn is only required if parameters are present.
3528
3529    --  The assignments after the call are present only in the case of in-out
3530    --  or out parameters for elementary types, and are used to assign back the
3531    --  resulting values of such parameters.
3532
3533    --  Note: the reason that we insert a block here is that in the context
3534    --  of selects, conditional entry calls etc. the entry call statement
3535    --  appears on its own, not as an element of a list.
3536
3537    --  A protected entry call is converted to a Protected_Entry_Call:
3538
3539    --  declare
3540    --     P   : E1_Params := (param, param, param);
3541    --     Pnn : Boolean;
3542    --     Bnn : Communications_Block;
3543
3544    --  declare
3545    --     P   : E1_Params := (param, param, param);
3546    --     Bnn : Communications_Block;
3547
3548    --  begin
3549    --     Protected_Entry_Call (
3550    --       Object => po._object'Access,
3551    --       E => <entry index>;
3552    --       Uninterpreted_Data => P'Address;
3553    --       Mode => Simple_Call;
3554    --       Block => Bnn);
3555    --     parm := P.param;
3556    --     parm := P.param;
3557    --       ...
3558    --  end;
3559
3560    procedure Build_Simple_Entry_Call
3561      (N       : Node_Id;
3562       Concval : Node_Id;
3563       Ename   : Node_Id;
3564       Index   : Node_Id)
3565    is
3566    begin
3567       Expand_Call (N);
3568
3569       --  If call has been inlined, nothing left to do
3570
3571       if Nkind (N) = N_Block_Statement then
3572          return;
3573       end if;
3574
3575       --  Convert entry call to Call_Simple call
3576
3577       declare
3578          Loc       : constant Source_Ptr := Sloc (N);
3579          Parms     : constant List_Id    := Parameter_Associations (N);
3580          Stats     : constant List_Id    := New_List;
3581          Actual    : Node_Id;
3582          Call      : Node_Id;
3583          Comm_Name : Entity_Id;
3584          Conctyp   : Node_Id;
3585          Decls     : List_Id;
3586          Ent       : Entity_Id;
3587          Ent_Acc   : Entity_Id;
3588          Formal    : Node_Id;
3589          Iface_Tag : Entity_Id;
3590          Iface_Typ : Entity_Id;
3591          N_Node    : Node_Id;
3592          N_Var     : Node_Id;
3593          P         : Entity_Id;
3594          Parm1     : Node_Id;
3595          Parm2     : Node_Id;
3596          Parm3     : Node_Id;
3597          Pdecl     : Node_Id;
3598          Plist     : List_Id;
3599          X         : Entity_Id;
3600          Xdecl     : Node_Id;
3601
3602       begin
3603          --  Simple entry and entry family cases merge here
3604
3605          Ent     := Entity (Ename);
3606          Ent_Acc := Entry_Parameters_Type (Ent);
3607          Conctyp := Etype (Concval);
3608
3609          --  If prefix is an access type, dereference to obtain the task type
3610
3611          if Is_Access_Type (Conctyp) then
3612             Conctyp := Designated_Type (Conctyp);
3613          end if;
3614
3615          --  Special case for protected subprogram calls
3616
3617          if Is_Protected_Type (Conctyp)
3618            and then Is_Subprogram (Entity (Ename))
3619          then
3620             if not Is_Eliminated (Entity (Ename)) then
3621                Build_Protected_Subprogram_Call
3622                  (N, Ename, Convert_Concurrent (Concval, Conctyp));
3623                Analyze (N);
3624             end if;
3625
3626             return;
3627          end if;
3628
3629          --  First parameter is the Task_Id value from the task value or the
3630          --  Object from the protected object value, obtained by selecting
3631          --  the _Task_Id or _Object from the result of doing an unchecked
3632          --  conversion to convert the value to the corresponding record type.
3633
3634          if Nkind (Concval) = N_Function_Call
3635            and then Is_Task_Type (Conctyp)
3636            and then Ada_Version >= Ada_2005
3637          then
3638             declare
3639                ExpR : constant Node_Id   := Relocate_Node (Concval);
3640                Obj  : constant Entity_Id := Make_Temporary (Loc, 'F', ExpR);
3641                Decl : Node_Id;
3642
3643             begin
3644                Decl :=
3645                  Make_Object_Declaration (Loc,
3646                    Defining_Identifier => Obj,
3647                    Object_Definition   => New_Occurrence_Of (Conctyp, Loc),
3648                    Expression          => ExpR);
3649                Set_Etype (Obj, Conctyp);
3650                Decls := New_List (Decl);
3651                Rewrite (Concval, New_Occurrence_Of (Obj, Loc));
3652             end;
3653
3654          else
3655             Decls := New_List;
3656          end if;
3657
3658          Parm1 := Concurrent_Ref (Concval);
3659
3660          --  Second parameter is the entry index, computed by the routine
3661          --  provided for this purpose. The value of this expression is
3662          --  assigned to an intermediate variable to assure that any entry
3663          --  family index expressions are evaluated before the entry
3664          --  parameters.
3665
3666          if Abort_Allowed
3667            or else Restriction_Active (No_Entry_Queue) = False
3668            or else not Is_Protected_Type (Conctyp)
3669            or else Number_Entries (Conctyp) > 1
3670            or else (Has_Attach_Handler (Conctyp)
3671                      and then not Restricted_Profile)
3672          then
3673             X := Make_Defining_Identifier (Loc, Name_uX);
3674
3675             Xdecl :=
3676               Make_Object_Declaration (Loc,
3677                 Defining_Identifier => X,
3678                 Object_Definition =>
3679                   New_Reference_To (RTE (RE_Task_Entry_Index), Loc),
3680                 Expression => Actual_Index_Expression (
3681                   Loc, Entity (Ename), Index, Concval));
3682
3683             Append_To (Decls, Xdecl);
3684             Parm2 := New_Reference_To (X, Loc);
3685
3686          else
3687             Xdecl := Empty;
3688             Parm2 := Empty;
3689          end if;
3690
3691          --  The third parameter is the packaged parameters. If there are
3692          --  none, then it is just the null address, since nothing is passed.
3693
3694          if No (Parms) then
3695             Parm3 := New_Reference_To (RTE (RE_Null_Address), Loc);
3696             P := Empty;
3697
3698          --  Case of parameters present, where third argument is the address
3699          --  of a packaged record containing the required parameter values.
3700
3701          else
3702             --  First build a list of parameter values, which are references to
3703             --  objects of the parameter types.
3704
3705             Plist := New_List;
3706
3707             Actual := First_Actual (N);
3708             Formal := First_Formal (Ent);
3709
3710             while Present (Actual) loop
3711
3712                --  If it is a by_copy_type, copy it to a new variable. The
3713                --  packaged record has a field that points to this variable.
3714
3715                if Is_By_Copy_Type (Etype (Actual)) then
3716                   N_Node :=
3717                     Make_Object_Declaration (Loc,
3718                       Defining_Identifier => Make_Temporary (Loc, 'J'),
3719                       Aliased_Present     => True,
3720                       Object_Definition   =>
3721                         New_Reference_To (Etype (Formal), Loc));
3722
3723                   --  Mark the object as not needing initialization since the
3724                   --  initialization is performed separately, avoiding errors
3725                   --  on cases such as formals of null-excluding access types.
3726
3727                   Set_No_Initialization (N_Node);
3728
3729                   --  We must make an assignment statement separate for the
3730                   --  case of limited type. We cannot assign it unless the
3731                   --  Assignment_OK flag is set first. An out formal of an
3732                   --  access type must also be initialized from the actual,
3733                   --  as stated in RM 6.4.1 (13).
3734
3735                   if Ekind (Formal) /= E_Out_Parameter
3736                     or else Is_Access_Type (Etype (Formal))
3737                   then
3738                      N_Var :=
3739                        New_Reference_To (Defining_Identifier (N_Node), Loc);
3740                      Set_Assignment_OK (N_Var);
3741                      Append_To (Stats,
3742                        Make_Assignment_Statement (Loc,
3743                          Name => N_Var,
3744                          Expression => Relocate_Node (Actual)));
3745                   end if;
3746
3747                   Append (N_Node, Decls);
3748
3749                   Append_To (Plist,
3750                     Make_Attribute_Reference (Loc,
3751                       Attribute_Name => Name_Unchecked_Access,
3752                     Prefix =>
3753                       New_Reference_To (Defining_Identifier (N_Node), Loc)));
3754                else
3755                   --  Interface class-wide formal
3756
3757                   if Ada_Version >= Ada_2005
3758                     and then Ekind (Etype (Formal)) = E_Class_Wide_Type
3759                     and then Is_Interface (Etype (Formal))
3760                   then
3761                      Iface_Typ := Etype (Etype (Formal));
3762
3763                      --  Generate:
3764                      --    formal_iface_type! (actual.iface_tag)'reference
3765
3766                      Iface_Tag :=
3767                        Find_Interface_Tag (Etype (Actual), Iface_Typ);
3768                      pragma Assert (Present (Iface_Tag));
3769
3770                      Append_To (Plist,
3771                        Make_Reference (Loc,
3772                          Unchecked_Convert_To (Iface_Typ,
3773                            Make_Selected_Component (Loc,
3774                              Prefix =>
3775                                Relocate_Node (Actual),
3776                              Selector_Name =>
3777                                New_Reference_To (Iface_Tag, Loc)))));
3778                   else
3779                      --  Generate:
3780                      --    actual'reference
3781
3782                      Append_To (Plist,
3783                        Make_Reference (Loc, Relocate_Node (Actual)));
3784                   end if;
3785                end if;
3786
3787                Next_Actual (Actual);
3788                Next_Formal_With_Extras (Formal);
3789             end loop;
3790
3791             --  Now build the declaration of parameters initialized with the
3792             --  aggregate containing this constructed parameter list.
3793
3794             P := Make_Defining_Identifier (Loc, Name_uP);
3795
3796             Pdecl :=
3797               Make_Object_Declaration (Loc,
3798                 Defining_Identifier => P,
3799                 Object_Definition =>
3800                   New_Reference_To (Designated_Type (Ent_Acc), Loc),
3801                 Expression =>
3802                   Make_Aggregate (Loc, Expressions => Plist));
3803
3804             Parm3 :=
3805               Make_Attribute_Reference (Loc,
3806                 Prefix => New_Reference_To (P, Loc),
3807                 Attribute_Name => Name_Address);
3808
3809             Append (Pdecl, Decls);
3810          end if;
3811
3812          --  Now we can create the call, case of protected type
3813
3814          if Is_Protected_Type (Conctyp) then
3815             case Corresponding_Runtime_Package (Conctyp) is
3816                when System_Tasking_Protected_Objects_Entries =>
3817
3818                   --  Change the type of the index declaration
3819
3820                   Set_Object_Definition (Xdecl,
3821                     New_Reference_To (RTE (RE_Protected_Entry_Index), Loc));
3822
3823                   --  Some additional declarations for protected entry calls
3824
3825                   if No (Decls) then
3826                      Decls := New_List;
3827                   end if;
3828
3829                   --  Bnn : Communications_Block;
3830
3831                   Comm_Name := Make_Temporary (Loc, 'B');
3832
3833                   Append_To (Decls,
3834                     Make_Object_Declaration (Loc,
3835                       Defining_Identifier => Comm_Name,
3836                       Object_Definition   =>
3837                         New_Reference_To (RTE (RE_Communication_Block), Loc)));
3838
3839                   --  Some additional statements for protected entry calls
3840
3841                   --     Protected_Entry_Call (
3842                   --       Object => po._object'Access,
3843                   --       E => <entry index>;
3844                   --       Uninterpreted_Data => P'Address;
3845                   --       Mode => Simple_Call;
3846                   --       Block => Bnn);
3847
3848                   Call :=
3849                     Make_Procedure_Call_Statement (Loc,
3850                       Name =>
3851                         New_Reference_To (RTE (RE_Protected_Entry_Call), Loc),
3852
3853                       Parameter_Associations => New_List (
3854                         Make_Attribute_Reference (Loc,
3855                           Attribute_Name => Name_Unchecked_Access,
3856                           Prefix         => Parm1),
3857                         Parm2,
3858                         Parm3,
3859                         New_Reference_To (RTE (RE_Simple_Call), Loc),
3860                         New_Occurrence_Of (Comm_Name, Loc)));
3861
3862                when System_Tasking_Protected_Objects_Single_Entry =>
3863                   --     Protected_Single_Entry_Call (
3864                   --       Object => po._object'Access,
3865                   --       Uninterpreted_Data => P'Address;
3866                   --       Mode => Simple_Call);
3867
3868                   Call :=
3869                     Make_Procedure_Call_Statement (Loc,
3870                       Name => New_Reference_To (
3871                         RTE (RE_Protected_Single_Entry_Call), Loc),
3872
3873                       Parameter_Associations => New_List (
3874                         Make_Attribute_Reference (Loc,
3875                           Attribute_Name => Name_Unchecked_Access,
3876                           Prefix         => Parm1),
3877                         Parm3,
3878                         New_Reference_To (RTE (RE_Simple_Call), Loc)));
3879
3880                when others =>
3881                   raise Program_Error;
3882             end case;
3883
3884          --  Case of task type
3885
3886          else
3887             Call :=
3888               Make_Procedure_Call_Statement (Loc,
3889                 Name => New_Reference_To (RTE (RE_Call_Simple), Loc),
3890                 Parameter_Associations => New_List (Parm1, Parm2, Parm3));
3891
3892          end if;
3893
3894          Append_To (Stats, Call);
3895
3896          --  If there are out or in/out parameters by copy add assignment
3897          --  statements for the result values.
3898
3899          if Present (Parms) then
3900             Actual := First_Actual (N);
3901             Formal := First_Formal (Ent);
3902
3903             Set_Assignment_OK (Actual);
3904             while Present (Actual) loop
3905                if Is_By_Copy_Type (Etype (Actual))
3906                  and then Ekind (Formal) /= E_In_Parameter
3907                then
3908                   N_Node :=
3909                     Make_Assignment_Statement (Loc,
3910                       Name => New_Copy (Actual),
3911                       Expression =>
3912                         Make_Explicit_Dereference (Loc,
3913                           Make_Selected_Component (Loc,
3914                             Prefix => New_Reference_To (P, Loc),
3915                             Selector_Name =>
3916                               Make_Identifier (Loc, Chars (Formal)))));
3917
3918                   --  In all cases (including limited private types) we want
3919                   --  the assignment to be valid.
3920
3921                   Set_Assignment_OK (Name (N_Node));
3922
3923                   --  If the call is the triggering alternative in an
3924                   --  asynchronous select, or the entry_call alternative of a
3925                   --  conditional entry call, the assignments for in-out
3926                   --  parameters are incorporated into the statement list that
3927                   --  follows, so that there are executed only if the entry
3928                   --  call succeeds.
3929
3930                   if (Nkind (Parent (N)) = N_Triggering_Alternative
3931                        and then N = Triggering_Statement (Parent (N)))
3932                     or else
3933                      (Nkind (Parent (N)) = N_Entry_Call_Alternative
3934                        and then N = Entry_Call_Statement (Parent (N)))
3935                   then
3936                      if No (Statements (Parent (N))) then
3937                         Set_Statements (Parent (N), New_List);
3938                      end if;
3939
3940                      Prepend (N_Node, Statements (Parent (N)));
3941
3942                   else
3943                      Insert_After (Call, N_Node);
3944                   end if;
3945                end if;
3946
3947                Next_Actual (Actual);
3948                Next_Formal_With_Extras (Formal);
3949             end loop;
3950          end if;
3951
3952          --  Finally, create block and analyze it
3953
3954          Rewrite (N,
3955            Make_Block_Statement (Loc,
3956              Declarations => Decls,
3957              Handled_Statement_Sequence =>
3958                Make_Handled_Sequence_Of_Statements (Loc,
3959                  Statements => Stats)));
3960
3961          Analyze (N);
3962       end;
3963    end Build_Simple_Entry_Call;
3964
3965    --------------------------------
3966    -- Build_Task_Activation_Call --
3967    --------------------------------
3968
3969    procedure Build_Task_Activation_Call (N : Node_Id) is
3970       Loc   : constant Source_Ptr := Sloc (N);
3971       Chain : Entity_Id;
3972       Call  : Node_Id;
3973       Name  : Node_Id;
3974       P     : Node_Id;
3975
3976    begin
3977       --  Get the activation chain entity. Except in the case of a package
3978       --  body, this is in the node that was passed. For a package body, we
3979       --  have to find the corresponding package declaration node.
3980
3981       if Nkind (N) = N_Package_Body then
3982          P := Corresponding_Spec (N);
3983          loop
3984             P := Parent (P);
3985             exit when Nkind (P) = N_Package_Declaration;
3986          end loop;
3987
3988          Chain := Activation_Chain_Entity (P);
3989
3990       else
3991          Chain := Activation_Chain_Entity (N);
3992       end if;
3993
3994       if Present (Chain) then
3995          if Restricted_Profile then
3996             Name := New_Reference_To (RTE (RE_Activate_Restricted_Tasks), Loc);
3997          else
3998             Name := New_Reference_To (RTE (RE_Activate_Tasks), Loc);
3999          end if;
4000
4001          Call :=
4002            Make_Procedure_Call_Statement (Loc,
4003              Name => Name,
4004              Parameter_Associations =>
4005                New_List (Make_Attribute_Reference (Loc,
4006                  Prefix => New_Occurrence_Of (Chain, Loc),
4007                  Attribute_Name => Name_Unchecked_Access)));
4008
4009          if Nkind (N) = N_Package_Declaration then
4010             if Present (Corresponding_Body (N)) then
4011                null;
4012
4013             elsif Present (Private_Declarations (Specification (N))) then
4014                Append (Call, Private_Declarations (Specification (N)));
4015
4016             else
4017                Append (Call, Visible_Declarations (Specification (N)));
4018             end if;
4019
4020          else
4021             if Present (Handled_Statement_Sequence (N)) then
4022
4023                --  The call goes at the start of the statement sequence
4024                --  after the start of exception range label if one is present.
4025
4026                declare
4027                   Stm : Node_Id;
4028
4029                begin
4030                   Stm := First (Statements (Handled_Statement_Sequence (N)));
4031
4032                   --  A special case, skip exception range label if one is
4033                   --  present (from front end zcx processing).
4034
4035                   if Nkind (Stm) = N_Label and then Exception_Junk (Stm) then
4036                      Next (Stm);
4037                   end if;
4038
4039                   --  Another special case, if the first statement is a block
4040                   --  from optimization of a local raise to a goto, then the
4041                   --  call goes inside this block.
4042
4043                   if Nkind (Stm) = N_Block_Statement
4044                     and then Exception_Junk (Stm)
4045                   then
4046                      Stm :=
4047                        First (Statements (Handled_Statement_Sequence (Stm)));
4048                   end if;
4049
4050                   --  Insertion point is after any exception label pushes,
4051                   --  since we want it covered by any local handlers.
4052
4053                   while Nkind (Stm) in N_Push_xxx_Label loop
4054                      Next (Stm);
4055                   end loop;
4056
4057                   --  Now we have the proper insertion point
4058
4059                   Insert_Before (Stm, Call);
4060                end;
4061
4062             else
4063                Set_Handled_Statement_Sequence (N,
4064                   Make_Handled_Sequence_Of_Statements (Loc,
4065                      Statements => New_List (Call)));
4066             end if;
4067          end if;
4068
4069          Analyze (Call);
4070          Check_Task_Activation (N);
4071       end if;
4072    end Build_Task_Activation_Call;
4073
4074    -------------------------------
4075    -- Build_Task_Allocate_Block --
4076    -------------------------------
4077
4078    procedure Build_Task_Allocate_Block
4079      (Actions : List_Id;
4080       N       : Node_Id;
4081       Args    : List_Id)
4082    is
4083       T      : constant Entity_Id  := Entity (Expression (N));
4084       Init   : constant Entity_Id  := Base_Init_Proc (T);
4085       Loc    : constant Source_Ptr := Sloc (N);
4086       Chain  : constant Entity_Id  :=
4087                  Make_Defining_Identifier (Loc, Name_uChain);
4088       Blkent : constant Entity_Id  := Make_Temporary (Loc, 'A');
4089       Block  : Node_Id;
4090
4091    begin
4092       Block :=
4093         Make_Block_Statement (Loc,
4094           Identifier   => New_Reference_To (Blkent, Loc),
4095           Declarations => New_List (
4096
4097             --  _Chain  : Activation_Chain;
4098
4099             Make_Object_Declaration (Loc,
4100               Defining_Identifier => Chain,
4101               Aliased_Present => True,
4102               Object_Definition   =>
4103                 New_Reference_To (RTE (RE_Activation_Chain), Loc))),
4104
4105           Handled_Statement_Sequence =>
4106             Make_Handled_Sequence_Of_Statements (Loc,
4107
4108               Statements => New_List (
4109
4110                --  Init (Args);
4111
4112                 Make_Procedure_Call_Statement (Loc,
4113                   Name => New_Reference_To (Init, Loc),
4114                   Parameter_Associations => Args),
4115
4116                --  Activate_Tasks (_Chain);
4117
4118                 Make_Procedure_Call_Statement (Loc,
4119                   Name => New_Reference_To (RTE (RE_Activate_Tasks), Loc),
4120                   Parameter_Associations => New_List (
4121                     Make_Attribute_Reference (Loc,
4122                       Prefix => New_Reference_To (Chain, Loc),
4123                       Attribute_Name => Name_Unchecked_Access))))),
4124
4125           Has_Created_Identifier => True,
4126           Is_Task_Allocation_Block => True);
4127
4128       Append_To (Actions,
4129         Make_Implicit_Label_Declaration (Loc,
4130           Defining_Identifier => Blkent,
4131           Label_Construct     => Block));
4132
4133       Append_To (Actions, Block);
4134
4135       Set_Activation_Chain_Entity (Block, Chain);
4136    end Build_Task_Allocate_Block;
4137
4138    -----------------------------------------------
4139    -- Build_Task_Allocate_Block_With_Init_Stmts --
4140    -----------------------------------------------
4141
4142    procedure Build_Task_Allocate_Block_With_Init_Stmts
4143      (Actions    : List_Id;
4144       N          : Node_Id;
4145       Init_Stmts : List_Id)
4146    is
4147       Loc    : constant Source_Ptr := Sloc (N);
4148       Chain  : constant Entity_Id  :=
4149                  Make_Defining_Identifier (Loc, Name_uChain);
4150       Blkent : constant Entity_Id  := Make_Temporary (Loc, 'A');
4151       Block  : Node_Id;
4152
4153    begin
4154       Append_To (Init_Stmts,
4155         Make_Procedure_Call_Statement (Loc,
4156           Name => New_Reference_To (RTE (RE_Activate_Tasks), Loc),
4157           Parameter_Associations => New_List (
4158             Make_Attribute_Reference (Loc,
4159               Prefix => New_Reference_To (Chain, Loc),
4160               Attribute_Name => Name_Unchecked_Access))));
4161
4162       Block :=
4163         Make_Block_Statement (Loc,
4164           Identifier => New_Reference_To (Blkent, Loc),
4165           Declarations => New_List (
4166
4167             --  _Chain  : Activation_Chain;
4168
4169             Make_Object_Declaration (Loc,
4170               Defining_Identifier => Chain,
4171               Aliased_Present => True,
4172               Object_Definition   =>
4173                 New_Reference_To (RTE (RE_Activation_Chain), Loc))),
4174
4175           Handled_Statement_Sequence =>
4176             Make_Handled_Sequence_Of_Statements (Loc, Init_Stmts),
4177
4178           Has_Created_Identifier => True,
4179           Is_Task_Allocation_Block => True);
4180
4181       Append_To (Actions,
4182         Make_Implicit_Label_Declaration (Loc,
4183           Defining_Identifier => Blkent,
4184           Label_Construct     => Block));
4185
4186       Append_To (Actions, Block);
4187
4188       Set_Activation_Chain_Entity (Block, Chain);
4189    end Build_Task_Allocate_Block_With_Init_Stmts;
4190
4191    -----------------------------------
4192    -- Build_Task_Proc_Specification --
4193    -----------------------------------
4194
4195    function Build_Task_Proc_Specification (T : Entity_Id) return Node_Id is
4196       Loc     : constant Source_Ptr := Sloc (T);
4197       Spec_Id : Entity_Id;
4198
4199    begin
4200       --  Case of explicit task type, suffix TB
4201
4202       if Comes_From_Source (T) then
4203          Spec_Id :=
4204            Make_Defining_Identifier (Loc,
4205              Chars => New_External_Name (Chars (T), "TB"));
4206
4207       --  Case of anonymous task type, suffix B
4208
4209       else
4210          Spec_Id :=
4211            Make_Defining_Identifier (Loc,
4212              Chars => New_External_Name (Chars (T), 'B'));
4213       end if;
4214
4215       Set_Is_Internal (Spec_Id);
4216
4217       --  Associate the procedure with the task, if this is the declaration
4218       --  (and not the body) of the procedure.
4219
4220       if No (Task_Body_Procedure (T)) then
4221          Set_Task_Body_Procedure (T, Spec_Id);
4222       end if;
4223
4224       return
4225         Make_Procedure_Specification (Loc,
4226           Defining_Unit_Name       => Spec_Id,
4227           Parameter_Specifications => New_List (
4228             Make_Parameter_Specification (Loc,
4229               Defining_Identifier =>
4230                 Make_Defining_Identifier (Loc, Name_uTask),
4231               Parameter_Type      =>
4232                 Make_Access_Definition (Loc,
4233                   Subtype_Mark =>
4234                     New_Reference_To (Corresponding_Record_Type (T), Loc)))));
4235    end Build_Task_Proc_Specification;
4236
4237    ---------------------------------------
4238    -- Build_Unprotected_Subprogram_Body --
4239    ---------------------------------------
4240
4241    function Build_Unprotected_Subprogram_Body
4242      (N   : Node_Id;
4243       Pid : Node_Id) return Node_Id
4244    is
4245       Decls : constant List_Id := Declarations (N);
4246
4247    begin
4248       --  Add renamings for the Protection object, discriminals, privals and
4249       --  the entry index constant for use by debugger.
4250
4251       Debug_Private_Data_Declarations (Decls);
4252
4253       --  Make an unprotected version of the subprogram for use within the same
4254       --  object, with a new name and an additional parameter representing the
4255       --  object.
4256
4257       return
4258         Make_Subprogram_Body (Sloc (N),
4259           Specification              =>
4260             Build_Protected_Sub_Specification (N, Pid, Unprotected_Mode),
4261           Declarations               => Decls,
4262           Handled_Statement_Sequence => Handled_Statement_Sequence (N));
4263    end Build_Unprotected_Subprogram_Body;
4264
4265    ----------------------------
4266    -- Collect_Entry_Families --
4267    ----------------------------
4268
4269    procedure Collect_Entry_Families
4270      (Loc          : Source_Ptr;
4271       Cdecls       : List_Id;
4272       Current_Node : in out Node_Id;
4273       Conctyp      : Entity_Id)
4274    is
4275       Efam      : Entity_Id;
4276       Efam_Decl : Node_Id;
4277       Efam_Type : Entity_Id;
4278
4279    begin
4280       Efam := First_Entity (Conctyp);
4281       while Present (Efam) loop
4282          if Ekind (Efam) = E_Entry_Family then
4283             Efam_Type := Make_Temporary (Loc, 'F');
4284
4285             declare
4286                Bas : Entity_Id :=
4287                        Base_Type
4288                         (Etype (Discrete_Subtype_Definition (Parent (Efam))));
4289
4290                Bas_Decl : Node_Id := Empty;
4291                Lo, Hi   : Node_Id;
4292
4293             begin
4294                Get_Index_Bounds
4295                  (Discrete_Subtype_Definition (Parent (Efam)), Lo, Hi);
4296
4297                if Is_Potentially_Large_Family (Bas, Conctyp, Lo, Hi) then
4298                   Bas := Make_Temporary (Loc, 'B');
4299
4300                   Bas_Decl :=
4301                     Make_Subtype_Declaration (Loc,
4302                        Defining_Identifier => Bas,
4303                        Subtype_Indication  =>
4304                          Make_Subtype_Indication (Loc,
4305                            Subtype_Mark =>
4306                              New_Occurrence_Of (Standard_Integer, Loc),
4307                            Constraint   =>
4308                              Make_Range_Constraint (Loc,
4309                                Range_Expression => Make_Range (Loc,
4310                                  Make_Integer_Literal
4311                                    (Loc, -Entry_Family_Bound),
4312                                  Make_Integer_Literal
4313                                    (Loc, Entry_Family_Bound - 1)))));
4314
4315                   Insert_After (Current_Node, Bas_Decl);
4316                   Current_Node := Bas_Decl;
4317                   Analyze (Bas_Decl);
4318                end if;
4319
4320                Efam_Decl :=
4321                  Make_Full_Type_Declaration (Loc,
4322                    Defining_Identifier => Efam_Type,
4323                    Type_Definition =>
4324                      Make_Unconstrained_Array_Definition (Loc,
4325                        Subtype_Marks =>
4326                          (New_List (New_Occurrence_Of (Bas, Loc))),
4327
4328                     Component_Definition =>
4329                       Make_Component_Definition (Loc,
4330                         Aliased_Present    => False,
4331                         Subtype_Indication =>
4332                           New_Reference_To (Standard_Character, Loc))));
4333             end;
4334
4335             Insert_After (Current_Node, Efam_Decl);
4336             Current_Node := Efam_Decl;
4337             Analyze (Efam_Decl);
4338
4339             Append_To (Cdecls,
4340               Make_Component_Declaration (Loc,
4341                 Defining_Identifier =>
4342                   Make_Defining_Identifier (Loc, Chars (Efam)),
4343
4344                 Component_Definition =>
4345                   Make_Component_Definition (Loc,
4346                     Aliased_Present    => False,
4347                     Subtype_Indication =>
4348                       Make_Subtype_Indication (Loc,
4349                         Subtype_Mark =>
4350                           New_Occurrence_Of (Efam_Type, Loc),
4351
4352                         Constraint  =>
4353                           Make_Index_Or_Discriminant_Constraint (Loc,
4354                             Constraints => New_List (
4355                               New_Occurrence_Of
4356                                 (Etype (Discrete_Subtype_Definition
4357                                   (Parent (Efam))), Loc)))))));
4358
4359          end if;
4360
4361          Next_Entity (Efam);
4362       end loop;
4363    end Collect_Entry_Families;
4364
4365    -----------------------
4366    -- Concurrent_Object --
4367    -----------------------
4368
4369    function Concurrent_Object
4370      (Spec_Id  : Entity_Id;
4371       Conc_Typ : Entity_Id) return Entity_Id
4372    is
4373    begin
4374       --  Parameter _O or _object
4375
4376       if Is_Protected_Type (Conc_Typ) then
4377          return First_Formal (Protected_Body_Subprogram (Spec_Id));
4378
4379       --  Parameter _task
4380
4381       else
4382          pragma Assert (Is_Task_Type (Conc_Typ));
4383          return First_Formal (Task_Body_Procedure (Conc_Typ));
4384       end if;
4385    end Concurrent_Object;
4386
4387    ----------------------
4388    -- Copy_Result_Type --
4389    ----------------------
4390
4391    function Copy_Result_Type (Res : Node_Id) return Node_Id is
4392       New_Res  : constant Node_Id := New_Copy_Tree (Res);
4393       Par_Spec : Node_Id;
4394       Formal   : Entity_Id;
4395
4396    begin
4397       --  If the result type is an access_to_subprogram, we must create
4398       --  new entities for its spec.
4399
4400       if Nkind (New_Res) = N_Access_Definition
4401         and then Present (Access_To_Subprogram_Definition (New_Res))
4402       then
4403          --  Provide new entities for the formals
4404
4405          Par_Spec := First (Parameter_Specifications
4406                               (Access_To_Subprogram_Definition (New_Res)));
4407          while Present (Par_Spec) loop
4408             Formal := Defining_Identifier (Par_Spec);
4409             Set_Defining_Identifier (Par_Spec,
4410               Make_Defining_Identifier (Sloc (Formal), Chars (Formal)));
4411             Next (Par_Spec);
4412          end loop;
4413       end if;
4414
4415       return New_Res;
4416    end Copy_Result_Type;
4417
4418    --------------------
4419    -- Concurrent_Ref --
4420    --------------------
4421
4422    --  The expression returned for a reference to a concurrent object has the
4423    --  form:
4424
4425    --    taskV!(name)._Task_Id
4426
4427    --  for a task, and
4428
4429    --    objectV!(name)._Object
4430
4431    --  for a protected object. For the case of an access to a concurrent
4432    --  object, there is an extra explicit dereference:
4433
4434    --    taskV!(name.all)._Task_Id
4435    --    objectV!(name.all)._Object
4436
4437    --  here taskV and objectV are the types for the associated records, which
4438    --  contain the required _Task_Id and _Object fields for tasks and protected
4439    --  objects, respectively.
4440
4441    --  For the case of a task type name, the expression is
4442
4443    --    Self;
4444
4445    --  i.e. a call to the Self function which returns precisely this Task_Id
4446
4447    --  For the case of a protected type name, the expression is
4448
4449    --    objectR
4450
4451    --  which is a renaming of the _object field of the current object
4452    --  record, passed into protected operations as a parameter.
4453
4454    function Concurrent_Ref (N : Node_Id) return Node_Id is
4455       Loc  : constant Source_Ptr := Sloc (N);
4456       Ntyp : constant Entity_Id  := Etype (N);
4457       Dtyp : Entity_Id;
4458       Sel  : Name_Id;
4459
4460       function Is_Current_Task (T : Entity_Id) return Boolean;
4461       --  Check whether the reference is to the immediately enclosing task
4462       --  type, or to an outer one (rare but legal).
4463
4464       ---------------------
4465       -- Is_Current_Task --
4466       ---------------------
4467
4468       function Is_Current_Task (T : Entity_Id) return Boolean is
4469          Scop : Entity_Id;
4470
4471       begin
4472          Scop := Current_Scope;
4473          while Present (Scop)
4474            and then Scop /= Standard_Standard
4475          loop
4476
4477             if Scop = T then
4478                return True;
4479
4480             elsif Is_Task_Type (Scop) then
4481                return False;
4482
4483             --  If this is a procedure nested within the task type, we must
4484             --  assume that it can be called from an inner task, and therefore
4485             --  cannot treat it as a local reference.
4486
4487             elsif Is_Overloadable (Scop)
4488               and then In_Open_Scopes (T)
4489             then
4490                return False;
4491
4492             else
4493                Scop := Scope (Scop);
4494             end if;
4495          end loop;
4496
4497          --  We know that we are within the task body, so should have found it
4498          --  in scope.
4499
4500          raise Program_Error;
4501       end Is_Current_Task;
4502
4503    --  Start of processing for Concurrent_Ref
4504
4505    begin
4506       if Is_Access_Type (Ntyp) then
4507          Dtyp := Designated_Type (Ntyp);
4508
4509          if Is_Protected_Type (Dtyp) then
4510             Sel := Name_uObject;
4511          else
4512             Sel := Name_uTask_Id;
4513          end if;
4514
4515          return
4516            Make_Selected_Component (Loc,
4517              Prefix =>
4518                Unchecked_Convert_To (Corresponding_Record_Type (Dtyp),
4519                  Make_Explicit_Dereference (Loc, N)),
4520              Selector_Name => Make_Identifier (Loc, Sel));
4521
4522       elsif Is_Entity_Name (N)
4523         and then Is_Concurrent_Type (Entity (N))
4524       then
4525          if Is_Task_Type (Entity (N)) then
4526
4527             if Is_Current_Task (Entity (N)) then
4528                return
4529                  Make_Function_Call (Loc,
4530                    Name => New_Reference_To (RTE (RE_Self), Loc));
4531
4532             else
4533                declare
4534                   Decl   : Node_Id;
4535                   T_Self : constant Entity_Id := Make_Temporary (Loc, 'T');
4536                   T_Body : constant Node_Id :=
4537                              Parent (Corresponding_Body (Parent (Entity (N))));
4538
4539                begin
4540                   Decl :=
4541                     Make_Object_Declaration (Loc,
4542                       Defining_Identifier => T_Self,
4543                       Object_Definition   =>
4544                         New_Occurrence_Of (RTE (RO_ST_Task_Id), Loc),
4545                       Expression          =>
4546                         Make_Function_Call (Loc,
4547                           Name => New_Reference_To (RTE (RE_Self), Loc)));
4548                   Prepend (Decl, Declarations (T_Body));
4549                   Analyze (Decl);
4550                   Set_Scope (T_Self, Entity (N));
4551                   return New_Occurrence_Of (T_Self,  Loc);
4552                end;
4553             end if;
4554
4555          else
4556             pragma Assert (Is_Protected_Type (Entity (N)));
4557
4558             return
4559               New_Reference_To (Find_Protection_Object (Current_Scope), Loc);
4560          end if;
4561
4562       else
4563          if Is_Protected_Type (Ntyp) then
4564             Sel := Name_uObject;
4565
4566          elsif Is_Task_Type (Ntyp) then
4567             Sel := Name_uTask_Id;
4568
4569          else
4570             raise Program_Error;
4571          end if;
4572
4573          return
4574            Make_Selected_Component (Loc,
4575              Prefix =>
4576                Unchecked_Convert_To (Corresponding_Record_Type (Ntyp),
4577                  New_Copy_Tree (N)),
4578              Selector_Name => Make_Identifier (Loc, Sel));
4579       end if;
4580    end Concurrent_Ref;
4581
4582    ------------------------
4583    -- Convert_Concurrent --
4584    ------------------------
4585
4586    function Convert_Concurrent
4587      (N   : Node_Id;
4588       Typ : Entity_Id) return Node_Id
4589    is
4590    begin
4591       if not Is_Concurrent_Type (Typ) then
4592          return N;
4593       else
4594          return
4595            Unchecked_Convert_To
4596              (Corresponding_Record_Type (Typ), New_Copy_Tree (N));
4597       end if;
4598    end Convert_Concurrent;
4599
4600    -------------------------------------
4601    -- Debug_Private_Data_Declarations --
4602    -------------------------------------
4603
4604    procedure Debug_Private_Data_Declarations (Decls : List_Id) is
4605       Debug_Nod : Node_Id;
4606       Decl      : Node_Id;
4607
4608    begin
4609       Decl := First (Decls);
4610       while Present (Decl)
4611         and then not Comes_From_Source (Decl)
4612       loop
4613          --  Declaration for concurrent entity _object and its access type,
4614          --  along with the entry index subtype:
4615          --    type prot_typVP is access prot_typV;
4616          --    _object : prot_typVP := prot_typV (_O);
4617          --    subtype Jnn is <Type of Index> range Low .. High;
4618
4619          if Nkind_In (Decl, N_Full_Type_Declaration, N_Object_Declaration) then
4620             Set_Debug_Info_Needed (Defining_Identifier (Decl));
4621
4622          --  Declaration for the Protection object, discriminals, privals and
4623          --  entry index constant:
4624          --    conc_typR   : protection_typ renames _object._object;
4625          --    discr_nameD : discr_typ renames _object.discr_name;
4626          --    discr_nameD : discr_typ renames _task.discr_name;
4627          --    prival_name : comp_typ  renames _object.comp_name;
4628          --    J : constant Jnn :=
4629          --          Jnn'Val (_E - <Index expression> + Jnn'Pos (Jnn'First));
4630
4631          elsif Nkind (Decl) = N_Object_Renaming_Declaration then
4632             Set_Debug_Info_Needed (Defining_Identifier (Decl));
4633             Debug_Nod := Debug_Renaming_Declaration (Decl);
4634
4635             if Present (Debug_Nod) then
4636                Insert_After (Decl, Debug_Nod);
4637             end if;
4638          end if;
4639
4640          Next (Decl);
4641       end loop;
4642    end Debug_Private_Data_Declarations;
4643
4644    ----------------------------
4645    -- Entry_Index_Expression --
4646    ----------------------------
4647
4648    function Entry_Index_Expression
4649      (Sloc  : Source_Ptr;
4650       Ent   : Entity_Id;
4651       Index : Node_Id;
4652       Ttyp  : Entity_Id) return Node_Id
4653    is
4654       Expr : Node_Id;
4655       Num  : Node_Id;
4656       Lo   : Node_Id;
4657       Hi   : Node_Id;
4658       Prev : Entity_Id;
4659       S    : Node_Id;
4660
4661    begin
4662       --  The queues of entries and entry families appear in textual order in
4663       --  the associated record. The entry index is computed as the sum of the
4664       --  number of queues for all entries that precede the designated one, to
4665       --  which is added the index expression, if this expression denotes a
4666       --  member of a family.
4667
4668       --  The following is a place holder for the count of simple entries
4669
4670       Num := Make_Integer_Literal (Sloc, 1);
4671
4672       --  We construct an expression which is a series of addition operations.
4673       --  The first operand is the number of single entries that precede this
4674       --  one, the second operand is the index value relative to the start of
4675       --  the referenced family, and the remaining operands are the lengths of
4676       --  the entry families that precede this entry, i.e. the constructed
4677       --  expression is:
4678
4679       --    number_simple_entries +
4680       --      (s'pos (index-value) - s'pos (family'first)) + 1 +
4681       --      family'length + ...
4682
4683       --  where index-value is the given index value, and s is the index
4684       --  subtype (we have to use pos because the subtype might be an
4685       --  enumeration type preventing direct subtraction). Note that the task
4686       --  entry array is one-indexed.
4687
4688       --  The upper bound of the entry family may be a discriminant, so we
4689       --  retrieve the lower bound explicitly to compute offset, rather than
4690       --  using the index subtype which may mention a discriminant.
4691
4692       if Present (Index) then
4693          S := Etype (Discrete_Subtype_Definition (Declaration_Node (Ent)));
4694
4695          Expr :=
4696            Make_Op_Add (Sloc,
4697              Left_Opnd  => Num,
4698
4699              Right_Opnd =>
4700                Family_Offset (
4701                  Sloc,
4702                  Make_Attribute_Reference (Sloc,
4703                    Attribute_Name => Name_Pos,
4704                    Prefix => New_Reference_To (Base_Type (S), Sloc),
4705                    Expressions => New_List (Relocate_Node (Index))),
4706                  Type_Low_Bound (S),
4707                  Ttyp,
4708                  False));
4709       else
4710          Expr := Num;
4711       end if;
4712
4713       --  Now add lengths of preceding entries and entry families
4714
4715       Prev := First_Entity (Ttyp);
4716
4717       while Chars (Prev) /= Chars (Ent)
4718         or else (Ekind (Prev) /= Ekind (Ent))
4719         or else not Sem_Ch6.Type_Conformant (Ent, Prev)
4720       loop
4721          if Ekind (Prev) = E_Entry then
4722             Set_Intval (Num, Intval (Num) + 1);
4723
4724          elsif Ekind (Prev) = E_Entry_Family then
4725             S :=
4726               Etype (Discrete_Subtype_Definition (Declaration_Node (Prev)));
4727             Lo := Type_Low_Bound  (S);
4728             Hi := Type_High_Bound (S);
4729
4730             Expr :=
4731               Make_Op_Add (Sloc,
4732               Left_Opnd  => Expr,
4733               Right_Opnd => Family_Size (Sloc, Hi, Lo, Ttyp, False));
4734
4735          --  Other components are anonymous types to be ignored
4736
4737          else
4738             null;
4739          end if;
4740
4741          Next_Entity (Prev);
4742       end loop;
4743
4744       return Expr;
4745    end Entry_Index_Expression;
4746
4747    ---------------------------
4748    -- Establish_Task_Master --
4749    ---------------------------
4750
4751    procedure Establish_Task_Master (N : Node_Id) is
4752       Call : Node_Id;
4753    begin
4754       if Restriction_Active (No_Task_Hierarchy) = False then
4755          Call := Build_Runtime_Call (Sloc (N), RE_Enter_Master);
4756          Prepend_To (Declarations (N), Call);
4757          Analyze (Call);
4758       end if;
4759    end Establish_Task_Master;
4760
4761    --------------------------------
4762    -- Expand_Accept_Declarations --
4763    --------------------------------
4764
4765    --  Part of the expansion of an accept statement involves the creation of
4766    --  a declaration that can be referenced from the statement sequence of
4767    --  the accept:
4768
4769    --    Ann : Address;
4770
4771    --  This declaration is inserted immediately before the accept statement
4772    --  and it is important that it be inserted before the statements of the
4773    --  statement sequence are analyzed. Thus it would be too late to create
4774    --  this declaration in the Expand_N_Accept_Statement routine, which is
4775    --  why there is a separate procedure to be called directly from Sem_Ch9.
4776
4777    --  Ann is used to hold the address of the record containing the parameters
4778    --  (see Expand_N_Entry_Call for more details on how this record is built).
4779    --  References to the parameters do an unchecked conversion of this address
4780    --  to a pointer to the required record type, and then access the field that
4781    --  holds the value of the required parameter. The entity for the address
4782    --  variable is held as the top stack element (i.e. the last element) of the
4783    --  Accept_Address stack in the corresponding entry entity, and this element
4784    --  must be set in place  before the statements are processed.
4785
4786    --  The above description applies to the case of a stand alone accept
4787    --  statement, i.e. one not appearing as part of a select alternative.
4788
4789    --  For the case of an accept that appears as part of a select alternative
4790    --  of a selective accept, we must still create the declaration right away,
4791    --  since Ann is needed immediately, but there is an important difference:
4792
4793    --    The declaration is inserted before the selective accept, not before
4794    --    the accept statement (which is not part of a list anyway, and so would
4795    --    not accommodate inserted declarations)
4796
4797    --    We only need one address variable for the entire selective accept. So
4798    --    the Ann declaration is created only for the first accept alternative,
4799    --    and subsequent accept alternatives reference the same Ann variable.
4800
4801    --  We can distinguish the two cases by seeing whether the accept statement
4802    --  is part of a list. If not, then it must be in an accept alternative.
4803
4804    --  To expand the requeue statement, a label is provided at the end of the
4805    --  accept statement or alternative of which it is a part, so that the
4806    --  statement can be skipped after the requeue is complete. This label is
4807    --  created here rather than during the expansion of the accept statement,
4808    --  because it will be needed by any requeue statements within the accept,
4809    --  which are expanded before the accept.
4810
4811    procedure Expand_Accept_Declarations (N : Node_Id; Ent : Entity_Id) is
4812       Loc    : constant Source_Ptr := Sloc (N);
4813       Stats  : constant Node_Id    := Handled_Statement_Sequence (N);
4814       Ann    : Entity_Id           := Empty;
4815       Adecl  : Node_Id;
4816       Lab_Id : Node_Id;
4817       Lab    : Node_Id;
4818       Ldecl  : Node_Id;
4819       Ldecl2 : Node_Id;
4820
4821    begin
4822       if Expander_Active then
4823
4824          --  If we have no handled statement sequence, we may need to build
4825          --  a dummy sequence consisting of a null statement. This can be
4826          --  skipped if the trivial accept optimization is permitted.
4827
4828          if not Trivial_Accept_OK
4829            and then
4830              (No (Stats) or else Null_Statements (Statements (Stats)))
4831          then
4832             Set_Handled_Statement_Sequence (N,
4833               Make_Handled_Sequence_Of_Statements (Loc,
4834                 New_List (Make_Null_Statement (Loc))));
4835          end if;
4836
4837          --  Create and declare two labels to be placed at the end of the
4838          --  accept statement. The first label is used to allow requeues to
4839          --  skip the remainder of entry processing. The second label is used
4840          --  to skip the remainder of entry processing if the rendezvous
4841          --  completes in the middle of the accept body.
4842
4843          if Present (Handled_Statement_Sequence (N)) then
4844             declare
4845                Ent : Entity_Id;
4846
4847             begin
4848                Ent := Make_Temporary (Loc, 'L');
4849                Lab_Id := New_Reference_To (Ent, Loc);
4850                Lab := Make_Label (Loc, Lab_Id);
4851                Ldecl :=
4852                  Make_Implicit_Label_Declaration (Loc,
4853                    Defining_Identifier  => Ent,
4854                    Label_Construct      => Lab);
4855                Append (Lab, Statements (Handled_Statement_Sequence (N)));
4856
4857                Ent := Make_Temporary (Loc, 'L');
4858                Lab_Id := New_Reference_To (Ent, Loc);
4859                Lab := Make_Label (Loc, Lab_Id);
4860                Ldecl2 :=
4861                  Make_Implicit_Label_Declaration (Loc,
4862                    Defining_Identifier  => Ent,
4863                    Label_Construct      => Lab);
4864                Append (Lab, Statements (Handled_Statement_Sequence (N)));
4865             end;
4866
4867          else
4868             Ldecl := Empty;
4869             Ldecl2 := Empty;
4870          end if;
4871
4872          --  Case of stand alone accept statement
4873
4874          if Is_List_Member (N) then
4875
4876             if Present (Handled_Statement_Sequence (N)) then
4877                Ann := Make_Temporary (Loc, 'A');
4878
4879                Adecl :=
4880                  Make_Object_Declaration (Loc,
4881                    Defining_Identifier => Ann,
4882                    Object_Definition =>
4883                      New_Reference_To (RTE (RE_Address), Loc));
4884
4885                Insert_Before (N, Adecl);
4886                Analyze (Adecl);
4887
4888                Insert_Before (N, Ldecl);
4889                Analyze (Ldecl);
4890
4891                Insert_Before (N, Ldecl2);
4892                Analyze (Ldecl2);
4893             end if;
4894
4895          --  Case of accept statement which is in an accept alternative
4896
4897          else
4898             declare
4899                Acc_Alt : constant Node_Id := Parent (N);
4900                Sel_Acc : constant Node_Id := Parent (Acc_Alt);
4901                Alt     : Node_Id;
4902
4903             begin
4904                pragma Assert (Nkind (Acc_Alt) = N_Accept_Alternative);
4905                pragma Assert (Nkind (Sel_Acc) = N_Selective_Accept);
4906
4907                --  ??? Consider a single label for select statements
4908
4909                if Present (Handled_Statement_Sequence (N)) then
4910                   Prepend (Ldecl2,
4911                      Statements (Handled_Statement_Sequence (N)));
4912                   Analyze (Ldecl2);
4913
4914                   Prepend (Ldecl,
4915                      Statements (Handled_Statement_Sequence (N)));
4916                   Analyze (Ldecl);
4917                end if;
4918
4919                --  Find first accept alternative of the selective accept. A
4920                --  valid selective accept must have at least one accept in it.
4921
4922                Alt := First (Select_Alternatives (Sel_Acc));
4923
4924                while Nkind (Alt) /= N_Accept_Alternative loop
4925                   Next (Alt);
4926                end loop;
4927
4928                --  If we are the first accept statement, then we have to create
4929                --  the Ann variable, as for the stand alone case, except that
4930                --  it is inserted before the selective accept. Similarly, a
4931                --  label for requeue expansion must be declared.
4932
4933                if N = Accept_Statement (Alt) then
4934                   Ann := Make_Temporary (Loc, 'A');
4935                   Adecl :=
4936                     Make_Object_Declaration (Loc,
4937                       Defining_Identifier => Ann,
4938                       Object_Definition =>
4939                         New_Reference_To (RTE (RE_Address), Loc));
4940
4941                   Insert_Before (Sel_Acc, Adecl);
4942                   Analyze (Adecl);
4943
4944                --  If we are not the first accept statement, then find the Ann
4945                --  variable allocated by the first accept and use it.
4946
4947                else
4948                   Ann :=
4949                     Node (Last_Elmt (Accept_Address
4950                       (Entity (Entry_Direct_Name (Accept_Statement (Alt))))));
4951                end if;
4952             end;
4953          end if;
4954
4955          --  Merge here with Ann either created or referenced, and Adecl
4956          --  pointing to the corresponding declaration. Remaining processing
4957          --  is the same for the two cases.
4958
4959          if Present (Ann) then
4960             Append_Elmt (Ann, Accept_Address (Ent));
4961             Set_Debug_Info_Needed (Ann);
4962          end if;
4963
4964          --  Create renaming declarations for the entry formals. Each reference
4965          --  to a formal becomes a dereference of a component of the parameter
4966          --  block, whose address is held in Ann. These declarations are
4967          --  eventually inserted into the accept block, and analyzed there so
4968          --  that they have the proper scope for gdb and do not conflict with
4969          --  other declarations.
4970
4971          if Present (Parameter_Specifications (N))
4972            and then Present (Handled_Statement_Sequence (N))
4973          then
4974             declare
4975                Comp   : Entity_Id;
4976                Decl   : Node_Id;
4977                Formal : Entity_Id;
4978                New_F  : Entity_Id;
4979
4980             begin
4981                Push_Scope (Ent);
4982                Formal := First_Formal (Ent);
4983
4984                while Present (Formal) loop
4985                   Comp  := Entry_Component (Formal);
4986                   New_F :=
4987                     Make_Defining_Identifier (Loc, Chars (Formal));
4988
4989                   Set_Etype (New_F, Etype (Formal));
4990                   Set_Scope (New_F, Ent);
4991
4992                   --  Now we set debug info needed on New_F even though it does
4993                   --  not come from source, so that the debugger will get the
4994                   --  right information for these generated names.
4995
4996                   Set_Debug_Info_Needed (New_F);
4997
4998                   if Ekind (Formal) = E_In_Parameter then
4999                      Set_Ekind (New_F, E_Constant);
5000                   else
5001                      Set_Ekind (New_F, E_Variable);
5002                      Set_Extra_Constrained (New_F, Extra_Constrained (Formal));
5003                   end if;
5004
5005                   Set_Actual_Subtype (New_F, Actual_Subtype (Formal));
5006
5007                   Decl :=
5008                     Make_Object_Renaming_Declaration (Loc,
5009                       Defining_Identifier =>
5010                         New_F,
5011                       Subtype_Mark =>
5012                         New_Reference_To (Etype (Formal), Loc),
5013                       Name =>
5014                         Make_Explicit_Dereference (Loc,
5015                           Make_Selected_Component (Loc,
5016                             Prefix =>
5017                               Unchecked_Convert_To (
5018                                 Entry_Parameters_Type (Ent),
5019                                 New_Reference_To (Ann, Loc)),
5020                             Selector_Name =>
5021                               New_Reference_To (Comp, Loc))));
5022
5023                   if No (Declarations (N)) then
5024                      Set_Declarations (N, New_List);
5025                   end if;
5026
5027                   Append (Decl, Declarations (N));
5028                   Set_Renamed_Object (Formal, New_F);
5029                   Next_Formal (Formal);
5030                end loop;
5031
5032                End_Scope;
5033             end;
5034          end if;
5035       end if;
5036    end Expand_Accept_Declarations;
5037
5038    ---------------------------------------------
5039    -- Expand_Access_Protected_Subprogram_Type --
5040    ---------------------------------------------
5041
5042    procedure Expand_Access_Protected_Subprogram_Type (N : Node_Id) is
5043       Loc    : constant Source_Ptr := Sloc (N);
5044       Comps  : List_Id;
5045       T      : constant Entity_Id  := Defining_Identifier (N);
5046       D_T    : constant Entity_Id  := Designated_Type (T);
5047       D_T2   : constant Entity_Id  := Make_Temporary (Loc, 'D');
5048       E_T    : constant Entity_Id  := Make_Temporary (Loc, 'E');
5049       P_List : constant List_Id    := Build_Protected_Spec
5050                                         (N, RTE (RE_Address), D_T, False);
5051       Decl1  : Node_Id;
5052       Decl2  : Node_Id;
5053       Def1   : Node_Id;
5054
5055    begin
5056       --  Create access to subprogram with full signature
5057
5058       if Etype (D_T) /= Standard_Void_Type then
5059          Def1 :=
5060            Make_Access_Function_Definition (Loc,
5061              Parameter_Specifications => P_List,
5062              Result_Definition =>
5063                Copy_Result_Type (Result_Definition (Type_Definition (N))));
5064
5065       else
5066          Def1 :=
5067            Make_Access_Procedure_Definition (Loc,
5068              Parameter_Specifications => P_List);
5069       end if;
5070
5071       Decl1 :=
5072         Make_Full_Type_Declaration (Loc,
5073           Defining_Identifier => D_T2,
5074           Type_Definition => Def1);
5075
5076       Insert_After (N, Decl1);
5077       Analyze (Decl1);
5078
5079       --  Create Equivalent_Type, a record with two components for an access to
5080       --  object and an access to subprogram.
5081
5082       Comps := New_List (
5083         Make_Component_Declaration (Loc,
5084           Defining_Identifier => Make_Temporary (Loc, 'P'),
5085           Component_Definition =>
5086             Make_Component_Definition (Loc,
5087               Aliased_Present => False,
5088               Subtype_Indication =>
5089                 New_Occurrence_Of (RTE (RE_Address), Loc))),
5090
5091         Make_Component_Declaration (Loc,
5092           Defining_Identifier  => Make_Temporary (Loc, 'S'),
5093           Component_Definition =>
5094             Make_Component_Definition (Loc,
5095               Aliased_Present    => False,
5096               Subtype_Indication => New_Occurrence_Of (D_T2, Loc))));
5097
5098       Decl2 :=
5099         Make_Full_Type_Declaration (Loc,
5100           Defining_Identifier => E_T,
5101           Type_Definition =>
5102             Make_Record_Definition (Loc,
5103               Component_List =>
5104                 Make_Component_List (Loc,
5105                   Component_Items => Comps)));
5106
5107       Insert_After (Decl1, Decl2);
5108       Analyze (Decl2);
5109       Set_Equivalent_Type (T, E_T);
5110    end Expand_Access_Protected_Subprogram_Type;
5111
5112    --------------------------
5113    -- Expand_Entry_Barrier --
5114    --------------------------
5115
5116    procedure Expand_Entry_Barrier (N : Node_Id; Ent : Entity_Id) is
5117       Cond      : constant Node_Id   :=
5118                     Condition (Entry_Body_Formal_Part (N));
5119       Prot      : constant Entity_Id := Scope (Ent);
5120       Spec_Decl : constant Node_Id   := Parent (Prot);
5121       Func      : Node_Id;
5122       B_F       : Node_Id;
5123       Body_Decl : Node_Id;
5124
5125    begin
5126       if No_Run_Time_Mode then
5127          Error_Msg_CRT ("entry barrier", N);
5128          return;
5129       end if;
5130
5131       --  The body of the entry barrier must be analyzed in the context of the
5132       --  protected object, but its scope is external to it, just as any other
5133       --  unprotected version of a protected operation. The specification has
5134       --  been produced when the protected type declaration was elaborated. We
5135       --  build the body, insert it in the enclosing scope, but analyze it in
5136       --  the current context. A more uniform approach would be to treat the
5137       --  barrier just as a protected function, and discard the protected
5138       --  version of it because it is never called.
5139
5140       if Expander_Active then
5141          B_F := Build_Barrier_Function (N, Ent, Prot);
5142          Func := Barrier_Function (Ent);
5143          Set_Corresponding_Spec (B_F, Func);
5144
5145          Body_Decl := Parent (Corresponding_Body (Spec_Decl));
5146
5147          if Nkind (Parent (Body_Decl)) = N_Subunit then
5148             Body_Decl := Corresponding_Stub (Parent (Body_Decl));
5149          end if;
5150
5151          Insert_Before_And_Analyze (Body_Decl, B_F);
5152
5153          Set_Discriminals (Spec_Decl);
5154          Set_Scope (Func, Scope (Prot));
5155
5156       else
5157          Analyze_And_Resolve (Cond, Any_Boolean);
5158       end if;
5159
5160       --  The Ravenscar profile restricts barriers to simple variables declared
5161       --  within the protected object. We also allow Boolean constants, since
5162       --  these appear in several published examples and are also allowed by
5163       --  the Aonix compiler.
5164
5165       --  Note that after analysis variables in this context will be replaced
5166       --  by the corresponding prival, that is to say a renaming of a selected
5167       --  component of the form _Object.Var. If expansion is disabled, as
5168       --  within a generic, we check that the entity appears in the current
5169       --  scope.
5170
5171       if Is_Entity_Name (Cond) then
5172
5173          --  A small optimization of useless renamings. If the scope of the
5174          --  entity of the condition is not the barrier function, then the
5175          --  condition does not reference any of the generated renamings
5176          --  within the function.
5177
5178          if Expander_Active
5179            and then Scope (Entity (Cond)) /= Func
5180          then
5181             Set_Declarations (B_F, Empty_List);
5182          end if;
5183
5184          if Entity (Cond) = Standard_False
5185               or else
5186             Entity (Cond) = Standard_True
5187          then
5188             return;
5189
5190          elsif not Expander_Active
5191            and then Scope (Entity (Cond)) = Current_Scope
5192          then
5193             return;
5194
5195          --  Check for case of _object.all.field (note that the explicit
5196          --  dereference gets inserted by analyze/expand of _object.field)
5197
5198          elsif Present (Renamed_Object (Entity (Cond)))
5199            and then
5200              Nkind (Renamed_Object (Entity (Cond))) = N_Selected_Component
5201            and then
5202              Chars
5203                (Prefix
5204                  (Prefix (Renamed_Object (Entity (Cond))))) = Name_uObject
5205          then
5206             return;
5207          end if;
5208       end if;
5209
5210       --  It is not a boolean variable or literal, so check the restriction
5211
5212       Check_Restriction (Simple_Barriers, Cond);
5213    end Expand_Entry_Barrier;
5214
5215    ------------------------------
5216    -- Expand_N_Abort_Statement --
5217    ------------------------------
5218
5219    --  Expand abort T1, T2, .. Tn; into:
5220    --    Abort_Tasks (Task_List'(1 => T1.Task_Id, 2 => T2.Task_Id ...))
5221
5222    procedure Expand_N_Abort_Statement (N : Node_Id) is
5223       Loc    : constant Source_Ptr := Sloc (N);
5224       Tlist  : constant List_Id    := Names (N);
5225       Count  : Nat;
5226       Aggr   : Node_Id;
5227       Tasknm : Node_Id;
5228
5229    begin
5230       Aggr := Make_Aggregate (Loc, Component_Associations => New_List);
5231       Count := 0;
5232
5233       Tasknm := First (Tlist);
5234
5235       while Present (Tasknm) loop
5236          Count := Count + 1;
5237
5238          --  A task interface class-wide type object is being aborted.
5239          --  Retrieve its _task_id by calling a dispatching routine.
5240
5241          if Ada_Version >= Ada_2005
5242            and then Ekind (Etype (Tasknm)) = E_Class_Wide_Type
5243            and then Is_Interface (Etype (Tasknm))
5244            and then Is_Task_Interface (Etype (Tasknm))
5245          then
5246             Append_To (Component_Associations (Aggr),
5247               Make_Component_Association (Loc,
5248                 Choices => New_List (
5249                   Make_Integer_Literal (Loc, Count)),
5250                 Expression =>
5251
5252                   --  Task_Id (Tasknm._disp_get_task_id)
5253
5254                   Make_Unchecked_Type_Conversion (Loc,
5255                     Subtype_Mark =>
5256                       New_Reference_To (RTE (RO_ST_Task_Id), Loc),
5257                     Expression =>
5258                       Make_Selected_Component (Loc,
5259                         Prefix =>
5260                           New_Copy_Tree (Tasknm),
5261                         Selector_Name =>
5262                           Make_Identifier (Loc, Name_uDisp_Get_Task_Id)))));
5263
5264          else
5265             Append_To (Component_Associations (Aggr),
5266               Make_Component_Association (Loc,
5267                 Choices => New_List (
5268                   Make_Integer_Literal (Loc, Count)),
5269                 Expression => Concurrent_Ref (Tasknm)));
5270          end if;
5271
5272          Next (Tasknm);
5273       end loop;
5274
5275       Rewrite (N,
5276         Make_Procedure_Call_Statement (Loc,
5277           Name => New_Reference_To (RTE (RE_Abort_Tasks), Loc),
5278           Parameter_Associations => New_List (
5279             Make_Qualified_Expression (Loc,
5280               Subtype_Mark => New_Reference_To (RTE (RE_Task_List), Loc),
5281               Expression => Aggr))));
5282
5283       Analyze (N);
5284    end Expand_N_Abort_Statement;
5285
5286    -------------------------------
5287    -- Expand_N_Accept_Statement --
5288    -------------------------------
5289
5290    --  This procedure handles expansion of accept statements that stand
5291    --  alone, i.e. they are not part of an accept alternative. The expansion
5292    --  of accept statement in accept alternatives is handled by the routines
5293    --  Expand_N_Accept_Alternative and Expand_N_Selective_Accept. The
5294    --  following description applies only to stand alone accept statements.
5295
5296    --  If there is no handled statement sequence, or only null statements,
5297    --  then this is called a trivial accept, and the expansion is:
5298
5299    --    Accept_Trivial (entry-index)
5300
5301    --  If there is a handled statement sequence, then the expansion is:
5302
5303    --    Ann : Address;
5304    --    {Lnn : Label}
5305
5306    --    begin
5307    --       begin
5308    --          Accept_Call (entry-index, Ann);
5309    --          Renaming_Declarations for formals
5310    --          <statement sequence from N_Accept_Statement node>
5311    --          Complete_Rendezvous;
5312    --          <<Lnn>>
5313    --
5314    --       exception
5315    --          when ... =>
5316    --             <exception handler from N_Accept_Statement node>
5317    --             Complete_Rendezvous;
5318    --          when ... =>
5319    --             <exception handler from N_Accept_Statement node>
5320    --             Complete_Rendezvous;
5321    --          ...
5322    --       end;
5323
5324    --    exception
5325    --       when all others =>
5326    --          Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
5327    --    end;
5328
5329    --  The first three declarations were already inserted ahead of the accept
5330    --  statement by the Expand_Accept_Declarations procedure, which was called
5331    --  directly from the semantics during analysis of the accept statement,
5332    --  before analyzing its contained statements.
5333
5334    --  The declarations from the N_Accept_Statement, as noted in Sinfo, come
5335    --  from possible expansion activity (the original source of course does
5336    --  not have any declarations associated with the accept statement, since
5337    --  an accept statement has no declarative part). In particular, if the
5338    --  expander is active, the first such declaration is the declaration of
5339    --  the Accept_Params_Ptr entity (see Sem_Ch9.Analyze_Accept_Statement).
5340    --
5341    --  The two blocks are merged into a single block if the inner block has
5342    --  no exception handlers, but otherwise two blocks are required, since
5343    --  exceptions might be raised in the exception handlers of the inner
5344    --  block, and Exceptional_Complete_Rendezvous must be called.
5345
5346    procedure Expand_N_Accept_Statement (N : Node_Id) is
5347       Loc     : constant Source_Ptr := Sloc (N);
5348       Stats   : constant Node_Id    := Handled_Statement_Sequence (N);
5349       Ename   : constant Node_Id    := Entry_Direct_Name (N);
5350       Eindx   : constant Node_Id    := Entry_Index (N);
5351       Eent    : constant Entity_Id  := Entity (Ename);
5352       Acstack : constant Elist_Id   := Accept_Address (Eent);
5353       Ann     : constant Entity_Id  := Node (Last_Elmt (Acstack));
5354       Ttyp    : constant Entity_Id  := Etype (Scope (Eent));
5355       Blkent  : Entity_Id;
5356       Call    : Node_Id;
5357       Block   : Node_Id;
5358
5359    --  Start of processing for Expand_N_Accept_Statement
5360
5361    begin
5362       --  If accept statement is not part of a list, then its parent must be
5363       --  an accept alternative, and, as described above, we do not do any
5364       --  expansion for such accept statements at this level.
5365
5366       if not Is_List_Member (N) then
5367          pragma Assert (Nkind (Parent (N)) = N_Accept_Alternative);
5368          return;
5369
5370       --  Trivial accept case (no statement sequence, or null statements).
5371       --  If the accept statement has declarations, then just insert them
5372       --  before the procedure call.
5373
5374       elsif Trivial_Accept_OK
5375         and then (No (Stats) or else Null_Statements (Statements (Stats)))
5376       then
5377          --  Remove declarations for renamings, because the parameter block
5378          --  will not be assigned.
5379
5380          declare
5381             D      : Node_Id;
5382             Next_D : Node_Id;
5383
5384          begin
5385             D := First (Declarations (N));
5386
5387             while Present (D) loop
5388                Next_D := Next (D);
5389                if Nkind (D) = N_Object_Renaming_Declaration then
5390                   Remove (D);
5391                end if;
5392
5393                D := Next_D;
5394             end loop;
5395          end;
5396
5397          if Present (Declarations (N)) then
5398             Insert_Actions (N, Declarations (N));
5399          end if;
5400
5401          Rewrite (N,
5402            Make_Procedure_Call_Statement (Loc,
5403              Name => New_Reference_To (RTE (RE_Accept_Trivial), Loc),
5404              Parameter_Associations => New_List (
5405                Entry_Index_Expression (Loc, Entity (Ename), Eindx, Ttyp))));
5406
5407          Analyze (N);
5408
5409          --  Discard Entry_Address that was created for it, so it will not be
5410          --  emitted if this accept statement is in the statement part of a
5411          --  delay alternative.
5412
5413          if Present (Stats) then
5414             Remove_Last_Elmt (Acstack);
5415          end if;
5416
5417       --  Case of statement sequence present
5418
5419       else
5420          --  Construct the block, using the declarations from the accept
5421          --  statement if any to initialize the declarations of the block.
5422
5423          Blkent := Make_Temporary (Loc, 'A');
5424          Set_Ekind (Blkent, E_Block);
5425          Set_Etype (Blkent, Standard_Void_Type);
5426          Set_Scope (Blkent, Current_Scope);
5427
5428          Block :=
5429            Make_Block_Statement (Loc,
5430              Identifier                 => New_Reference_To (Blkent, Loc),
5431              Declarations               => Declarations (N),
5432              Handled_Statement_Sequence => Build_Accept_Body (N));
5433
5434          --  For the analysis of the generated declarations, the parent node
5435          --  must be properly set.
5436
5437          Set_Parent (Block, Parent (N));
5438
5439          --  Prepend call to Accept_Call to main statement sequence If the
5440          --  accept has exception handlers, the statement sequence is wrapped
5441          --  in a block. Insert call and renaming declarations in the
5442          --  declarations of the block, so they are elaborated before the
5443          --  handlers.
5444
5445          Call :=
5446            Make_Procedure_Call_Statement (Loc,
5447              Name => New_Reference_To (RTE (RE_Accept_Call), Loc),
5448              Parameter_Associations => New_List (
5449                Entry_Index_Expression (Loc, Entity (Ename), Eindx, Ttyp),
5450                New_Reference_To (Ann, Loc)));
5451
5452          if Parent (Stats) = N then
5453             Prepend (Call, Statements (Stats));
5454          else
5455             Set_Declarations
5456               (Parent (Stats),
5457                 New_List (Call));
5458          end if;
5459
5460          Analyze (Call);
5461
5462          Push_Scope (Blkent);
5463
5464          declare
5465             D      : Node_Id;
5466             Next_D : Node_Id;
5467             Typ    : Entity_Id;
5468
5469          begin
5470             D := First (Declarations (N));
5471             while Present (D) loop
5472                Next_D := Next (D);
5473
5474                if Nkind (D) = N_Object_Renaming_Declaration then
5475
5476                   --  The renaming declarations for the formals were created
5477                   --  during analysis of the accept statement, and attached to
5478                   --  the list of declarations. Place them now in the context
5479                   --  of the accept block or subprogram.
5480
5481                   Remove (D);
5482                   Typ := Entity (Subtype_Mark (D));
5483                   Insert_After (Call, D);
5484                   Analyze (D);
5485
5486                   --  If the formal is class_wide, it does not have an actual
5487                   --  subtype. The analysis of the renaming declaration creates
5488                   --  one, but we need to retain the class-wide nature of the
5489                   --  entity.
5490
5491                   if Is_Class_Wide_Type (Typ) then
5492                      Set_Etype (Defining_Identifier (D), Typ);
5493                   end if;
5494
5495                end if;
5496
5497                D := Next_D;
5498             end loop;
5499          end;
5500
5501          End_Scope;
5502
5503          --  Replace the accept statement by the new block
5504
5505          Rewrite (N, Block);
5506          Analyze (N);
5507
5508          --  Last step is to unstack the Accept_Address value
5509
5510          Remove_Last_Elmt (Acstack);
5511       end if;
5512    end Expand_N_Accept_Statement;
5513
5514    ----------------------------------
5515    -- Expand_N_Asynchronous_Select --
5516    ----------------------------------
5517
5518    --  This procedure assumes that the trigger statement is an entry call or
5519    --  a dispatching procedure call. A delay alternative should already have
5520    --  been expanded into an entry call to the appropriate delay object Wait
5521    --  entry.
5522
5523    --  If the trigger is a task entry call, the select is implemented with
5524    --  a Task_Entry_Call:
5525
5526    --    declare
5527    --       B : Boolean;
5528    --       C : Boolean;
5529    --       P : parms := (parm, parm, parm);
5530
5531    --        --  Clean is added by Exp_Ch7.Expand_Cleanup_Actions
5532
5533    --       procedure _clean is
5534    --       begin
5535    --          ...
5536    --          Cancel_Task_Entry_Call (C);
5537    --          ...
5538    --       end _clean;
5539
5540    --    begin
5541    --       Abort_Defer;
5542    --       Task_Entry_Call
5543    --         (<acceptor-task>,    --  Acceptor
5544    --          <entry-index>,      --  E
5545    --          P'Address,          --  Uninterpreted_Data
5546    --          Asynchronous_Call,  --  Mode
5547    --          B);                 --  Rendezvous_Successful
5548
5549    --       begin
5550    --          begin
5551    --             Abort_Undefer;
5552    --             <abortable-part>
5553    --          at end
5554    --             _clean;  --  Added by Exp_Ch7.Expand_Cleanup_Actions
5555    --          end;
5556    --       exception
5557    --          when Abort_Signal => Abort_Undefer;
5558    --       end;
5559
5560    --       parm := P.param;
5561    --       parm := P.param;
5562    --       ...
5563    --       if not C then
5564    --          <triggered-statements>
5565    --       end if;
5566    --    end;
5567
5568    --  Note that Build_Simple_Entry_Call is used to expand the entry of the
5569    --  asynchronous entry call (by Expand_N_Entry_Call_Statement procedure)
5570    --  as follows:
5571
5572    --    declare
5573    --       P : parms := (parm, parm, parm);
5574    --    begin
5575    --       Call_Simple (acceptor-task, entry-index, P'Address);
5576    --       parm := P.param;
5577    --       parm := P.param;
5578    --       ...
5579    --    end;
5580
5581    --  so the task at hand is to convert the latter expansion into the former
5582
5583    --  If the trigger is a protected entry call, the select is implemented
5584    --  with Protected_Entry_Call:
5585
5586    --  declare
5587    --     P   : E1_Params := (param, param, param);
5588    --     Bnn : Communications_Block;
5589
5590    --  begin
5591    --     declare
5592
5593    --        --  Clean is added by Exp_Ch7.Expand_Cleanup_Actions
5594
5595    --        procedure _clean is
5596    --        begin
5597    --           ...
5598    --           if Enqueued (Bnn) then
5599    --              Cancel_Protected_Entry_Call (Bnn);
5600    --           end if;
5601    --           ...
5602    --        end _clean;
5603
5604    --     begin
5605    --        begin
5606    --           Protected_Entry_Call
5607    --             (po._object'Access,  --  Object
5608    --              <entry index>,      --  E
5609    --              P'Address,          --  Uninterpreted_Data
5610    --              Asynchronous_Call,  --  Mode
5611    --              Bnn);               --  Block
5612
5613    --           if Enqueued (Bnn) then
5614    --              <abortable-part>
5615    --           end if;
5616    --        at end
5617    --           _clean;  --  Added by Exp_Ch7.Expand_Cleanup_Actions
5618    --        end;
5619    --     exception
5620    --        when Abort_Signal => Abort_Undefer;
5621    --     end;
5622
5623    --     if not Cancelled (Bnn) then
5624    --        <triggered-statements>
5625    --     end if;
5626    --  end;
5627
5628    --  Build_Simple_Entry_Call is used to expand the all to a simple protected
5629    --  entry call:
5630
5631    --  declare
5632    --     P   : E1_Params := (param, param, param);
5633    --     Bnn : Communications_Block;
5634
5635    --  begin
5636    --     Protected_Entry_Call
5637    --       (po._object'Access,  --  Object
5638    --        <entry index>,      --  E
5639    --        P'Address,          --  Uninterpreted_Data
5640    --        Simple_Call,        --  Mode
5641    --        Bnn);               --  Block
5642    --     parm := P.param;
5643    --     parm := P.param;
5644    --       ...
5645    --  end;
5646
5647    --  Ada 2005 (AI-345): If the trigger is a dispatching call, the select is
5648    --  expanded into:
5649
5650    --    declare
5651    --       B   : Boolean := False;
5652    --       Bnn : Communication_Block;
5653    --       C   : Ada.Tags.Prim_Op_Kind;
5654    --       D   : System.Storage_Elements.Dummy_Communication_Block;
5655    --       K   : Ada.Tags.Tagged_Kind :=
5656    --               Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
5657    --       P   : Parameters := (Param1 .. ParamN);
5658    --       S   : Integer;
5659    --       U   : Boolean;
5660
5661    --    begin
5662    --       if K = Ada.Tags.TK_Limited_Tagged then
5663    --          <dispatching-call>;
5664    --          <triggering-statements>;
5665
5666    --       else
5667    --          S :=
5668    --            Ada.Tags.Get_Offset_Index
5669    --              (Ada.Tags.Tag (<object>), DT_Position (<dispatching-call>));
5670
5671    --          _Disp_Get_Prim_Op_Kind (<object>, S, C);
5672
5673    --          if C = POK_Protected_Entry then
5674    --             declare
5675    --                procedure _clean is
5676    --                begin
5677    --                   if Enqueued (Bnn) then
5678    --                      Cancel_Protected_Entry_Call (Bnn);
5679    --                   end if;
5680    --                end _clean;
5681
5682    --             begin
5683    --                begin
5684    --                   _Disp_Asynchronous_Select
5685    --                     (<object>, S, P'Address, D, B);
5686    --                   Bnn := Communication_Block (D);
5687
5688    --                   Param1 := P.Param1;
5689    --                   ...
5690    --                   ParamN := P.ParamN;
5691
5692    --                   if Enqueued (Bnn) then
5693    --                      <abortable-statements>
5694    --                   end if;
5695    --                at end
5696    --                   _clean;  --  Added by Exp_Ch7.Expand_Cleanup_Actions
5697    --                end;
5698    --             exception
5699    --                when Abort_Signal => Abort_Undefer;
5700    --             end;
5701
5702    --             if not Cancelled (Bnn) then
5703    --                <triggering-statements>
5704    --             end if;
5705
5706    --          elsif C = POK_Task_Entry then
5707    --             declare
5708    --                procedure _clean is
5709    --                begin
5710    --                   Cancel_Task_Entry_Call (U);
5711    --                end _clean;
5712
5713    --             begin
5714    --                Abort_Defer;
5715
5716    --                _Disp_Asynchronous_Select
5717    --                  (<object>, S, P'Address, D, B);
5718    --                Bnn := Communication_Bloc (D);
5719
5720    --                Param1 := P.Param1;
5721    --                ...
5722    --                ParamN := P.ParamN;
5723
5724    --                begin
5725    --                   begin
5726    --                      Abort_Undefer;
5727    --                      <abortable-statements>
5728    --                   at end
5729    --                      _clean;  --  Added by Exp_Ch7.Expand_Cleanup_Actions
5730    --                   end;
5731    --                exception
5732    --                   when Abort_Signal => Abort_Undefer;
5733    --                end;
5734
5735    --                if not U then
5736    --                   <triggering-statements>
5737    --                end if;
5738    --             end;
5739
5740    --          else
5741    --             <dispatching-call>;
5742    --             <triggering-statements>
5743    --          end if;
5744    --       end if;
5745    --    end;
5746
5747    --  The job is to convert this to the asynchronous form
5748
5749    --  If the trigger is a delay statement, it will have been expanded into a
5750    --  call to one of the GNARL delay procedures. This routine will convert
5751    --  this into a protected entry call on a delay object and then continue
5752    --  processing as for a protected entry call trigger. This requires
5753    --  declaring a Delay_Block object and adding a pointer to this object to
5754    --  the parameter list of the delay procedure to form the parameter list of
5755    --  the entry call. This object is used by the runtime to queue the delay
5756    --  request.
5757
5758    --  For a description of the use of P and the assignments after the call,
5759    --  see Expand_N_Entry_Call_Statement.
5760
5761    procedure Expand_N_Asynchronous_Select (N : Node_Id) is
5762       Loc    : constant Source_Ptr := Sloc (N);
5763       Abrt   : constant Node_Id    := Abortable_Part (N);
5764       Astats : constant List_Id    := Statements (Abrt);
5765       Trig   : constant Node_Id    := Triggering_Alternative (N);
5766       Tstats : constant List_Id    := Statements (Trig);
5767
5768       Abort_Block_Ent   : Entity_Id;
5769       Abortable_Block   : Node_Id;
5770       Actuals           : List_Id;
5771       Blk_Ent           : Entity_Id;
5772       Blk_Typ           : Entity_Id;
5773       Call              : Node_Id;
5774       Call_Ent          : Entity_Id;
5775       Cancel_Param      : Entity_Id;
5776       Cleanup_Block     : Node_Id;
5777       Cleanup_Block_Ent : Entity_Id;
5778       Cleanup_Stmts     : List_Id;
5779       Conc_Typ_Stmts    : List_Id;
5780       Concval           : Node_Id;
5781       Dblock_Ent        : Entity_Id;
5782       Decl              : Node_Id;
5783       Decls             : List_Id;
5784       Ecall             : Node_Id;
5785       Ename             : Node_Id;
5786       Enqueue_Call      : Node_Id;
5787       Formals           : List_Id;
5788       Hdle              : List_Id;
5789       Index             : Node_Id;
5790       Lim_Typ_Stmts     : List_Id;
5791       N_Orig            : Node_Id;
5792       Obj               : Entity_Id;
5793       Param             : Node_Id;
5794       Params            : List_Id;
5795       Pdef              : Entity_Id;
5796       ProtE_Stmts       : List_Id;
5797       ProtP_Stmts       : List_Id;
5798       Stmt              : Node_Id;
5799       Stmts             : List_Id;
5800       Target_Undefer    : RE_Id;
5801       TaskE_Stmts       : List_Id;
5802       Undefer_Args      : List_Id := No_List;
5803
5804       B   : Entity_Id;  --  Call status flag
5805       Bnn : Entity_Id;  --  Communication block
5806       C   : Entity_Id;  --  Call kind
5807       K   : Entity_Id;  --  Tagged kind
5808       P   : Entity_Id;  --  Parameter block
5809       S   : Entity_Id;  --  Primitive operation slot
5810       T   : Entity_Id;  --  Additional status flag
5811
5812    begin
5813       Blk_Ent := Make_Temporary (Loc, 'A');
5814       Ecall   := Triggering_Statement (Trig);
5815
5816       --  The arguments in the call may require dynamic allocation, and the
5817       --  call statement may have been transformed into a block. The block
5818       --  may contain additional declarations for internal entities, and the
5819       --  original call is found by sequential search.
5820
5821       if Nkind (Ecall) = N_Block_Statement then
5822          Ecall := First (Statements (Handled_Statement_Sequence (Ecall)));
5823          while not Nkind_In (Ecall, N_Procedure_Call_Statement,
5824                                     N_Entry_Call_Statement)
5825          loop
5826             Next (Ecall);
5827          end loop;
5828       end if;
5829
5830       --  This is either a dispatching call or a delay statement used as a
5831       --  trigger which was expanded into a procedure call.
5832
5833       if Nkind (Ecall) = N_Procedure_Call_Statement then
5834          if Ada_Version >= Ada_2005
5835            and then
5836              (No (Original_Node (Ecall))
5837                 or else not Nkind_In (Original_Node (Ecall),
5838                                         N_Delay_Relative_Statement,
5839                                         N_Delay_Until_Statement))
5840          then
5841             Extract_Dispatching_Call (Ecall, Call_Ent, Obj, Actuals, Formals);
5842
5843             Decls := New_List;
5844             Stmts := New_List;
5845
5846             --  Call status flag processing, generate:
5847             --    B : Boolean := False;
5848
5849             B := Build_B (Loc, Decls);
5850
5851             --  Communication block processing, generate:
5852             --    Bnn : Communication_Block;
5853
5854             Bnn := Make_Temporary (Loc, 'B');
5855             Append_To (Decls,
5856               Make_Object_Declaration (Loc,
5857                 Defining_Identifier => Bnn,
5858                 Object_Definition   =>
5859                   New_Reference_To (RTE (RE_Communication_Block), Loc)));
5860
5861             --  Call kind processing, generate:
5862             --    C : Ada.Tags.Prim_Op_Kind;
5863
5864             C := Build_C (Loc, Decls);
5865
5866             --  Tagged kind processing, generate:
5867             --    K : Ada.Tags.Tagged_Kind :=
5868             --          Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
5869
5870             --  Dummy communication block, generate:
5871             --    D : Dummy_Communication_Block;
5872
5873             Append_To (Decls,
5874               Make_Object_Declaration (Loc,
5875                 Defining_Identifier =>
5876                   Make_Defining_Identifier (Loc, Name_uD),
5877                 Object_Definition =>
5878                   New_Reference_To (
5879                     RTE (RE_Dummy_Communication_Block), Loc)));
5880
5881             K := Build_K (Loc, Decls, Obj);
5882
5883             --  Parameter block processing
5884
5885             Blk_Typ := Build_Parameter_Block
5886                          (Loc, Actuals, Formals, Decls);
5887             P       := Parameter_Block_Pack
5888                          (Loc, Blk_Typ, Actuals, Formals, Decls, Stmts);
5889
5890             --  Dispatch table slot processing, generate:
5891             --    S : Integer;
5892
5893             S := Build_S (Loc, Decls);
5894
5895             --  Additional status flag processing, generate:
5896             --    Tnn : Boolean;
5897
5898             T := Make_Temporary (Loc, 'T');
5899             Append_To (Decls,
5900               Make_Object_Declaration (Loc,
5901                 Defining_Identifier => T,
5902                 Object_Definition   =>
5903                   New_Reference_To (Standard_Boolean, Loc)));
5904
5905             ------------------------------
5906             -- Protected entry handling --
5907             ------------------------------
5908
5909             --  Generate:
5910             --    Param1 := P.Param1;
5911             --    ...
5912             --    ParamN := P.ParamN;
5913
5914             Cleanup_Stmts := Parameter_Block_Unpack (Loc, P, Actuals, Formals);
5915
5916             --  Generate:
5917             --    Bnn := Communication_Block (D);
5918
5919             Prepend_To (Cleanup_Stmts,
5920               Make_Assignment_Statement (Loc,
5921                 Name =>
5922                   New_Reference_To (Bnn, Loc),
5923                 Expression =>
5924                   Make_Unchecked_Type_Conversion (Loc,
5925                     Subtype_Mark =>
5926                       New_Reference_To (RTE (RE_Communication_Block), Loc),
5927                     Expression =>
5928                       Make_Identifier (Loc, Name_uD))));
5929
5930             --  Generate:
5931             --    _Disp_Asynchronous_Select (<object>, S, P'Address, D, B);
5932
5933             Prepend_To (Cleanup_Stmts,
5934               Make_Procedure_Call_Statement (Loc,
5935                 Name =>
5936                   New_Reference_To (
5937                     Find_Prim_Op (Etype (Etype (Obj)),
5938                       Name_uDisp_Asynchronous_Select),
5939                     Loc),
5940                 Parameter_Associations =>
5941                   New_List (
5942                     New_Copy_Tree (Obj),             --  <object>
5943                     New_Reference_To (S, Loc),       --  S
5944                     Make_Attribute_Reference (Loc,   --  P'Address
5945                       Prefix =>
5946                         New_Reference_To (P, Loc),
5947                       Attribute_Name =>
5948                         Name_Address),
5949                     Make_Identifier (Loc, Name_uD),  --  D
5950                     New_Reference_To (B, Loc))));    --  B
5951
5952             --  Generate:
5953             --    if Enqueued (Bnn) then
5954             --       <abortable-statements>
5955             --    end if;
5956
5957             Append_To (Cleanup_Stmts,
5958               Make_If_Statement (Loc,
5959                 Condition =>
5960                   Make_Function_Call (Loc,
5961                     Name =>
5962                       New_Reference_To (RTE (RE_Enqueued), Loc),
5963                     Parameter_Associations =>
5964                       New_List (
5965                         New_Reference_To (Bnn, Loc))),
5966
5967                 Then_Statements =>
5968                   New_Copy_List_Tree (Astats)));
5969
5970             --  Wrap the statements in a block. Exp_Ch7.Expand_Cleanup_Actions
5971             --  will then generate a _clean for the communication block Bnn.
5972
5973             --  Generate:
5974             --    declare
5975             --       procedure _clean is
5976             --       begin
5977             --          if Enqueued (Bnn) then
5978             --             Cancel_Protected_Entry_Call (Bnn);
5979             --          end if;
5980             --       end _clean;
5981             --    begin
5982             --       Cleanup_Stmts
5983             --    at end
5984             --       _clean;
5985             --    end;
5986
5987             Cleanup_Block_Ent := Make_Temporary (Loc, 'C');
5988             Cleanup_Block :=
5989               Build_Cleanup_Block (Loc, Cleanup_Block_Ent, Cleanup_Stmts, Bnn);
5990
5991             --  Wrap the cleanup block in an exception handling block
5992
5993             --  Generate:
5994             --    begin
5995             --       Cleanup_Block
5996             --    exception
5997             --       when Abort_Signal => Abort_Undefer;
5998             --    end;
5999
6000             Abort_Block_Ent := Make_Temporary (Loc, 'A');
6001             ProtE_Stmts :=
6002               New_List (
6003                 Make_Implicit_Label_Declaration (Loc,
6004                   Defining_Identifier =>
6005                     Abort_Block_Ent),
6006
6007                 Build_Abort_Block
6008                   (Loc, Abort_Block_Ent, Cleanup_Block_Ent, Cleanup_Block));
6009
6010             --  Generate:
6011             --    if not Cancelled (Bnn) then
6012             --       <triggering-statements>
6013             --    end if;
6014
6015             Append_To (ProtE_Stmts,
6016               Make_If_Statement (Loc,
6017                 Condition =>
6018                   Make_Op_Not (Loc,
6019                     Right_Opnd =>
6020                       Make_Function_Call (Loc,
6021                         Name =>
6022                           New_Reference_To (RTE (RE_Cancelled), Loc),
6023                         Parameter_Associations =>
6024                           New_List (
6025                             New_Reference_To (Bnn, Loc)))),
6026
6027                 Then_Statements =>
6028                   New_Copy_List_Tree (Tstats)));
6029
6030             -------------------------
6031             -- Task entry handling --
6032             -------------------------
6033
6034             --  Generate:
6035             --    Param1 := P.Param1;
6036             --    ...
6037             --    ParamN := P.ParamN;
6038
6039             TaskE_Stmts := Parameter_Block_Unpack (Loc, P, Actuals, Formals);
6040
6041             --  Generate:
6042             --    Bnn := Communication_Block (D);
6043
6044             Append_To (TaskE_Stmts,
6045               Make_Assignment_Statement (Loc,
6046                 Name =>
6047                   New_Reference_To (Bnn, Loc),
6048                 Expression =>
6049                   Make_Unchecked_Type_Conversion (Loc,
6050                     Subtype_Mark =>
6051                       New_Reference_To (RTE (RE_Communication_Block), Loc),
6052                     Expression =>
6053                       Make_Identifier (Loc, Name_uD))));
6054
6055             --  Generate:
6056             --    _Disp_Asynchronous_Select (<object>, S, P'Address, D, B);
6057
6058             Prepend_To (TaskE_Stmts,
6059               Make_Procedure_Call_Statement (Loc,
6060                 Name =>
6061                   New_Reference_To (
6062                     Find_Prim_Op (Etype (Etype (Obj)),
6063                       Name_uDisp_Asynchronous_Select),
6064                     Loc),
6065                 Parameter_Associations =>
6066                   New_List (
6067                     New_Copy_Tree (Obj),             --  <object>
6068                     New_Reference_To (S, Loc),       --  S
6069                     Make_Attribute_Reference (Loc,   --  P'Address
6070                       Prefix =>
6071                         New_Reference_To (P, Loc),
6072                       Attribute_Name =>
6073                         Name_Address),
6074                     Make_Identifier (Loc, Name_uD),  --  D
6075                     New_Reference_To (B, Loc))));    --  B
6076
6077             --  Generate:
6078             --    Abort_Defer;
6079
6080             Prepend_To (TaskE_Stmts,
6081               Make_Procedure_Call_Statement (Loc,
6082                 Name =>
6083                   New_Reference_To (RTE (RE_Abort_Defer), Loc),
6084                 Parameter_Associations =>
6085                   No_List));
6086
6087             --  Generate:
6088             --    Abort_Undefer;
6089             --    <abortable-statements>
6090
6091             Cleanup_Stmts := New_Copy_List_Tree (Astats);
6092
6093             Prepend_To (Cleanup_Stmts,
6094               Make_Procedure_Call_Statement (Loc,
6095                 Name =>
6096                   New_Reference_To (RTE (RE_Abort_Undefer), Loc),
6097                 Parameter_Associations =>
6098                   No_List));
6099
6100             --  Wrap the statements in a block. Exp_Ch7.Expand_Cleanup_Actions
6101             --  will generate a _clean for the additional status flag.
6102
6103             --  Generate:
6104             --    declare
6105             --       procedure _clean is
6106             --       begin
6107             --          Cancel_Task_Entry_Call (U);
6108             --       end _clean;
6109             --    begin
6110             --       Cleanup_Stmts
6111             --    at end
6112             --       _clean;
6113             --    end;
6114
6115             Cleanup_Block_Ent := Make_Temporary (Loc, 'C');
6116             Cleanup_Block :=
6117               Build_Cleanup_Block (Loc, Cleanup_Block_Ent, Cleanup_Stmts, T);
6118
6119             --  Wrap the cleanup block in an exception handling block
6120
6121             --  Generate:
6122             --    begin
6123             --       Cleanup_Block
6124             --    exception
6125             --       when Abort_Signal => Abort_Undefer;
6126             --    end;
6127
6128             Abort_Block_Ent := Make_Temporary (Loc, 'A');
6129
6130             Append_To (TaskE_Stmts,
6131               Make_Implicit_Label_Declaration (Loc,
6132                 Defining_Identifier => Abort_Block_Ent));
6133
6134             Append_To (TaskE_Stmts,
6135               Build_Abort_Block
6136                 (Loc, Abort_Block_Ent, Cleanup_Block_Ent, Cleanup_Block));
6137
6138             --  Generate:
6139             --    if not T then
6140             --       <triggering-statements>
6141             --    end if;
6142
6143             Append_To (TaskE_Stmts,
6144               Make_If_Statement (Loc,
6145                 Condition =>
6146                   Make_Op_Not (Loc,
6147                     Right_Opnd =>
6148                       New_Reference_To (T, Loc)),
6149
6150                 Then_Statements =>
6151                   New_Copy_List_Tree (Tstats)));
6152
6153             ----------------------------------
6154             -- Protected procedure handling --
6155             ----------------------------------
6156
6157             --  Generate:
6158             --    <dispatching-call>;
6159             --    <triggering-statements>
6160
6161             ProtP_Stmts := New_Copy_List_Tree (Tstats);
6162             Prepend_To (ProtP_Stmts, New_Copy_Tree (Ecall));
6163
6164             --  Generate:
6165             --    S := Ada.Tags.Get_Offset_Index
6166             --           (Ada.Tags.Tag (<object>), DT_Position (Call_Ent));
6167
6168             Conc_Typ_Stmts :=
6169               New_List (Build_S_Assignment (Loc, S, Obj, Call_Ent));
6170
6171             --  Generate:
6172             --    _Disp_Get_Prim_Op_Kind (<object>, S, C);
6173
6174             Append_To (Conc_Typ_Stmts,
6175               Make_Procedure_Call_Statement (Loc,
6176                 Name =>
6177                   New_Reference_To (
6178                     Find_Prim_Op (Etype (Etype (Obj)),
6179                       Name_uDisp_Get_Prim_Op_Kind),
6180                     Loc),
6181                 Parameter_Associations =>
6182                   New_List (
6183                     New_Copy_Tree (Obj),
6184                     New_Reference_To (S, Loc),
6185                     New_Reference_To (C, Loc))));
6186
6187             --  Generate:
6188             --    if C = POK_Procedure_Entry then
6189             --       ProtE_Stmts
6190             --    elsif C = POK_Task_Entry then
6191             --       TaskE_Stmts
6192             --    else
6193             --       ProtP_Stmts
6194             --    end if;
6195
6196             Append_To (Conc_Typ_Stmts,
6197               Make_If_Statement (Loc,
6198                 Condition =>
6199                   Make_Op_Eq (Loc,
6200                     Left_Opnd =>
6201                       New_Reference_To (C, Loc),
6202                     Right_Opnd =>
6203                       New_Reference_To (RTE (RE_POK_Protected_Entry), Loc)),
6204
6205                 Then_Statements =>
6206                   ProtE_Stmts,
6207
6208                 Elsif_Parts =>
6209                   New_List (
6210                     Make_Elsif_Part (Loc,
6211                       Condition =>
6212                         Make_Op_Eq (Loc,
6213                           Left_Opnd =>
6214                             New_Reference_To (C, Loc),
6215                           Right_Opnd =>
6216                             New_Reference_To (RTE (RE_POK_Task_Entry), Loc)),
6217
6218                       Then_Statements =>
6219                         TaskE_Stmts)),
6220
6221                 Else_Statements =>
6222                   ProtP_Stmts));
6223
6224             --  Generate:
6225             --    <dispatching-call>;
6226             --    <triggering-statements>
6227
6228             Lim_Typ_Stmts := New_Copy_List_Tree (Tstats);
6229             Prepend_To (Lim_Typ_Stmts, New_Copy_Tree (Ecall));
6230
6231             --  Generate:
6232             --    if K = Ada.Tags.TK_Limited_Tagged then
6233             --       Lim_Typ_Stmts
6234             --    else
6235             --       Conc_Typ_Stmts
6236             --    end if;
6237
6238             Append_To (Stmts,
6239               Make_If_Statement (Loc,
6240                 Condition =>
6241                    Make_Op_Eq (Loc,
6242                      Left_Opnd =>
6243                        New_Reference_To (K, Loc),
6244                      Right_Opnd =>
6245                        New_Reference_To (RTE (RE_TK_Limited_Tagged), Loc)),
6246
6247                 Then_Statements =>
6248                   Lim_Typ_Stmts,
6249
6250                 Else_Statements =>
6251                   Conc_Typ_Stmts));
6252
6253             Rewrite (N,
6254               Make_Block_Statement (Loc,
6255                 Declarations =>
6256                   Decls,
6257                 Handled_Statement_Sequence =>
6258                   Make_Handled_Sequence_Of_Statements (Loc, Stmts)));
6259
6260             Analyze (N);
6261             return;
6262
6263          --  Delay triggering statement processing
6264
6265          else
6266             --  Add a Delay_Block object to the parameter list of the delay
6267             --  procedure to form the parameter list of the Wait entry call.
6268
6269             Dblock_Ent := Make_Temporary (Loc, 'D');
6270
6271             Pdef := Entity (Name (Ecall));
6272
6273             if Is_RTE (Pdef, RO_CA_Delay_For) then
6274                Enqueue_Call :=
6275                  New_Reference_To (RTE (RE_Enqueue_Duration), Loc);
6276
6277             elsif Is_RTE (Pdef, RO_CA_Delay_Until) then
6278                Enqueue_Call :=
6279                  New_Reference_To (RTE (RE_Enqueue_Calendar), Loc);
6280
6281             else pragma Assert (Is_RTE (Pdef, RO_RT_Delay_Until));
6282                Enqueue_Call := New_Reference_To (RTE (RE_Enqueue_RT), Loc);
6283             end if;
6284
6285             Append_To (Parameter_Associations (Ecall),
6286               Make_Attribute_Reference (Loc,
6287                 Prefix => New_Reference_To (Dblock_Ent, Loc),
6288                 Attribute_Name => Name_Unchecked_Access));
6289
6290             --  Create the inner block to protect the abortable part
6291
6292             Hdle := New_List (
6293               Make_Implicit_Exception_Handler (Loc,
6294                 Exception_Choices =>
6295                   New_List (New_Reference_To (Stand.Abort_Signal, Loc)),
6296                 Statements => New_List (
6297                   Make_Procedure_Call_Statement (Loc,
6298                     Name => New_Reference_To (RTE (RE_Abort_Undefer), Loc)))));
6299
6300             Prepend_To (Astats,
6301               Make_Procedure_Call_Statement (Loc,
6302                 Name => New_Reference_To (RTE (RE_Abort_Undefer), Loc)));
6303
6304             Abortable_Block :=
6305               Make_Block_Statement (Loc,
6306                 Identifier => New_Reference_To (Blk_Ent, Loc),
6307                 Handled_Statement_Sequence =>
6308                   Make_Handled_Sequence_Of_Statements (Loc,
6309                     Statements => Astats),
6310                 Has_Created_Identifier => True,
6311                 Is_Asynchronous_Call_Block => True);
6312
6313             --  Append call to if Enqueue (When, DB'Unchecked_Access) then
6314
6315             Rewrite (Ecall,
6316               Make_Implicit_If_Statement (N,
6317                 Condition => Make_Function_Call (Loc,
6318                   Name => Enqueue_Call,
6319                   Parameter_Associations => Parameter_Associations (Ecall)),
6320                 Then_Statements =>
6321                   New_List (Make_Block_Statement (Loc,
6322                     Handled_Statement_Sequence =>
6323                       Make_Handled_Sequence_Of_Statements (Loc,
6324                         Statements => New_List (
6325                           Make_Implicit_Label_Declaration (Loc,
6326                             Defining_Identifier => Blk_Ent,
6327                             Label_Construct     => Abortable_Block),
6328                           Abortable_Block),
6329                         Exception_Handlers => Hdle)))));
6330
6331             Stmts := New_List (Ecall);
6332
6333             --  Construct statement sequence for new block
6334
6335             Append_To (Stmts,
6336               Make_Implicit_If_Statement (N,
6337                 Condition => Make_Function_Call (Loc,
6338                   Name => New_Reference_To (
6339                     RTE (RE_Timed_Out), Loc),
6340                   Parameter_Associations => New_List (
6341                     Make_Attribute_Reference (Loc,
6342                       Prefix => New_Reference_To (Dblock_Ent, Loc),
6343                       Attribute_Name => Name_Unchecked_Access))),
6344                 Then_Statements => Tstats));
6345
6346             --  The result is the new block
6347
6348             Set_Entry_Cancel_Parameter (Blk_Ent, Dblock_Ent);
6349
6350             Rewrite (N,
6351               Make_Block_Statement (Loc,
6352                 Declarations => New_List (
6353                   Make_Object_Declaration (Loc,
6354                     Defining_Identifier => Dblock_Ent,
6355                     Aliased_Present => True,
6356                     Object_Definition => New_Reference_To (
6357                       RTE (RE_Delay_Block), Loc))),
6358
6359                 Handled_Statement_Sequence =>
6360                   Make_Handled_Sequence_Of_Statements (Loc, Stmts)));
6361
6362             Analyze (N);
6363             return;
6364          end if;
6365
6366       else
6367          N_Orig := N;
6368       end if;
6369
6370       Extract_Entry (Ecall, Concval, Ename, Index);
6371       Build_Simple_Entry_Call (Ecall, Concval, Ename, Index);
6372
6373       Stmts := Statements (Handled_Statement_Sequence (Ecall));
6374       Decls := Declarations (Ecall);
6375
6376       if Is_Protected_Type (Etype (Concval)) then
6377
6378          --  Get the declarations of the block expanded from the entry call
6379
6380          Decl := First (Decls);
6381          while Present (Decl)
6382            and then
6383              (Nkind (Decl) /= N_Object_Declaration
6384                or else not Is_RTE (Etype (Object_Definition (Decl)),
6385                                    RE_Communication_Block))
6386          loop
6387             Next (Decl);
6388          end loop;
6389
6390          pragma Assert (Present (Decl));
6391          Cancel_Param := Defining_Identifier (Decl);
6392
6393          --  Change the mode of the Protected_Entry_Call call
6394
6395          --  Protected_Entry_Call (
6396          --    Object => po._object'Access,
6397          --    E => <entry index>;
6398          --    Uninterpreted_Data => P'Address;
6399          --    Mode => Asynchronous_Call;
6400          --    Block => Bnn);
6401
6402          Stmt := First (Stmts);
6403
6404          --  Skip assignments to temporaries created for in-out parameters
6405
6406          --  This makes unwarranted assumptions about the shape of the expanded
6407          --  tree for the call, and should be cleaned up ???
6408
6409          while Nkind (Stmt) /= N_Procedure_Call_Statement loop
6410             Next (Stmt);
6411          end loop;
6412
6413          Call := Stmt;
6414
6415          Param := First (Parameter_Associations (Call));
6416          while Present (Param)
6417            and then not Is_RTE (Etype (Param), RE_Call_Modes)
6418          loop
6419             Next (Param);
6420          end loop;
6421
6422          pragma Assert (Present (Param));
6423          Rewrite (Param, New_Reference_To (RTE (RE_Asynchronous_Call), Loc));
6424          Analyze (Param);
6425
6426          --  Append an if statement to execute the abortable part
6427
6428          --  Generate:
6429          --    if Enqueued (Bnn) then
6430
6431          Append_To (Stmts,
6432            Make_Implicit_If_Statement (N,
6433              Condition => Make_Function_Call (Loc,
6434                Name => New_Reference_To (
6435                  RTE (RE_Enqueued), Loc),
6436                Parameter_Associations => New_List (
6437                  New_Reference_To (Cancel_Param, Loc))),
6438              Then_Statements => Astats));
6439
6440          Abortable_Block :=
6441            Make_Block_Statement (Loc,
6442              Identifier => New_Reference_To (Blk_Ent, Loc),
6443              Handled_Statement_Sequence =>
6444                Make_Handled_Sequence_Of_Statements (Loc,
6445                  Statements => Stmts),
6446              Has_Created_Identifier => True,
6447              Is_Asynchronous_Call_Block => True);
6448
6449          --  For the VM call Update_Exception instead of Abort_Undefer.
6450          --  See 4jexcept.ads for an explanation.
6451
6452          if VM_Target = No_VM then
6453             Target_Undefer := RE_Abort_Undefer;
6454          else
6455             Target_Undefer := RE_Update_Exception;
6456             Undefer_Args :=
6457               New_List (Make_Function_Call (Loc,
6458                           Name => New_Occurrence_Of
6459                                     (RTE (RE_Current_Target_Exception), Loc)));
6460          end if;
6461
6462          Stmts := New_List (
6463            Make_Block_Statement (Loc,
6464              Handled_Statement_Sequence =>
6465                Make_Handled_Sequence_Of_Statements (Loc,
6466                  Statements => New_List (
6467                    Make_Implicit_Label_Declaration (Loc,
6468                      Defining_Identifier => Blk_Ent,
6469                      Label_Construct     => Abortable_Block),
6470                    Abortable_Block),
6471
6472                --  exception
6473
6474                  Exception_Handlers => New_List (
6475                    Make_Implicit_Exception_Handler (Loc,
6476
6477                --  when Abort_Signal =>
6478                --     Abort_Undefer.all;
6479
6480                      Exception_Choices =>
6481                        New_List (New_Reference_To (Stand.Abort_Signal, Loc)),
6482                      Statements => New_List (
6483                        Make_Procedure_Call_Statement (Loc,
6484                          Name => New_Reference_To (
6485                            RTE (Target_Undefer), Loc),
6486                          Parameter_Associations => Undefer_Args)))))),
6487
6488          --  if not Cancelled (Bnn) then
6489          --     triggered statements
6490          --  end if;
6491
6492            Make_Implicit_If_Statement (N,
6493              Condition => Make_Op_Not (Loc,
6494                Right_Opnd =>
6495                  Make_Function_Call (Loc,
6496                    Name => New_Occurrence_Of (RTE (RE_Cancelled), Loc),
6497                    Parameter_Associations => New_List (
6498                      New_Occurrence_Of (Cancel_Param, Loc)))),
6499              Then_Statements => Tstats));
6500
6501       --  Asynchronous task entry call
6502
6503       else
6504          if No (Decls) then
6505             Decls := New_List;
6506          end if;
6507
6508          B := Make_Defining_Identifier (Loc, Name_uB);
6509
6510          --  Insert declaration of B in declarations of existing block
6511
6512          Prepend_To (Decls,
6513            Make_Object_Declaration (Loc,
6514              Defining_Identifier => B,
6515              Object_Definition => New_Reference_To (Standard_Boolean, Loc)));
6516
6517          Cancel_Param := Make_Defining_Identifier (Loc, Name_uC);
6518
6519          --  Insert declaration of C in declarations of existing block
6520
6521          Prepend_To (Decls,
6522            Make_Object_Declaration (Loc,
6523              Defining_Identifier => Cancel_Param,
6524              Object_Definition => New_Reference_To (Standard_Boolean, Loc)));
6525
6526          --  Remove and save the call to Call_Simple
6527
6528          Stmt := First (Stmts);
6529
6530          --  Skip assignments to temporaries created for in-out parameters.
6531          --  This makes unwarranted assumptions about the shape of the expanded
6532          --  tree for the call, and should be cleaned up ???
6533
6534          while Nkind (Stmt) /= N_Procedure_Call_Statement loop
6535             Next (Stmt);
6536          end loop;
6537
6538          Call := Stmt;
6539
6540          --  Create the inner block to protect the abortable part
6541
6542          Hdle :=  New_List (
6543            Make_Implicit_Exception_Handler (Loc,
6544              Exception_Choices =>
6545                New_List (New_Reference_To (Stand.Abort_Signal, Loc)),
6546              Statements =>
6547                New_List (
6548                  Make_Procedure_Call_Statement (Loc,
6549                    Name => New_Reference_To (RTE (RE_Abort_Undefer), Loc)))));
6550
6551          Prepend_To (Astats,
6552            Make_Procedure_Call_Statement (Loc,
6553              Name => New_Reference_To (RTE (RE_Abort_Undefer), Loc)));
6554
6555          Abortable_Block :=
6556            Make_Block_Statement (Loc,
6557              Identifier => New_Reference_To (Blk_Ent, Loc),
6558              Handled_Statement_Sequence =>
6559                Make_Handled_Sequence_Of_Statements (Loc,
6560                  Statements => Astats),
6561              Has_Created_Identifier => True,
6562              Is_Asynchronous_Call_Block => True);
6563
6564          Insert_After (Call,
6565            Make_Block_Statement (Loc,
6566              Handled_Statement_Sequence =>
6567                Make_Handled_Sequence_Of_Statements (Loc,
6568                  Statements => New_List (
6569                    Make_Implicit_Label_Declaration (Loc,
6570                      Defining_Identifier =>
6571                        Blk_Ent,
6572                      Label_Construct =>
6573                        Abortable_Block),
6574                    Abortable_Block),
6575                  Exception_Handlers => Hdle)));
6576
6577          --  Create new call statement
6578
6579          Params := Parameter_Associations (Call);
6580
6581          Append_To (Params,
6582            New_Reference_To (RTE (RE_Asynchronous_Call), Loc));
6583          Append_To (Params,
6584            New_Reference_To (B, Loc));
6585
6586          Rewrite (Call,
6587            Make_Procedure_Call_Statement (Loc,
6588              Name =>
6589                New_Reference_To (RTE (RE_Task_Entry_Call), Loc),
6590              Parameter_Associations => Params));
6591
6592          --  Construct statement sequence for new block
6593
6594          Append_To (Stmts,
6595            Make_Implicit_If_Statement (N,
6596              Condition =>
6597                Make_Op_Not (Loc,
6598                  New_Reference_To (Cancel_Param, Loc)),
6599              Then_Statements => Tstats));
6600
6601          --  Protected the call against abort
6602
6603          Prepend_To (Stmts,
6604            Make_Procedure_Call_Statement (Loc,
6605              Name => New_Reference_To (RTE (RE_Abort_Defer), Loc),
6606              Parameter_Associations => Empty_List));
6607       end if;
6608
6609       Set_Entry_Cancel_Parameter (Blk_Ent, Cancel_Param);
6610
6611       --  The result is the new block
6612
6613       Rewrite (N_Orig,
6614         Make_Block_Statement (Loc,
6615           Declarations => Decls,
6616           Handled_Statement_Sequence =>
6617             Make_Handled_Sequence_Of_Statements (Loc, Stmts)));
6618
6619       Analyze (N_Orig);
6620    end Expand_N_Asynchronous_Select;
6621
6622    -------------------------------------
6623    -- Expand_N_Conditional_Entry_Call --
6624    -------------------------------------
6625
6626    --  The conditional task entry call is converted to a call to
6627    --  Task_Entry_Call:
6628
6629    --    declare
6630    --       B : Boolean;
6631    --       P : parms := (parm, parm, parm);
6632
6633    --    begin
6634    --       Task_Entry_Call
6635    --         (<acceptor-task>,   --  Acceptor
6636    --          <entry-index>,     --  E
6637    --          P'Address,         --  Uninterpreted_Data
6638    --          Conditional_Call,  --  Mode
6639    --          B);                --  Rendezvous_Successful
6640    --       parm := P.param;
6641    --       parm := P.param;
6642    --       ...
6643    --       if B then
6644    --          normal-statements
6645    --       else
6646    --          else-statements
6647    --       end if;
6648    --    end;
6649
6650    --  For a description of the use of P and the assignments after the call,
6651    --  see Expand_N_Entry_Call_Statement. Note that the entry call of the
6652    --  conditional entry call has already been expanded (by the Expand_N_Entry
6653    --  _Call_Statement procedure) as follows:
6654
6655    --    declare
6656    --       P : parms := (parm, parm, parm);
6657    --    begin
6658    --       ... info for in-out parameters
6659    --       Call_Simple (acceptor-task, entry-index, P'Address);
6660    --       parm := P.param;
6661    --       parm := P.param;
6662    --       ...
6663    --    end;
6664
6665    --  so the task at hand is to convert the latter expansion into the former
6666
6667    --  The conditional protected entry call is converted to a call to
6668    --  Protected_Entry_Call:
6669
6670    --    declare
6671    --       P : parms := (parm, parm, parm);
6672    --       Bnn : Communications_Block;
6673
6674    --    begin
6675    --       Protected_Entry_Call
6676    --         (po._object'Access,  --  Object
6677    --          <entry index>,      --  E
6678    --          P'Address,          --  Uninterpreted_Data
6679    --          Conditional_Call,   --  Mode
6680    --          Bnn);               --  Block
6681    --       parm := P.param;
6682    --       parm := P.param;
6683    --       ...
6684    --       if Cancelled (Bnn) then
6685    --          else-statements
6686    --       else
6687    --          normal-statements
6688    --       end if;
6689    --    end;
6690
6691    --  Ada 2005 (AI-345): A dispatching conditional entry call is converted
6692    --  into:
6693
6694    --    declare
6695    --       B : Boolean := False;
6696    --       C : Ada.Tags.Prim_Op_Kind;
6697    --       K : Ada.Tags.Tagged_Kind :=
6698    --             Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
6699    --       P : Parameters := (Param1 .. ParamN);
6700    --       S : Integer;
6701
6702    --    begin
6703    --       if K = Ada.Tags.TK_Limited_Tagged then
6704    --          <dispatching-call>;
6705    --          <triggering-statements>
6706
6707    --       else
6708    --          S :=
6709    --            Ada.Tags.Get_Offset_Index
6710    --              (Ada.Tags.Tag (<object>), DT_Position (<dispatching-call>));
6711
6712    --          _Disp_Conditional_Select (<object>, S, P'Address, C, B);
6713
6714    --          if C = POK_Protected_Entry
6715    --            or else C = POK_Task_Entry
6716    --          then
6717    --             Param1 := P.Param1;
6718    --             ...
6719    --             ParamN := P.ParamN;
6720    --          end if;
6721
6722    --          if B then
6723    --             if C = POK_Procedure
6724    --               or else C = POK_Protected_Procedure
6725    --               or else C = POK_Task_Procedure
6726    --             then
6727    --                <dispatching-call>;
6728    --             end if;
6729
6730    --             <triggering-statements>
6731    --          else
6732    --             <else-statements>
6733    --          end if;
6734    --       end if;
6735    --    end;
6736
6737    procedure Expand_N_Conditional_Entry_Call (N : Node_Id) is
6738       Loc : constant Source_Ptr := Sloc (N);
6739       Alt : constant Node_Id    := Entry_Call_Alternative (N);
6740       Blk : Node_Id             := Entry_Call_Statement (Alt);
6741
6742       Actuals        : List_Id;
6743       Blk_Typ        : Entity_Id;
6744       Call           : Node_Id;
6745       Call_Ent       : Entity_Id;
6746       Conc_Typ_Stmts : List_Id;
6747       Decl           : Node_Id;
6748       Decls          : List_Id;
6749       Formals        : List_Id;
6750       Lim_Typ_Stmts  : List_Id;
6751       N_Stats        : List_Id;
6752       Obj            : Entity_Id;
6753       Param          : Node_Id;
6754       Params         : List_Id;
6755       Stmt           : Node_Id;
6756       Stmts          : List_Id;
6757       Transient_Blk  : Node_Id;
6758       Unpack         : List_Id;
6759
6760       B : Entity_Id;  --  Call status flag
6761       C : Entity_Id;  --  Call kind
6762       K : Entity_Id;  --  Tagged kind
6763       P : Entity_Id;  --  Parameter block
6764       S : Entity_Id;  --  Primitive operation slot
6765
6766    begin
6767       if Ada_Version >= Ada_2005
6768         and then Nkind (Blk) = N_Procedure_Call_Statement
6769       then
6770          Extract_Dispatching_Call (Blk, Call_Ent, Obj, Actuals, Formals);
6771
6772          Decls := New_List;
6773          Stmts := New_List;
6774
6775          --  Call status flag processing, generate:
6776          --    B : Boolean := False;
6777
6778          B := Build_B (Loc, Decls);
6779
6780          --  Call kind processing, generate:
6781          --    C : Ada.Tags.Prim_Op_Kind;
6782
6783          C := Build_C (Loc, Decls);
6784
6785          --  Tagged kind processing, generate:
6786          --    K : Ada.Tags.Tagged_Kind :=
6787          --          Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
6788
6789          K := Build_K (Loc, Decls, Obj);
6790
6791          --  Parameter block processing
6792
6793          Blk_Typ := Build_Parameter_Block (Loc, Actuals, Formals, Decls);
6794          P       := Parameter_Block_Pack
6795                       (Loc, Blk_Typ, Actuals, Formals, Decls, Stmts);
6796
6797          --  Dispatch table slot processing, generate:
6798          --    S : Integer;
6799
6800          S := Build_S (Loc, Decls);
6801
6802          --  Generate:
6803          --    S := Ada.Tags.Get_Offset_Index
6804          --           (Ada.Tags.Tag (<object>), DT_Position (Call_Ent));
6805
6806          Conc_Typ_Stmts :=
6807            New_List (Build_S_Assignment (Loc, S, Obj, Call_Ent));
6808
6809          --  Generate:
6810          --    _Disp_Conditional_Select (<object>, S, P'Address, C, B);
6811
6812          Append_To (Conc_Typ_Stmts,
6813            Make_Procedure_Call_Statement (Loc,
6814              Name =>
6815                New_Reference_To (
6816                  Find_Prim_Op (Etype (Etype (Obj)),
6817                    Name_uDisp_Conditional_Select),
6818                  Loc),
6819              Parameter_Associations =>
6820                New_List (
6821                  New_Copy_Tree (Obj),            --  <object>
6822                  New_Reference_To (S, Loc),      --  S
6823                  Make_Attribute_Reference (Loc,  --  P'Address
6824                    Prefix =>
6825                      New_Reference_To (P, Loc),
6826                    Attribute_Name =>
6827                      Name_Address),
6828                  New_Reference_To (C, Loc),      --  C
6829                  New_Reference_To (B, Loc))));   --  B
6830
6831          --  Generate:
6832          --    if C = POK_Protected_Entry
6833          --      or else C = POK_Task_Entry
6834          --    then
6835          --       Param1 := P.Param1;
6836          --       ...
6837          --       ParamN := P.ParamN;
6838          --    end if;
6839
6840          Unpack := Parameter_Block_Unpack (Loc, P, Actuals, Formals);
6841
6842          --  Generate the if statement only when the packed parameters need
6843          --  explicit assignments to their corresponding actuals.
6844
6845          if Present (Unpack) then
6846             Append_To (Conc_Typ_Stmts,
6847               Make_If_Statement (Loc,
6848
6849                 Condition =>
6850                   Make_Or_Else (Loc,
6851                     Left_Opnd =>
6852                       Make_Op_Eq (Loc,
6853                         Left_Opnd =>
6854                           New_Reference_To (C, Loc),
6855                         Right_Opnd =>
6856                           New_Reference_To (RTE (
6857                             RE_POK_Protected_Entry), Loc)),
6858                     Right_Opnd =>
6859                       Make_Op_Eq (Loc,
6860                         Left_Opnd =>
6861                           New_Reference_To (C, Loc),
6862                         Right_Opnd =>
6863                           New_Reference_To (RTE (RE_POK_Task_Entry), Loc))),
6864
6865                  Then_Statements =>
6866                    Unpack));
6867          end if;
6868
6869          --  Generate:
6870          --    if B then
6871          --       if C = POK_Procedure
6872          --         or else C = POK_Protected_Procedure
6873          --         or else C = POK_Task_Procedure
6874          --       then
6875          --          <dispatching-call>
6876          --       end if;
6877          --       <normal-statements>
6878          --    else
6879          --       <else-statements>
6880          --    end if;
6881
6882          N_Stats := New_Copy_List_Tree (Statements (Alt));
6883
6884          Prepend_To (N_Stats,
6885            Make_If_Statement (Loc,
6886              Condition =>
6887                Make_Or_Else (Loc,
6888                  Left_Opnd =>
6889                    Make_Op_Eq (Loc,
6890                      Left_Opnd =>
6891                        New_Reference_To (C, Loc),
6892                      Right_Opnd =>
6893                        New_Reference_To (RTE (RE_POK_Procedure), Loc)),
6894
6895                  Right_Opnd =>
6896                    Make_Or_Else (Loc,
6897                      Left_Opnd =>
6898                        Make_Op_Eq (Loc,
6899                          Left_Opnd =>
6900                            New_Reference_To (C, Loc),
6901                          Right_Opnd =>
6902                            New_Reference_To (RTE (
6903                              RE_POK_Protected_Procedure), Loc)),
6904
6905                      Right_Opnd =>
6906                        Make_Op_Eq (Loc,
6907                          Left_Opnd =>
6908                            New_Reference_To (C, Loc),
6909                          Right_Opnd =>
6910                            New_Reference_To (RTE (
6911                              RE_POK_Task_Procedure), Loc)))),
6912
6913              Then_Statements =>
6914                New_List (Blk)));
6915
6916          Append_To (Conc_Typ_Stmts,
6917            Make_If_Statement (Loc,
6918              Condition => New_Reference_To (B, Loc),
6919              Then_Statements => N_Stats,
6920              Else_Statements => Else_Statements (N)));
6921
6922          --  Generate:
6923          --    <dispatching-call>;
6924          --    <triggering-statements>
6925
6926          Lim_Typ_Stmts := New_Copy_List_Tree (Statements (Alt));
6927          Prepend_To (Lim_Typ_Stmts, New_Copy_Tree (Blk));
6928
6929          --  Generate:
6930          --    if K = Ada.Tags.TK_Limited_Tagged then
6931          --       Lim_Typ_Stmts
6932          --    else
6933          --       Conc_Typ_Stmts
6934          --    end if;
6935
6936          Append_To (Stmts,
6937            Make_If_Statement (Loc,
6938              Condition =>
6939                Make_Op_Eq (Loc,
6940                  Left_Opnd =>
6941                    New_Reference_To (K, Loc),
6942                  Right_Opnd =>
6943                    New_Reference_To (RTE (RE_TK_Limited_Tagged), Loc)),
6944
6945              Then_Statements =>
6946                Lim_Typ_Stmts,
6947
6948              Else_Statements =>
6949                Conc_Typ_Stmts));
6950
6951          Rewrite (N,
6952            Make_Block_Statement (Loc,
6953              Declarations =>
6954                Decls,
6955              Handled_Statement_Sequence =>
6956                Make_Handled_Sequence_Of_Statements (Loc, Stmts)));
6957
6958       --  As described above, The entry alternative is transformed into a
6959       --  block that contains the gnulli call, and possibly assignment
6960       --  statements for in-out parameters. The gnulli call may itself be
6961       --  rewritten into a transient block if some unconstrained parameters
6962       --  require it. We need to retrieve the call to complete its parameter
6963       --  list.
6964
6965       else
6966          Transient_Blk :=
6967            First_Real_Statement (Handled_Statement_Sequence (Blk));
6968
6969          if Present (Transient_Blk)
6970            and then Nkind (Transient_Blk) = N_Block_Statement
6971          then
6972             Blk := Transient_Blk;
6973          end if;
6974
6975          Stmts := Statements (Handled_Statement_Sequence (Blk));
6976          Stmt  := First (Stmts);
6977          while Nkind (Stmt) /= N_Procedure_Call_Statement loop
6978             Next (Stmt);
6979          end loop;
6980
6981          Call   := Stmt;
6982          Params := Parameter_Associations (Call);
6983
6984          if Is_RTE (Entity (Name (Call)), RE_Protected_Entry_Call) then
6985
6986             --  Substitute Conditional_Entry_Call for Simple_Call parameter
6987
6988             Param := First (Params);
6989             while Present (Param)
6990               and then not Is_RTE (Etype (Param), RE_Call_Modes)
6991             loop
6992                Next (Param);
6993             end loop;
6994
6995             pragma Assert (Present (Param));
6996             Rewrite (Param, New_Reference_To (RTE (RE_Conditional_Call), Loc));
6997
6998             Analyze (Param);
6999
7000             --  Find the Communication_Block parameter for the call to the
7001             --  Cancelled function.
7002
7003             Decl := First (Declarations (Blk));
7004             while Present (Decl)
7005               and then not Is_RTE (Etype (Object_Definition (Decl)),
7006                              RE_Communication_Block)
7007             loop
7008                Next (Decl);
7009             end loop;
7010
7011             --  Add an if statement to execute the else part if the call
7012             --  does not succeed (as indicated by the Cancelled predicate).
7013
7014             Append_To (Stmts,
7015               Make_Implicit_If_Statement (N,
7016                 Condition => Make_Function_Call (Loc,
7017                   Name => New_Reference_To (RTE (RE_Cancelled), Loc),
7018                   Parameter_Associations => New_List (
7019                     New_Reference_To (Defining_Identifier (Decl), Loc))),
7020                 Then_Statements => Else_Statements (N),
7021                 Else_Statements => Statements (Alt)));
7022
7023          else
7024             B := Make_Defining_Identifier (Loc, Name_uB);
7025
7026             --  Insert declaration of B in declarations of existing block
7027
7028             if No (Declarations (Blk)) then
7029                Set_Declarations (Blk, New_List);
7030             end if;
7031
7032             Prepend_To (Declarations (Blk),
7033               Make_Object_Declaration (Loc,
7034                 Defining_Identifier => B,
7035                 Object_Definition =>
7036                   New_Reference_To (Standard_Boolean, Loc)));
7037
7038             --  Create new call statement
7039
7040             Append_To (Params,
7041               New_Reference_To (RTE (RE_Conditional_Call), Loc));
7042             Append_To (Params, New_Reference_To (B, Loc));
7043
7044             Rewrite (Call,
7045               Make_Procedure_Call_Statement (Loc,
7046                 Name => New_Reference_To (RTE (RE_Task_Entry_Call), Loc),
7047                 Parameter_Associations => Params));
7048
7049             --  Construct statement sequence for new block
7050
7051             Append_To (Stmts,
7052               Make_Implicit_If_Statement (N,
7053                 Condition => New_Reference_To (B, Loc),
7054                 Then_Statements => Statements (Alt),
7055                 Else_Statements => Else_Statements (N)));
7056          end if;
7057
7058          --  The result is the new block
7059
7060          Rewrite (N,
7061            Make_Block_Statement (Loc,
7062              Declarations => Declarations (Blk),
7063              Handled_Statement_Sequence =>
7064                Make_Handled_Sequence_Of_Statements (Loc, Stmts)));
7065       end if;
7066
7067       Analyze (N);
7068    end Expand_N_Conditional_Entry_Call;
7069
7070    ---------------------------------------
7071    -- Expand_N_Delay_Relative_Statement --
7072    ---------------------------------------
7073
7074    --  Delay statement is implemented as a procedure call to Delay_For
7075    --  defined in Ada.Calendar.Delays in order to reduce the overhead of
7076    --  simple delays imposed by the use of Protected Objects.
7077
7078    procedure Expand_N_Delay_Relative_Statement (N : Node_Id) is
7079       Loc : constant Source_Ptr := Sloc (N);
7080    begin
7081       Rewrite (N,
7082         Make_Procedure_Call_Statement (Loc,
7083           Name => New_Reference_To (RTE (RO_CA_Delay_For), Loc),
7084           Parameter_Associations => New_List (Expression (N))));
7085       Analyze (N);
7086    end Expand_N_Delay_Relative_Statement;
7087
7088    ------------------------------------
7089    -- Expand_N_Delay_Until_Statement --
7090    ------------------------------------
7091
7092    --  Delay Until statement is implemented as a procedure call to
7093    --  Delay_Until defined in Ada.Calendar.Delays and Ada.Real_Time.Delays.
7094
7095    procedure Expand_N_Delay_Until_Statement (N : Node_Id) is
7096       Loc : constant Source_Ptr := Sloc (N);
7097       Typ : Entity_Id;
7098
7099    begin
7100       if Is_RTE (Base_Type (Etype (Expression (N))), RO_CA_Time) then
7101          Typ := RTE (RO_CA_Delay_Until);
7102       else
7103          Typ := RTE (RO_RT_Delay_Until);
7104       end if;
7105
7106       Rewrite (N,
7107         Make_Procedure_Call_Statement (Loc,
7108           Name => New_Reference_To (Typ, Loc),
7109           Parameter_Associations => New_List (Expression (N))));
7110
7111       Analyze (N);
7112    end Expand_N_Delay_Until_Statement;
7113
7114    -------------------------
7115    -- Expand_N_Entry_Body --
7116    -------------------------
7117
7118    procedure Expand_N_Entry_Body (N : Node_Id) is
7119    begin
7120       --  Associate discriminals with the next protected operation body to be
7121       --  expanded.
7122
7123       if Present (Next_Protected_Operation (N)) then
7124          Set_Discriminals (Parent (Current_Scope));
7125       end if;
7126    end Expand_N_Entry_Body;
7127
7128    -----------------------------------
7129    -- Expand_N_Entry_Call_Statement --
7130    -----------------------------------
7131
7132    --  An entry call is expanded into GNARLI calls to implement a simple entry
7133    --  call (see Build_Simple_Entry_Call).
7134
7135    procedure Expand_N_Entry_Call_Statement (N : Node_Id) is
7136       Concval : Node_Id;
7137       Ename   : Node_Id;
7138       Index   : Node_Id;
7139
7140    begin
7141       if No_Run_Time_Mode then
7142          Error_Msg_CRT ("entry call", N);
7143          return;
7144       end if;
7145
7146       --  If this entry call is part of an asynchronous select, don't expand it
7147       --  here; it will be expanded with the select statement. Don't expand
7148       --  timed entry calls either, as they are translated into asynchronous
7149       --  entry calls.
7150
7151       --  ??? This whole approach is questionable; it may be better to go back
7152       --  to allowing the expansion to take place and then attempting to fix it
7153       --  up in Expand_N_Asynchronous_Select. The tricky part is figuring out
7154       --  whether the expanded call is on a task or protected entry.
7155
7156       if (Nkind (Parent (N)) /= N_Triggering_Alternative
7157            or else N /= Triggering_Statement (Parent (N)))
7158         and then (Nkind (Parent (N)) /= N_Entry_Call_Alternative
7159                    or else N /= Entry_Call_Statement (Parent (N))
7160                    or else Nkind (Parent (Parent (N))) /= N_Timed_Entry_Call)
7161       then
7162          Extract_Entry (N, Concval, Ename, Index);
7163          Build_Simple_Entry_Call (N, Concval, Ename, Index);
7164       end if;
7165    end Expand_N_Entry_Call_Statement;
7166
7167    --------------------------------
7168    -- Expand_N_Entry_Declaration --
7169    --------------------------------
7170
7171    --  If there are parameters, then first, each of the formals is marked by
7172    --  setting Is_Entry_Formal. Next a record type is built which is used to
7173    --  hold the parameter values. The name of this record type is entryP where
7174    --  entry is the name of the entry, with an additional corresponding access
7175    --  type called entryPA. The record type has matching components for each
7176    --  formal (the component names are the same as the formal names). For
7177    --  elementary types, the component type matches the formal type. For
7178    --  composite types, an access type is declared (with the name formalA)
7179    --  which designates the formal type, and the type of the component is this
7180    --  access type. Finally the Entry_Component of each formal is set to
7181    --  reference the corresponding record component.
7182
7183    procedure Expand_N_Entry_Declaration (N : Node_Id) is
7184       Loc        : constant Source_Ptr := Sloc (N);
7185       Entry_Ent  : constant Entity_Id  := Defining_Identifier (N);
7186       Components : List_Id;
7187       Formal     : Node_Id;
7188       Ftype      : Entity_Id;
7189       Last_Decl  : Node_Id;
7190       Component  : Entity_Id;
7191       Ctype      : Entity_Id;
7192       Decl       : Node_Id;
7193       Rec_Ent    : Entity_Id;
7194       Acc_Ent    : Entity_Id;
7195
7196    begin
7197       Formal := First_Formal (Entry_Ent);
7198       Last_Decl := N;
7199
7200       --  Most processing is done only if parameters are present
7201
7202       if Present (Formal) then
7203          Components := New_List;
7204
7205          --  Loop through formals
7206
7207          while Present (Formal) loop
7208             Set_Is_Entry_Formal (Formal);
7209             Component :=
7210               Make_Defining_Identifier (Sloc (Formal), Chars (Formal));
7211             Set_Entry_Component (Formal, Component);
7212             Set_Entry_Formal (Component, Formal);
7213             Ftype := Etype (Formal);
7214
7215             --  Declare new access type and then append
7216
7217             Ctype := Make_Temporary (Loc, 'A');
7218
7219             Decl :=
7220               Make_Full_Type_Declaration (Loc,
7221                 Defining_Identifier => Ctype,
7222                 Type_Definition     =>
7223                   Make_Access_To_Object_Definition (Loc,
7224                     All_Present        => True,
7225                     Constant_Present   => Ekind (Formal) = E_In_Parameter,
7226                     Subtype_Indication => New_Reference_To (Ftype, Loc)));
7227
7228             Insert_After (Last_Decl, Decl);
7229             Last_Decl := Decl;
7230
7231             Append_To (Components,
7232               Make_Component_Declaration (Loc,
7233                 Defining_Identifier => Component,
7234                 Component_Definition =>
7235                   Make_Component_Definition (Loc,
7236                     Aliased_Present    => False,
7237                     Subtype_Indication => New_Reference_To (Ctype, Loc))));
7238
7239             Next_Formal_With_Extras (Formal);
7240          end loop;
7241
7242          --  Create the Entry_Parameter_Record declaration
7243
7244          Rec_Ent := Make_Temporary (Loc, 'P');
7245
7246          Decl :=
7247            Make_Full_Type_Declaration (Loc,
7248              Defining_Identifier => Rec_Ent,
7249              Type_Definition     =>
7250                Make_Record_Definition (Loc,
7251                  Component_List =>
7252                    Make_Component_List (Loc,
7253                      Component_Items => Components)));
7254
7255          Insert_After (Last_Decl, Decl);
7256          Last_Decl := Decl;
7257
7258          --  Construct and link in the corresponding access type
7259
7260          Acc_Ent := Make_Temporary (Loc, 'A');
7261
7262          Set_Entry_Parameters_Type (Entry_Ent, Acc_Ent);
7263
7264          Decl :=
7265            Make_Full_Type_Declaration (Loc,
7266              Defining_Identifier => Acc_Ent,
7267              Type_Definition     =>
7268                Make_Access_To_Object_Definition (Loc,
7269                  All_Present        => True,
7270                  Subtype_Indication => New_Reference_To (Rec_Ent, Loc)));
7271
7272          Insert_After (Last_Decl, Decl);
7273          Last_Decl := Decl;
7274       end if;
7275    end Expand_N_Entry_Declaration;
7276
7277    -----------------------------
7278    -- Expand_N_Protected_Body --
7279    -----------------------------
7280
7281    --  Protected bodies are expanded to the completion of the subprograms
7282    --  created for the corresponding protected type. These are a protected and
7283    --  unprotected version of each protected subprogram in the object, a
7284    --  function to calculate each entry barrier, and a procedure to execute the
7285    --  sequence of statements of each protected entry body. For example, for
7286    --  protected type ptype:
7287
7288    --  function entB
7289    --    (O : System.Address;
7290    --     E : Protected_Entry_Index)
7291    --     return Boolean
7292    --  is
7293    --     <discriminant renamings>
7294    --     <private object renamings>
7295    --  begin
7296    --     return <barrier expression>;
7297    --  end entB;
7298
7299    --  procedure pprocN (_object : in out poV;...) is
7300    --     <discriminant renamings>
7301    --     <private object renamings>
7302    --  begin
7303    --     <sequence of statements>
7304    --  end pprocN;
7305
7306    --  procedure pprocP (_object : in out poV;...) is
7307    --     procedure _clean is
7308    --       Pn : Boolean;
7309    --     begin
7310    --       ptypeS (_object, Pn);
7311    --       Unlock (_object._object'Access);
7312    --       Abort_Undefer.all;
7313    --     end _clean;
7314
7315    --  begin
7316    --     Abort_Defer.all;
7317    --     Lock (_object._object'Access);
7318    --     pprocN (_object;...);
7319    --  at end
7320    --     _clean;
7321    --  end pproc;
7322
7323    --  function pfuncN (_object : poV;...) return Return_Type is
7324    --     <discriminant renamings>
7325    --     <private object renamings>
7326    --  begin
7327    --     <sequence of statements>
7328    --  end pfuncN;
7329
7330    --  function pfuncP (_object : poV) return Return_Type is
7331    --     procedure _clean is
7332    --     begin
7333    --        Unlock (_object._object'Access);
7334    --        Abort_Undefer.all;
7335    --     end _clean;
7336
7337    --  begin
7338    --     Abort_Defer.all;
7339    --     Lock (_object._object'Access);
7340    --     return pfuncN (_object);
7341
7342    --  at end
7343    --     _clean;
7344    --  end pfunc;
7345
7346    --  procedure entE
7347    --    (O : System.Address;
7348    --     P : System.Address;
7349    --     E : Protected_Entry_Index)
7350    --  is
7351    --     <discriminant renamings>
7352    --     <private object renamings>
7353    --     type poVP is access poV;
7354    --     _Object : ptVP := ptVP!(O);
7355
7356    --  begin
7357    --     begin
7358    --        <statement sequence>
7359    --        Complete_Entry_Body (_Object._Object);
7360    --     exception
7361    --        when all others =>
7362    --           Exceptional_Complete_Entry_Body (
7363    --             _Object._Object, Get_GNAT_Exception);
7364    --     end;
7365    --  end entE;
7366
7367    --  The type poV is the record created for the protected type to hold
7368    --  the state of the protected object.
7369
7370    procedure Expand_N_Protected_Body (N : Node_Id) is
7371       Loc          : constant Source_Ptr := Sloc (N);
7372       Pid          : constant Entity_Id  := Corresponding_Spec (N);
7373
7374       Current_Node : Node_Id;
7375       Disp_Op_Body : Node_Id;
7376       New_Op_Body  : Node_Id;
7377       Num_Entries  : Natural := 0;
7378       Op_Body      : Node_Id;
7379       Op_Id        : Entity_Id;
7380
7381       Chain        : Entity_Id := Empty;
7382       --  Finalization chain that may be attached to new body
7383
7384       function Build_Dispatching_Subprogram_Body
7385         (N        : Node_Id;
7386          Pid      : Node_Id;
7387          Prot_Bod : Node_Id) return Node_Id;
7388       --  Build a dispatching version of the protected subprogram body. The
7389       --  newly generated subprogram contains a call to the original protected
7390       --  body. The following code is generated:
7391       --
7392       --  function <protected-function-name> (Param1 .. ParamN) return
7393       --    <return-type> is
7394       --  begin
7395       --     return <protected-function-name>P (Param1 .. ParamN);
7396       --  end <protected-function-name>;
7397       --
7398       --  or
7399       --
7400       --  procedure <protected-procedure-name> (Param1 .. ParamN) is
7401       --  begin
7402       --     <protected-procedure-name>P (Param1 .. ParamN);
7403       --  end <protected-procedure-name>
7404
7405       ---------------------------------------
7406       -- Build_Dispatching_Subprogram_Body --
7407       ---------------------------------------
7408
7409       function Build_Dispatching_Subprogram_Body
7410         (N        : Node_Id;
7411          Pid      : Node_Id;
7412          Prot_Bod : Node_Id) return Node_Id
7413       is
7414          Loc     : constant Source_Ptr := Sloc (N);
7415          Actuals : List_Id;
7416          Formal  : Node_Id;
7417          Spec    : Node_Id;
7418          Stmts   : List_Id;
7419
7420       begin
7421          --  Generate a specification without a letter suffix in order to
7422          --  override an interface function or procedure.
7423
7424          Spec := Build_Protected_Sub_Specification (N, Pid, Dispatching_Mode);
7425
7426          --  The formal parameters become the actuals of the protected function
7427          --  or procedure call.
7428
7429          Actuals := New_List;
7430          Formal  := First (Parameter_Specifications (Spec));
7431          while Present (Formal) loop
7432             Append_To (Actuals,
7433               Make_Identifier (Loc, Chars (Defining_Identifier (Formal))));
7434
7435             Next (Formal);
7436          end loop;
7437
7438          if Nkind (Spec) = N_Procedure_Specification then
7439             Stmts :=
7440               New_List (
7441                 Make_Procedure_Call_Statement (Loc,
7442                   Name =>
7443                     New_Reference_To (Corresponding_Spec (Prot_Bod), Loc),
7444                   Parameter_Associations => Actuals));
7445          else
7446             pragma Assert (Nkind (Spec) = N_Function_Specification);
7447
7448             Stmts :=
7449               New_List (
7450                 Make_Simple_Return_Statement (Loc,
7451                   Expression =>
7452                     Make_Function_Call (Loc,
7453                       Name =>
7454                         New_Reference_To (Corresponding_Spec (Prot_Bod), Loc),
7455                       Parameter_Associations => Actuals)));
7456          end if;
7457
7458          return
7459            Make_Subprogram_Body (Loc,
7460              Declarations               => Empty_List,
7461              Specification              => Spec,
7462              Handled_Statement_Sequence =>
7463                Make_Handled_Sequence_Of_Statements (Loc, Stmts));
7464       end Build_Dispatching_Subprogram_Body;
7465
7466    --  Start of processing for Expand_N_Protected_Body
7467
7468    begin
7469       if No_Run_Time_Mode then
7470          Error_Msg_CRT ("protected body", N);
7471          return;
7472       end if;
7473
7474       --  This is the proper body corresponding to a stub. The declarations
7475       --  must be inserted at the point of the stub, which in turn is in the
7476       --  declarative part of the parent unit.
7477
7478       if Nkind (Parent (N)) = N_Subunit then
7479          Current_Node := Corresponding_Stub (Parent (N));
7480       else
7481          Current_Node := N;
7482       end if;
7483
7484       Op_Body := First (Declarations (N));
7485
7486       --  The protected body is replaced with the bodies of its
7487       --  protected operations, and the declarations for internal objects
7488       --  that may have been created for entry family bounds.
7489
7490       Rewrite (N, Make_Null_Statement (Sloc (N)));
7491       Analyze (N);
7492
7493       while Present (Op_Body) loop
7494          case Nkind (Op_Body) is
7495             when N_Subprogram_Declaration =>
7496                null;
7497
7498             when N_Subprogram_Body =>
7499
7500                --  Do not create bodies for eliminated operations
7501
7502                if not Is_Eliminated (Defining_Entity (Op_Body))
7503                  and then not Is_Eliminated (Corresponding_Spec (Op_Body))
7504                then
7505                   New_Op_Body :=
7506                     Build_Unprotected_Subprogram_Body (Op_Body, Pid);
7507
7508                   --  Propagate the finalization chain to the new body. In the
7509                   --  unlikely event that the subprogram contains a declaration
7510                   --  or allocator for an object that requires finalization,
7511                   --  the corresponding chain is created when analyzing the
7512                   --  body, and attached to its entity. This entity is not
7513                   --  further elaborated, and so the chain properly belongs to
7514                   --  the newly created subprogram body.
7515
7516                   Chain :=
7517                     Finalization_Chain_Entity (Defining_Entity (Op_Body));
7518
7519                   if Present (Chain) then
7520                      Set_Finalization_Chain_Entity
7521                        (Protected_Body_Subprogram
7522                          (Corresponding_Spec (Op_Body)), Chain);
7523                      Set_Analyzed
7524                          (Handled_Statement_Sequence (New_Op_Body), False);
7525                   end if;
7526
7527                   Insert_After (Current_Node, New_Op_Body);
7528                   Current_Node := New_Op_Body;
7529                   Analyze (New_Op_Body);
7530
7531                   --  Build the corresponding protected operation. It may
7532                   --  appear that this is needed only if this is a visible
7533                   --  operation of the type, or if it is an interrupt handler,
7534                   --  and this was the strategy used previously in GNAT.
7535                   --  However, the operation may be exported through a 'Access
7536                   --  to an external caller. This is the common idiom in code
7537                   --  that uses the Ada 2005 Timing_Events package. As a result
7538                   --  we need to produce the protected body for both visible
7539                   --  and private operations, as well as operations that only
7540                   --  have a body in the source, and for which we create a
7541                   --  declaration in the protected body itself.
7542
7543                   if Present (Corresponding_Spec (Op_Body)) then
7544                      New_Op_Body :=
7545                        Build_Protected_Subprogram_Body (
7546                          Op_Body, Pid, Specification (New_Op_Body));
7547
7548                      Insert_After (Current_Node, New_Op_Body);
7549                      Analyze (New_Op_Body);
7550
7551                      Current_Node := New_Op_Body;
7552
7553                      --  Generate an overriding primitive operation body for
7554                      --  this subprogram if the protected type implements an
7555                      --  interface.
7556
7557                      if Ada_Version >= Ada_2005
7558                           and then
7559                         Present (Interfaces (Corresponding_Record_Type (Pid)))
7560                      then
7561                         Disp_Op_Body :=
7562                           Build_Dispatching_Subprogram_Body
7563                             (Op_Body, Pid, New_Op_Body);
7564
7565                         Insert_After (Current_Node, Disp_Op_Body);
7566                         Analyze (Disp_Op_Body);
7567
7568                         Current_Node := Disp_Op_Body;
7569                      end if;
7570                   end if;
7571                end if;
7572
7573             when N_Entry_Body =>
7574                Op_Id := Defining_Identifier (Op_Body);
7575                Num_Entries := Num_Entries + 1;
7576
7577                New_Op_Body := Build_Protected_Entry (Op_Body, Op_Id, Pid);
7578
7579                Insert_After (Current_Node, New_Op_Body);
7580                Current_Node := New_Op_Body;
7581                Analyze (New_Op_Body);
7582
7583             when N_Implicit_Label_Declaration =>
7584                null;
7585
7586             when N_Itype_Reference =>
7587                Insert_After (Current_Node, New_Copy (Op_Body));
7588
7589             when N_Freeze_Entity =>
7590                New_Op_Body := New_Copy (Op_Body);
7591
7592                if Present (Entity (Op_Body))
7593                  and then Freeze_Node (Entity (Op_Body)) = Op_Body
7594                then
7595                   Set_Freeze_Node (Entity (Op_Body), New_Op_Body);
7596                end if;
7597
7598                Insert_After (Current_Node, New_Op_Body);
7599                Current_Node := New_Op_Body;
7600                Analyze (New_Op_Body);
7601
7602             when N_Pragma =>
7603                New_Op_Body := New_Copy (Op_Body);
7604                Insert_After (Current_Node, New_Op_Body);
7605                Current_Node := New_Op_Body;
7606                Analyze (New_Op_Body);
7607
7608             when N_Object_Declaration =>
7609                pragma Assert (not Comes_From_Source (Op_Body));
7610                New_Op_Body := New_Copy (Op_Body);
7611                Insert_After (Current_Node, New_Op_Body);
7612                Current_Node := New_Op_Body;
7613                Analyze (New_Op_Body);
7614
7615             when others =>
7616                raise Program_Error;
7617
7618          end case;
7619
7620          Next (Op_Body);
7621       end loop;
7622
7623       --  Finally, create the body of the function that maps an entry index
7624       --  into the corresponding body index, except when there is no entry, or
7625       --  in a Ravenscar-like profile.
7626
7627       if Corresponding_Runtime_Package (Pid) =
7628            System_Tasking_Protected_Objects_Entries
7629       then
7630          New_Op_Body := Build_Find_Body_Index (Pid);
7631          Insert_After (Current_Node, New_Op_Body);
7632          Current_Node := New_Op_Body;
7633          Analyze (New_Op_Body);
7634       end if;
7635
7636       --  Ada 2005 (AI-345): Construct the primitive wrapper bodies after the
7637       --  protected body. At this point all wrapper specs have been created,
7638       --  frozen and included in the dispatch table for the protected type.
7639
7640       if Ada_Version >= Ada_2005 then
7641          Build_Wrapper_Bodies (Loc, Pid, Current_Node);
7642       end if;
7643    end Expand_N_Protected_Body;
7644
7645    -----------------------------------------
7646    -- Expand_N_Protected_Type_Declaration --
7647    -----------------------------------------
7648
7649    --  First we create a corresponding record type declaration used to
7650    --  represent values of this protected type.
7651    --  The general form of this type declaration is
7652
7653    --    type poV (discriminants) is record
7654    --      _Object       : aliased <kind>Protection
7655    --         [(<entry count> [, <handler count>])];
7656    --      [entry_family  : array (bounds) of Void;]
7657    --      <private data fields>
7658    --    end record;
7659
7660    --  The discriminants are present only if the corresponding protected type
7661    --  has discriminants, and they exactly mirror the protected type
7662    --  discriminants. The private data fields similarly mirror the private
7663    --  declarations of the protected type.
7664
7665    --  The Object field is always present. It contains RTS specific data used
7666    --  to control the protected object. It is declared as Aliased so that it
7667    --  can be passed as a pointer to the RTS. This allows the protected record
7668    --  to be referenced within RTS data structures. An appropriate Protection
7669    --  type and discriminant are generated.
7670
7671    --  The Service field is present for protected objects with entries. It
7672    --  contains sufficient information to allow the entry service procedure for
7673    --  this object to be called when the object is not known till runtime.
7674
7675    --  One entry_family component is present for each entry family in the
7676    --  task definition (see Expand_N_Task_Type_Declaration).
7677
7678    --  When a protected object is declared, an instance of the protected type
7679    --  value record is created. The elaboration of this declaration creates the
7680    --  correct bounds for the entry families, and also evaluates the priority
7681    --  expression if needed. The initialization routine for the protected type
7682    --  itself then calls Initialize_Protection with appropriate parameters to
7683    --  initialize the value of the Task_Id field. Install_Handlers may be also
7684    --  called if a pragma Attach_Handler applies.
7685
7686    --  Note: this record is passed to the subprograms created by the expansion
7687    --  of protected subprograms and entries. It is an in parameter to protected
7688    --  functions and an in out parameter to procedures and entry bodies. The
7689    --  Entity_Id for this created record type is placed in the
7690    --  Corresponding_Record_Type field of the associated protected type entity.
7691
7692    --  Next we create a procedure specifications for protected subprograms and
7693    --  entry bodies. For each protected subprograms two subprograms are
7694    --  created, an unprotected and a protected version. The unprotected version
7695    --  is called from within other operations of the same protected object.
7696
7697    --  We also build the call to register the procedure if a pragma
7698    --  Interrupt_Handler applies.
7699
7700    --  A single subprogram is created to service all entry bodies; it has an
7701    --  additional boolean out parameter indicating that the previous entry call
7702    --  made by the current task was serviced immediately, i.e. not by proxy.
7703    --  The O parameter contains a pointer to a record object of the type
7704    --  described above. An untyped interface is used here to allow this
7705    --  procedure to be called in places where the type of the object to be
7706    --  serviced is not known. This must be done, for example, when a call that
7707    --  may have been requeued is cancelled; the corresponding object must be
7708    --  serviced, but which object that is not known till runtime.
7709
7710    --  procedure ptypeS
7711    --    (O : System.Address; P : out Boolean);
7712    --  procedure pprocN (_object : in out poV);
7713    --  procedure pproc (_object : in out poV);
7714    --  function pfuncN (_object : poV);
7715    --  function pfunc (_object : poV);
7716    --  ...
7717
7718    --  Note that this must come after the record type declaration, since
7719    --  the specs refer to this type.
7720
7721    procedure Expand_N_Protected_Type_Declaration (N : Node_Id) is
7722       Loc      : constant Source_Ptr := Sloc (N);
7723       Prot_Typ : constant Entity_Id  := Defining_Identifier (N);
7724
7725       Pdef : constant Node_Id := Protected_Definition (N);
7726       --  This contains two lists; one for visible and one for private decls
7727
7728       Rec_Decl     : Node_Id;
7729       Cdecls       : List_Id;
7730       Discr_Map    : constant Elist_Id := New_Elmt_List;
7731       Priv         : Node_Id;
7732       New_Priv     : Node_Id;
7733       Comp         : Node_Id;
7734       Comp_Id      : Entity_Id;
7735       Sub          : Node_Id;
7736       Current_Node : Node_Id := N;
7737       Bdef         : Entity_Id := Empty; -- avoid uninit warning
7738       Edef         : Entity_Id := Empty; -- avoid uninit warning
7739       Entries_Aggr : Node_Id;
7740       Body_Id      : Entity_Id;
7741       Body_Arr     : Node_Id;
7742       E_Count      : Int;
7743       Object_Comp  : Node_Id;
7744
7745       procedure Check_Inlining (Subp : Entity_Id);
7746       --  If the original operation has a pragma Inline, propagate the flag
7747       --  to the internal body, for possible inlining later on. The source
7748       --  operation is invisible to the back-end and is never actually called.
7749
7750       function Static_Component_Size (Comp : Entity_Id) return Boolean;
7751       --  When compiling under the Ravenscar profile, private components must
7752       --  have a static size, or else a protected object  will require heap
7753       --  allocation, violating the corresponding restriction. It is preferable
7754       --  to make this check here, because it provides a better error message
7755       --  than the back-end, which refers to the object as a whole.
7756
7757       procedure Register_Handler;
7758       --  For a protected operation that is an interrupt handler, add the
7759       --  freeze action that will register it as such.
7760
7761       --------------------
7762       -- Check_Inlining --
7763       --------------------
7764
7765       procedure Check_Inlining (Subp : Entity_Id) is
7766       begin
7767          if Is_Inlined (Subp) then
7768             Set_Is_Inlined (Protected_Body_Subprogram (Subp));
7769             Set_Is_Inlined (Subp, False);
7770          end if;
7771       end Check_Inlining;
7772
7773       ---------------------------------
7774       -- Check_Static_Component_Size --
7775       ---------------------------------
7776
7777       function Static_Component_Size (Comp : Entity_Id) return Boolean is
7778          Typ : constant Entity_Id := Etype (Comp);
7779          C   : Entity_Id;
7780
7781       begin
7782          if Is_Scalar_Type (Typ) then
7783             return True;
7784
7785          elsif Is_Array_Type (Typ) then
7786             return Compile_Time_Known_Bounds (Typ);
7787
7788          elsif Is_Record_Type (Typ) then
7789             C := First_Component (Typ);
7790             while Present (C) loop
7791                if not Static_Component_Size (C) then
7792                   return False;
7793                end if;
7794
7795                Next_Component (C);
7796             end loop;
7797
7798             return True;
7799
7800          --  Any other types will be checked by the back-end
7801
7802          else
7803             return True;
7804          end if;
7805       end Static_Component_Size;
7806
7807       ----------------------
7808       -- Register_Handler --
7809       ----------------------
7810
7811       procedure Register_Handler is
7812
7813          --  All semantic checks already done in Sem_Prag
7814
7815          Prot_Proc    : constant Entity_Id :=
7816                        Defining_Unit_Name
7817                          (Specification (Current_Node));
7818
7819          Proc_Address : constant Node_Id :=
7820                           Make_Attribute_Reference (Loc,
7821                           Prefix => New_Reference_To (Prot_Proc, Loc),
7822                           Attribute_Name => Name_Address);
7823
7824          RTS_Call     : constant Entity_Id :=
7825                           Make_Procedure_Call_Statement (Loc,
7826                             Name =>
7827                               New_Reference_To (
7828                                 RTE (RE_Register_Interrupt_Handler), Loc),
7829                             Parameter_Associations =>
7830                               New_List (Proc_Address));
7831       begin
7832          Append_Freeze_Action (Prot_Proc, RTS_Call);
7833       end Register_Handler;
7834
7835    --  Start of processing for Expand_N_Protected_Type_Declaration
7836
7837    begin
7838       if Present (Corresponding_Record_Type (Prot_Typ)) then
7839          return;
7840       else
7841          Rec_Decl := Build_Corresponding_Record (N, Prot_Typ, Loc);
7842       end if;
7843
7844       Cdecls := Component_Items (Component_List (Type_Definition (Rec_Decl)));
7845
7846       Qualify_Entity_Names (N);
7847
7848       --  If the type has discriminants, their occurrences in the declaration
7849       --  have been replaced by the corresponding discriminals. For components
7850       --  that are constrained by discriminants, their homologues in the
7851       --  corresponding record type must refer to the discriminants of that
7852       --  record, so we must apply a new renaming to subtypes_indications:
7853
7854       --     protected discriminant => discriminal => record discriminant
7855
7856       --  This replacement is not applied to default expressions, for which
7857       --  the discriminal is correct.
7858
7859       if Has_Discriminants (Prot_Typ) then
7860          declare
7861             Disc : Entity_Id;
7862             Decl : Node_Id;
7863
7864          begin
7865             Disc := First_Discriminant (Prot_Typ);
7866             Decl := First (Discriminant_Specifications (Rec_Decl));
7867             while Present (Disc) loop
7868                Append_Elmt (Discriminal (Disc), Discr_Map);
7869                Append_Elmt (Defining_Identifier (Decl), Discr_Map);
7870                Next_Discriminant (Disc);
7871                Next (Decl);
7872             end loop;
7873          end;
7874       end if;
7875
7876       --  Fill in the component declarations
7877
7878       --  Add components for entry families. For each entry family, create an
7879       --  anonymous type declaration with the same size, and analyze the type.
7880
7881       Collect_Entry_Families (Loc, Cdecls, Current_Node, Prot_Typ);
7882
7883       --  Prepend the _Object field with the right type to the component list.
7884       --  We need to compute the number of entries, and in some cases the
7885       --  number of Attach_Handler pragmas.
7886
7887       declare
7888          Ritem              : Node_Id;
7889          Num_Attach_Handler : Int := 0;
7890          Protection_Subtype : Node_Id;
7891          Entry_Count_Expr   : constant Node_Id :=
7892                                 Build_Entry_Count_Expression
7893                                   (Prot_Typ, Cdecls, Loc);
7894
7895       begin
7896          --  Could this be simplified using Corresponding_Runtime_Package???
7897
7898          if Has_Attach_Handler (Prot_Typ) then
7899             Ritem := First_Rep_Item (Prot_Typ);
7900             while Present (Ritem) loop
7901                if Nkind (Ritem) = N_Pragma
7902                  and then Pragma_Name (Ritem) = Name_Attach_Handler
7903                then
7904                   Num_Attach_Handler := Num_Attach_Handler + 1;
7905                end if;
7906
7907                Next_Rep_Item (Ritem);
7908             end loop;
7909
7910             if Restricted_Profile then
7911                if Has_Entries (Prot_Typ) then
7912                   Protection_Subtype :=
7913                     New_Reference_To (RTE (RE_Protection_Entry), Loc);
7914                else
7915                   Protection_Subtype :=
7916                     New_Reference_To (RTE (RE_Protection), Loc);
7917                end if;
7918             else
7919                Protection_Subtype :=
7920                  Make_Subtype_Indication
7921                    (Sloc => Loc,
7922                     Subtype_Mark =>
7923                       New_Reference_To
7924                         (RTE (RE_Static_Interrupt_Protection), Loc),
7925                     Constraint =>
7926                       Make_Index_Or_Discriminant_Constraint (
7927                         Sloc => Loc,
7928                         Constraints => New_List (
7929                           Entry_Count_Expr,
7930                           Make_Integer_Literal (Loc, Num_Attach_Handler))));
7931             end if;
7932
7933          elsif Has_Interrupt_Handler (Prot_Typ) then
7934             Protection_Subtype :=
7935                Make_Subtype_Indication (
7936                  Sloc => Loc,
7937                  Subtype_Mark => New_Reference_To
7938                    (RTE (RE_Dynamic_Interrupt_Protection), Loc),
7939                  Constraint =>
7940                    Make_Index_Or_Discriminant_Constraint (
7941                      Sloc => Loc,
7942                      Constraints => New_List (Entry_Count_Expr)));
7943
7944          --  Type has explicit entries or generated primitive entry wrappers
7945
7946          elsif Has_Entries (Prot_Typ)
7947            or else (Ada_Version >= Ada_2005
7948                       and then Present (Interface_List (N)))
7949          then
7950             case Corresponding_Runtime_Package (Prot_Typ) is
7951                when System_Tasking_Protected_Objects_Entries =>
7952                   Protection_Subtype :=
7953                      Make_Subtype_Indication (Loc,
7954                        Subtype_Mark =>
7955                          New_Reference_To (RTE (RE_Protection_Entries), Loc),
7956                        Constraint =>
7957                          Make_Index_Or_Discriminant_Constraint (
7958                            Sloc => Loc,
7959                            Constraints => New_List (Entry_Count_Expr)));
7960
7961                when System_Tasking_Protected_Objects_Single_Entry =>
7962                   Protection_Subtype :=
7963                     New_Reference_To (RTE (RE_Protection_Entry), Loc);
7964
7965                when others =>
7966                   raise Program_Error;
7967             end case;
7968
7969          else
7970             Protection_Subtype := New_Reference_To (RTE (RE_Protection), Loc);
7971          end if;
7972
7973          Object_Comp :=
7974            Make_Component_Declaration (Loc,
7975              Defining_Identifier =>
7976                Make_Defining_Identifier (Loc, Name_uObject),
7977              Component_Definition =>
7978                Make_Component_Definition (Loc,
7979                  Aliased_Present    => True,
7980                  Subtype_Indication => Protection_Subtype));
7981       end;
7982
7983       pragma Assert (Present (Pdef));
7984
7985       --  Add private field components
7986
7987       if Present (Private_Declarations (Pdef)) then
7988          Priv := First (Private_Declarations (Pdef));
7989
7990          while Present (Priv) loop
7991
7992             if Nkind (Priv) = N_Component_Declaration then
7993                if not Static_Component_Size (Defining_Identifier (Priv)) then
7994
7995                   --  When compiling for a restricted profile, the private
7996                   --  components must have a static size. If not, this is an
7997                   --  error for a single protected declaration, and rates a
7998                   --  warning on a protected type declaration.
7999
8000                   if not Comes_From_Source (Prot_Typ) then
8001                      Check_Restriction (No_Implicit_Heap_Allocations, Priv);
8002
8003                   elsif Restriction_Active (No_Implicit_Heap_Allocations) then
8004                      Error_Msg_N ("component has non-static size?", Priv);
8005                      Error_Msg_NE
8006                        ("\creation of protected object of type& will violate"
8007                         & " restriction No_Implicit_Heap_Allocations?",
8008                         Priv, Prot_Typ);
8009                   end if;
8010                end if;
8011
8012                --  The component definition consists of a subtype indication,
8013                --  or (in Ada 2005) an access definition. Make a copy of the
8014                --  proper definition.
8015
8016                declare
8017                   Old_Comp : constant Node_Id   := Component_Definition (Priv);
8018                   Oent     : constant Entity_Id := Defining_Identifier (Priv);
8019                   New_Comp : Node_Id;
8020                   Nent     : constant Entity_Id :=
8021                                Make_Defining_Identifier (Sloc (Oent),
8022                                  Chars => Chars (Oent));
8023
8024                begin
8025                   if Present (Subtype_Indication (Old_Comp)) then
8026                      New_Comp :=
8027                        Make_Component_Definition (Sloc (Oent),
8028                          Aliased_Present    => False,
8029                          Subtype_Indication =>
8030                            New_Copy_Tree (Subtype_Indication (Old_Comp),
8031                                            Discr_Map));
8032                   else
8033                      New_Comp :=
8034                        Make_Component_Definition (Sloc (Oent),
8035                          Aliased_Present    => False,
8036                          Access_Definition  =>
8037                            New_Copy_Tree (Access_Definition (Old_Comp),
8038                                            Discr_Map));
8039                   end if;
8040
8041                   New_Priv :=
8042                     Make_Component_Declaration (Loc,
8043                       Defining_Identifier  => Nent,
8044                       Component_Definition => New_Comp,
8045                       Expression           => Expression (Priv));
8046
8047                   Set_Has_Per_Object_Constraint (Nent,
8048                     Has_Per_Object_Constraint (Oent));
8049
8050                   Append_To (Cdecls, New_Priv);
8051                end;
8052
8053             elsif Nkind (Priv) = N_Subprogram_Declaration then
8054
8055                --  Make the unprotected version of the subprogram available
8056                --  for expansion of intra object calls. There is need for
8057                --  a protected version only if the subprogram is an interrupt
8058                --  handler, otherwise  this operation can only be called from
8059                --  within the body.
8060
8061                Sub :=
8062                  Make_Subprogram_Declaration (Loc,
8063                    Specification =>
8064                      Build_Protected_Sub_Specification
8065                        (Priv, Prot_Typ, Unprotected_Mode));
8066
8067                Insert_After (Current_Node, Sub);
8068                Analyze (Sub);
8069
8070                Set_Protected_Body_Subprogram
8071                  (Defining_Unit_Name (Specification (Priv)),
8072                   Defining_Unit_Name (Specification (Sub)));
8073                Check_Inlining (Defining_Unit_Name (Specification (Priv)));
8074                Current_Node := Sub;
8075
8076                Sub :=
8077                  Make_Subprogram_Declaration (Loc,
8078                    Specification =>
8079                      Build_Protected_Sub_Specification
8080                        (Priv, Prot_Typ, Protected_Mode));
8081
8082                Insert_After (Current_Node, Sub);
8083                Analyze (Sub);
8084                Current_Node := Sub;
8085
8086                if Is_Interrupt_Handler
8087                  (Defining_Unit_Name (Specification (Priv)))
8088                then
8089                   if not Restricted_Profile then
8090                      Register_Handler;
8091                   end if;
8092                end if;
8093             end if;
8094
8095             Next (Priv);
8096          end loop;
8097       end if;
8098
8099       --  Put the _Object component after the private component so that it
8100       --  be finalized early as required by 9.4 (20)
8101
8102       Append_To (Cdecls, Object_Comp);
8103
8104       Insert_After (Current_Node, Rec_Decl);
8105       Current_Node := Rec_Decl;
8106
8107       --  Analyze the record declaration immediately after construction,
8108       --  because the initialization procedure is needed for single object
8109       --  declarations before the next entity is analyzed (the freeze call
8110       --  that generates this initialization procedure is found below).
8111
8112       Analyze (Rec_Decl, Suppress => All_Checks);
8113
8114       --  Ada 2005 (AI-345): Construct the primitive entry wrappers before
8115       --  the corresponding record is frozen. If any wrappers are generated,
8116       --  Current_Node is updated accordingly.
8117
8118       if Ada_Version >= Ada_2005 then
8119          Build_Wrapper_Specs (Loc, Prot_Typ, Current_Node);
8120       end if;
8121
8122       --  Collect pointers to entry bodies and their barriers, to be placed
8123       --  in the Entry_Bodies_Array for the type. For each entry/family we
8124       --  add an expression to the aggregate which is the initial value of
8125       --  this array. The array is declared after all protected subprograms.
8126
8127       if Has_Entries (Prot_Typ) then
8128          Entries_Aggr := Make_Aggregate (Loc, Expressions => New_List);
8129       else
8130          Entries_Aggr := Empty;
8131       end if;
8132
8133       --  Build two new procedure specifications for each protected subprogram;
8134       --  one to call from outside the object and one to call from inside.
8135       --  Build a barrier function and an entry body action procedure
8136       --  specification for each protected entry. Initialize the entry body
8137       --  array. If subprogram is flagged as eliminated, do not generate any
8138       --  internal operations.
8139
8140       E_Count := 0;
8141
8142       Comp := First (Visible_Declarations (Pdef));
8143
8144       while Present (Comp) loop
8145          if Nkind (Comp) = N_Subprogram_Declaration then
8146             Sub :=
8147               Make_Subprogram_Declaration (Loc,
8148                 Specification =>
8149                   Build_Protected_Sub_Specification
8150                     (Comp, Prot_Typ, Unprotected_Mode));
8151
8152             Insert_After (Current_Node, Sub);
8153             Analyze (Sub);
8154
8155             Set_Protected_Body_Subprogram
8156               (Defining_Unit_Name (Specification (Comp)),
8157                Defining_Unit_Name (Specification (Sub)));
8158                Check_Inlining (Defining_Unit_Name (Specification (Comp)));
8159
8160             --  Make the protected version of the subprogram available for
8161             --  expansion of external calls.
8162
8163             Current_Node := Sub;
8164
8165             Sub :=
8166               Make_Subprogram_Declaration (Loc,
8167                 Specification =>
8168                   Build_Protected_Sub_Specification
8169                     (Comp, Prot_Typ, Protected_Mode));
8170
8171             Insert_After (Current_Node, Sub);
8172             Analyze (Sub);
8173
8174             Current_Node := Sub;
8175
8176             --  Generate an overriding primitive operation specification for
8177             --  this subprogram if the protected type implements an interface.
8178
8179             if Ada_Version >= Ada_2005
8180               and then
8181                 Present (Interfaces (Corresponding_Record_Type (Prot_Typ)))
8182             then
8183                Sub :=
8184                  Make_Subprogram_Declaration (Loc,
8185                    Specification =>
8186                      Build_Protected_Sub_Specification
8187                        (Comp, Prot_Typ, Dispatching_Mode));
8188
8189                Insert_After (Current_Node, Sub);
8190                Analyze (Sub);
8191
8192                Current_Node := Sub;
8193             end if;
8194
8195             --  If a pragma Interrupt_Handler applies, build and add a call to
8196             --  Register_Interrupt_Handler to the freezing actions of the
8197             --  protected version (Current_Node) of the subprogram:
8198
8199             --    system.interrupts.register_interrupt_handler
8200             --       (prot_procP'address);
8201
8202             if not Restricted_Profile
8203               and then Is_Interrupt_Handler
8204                          (Defining_Unit_Name (Specification (Comp)))
8205             then
8206                Register_Handler;
8207             end if;
8208
8209          elsif Nkind (Comp) = N_Entry_Declaration then
8210             E_Count := E_Count + 1;
8211             Comp_Id := Defining_Identifier (Comp);
8212
8213             Edef :=
8214               Make_Defining_Identifier (Loc,
8215                 Build_Selected_Name (Prot_Typ, Comp_Id, 'E'));
8216             Sub :=
8217               Make_Subprogram_Declaration (Loc,
8218                 Specification =>
8219                   Build_Protected_Entry_Specification (Loc, Edef, Comp_Id));
8220
8221             Insert_After (Current_Node, Sub);
8222             Analyze (Sub);
8223
8224             --  build wrapper procedure for pre/postconditions.
8225
8226             Build_PPC_Wrapper (Comp_Id, N);
8227
8228             Set_Protected_Body_Subprogram
8229               (Defining_Identifier (Comp),
8230                Defining_Unit_Name (Specification (Sub)));
8231
8232             Current_Node := Sub;
8233
8234             Bdef :=
8235               Make_Defining_Identifier (Loc,
8236                 Chars => Build_Selected_Name (Prot_Typ, Comp_Id, 'B'));
8237             Sub :=
8238               Make_Subprogram_Declaration (Loc,
8239                 Specification =>
8240                   Build_Barrier_Function_Specification (Loc, Bdef));
8241
8242             Insert_After (Current_Node, Sub);
8243             Analyze (Sub);
8244             Set_Protected_Body_Subprogram (Bdef, Bdef);
8245             Set_Barrier_Function (Comp_Id, Bdef);
8246             Set_Scope (Bdef, Scope (Comp_Id));
8247             Current_Node := Sub;
8248
8249             --  Collect pointers to the protected subprogram and the barrier
8250             --  of the current entry, for insertion into Entry_Bodies_Array.
8251
8252             Append (
8253               Make_Aggregate (Loc,
8254                 Expressions => New_List (
8255                   Make_Attribute_Reference (Loc,
8256                     Prefix => New_Reference_To (Bdef, Loc),
8257                     Attribute_Name => Name_Unrestricted_Access),
8258                   Make_Attribute_Reference (Loc,
8259                     Prefix => New_Reference_To (Edef, Loc),
8260                     Attribute_Name => Name_Unrestricted_Access))),
8261               Expressions (Entries_Aggr));
8262
8263          end if;
8264
8265          Next (Comp);
8266       end loop;
8267
8268       --  If there are some private entry declarations, expand it as if they
8269       --  were visible entries.
8270
8271       if Present (Private_Declarations (Pdef)) then
8272          Comp := First (Private_Declarations (Pdef));
8273          while Present (Comp) loop
8274             if Nkind (Comp) = N_Entry_Declaration then
8275                E_Count := E_Count + 1;
8276                Comp_Id := Defining_Identifier (Comp);
8277
8278                Edef :=
8279                  Make_Defining_Identifier (Loc,
8280                   Build_Selected_Name (Prot_Typ, Comp_Id, 'E'));
8281                Sub :=
8282                  Make_Subprogram_Declaration (Loc,
8283                    Specification =>
8284                      Build_Protected_Entry_Specification (Loc, Edef, Comp_Id));
8285
8286                Insert_After (Current_Node, Sub);
8287                Analyze (Sub);
8288
8289                Set_Protected_Body_Subprogram
8290                  (Defining_Identifier (Comp),
8291                   Defining_Unit_Name (Specification (Sub)));
8292
8293                Current_Node := Sub;
8294
8295                Bdef :=
8296                  Make_Defining_Identifier (Loc,
8297                    Chars => Build_Selected_Name (Prot_Typ, Comp_Id, 'E'));
8298
8299                Sub :=
8300                  Make_Subprogram_Declaration (Loc,
8301                    Specification =>
8302                      Build_Barrier_Function_Specification (Loc, Bdef));
8303
8304                Insert_After (Current_Node, Sub);
8305                Analyze (Sub);
8306                Set_Protected_Body_Subprogram (Bdef, Bdef);
8307                Set_Barrier_Function (Comp_Id, Bdef);
8308                Set_Scope (Bdef, Scope (Comp_Id));
8309                Current_Node := Sub;
8310
8311                --  Collect pointers to the protected subprogram and the barrier
8312                --  of the current entry, for insertion into Entry_Bodies_Array.
8313
8314                Append_To (Expressions (Entries_Aggr),
8315                  Make_Aggregate (Loc,
8316                    Expressions => New_List (
8317                      Make_Attribute_Reference (Loc,
8318                        Prefix => New_Reference_To (Bdef, Loc),
8319                        Attribute_Name => Name_Unrestricted_Access),
8320                      Make_Attribute_Reference (Loc,
8321                        Prefix => New_Reference_To (Edef, Loc),
8322                        Attribute_Name => Name_Unrestricted_Access))));
8323             end if;
8324
8325             Next (Comp);
8326          end loop;
8327       end if;
8328
8329       --  Emit declaration for Entry_Bodies_Array, now that the addresses of
8330       --  all protected subprograms have been collected.
8331
8332       if Has_Entries (Prot_Typ) then
8333          Body_Id :=
8334            Make_Defining_Identifier (Sloc (Prot_Typ),
8335              Chars => New_External_Name (Chars (Prot_Typ), 'A'));
8336
8337          case Corresponding_Runtime_Package (Prot_Typ) is
8338             when System_Tasking_Protected_Objects_Entries =>
8339                Body_Arr := Make_Object_Declaration (Loc,
8340                  Defining_Identifier => Body_Id,
8341                  Aliased_Present => True,
8342                  Object_Definition =>
8343                    Make_Subtype_Indication (Loc,
8344                      Subtype_Mark => New_Reference_To (
8345                        RTE (RE_Protected_Entry_Body_Array), Loc),
8346                      Constraint =>
8347                        Make_Index_Or_Discriminant_Constraint (Loc,
8348                          Constraints => New_List (
8349                             Make_Range (Loc,
8350                               Make_Integer_Literal (Loc, 1),
8351                               Make_Integer_Literal (Loc, E_Count))))),
8352                  Expression => Entries_Aggr);
8353
8354             when System_Tasking_Protected_Objects_Single_Entry =>
8355                Body_Arr := Make_Object_Declaration (Loc,
8356                  Defining_Identifier => Body_Id,
8357                  Aliased_Present => True,
8358                  Object_Definition => New_Reference_To
8359                                         (RTE (RE_Entry_Body), Loc),
8360                  Expression =>
8361                    Make_Aggregate (Loc,
8362                      Expressions => New_List (
8363                        Make_Attribute_Reference (Loc,
8364                          Prefix => New_Reference_To (Bdef, Loc),
8365                          Attribute_Name => Name_Unrestricted_Access),
8366                        Make_Attribute_Reference (Loc,
8367                          Prefix => New_Reference_To (Edef, Loc),
8368                          Attribute_Name => Name_Unrestricted_Access))));
8369
8370             when others =>
8371                raise Program_Error;
8372          end case;
8373
8374          --  A pointer to this array will be placed in the corresponding record
8375          --  by its initialization procedure so this needs to be analyzed here.
8376
8377          Insert_After (Current_Node, Body_Arr);
8378          Current_Node := Body_Arr;
8379          Analyze (Body_Arr);
8380
8381          Set_Entry_Bodies_Array (Prot_Typ, Body_Id);
8382
8383          --  Finally, build the function that maps an entry index into the
8384          --  corresponding body. A pointer to this function is placed in each
8385          --  object of the type. Except for a ravenscar-like profile (no abort,
8386          --  no entry queue, 1 entry)
8387
8388          if Corresponding_Runtime_Package (Prot_Typ) =
8389               System_Tasking_Protected_Objects_Entries
8390          then
8391             Sub :=
8392               Make_Subprogram_Declaration (Loc,
8393                 Specification => Build_Find_Body_Index_Spec (Prot_Typ));
8394             Insert_After (Current_Node, Sub);
8395             Analyze (Sub);
8396          end if;
8397       end if;
8398    end Expand_N_Protected_Type_Declaration;
8399
8400    --------------------------------
8401    -- Expand_N_Requeue_Statement --
8402    --------------------------------
8403
8404    --  A non-dispatching requeue statement is expanded into one of four GNARLI
8405    --  operations, depending on the source and destination (task or protected
8406    --  object). A dispatching requeue statement is expanded into a call to the
8407    --  predefined primitive _Disp_Requeue. In addition, code is generated to
8408    --  jump around the remainder of processing for the original entry and, if
8409    --  the destination is (different) protected object, to attempt to service
8410    --  it. The following illustrates the various cases:
8411
8412    --  procedure entE
8413    --    (O : System.Address;
8414    --     P : System.Address;
8415    --     E : Protected_Entry_Index)
8416    --  is
8417    --     <discriminant renamings>
8418    --     <private object renamings>
8419    --     type poVP is access poV;
8420    --     _object : ptVP := ptVP!(O);
8421
8422    --  begin
8423    --     begin
8424    --        <start of statement sequence for entry>
8425
8426    --        -- Requeue from one protected entry body to another protected
8427    --        -- entry.
8428
8429    --        Requeue_Protected_Entry (
8430    --          _object._object'Access,
8431    --          new._object'Access,
8432    --          E,
8433    --          Abort_Present);
8434    --        return;
8435
8436    --        <some more of the statement sequence for entry>
8437
8438    --        --  Requeue from an entry body to a task entry
8439
8440    --        Requeue_Protected_To_Task_Entry (
8441    --          New._task_id,
8442    --          E,
8443    --          Abort_Present);
8444    --        return;
8445
8446    --        <rest of statement sequence for entry>
8447    --        Complete_Entry_Body (_object._object);
8448
8449    --     exception
8450    --        when all others =>
8451    --           Exceptional_Complete_Entry_Body (
8452    --             _object._object, Get_GNAT_Exception);
8453    --     end;
8454    --  end entE;
8455
8456    --  Requeue of a task entry call to a task entry
8457
8458    --  Accept_Call (E, Ann);
8459    --     <start of statement sequence for accept statement>
8460    --     Requeue_Task_Entry (New._task_id, E, Abort_Present);
8461    --     goto Lnn;
8462    --     <rest of statement sequence for accept statement>
8463    --     <<Lnn>>
8464    --     Complete_Rendezvous;
8465
8466    --  exception
8467    --     when all others =>
8468    --        Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
8469
8470    --  Requeue of a task entry call to a protected entry
8471
8472    --  Accept_Call (E, Ann);
8473    --     <start of statement sequence for accept statement>
8474    --     Requeue_Task_To_Protected_Entry (
8475    --       new._object'Access,
8476    --       E,
8477    --       Abort_Present);
8478    --     newS (new, Pnn);
8479    --     goto Lnn;
8480    --     <rest of statement sequence for accept statement>
8481    --     <<Lnn>>
8482    --     Complete_Rendezvous;
8483
8484    --  exception
8485    --     when all others =>
8486    --        Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
8487
8488    --  Ada 2012 (AI05-0030): Dispatching requeue to an interface primitive
8489    --  marked by pragma Implemented (XXX, By_Entry).
8490
8491    --  The requeue is inside a protected entry:
8492
8493    --  procedure entE
8494    --    (O : System.Address;
8495    --     P : System.Address;
8496    --     E : Protected_Entry_Index)
8497    --  is
8498    --     <discriminant renamings>
8499    --     <private object renamings>
8500    --     type poVP is access poV;
8501    --     _object : ptVP := ptVP!(O);
8502
8503    --  begin
8504    --     begin
8505    --        <start of statement sequence for entry>
8506
8507    --        _Disp_Requeue
8508    --          (<interface class-wide object>,
8509    --           True,
8510    --           _object'Address,
8511    --           Ada.Tags.Get_Offset_Index
8512    --             (Tag (_object),
8513    --              <interface dispatch table index of target entry>),
8514    --           Abort_Present);
8515    --        return;
8516
8517    --        <rest of statement sequence for entry>
8518    --        Complete_Entry_Body (_object._object);
8519
8520    --     exception
8521    --        when all others =>
8522    --           Exceptional_Complete_Entry_Body (
8523    --             _object._object, Get_GNAT_Exception);
8524    --     end;
8525    --  end entE;
8526
8527    --  The requeue is inside a task entry:
8528
8529    --    Accept_Call (E, Ann);
8530    --     <start of statement sequence for accept statement>
8531    --     _Disp_Requeue
8532    --       (<interface class-wide object>,
8533    --        False,
8534    --        null,
8535    --        Ada.Tags.Get_Offset_Index
8536    --          (Tag (_object),
8537    --           <interface dispatch table index of target entrt>),
8538    --        Abort_Present);
8539    --     newS (new, Pnn);
8540    --     goto Lnn;
8541    --     <rest of statement sequence for accept statement>
8542    --     <<Lnn>>
8543    --     Complete_Rendezvous;
8544
8545    --  exception
8546    --     when all others =>
8547    --        Exceptional_Complete_Rendezvous (Get_GNAT_Exception);
8548
8549    --  Ada 2012 (AI05-0030): Dispatching requeue to an interface primitive
8550    --  marked by pragma Implemented (XXX, By_Protected_Procedure). The requeue
8551    --  statement is replaced by a dispatching call with actual parameters taken
8552    --  from the inner-most accept statement or entry body.
8553
8554    --    Target.Primitive (Param1, ..., ParamN);
8555
8556    --  Ada 2012 (AI05-0030): Dispatching requeue to an interface primitive
8557    --  marked by pragma Implemented (XXX, By_Any) or not marked at all.
8558
8559    --    declare
8560    --       S : constant Offset_Index :=
8561    --             Get_Offset_Index (Tag (Concval), DT_Position (Ename));
8562    --       C : constant Prim_Op_Kind := Get_Prim_Op_Kind (Tag (Concval), S);
8563
8564    --    begin
8565    --       if C = POK_Protected_Entry
8566    --         or else C = POK_Task_Entry
8567    --       then
8568    --          <statements for dispatching requeue>
8569
8570    --       elsif C = POK_Protected_Procedure then
8571    --          <dispatching call equivalent>
8572
8573    --       else
8574    --          raise Program_Error;
8575    --       end if;
8576    --    end;
8577
8578    procedure Expand_N_Requeue_Statement (N : Node_Id) is
8579       Loc      : constant Source_Ptr := Sloc (N);
8580       Conc_Typ : Entity_Id;
8581       Concval  : Node_Id;
8582       Ename    : Node_Id;
8583       Index    : Node_Id;
8584       Old_Typ  : Entity_Id;
8585
8586       function Build_Dispatching_Call_Equivalent return Node_Id;
8587       --  Ada 2012 (AI05-0030): N denotes a dispatching requeue statement of
8588       --  the form Concval.Ename. It is statically known that Ename is allowed
8589       --  to be implemented by a protected procedure. Create a dispatching call
8590       --  equivalent of Concval.Ename taking the actual parameters from the
8591       --  inner-most accept statement or entry body.
8592
8593       function Build_Dispatching_Requeue return Node_Id;
8594       --  Ada 2012 (AI05-0030): N denotes a dispatching requeue statement of
8595       --  the form Concval.Ename. It is statically known that Ename is allowed
8596       --  to be implemented by a protected or a task entry. Create a call to
8597       --  primitive _Disp_Requeue which handles the low-level actions.
8598
8599       function Build_Dispatching_Requeue_To_Any return Node_Id;
8600       --  Ada 2012 (AI05-0030): N denotes a dispatching requeue statement of
8601       --  the form Concval.Ename. Ename is either marked by pragma Implemented
8602       --  (XXX, By_Any) or not marked at all. Create a block which determines
8603       --  at runtime whether Ename denotes an entry or a procedure and perform
8604       --  the appropriate kind of dispatching select.
8605
8606       function Build_Normal_Requeue return Node_Id;
8607       --  N denotes a non-dispatching requeue statement to either a task or a
8608       --  protected entry. Build the appropriate runtime call to perform the
8609       --  action.
8610
8611       function Build_Skip_Statement (Search : Node_Id) return Node_Id;
8612       --  For a protected entry, create a return statement to skip the rest of
8613       --  the entry body. Otherwise, create a goto statement to skip the rest
8614       --  of a task accept statement. The lookup for the enclosing entry body
8615       --  or accept statement starts from Search.
8616
8617       ---------------------------------------
8618       -- Build_Dispatching_Call_Equivalent --
8619       ---------------------------------------
8620
8621       function Build_Dispatching_Call_Equivalent return Node_Id is
8622          Call_Ent : constant Entity_Id := Entity (Ename);
8623          Obj      : constant Node_Id   := Original_Node (Concval);
8624          Acc_Ent  : Node_Id;
8625          Actuals  : List_Id;
8626          Formal   : Node_Id;
8627          Formals  : List_Id;
8628
8629       begin
8630          --  Climb the parent chain looking for the inner-most entry body or
8631          --  accept statement.
8632
8633          Acc_Ent := N;
8634          while Present (Acc_Ent)
8635            and then not Nkind_In (Acc_Ent, N_Accept_Statement,
8636                                            N_Entry_Body)
8637          loop
8638             Acc_Ent := Parent (Acc_Ent);
8639          end loop;
8640
8641          --  A requeue statement should be housed inside an entry body or an
8642          --  accept statement at some level. If this is not the case, then the
8643          --  tree is malformed.
8644
8645          pragma Assert (Present (Acc_Ent));
8646
8647          --  Recover the list of formal parameters
8648
8649          if Nkind (Acc_Ent) = N_Entry_Body then
8650             Acc_Ent := Entry_Body_Formal_Part (Acc_Ent);
8651          end if;
8652
8653          Formals := Parameter_Specifications (Acc_Ent);
8654
8655          --  Create the actual parameters for the dispatching call. These are
8656          --  simply copies of the entry body or accept statement formals in the
8657          --  same order as they appear.
8658
8659          Actuals := No_List;
8660
8661          if Present (Formals) then
8662             Actuals := New_List;
8663             Formal  := First (Formals);
8664             while Present (Formal) loop
8665                Append_To (Actuals,
8666                  Make_Identifier (Loc, Chars (Defining_Identifier (Formal))));
8667                Next (Formal);
8668             end loop;
8669          end if;
8670
8671          --  Generate:
8672          --    Obj.Call_Ent (Actuals);
8673
8674          return
8675            Make_Procedure_Call_Statement (Loc,
8676              Name =>
8677                Make_Selected_Component (Loc,
8678                  Prefix =>
8679                    Make_Identifier (Loc, Chars (Obj)),
8680                  Selector_Name =>
8681                    Make_Identifier (Loc, Chars (Call_Ent))),
8682
8683              Parameter_Associations => Actuals);
8684       end Build_Dispatching_Call_Equivalent;
8685
8686       -------------------------------
8687       -- Build_Dispatching_Requeue --
8688       -------------------------------
8689
8690       function Build_Dispatching_Requeue return Node_Id is
8691          Params : constant List_Id := New_List;
8692
8693       begin
8694          --  Process the "with abort" parameter
8695
8696          Prepend_To (Params,
8697            New_Reference_To (Boolean_Literals (Abort_Present (N)), Loc));
8698
8699          --  Process the entry wrapper's position in the primary dispatch
8700          --  table parameter. Generate:
8701
8702          --    Ada.Tags.Get_Offset_Index
8703          --      (Ada.Tags.Tag (Concval),
8704          --       <interface dispatch table position of Ename>)
8705
8706          Prepend_To (Params,
8707            Make_Function_Call (Loc,
8708              Name =>
8709                New_Reference_To (RTE (RE_Get_Offset_Index), Loc),
8710
8711              Parameter_Associations => New_List (
8712                Unchecked_Convert_To (RTE (RE_Tag), Concval),
8713                Make_Integer_Literal (Loc, DT_Position (Entity (Ename))))));
8714
8715          --  Specific actuals for protected to XXX requeue
8716
8717          if Is_Protected_Type (Old_Typ) then
8718             Prepend_To (Params,
8719               Make_Attribute_Reference (Loc,        --  _object'Address
8720                 Prefix =>
8721                   Concurrent_Ref (New_Occurrence_Of (Old_Typ, Loc)),
8722                 Attribute_Name => Name_Address));
8723
8724             Prepend_To (Params,                     --  True
8725               New_Reference_To (Standard_True, Loc));
8726
8727          --  Specific actuals for task to XXX requeue
8728
8729          else
8730             pragma Assert (Is_Task_Type (Old_Typ));
8731
8732             Prepend_To (Params,                     --  null
8733               New_Reference_To (RTE (RE_Null_Address), Loc));
8734
8735             Prepend_To (Params,                     --  False
8736               New_Reference_To (Standard_False, Loc));
8737          end if;
8738
8739          --  Add the object parameter
8740
8741          Prepend_To (Params, New_Copy_Tree (Concval));
8742
8743          --  Generate:
8744          --    _Disp_Requeue (<Params>);
8745
8746          return
8747            Make_Procedure_Call_Statement (Loc,
8748              Name =>
8749                Make_Identifier (Loc, Name_uDisp_Requeue),
8750              Parameter_Associations => Params);
8751       end Build_Dispatching_Requeue;
8752
8753       --------------------------------------
8754       -- Build_Dispatching_Requeue_To_Any --
8755       --------------------------------------
8756
8757       function Build_Dispatching_Requeue_To_Any return Node_Id is
8758          Call_Ent : constant Entity_Id := Entity (Ename);
8759          Obj      : constant Node_Id   := Original_Node (Concval);
8760          Skip     : constant Node_Id   := Build_Skip_Statement (N);
8761          C        : Entity_Id;
8762          Decls    : List_Id;
8763          S        : Entity_Id;
8764          Stmts    : List_Id;
8765
8766       begin
8767          Decls := New_List;
8768          Stmts := New_List;
8769
8770          --  Dispatch table slot processing, generate:
8771          --    S : Integer;
8772
8773          S := Build_S (Loc, Decls);
8774
8775          --  Call kind processing, generate:
8776          --    C : Ada.Tags.Prim_Op_Kind;
8777
8778          C := Build_C (Loc, Decls);
8779
8780          --  Generate:
8781          --    S := Ada.Tags.Get_Offset_Index
8782          --           (Ada.Tags.Tag (Obj), DT_Position (Call_Ent));
8783
8784          Append_To (Stmts, Build_S_Assignment (Loc, S, Obj, Call_Ent));
8785
8786          --  Generate:
8787          --    _Disp_Get_Prim_Op_Kind (Obj, S, C);
8788
8789          Append_To (Stmts,
8790            Make_Procedure_Call_Statement (Loc,
8791              Name =>
8792                New_Reference_To (
8793                  Find_Prim_Op (Etype (Etype (Obj)),
8794                    Name_uDisp_Get_Prim_Op_Kind),
8795                  Loc),
8796              Parameter_Associations => New_List (
8797                New_Copy_Tree (Obj),
8798                New_Reference_To (S, Loc),
8799                New_Reference_To (C, Loc))));
8800
8801          Append_To (Stmts,
8802
8803             --  if C = POK_Protected_Entry
8804             --    or else C = POK_Task_Entry
8805             --  then
8806
8807            Make_If_Statement (Loc,
8808              Condition =>
8809                Make_Op_Or (Loc,
8810                  Left_Opnd =>
8811                    Make_Op_Eq (Loc,
8812                      Left_Opnd =>
8813                        New_Reference_To (C, Loc),
8814                      Right_Opnd =>
8815                        New_Reference_To (RTE (RE_POK_Protected_Entry), Loc)),
8816
8817                  Right_Opnd =>
8818                    Make_Op_Eq (Loc,
8819                      Left_Opnd =>
8820                        New_Reference_To (C, Loc),
8821                      Right_Opnd =>
8822                        New_Reference_To (RTE (RE_POK_Task_Entry), Loc))),
8823
8824                --  Dispatching requeue equivalent
8825
8826              Then_Statements => New_List (
8827                Build_Dispatching_Requeue,
8828                Skip),
8829
8830                --  elsif C = POK_Protected_Procedure then
8831
8832              Elsif_Parts => New_List (
8833                Make_Elsif_Part (Loc,
8834                  Condition =>
8835                    Make_Op_Eq (Loc,
8836                      Left_Opnd =>
8837                        New_Reference_To (C, Loc),
8838                      Right_Opnd =>
8839                        New_Reference_To (
8840                          RTE (RE_POK_Protected_Procedure), Loc)),
8841
8842                   --  Dispatching call equivalent
8843
8844                  Then_Statements => New_List (
8845                    Build_Dispatching_Call_Equivalent))),
8846
8847             --  else
8848             --     raise Program_Error;
8849             --  end if;
8850
8851              Else_Statements => New_List (
8852                Make_Raise_Program_Error (Loc,
8853                  Reason => PE_Explicit_Raise))));
8854
8855          --  Wrap everything into a block
8856
8857          return
8858            Make_Block_Statement (Loc,
8859              Declarations => Decls,
8860              Handled_Statement_Sequence =>
8861                Make_Handled_Sequence_Of_Statements (Loc,
8862                  Statements => Stmts));
8863       end Build_Dispatching_Requeue_To_Any;
8864
8865       --------------------------
8866       -- Build_Normal_Requeue --
8867       --------------------------
8868
8869       function Build_Normal_Requeue return Node_Id is
8870          Params  : constant List_Id := New_List;
8871          Param   : Node_Id;
8872          RT_Call : Node_Id;
8873
8874       begin
8875          --  Process the "with abort" parameter
8876
8877          Prepend_To (Params,
8878            New_Reference_To (Boolean_Literals (Abort_Present (N)), Loc));
8879
8880          --  Add the index expression to the parameters. It is common among all
8881          --  four cases.
8882
8883          Prepend_To (Params,
8884            Entry_Index_Expression (Loc, Entity (Ename), Index, Conc_Typ));
8885
8886          if Is_Protected_Type (Old_Typ) then
8887             declare
8888                Self_Param : Node_Id;
8889
8890             begin
8891                Self_Param :=
8892                  Make_Attribute_Reference (Loc,
8893                    Prefix =>
8894                      Concurrent_Ref (New_Occurrence_Of (Old_Typ, Loc)),
8895                    Attribute_Name =>
8896                      Name_Unchecked_Access);
8897
8898                --  Protected to protected requeue
8899
8900                if Is_Protected_Type (Conc_Typ) then
8901                   RT_Call :=
8902                     New_Reference_To (
8903                       RTE (RE_Requeue_Protected_Entry), Loc);
8904
8905                   Param :=
8906                     Make_Attribute_Reference (Loc,
8907                       Prefix =>
8908                         Concurrent_Ref (Concval),
8909                       Attribute_Name =>
8910                         Name_Unchecked_Access);
8911
8912                --  Protected to task requeue
8913
8914                else pragma Assert (Is_Task_Type (Conc_Typ));
8915                   RT_Call :=
8916                     New_Reference_To (
8917                       RTE (RE_Requeue_Protected_To_Task_Entry), Loc);
8918
8919                   Param := Concurrent_Ref (Concval);
8920                end if;
8921
8922                Prepend_To (Params, Param);
8923                Prepend_To (Params, Self_Param);
8924             end;
8925
8926          else pragma Assert (Is_Task_Type (Old_Typ));
8927
8928             --  Task to protected requeue
8929
8930             if Is_Protected_Type (Conc_Typ) then
8931                RT_Call :=
8932                  New_Reference_To (
8933                    RTE (RE_Requeue_Task_To_Protected_Entry), Loc);
8934
8935                Param :=
8936                  Make_Attribute_Reference (Loc,
8937                    Prefix =>
8938                      Concurrent_Ref (Concval),
8939                    Attribute_Name =>
8940                      Name_Unchecked_Access);
8941
8942             --  Task to task requeue
8943
8944             else pragma Assert (Is_Task_Type (Conc_Typ));
8945                RT_Call :=
8946                  New_Reference_To (RTE (RE_Requeue_Task_Entry), Loc);
8947
8948                Param := Concurrent_Ref (Concval);
8949             end if;
8950
8951             Prepend_To (Params, Param);
8952          end if;
8953
8954          return
8955             Make_Procedure_Call_Statement (Loc,
8956               Name => RT_Call,
8957               Parameter_Associations => Params);
8958       end Build_Normal_Requeue;
8959
8960       --------------------------
8961       -- Build_Skip_Statement --
8962       --------------------------
8963
8964       function Build_Skip_Statement (Search : Node_Id) return Node_Id is
8965          Skip_Stmt : Node_Id;
8966
8967       begin
8968          --  Build a return statement to skip the rest of the entire body
8969
8970          if Is_Protected_Type (Old_Typ) then
8971             Skip_Stmt := Make_Simple_Return_Statement (Loc);
8972
8973          --  If the requeue is within a task, find the end label of the
8974          --  enclosing accept statement and create a goto statement to it.
8975
8976          else
8977             declare
8978                Acc   : Node_Id;
8979                Label : Node_Id;
8980
8981             begin
8982                --  Climb the parent chain looking for the enclosing accept
8983                --  statement.
8984
8985                Acc := Parent (Search);
8986                while Present (Acc)
8987                  and then Nkind (Acc) /= N_Accept_Statement
8988                loop
8989                   Acc := Parent (Acc);
8990                end loop;
8991
8992                --  The last statement is the second label used for completing
8993                --  the rendezvous the usual way. The label we are looking for
8994                --  is right before it.
8995
8996                Label :=
8997                  Prev (Last (Statements (Handled_Statement_Sequence (Acc))));
8998
8999                pragma Assert (Nkind (Label) = N_Label);
9000
9001                --  Generate a goto statement to skip the rest of the accept
9002
9003                Skip_Stmt :=
9004                  Make_Goto_Statement (Loc,
9005                    Name =>
9006                      New_Occurrence_Of (Entity (Identifier (Label)), Loc));
9007             end;
9008          end if;
9009
9010          Set_Analyzed (Skip_Stmt);
9011
9012          return Skip_Stmt;
9013       end Build_Skip_Statement;
9014
9015    --  Start of processing for Expand_N_Requeue_Statement
9016
9017    begin
9018       --  Extract the components of the entry call
9019
9020       Extract_Entry (N, Concval, Ename, Index);
9021       Conc_Typ := Etype (Concval);
9022
9023       --  Examine the scope stack in order to find nearest enclosing protected
9024       --  or task type. This will constitute our invocation source.
9025
9026       Old_Typ := Current_Scope;
9027       while Present (Old_Typ)
9028         and then not Is_Protected_Type (Old_Typ)
9029         and then not Is_Task_Type (Old_Typ)
9030       loop
9031          Old_Typ := Scope (Old_Typ);
9032       end loop;
9033
9034       --  Ada 2012 (AI05-0030): We have a dispatching requeue of the form
9035       --  Concval.Ename where the type of Concval is class-wide concurrent
9036       --  interface.
9037
9038       if Ada_Version >= Ada_2012
9039         and then Present (Concval)
9040         and then Is_Class_Wide_Type (Conc_Typ)
9041         and then Is_Concurrent_Interface (Conc_Typ)
9042       then
9043          declare
9044             Has_Impl  : Boolean := False;
9045             Impl_Kind : Name_Id := No_Name;
9046
9047          begin
9048             --  Check whether the Ename is flagged by pragma Implemented
9049
9050             if Has_Rep_Pragma (Entity (Ename), Name_Implemented) then
9051                Has_Impl  := True;
9052                Impl_Kind := Implementation_Kind (Entity (Ename));
9053             end if;
9054
9055             --  The procedure_or_entry_NAME is guaranteed to be overridden by
9056             --  an entry. Create a call to predefined primitive _Disp_Requeue.
9057
9058             if Has_Impl
9059               and then Impl_Kind = Name_By_Entry
9060             then
9061                Rewrite (N, Build_Dispatching_Requeue);
9062                Analyze (N);
9063                Insert_After (N, Build_Skip_Statement (N));
9064
9065             --  The procedure_or_entry_NAME is guaranteed to be overridden by
9066             --  a protected procedure. In this case the requeue is transformed
9067             --  into a dispatching call.
9068
9069             elsif Has_Impl
9070               and then Impl_Kind = Name_By_Protected_Procedure
9071             then
9072                Rewrite (N, Build_Dispatching_Call_Equivalent);
9073                Analyze (N);
9074
9075             --  The procedure_or_entry_NAME's implementation kind is either
9076             --  By_Any or pragma Implemented was not applied at all. In this
9077             --  case a runtime test determines whether Ename denotes an entry
9078             --  or a protected procedure and performs the appropriate call.
9079
9080             else
9081                Rewrite (N, Build_Dispatching_Requeue_To_Any);
9082                Analyze (N);
9083             end if;
9084          end;
9085
9086       --  Processing for regular (non-dispatching) requeues
9087
9088       else
9089          Rewrite (N, Build_Normal_Requeue);
9090          Analyze (N);
9091          Insert_After (N, Build_Skip_Statement (N));
9092       end if;
9093    end Expand_N_Requeue_Statement;
9094
9095    -------------------------------
9096    -- Expand_N_Selective_Accept --
9097    -------------------------------
9098
9099    procedure Expand_N_Selective_Accept (N : Node_Id) is
9100       Loc            : constant Source_Ptr := Sloc (N);
9101       Alts           : constant List_Id    := Select_Alternatives (N);
9102
9103       --  Note: in the below declarations a lot of new lists are allocated
9104       --  unconditionally which may well not end up being used. That's
9105       --  not a good idea since it wastes space gratuitously ???
9106
9107       Accept_Case    : List_Id;
9108       Accept_List    : constant List_Id := New_List;
9109
9110       Alt            : Node_Id;
9111       Alt_List       : constant List_Id := New_List;
9112       Alt_Stats      : List_Id;
9113       Ann            : Entity_Id := Empty;
9114
9115       Block          : Node_Id;
9116       Check_Guard    : Boolean := True;
9117
9118       Decls          : constant List_Id := New_List;
9119       Stats          : constant List_Id := New_List;
9120       Body_List      : constant List_Id := New_List;
9121       Trailing_List  : constant List_Id := New_List;
9122
9123       Choices        : List_Id;
9124       Else_Present   : Boolean := False;
9125       Terminate_Alt  : Node_Id := Empty;
9126       Select_Mode    : Node_Id;
9127
9128       Delay_Case     : List_Id;
9129       Delay_Count    : Integer := 0;
9130       Delay_Val      : Entity_Id;
9131       Delay_Index    : Entity_Id;
9132       Delay_Min      : Entity_Id;
9133       Delay_Num      : Int := 1;
9134       Delay_Alt_List : List_Id := New_List;
9135       Delay_List     : constant List_Id := New_List;
9136       D              : Entity_Id;
9137       M              : Entity_Id;
9138
9139       First_Delay    : Boolean := True;
9140       Guard_Open     : Entity_Id;
9141
9142       End_Lab        : Node_Id;
9143       Index          : Int := 1;
9144       Lab            : Node_Id;
9145       Num_Alts       : Int;
9146       Num_Accept     : Nat := 0;
9147       Proc           : Node_Id;
9148       Q              : Node_Id;
9149       Time_Type      : Entity_Id;
9150       X              : Node_Id;
9151       Select_Call    : Node_Id;
9152
9153       Qnam : constant Entity_Id :=
9154                Make_Defining_Identifier (Loc, New_External_Name ('S', 0));
9155
9156       Xnam : constant Entity_Id :=
9157                Make_Defining_Identifier (Loc, New_External_Name ('J', 1));
9158
9159       -----------------------
9160       -- Local subprograms --
9161       -----------------------
9162
9163       function Accept_Or_Raise return List_Id;
9164       --  For the rare case where delay alternatives all have guards, and
9165       --  all of them are closed, it is still possible that there were open
9166       --  accept alternatives with no callers. We must reexamine the
9167       --  Accept_List, and execute a selective wait with no else if some
9168       --  accept is open. If none, we raise program_error.
9169
9170       procedure Add_Accept (Alt : Node_Id);
9171       --  Process a single accept statement in a select alternative. Build
9172       --  procedure for body of accept, and add entry to dispatch table with
9173       --  expression for guard, in preparation for call to run time select.
9174
9175       function Make_And_Declare_Label (Num : Int) return Node_Id;
9176       --  Manufacture a label using Num as a serial number and declare it.
9177       --  The declaration is appended to Decls. The label marks the trailing
9178       --  statements of an accept or delay alternative.
9179
9180       function Make_Select_Call (Select_Mode : Entity_Id) return Node_Id;
9181       --  Build call to Selective_Wait runtime routine
9182
9183       procedure Process_Delay_Alternative (Alt : Node_Id; Index : Int);
9184       --  Add code to compare value of delay with previous values, and
9185       --  generate case entry for trailing statements.
9186
9187       procedure Process_Accept_Alternative
9188         (Alt   : Node_Id;
9189          Index : Int;
9190          Proc  : Node_Id);
9191       --  Add code to call corresponding procedure, and branch to
9192       --  trailing statements, if any.
9193
9194       ---------------------
9195       -- Accept_Or_Raise --
9196       ---------------------
9197
9198       function Accept_Or_Raise return List_Id is
9199          Cond  : Node_Id;
9200          Stats : List_Id;
9201          J     : constant Entity_Id := Make_Temporary (Loc, 'J');
9202
9203       begin
9204          --  We generate the following:
9205
9206          --    for J in q'range loop
9207          --       if q(J).S /=null_task_entry then
9208          --          selective_wait (simple_mode,...);
9209          --          done := True;
9210          --          exit;
9211          --       end if;
9212          --    end loop;
9213          --
9214          --    if no rendez_vous then
9215          --       raise program_error;
9216          --    end if;
9217
9218          --    Note that the code needs to know that the selector name
9219          --    in an Accept_Alternative is named S.
9220
9221          Cond := Make_Op_Ne (Loc,
9222            Left_Opnd =>
9223              Make_Selected_Component (Loc,
9224                Prefix => Make_Indexed_Component (Loc,
9225                  Prefix => New_Reference_To (Qnam, Loc),
9226                    Expressions => New_List (New_Reference_To (J, Loc))),
9227              Selector_Name => Make_Identifier (Loc, Name_S)),
9228            Right_Opnd =>
9229              New_Reference_To (RTE (RE_Null_Task_Entry), Loc));
9230
9231          Stats := New_List (
9232            Make_Implicit_Loop_Statement (N,
9233              Identifier => Empty,
9234              Iteration_Scheme =>
9235                Make_Iteration_Scheme (Loc,
9236                  Loop_Parameter_Specification =>
9237                    Make_Loop_Parameter_Specification (Loc,
9238                      Defining_Identifier => J,
9239                      Discrete_Subtype_Definition =>
9240                        Make_Attribute_Reference (Loc,
9241                          Prefix => New_Reference_To (Qnam, Loc),
9242                          Attribute_Name => Name_Range,
9243                          Expressions => New_List (
9244                            Make_Integer_Literal (Loc, 1))))),
9245
9246              Statements => New_List (
9247                Make_Implicit_If_Statement (N,
9248                  Condition =>  Cond,
9249                  Then_Statements => New_List (
9250                    Make_Select_Call (
9251                     New_Reference_To (RTE (RE_Simple_Mode), Loc)),
9252                    Make_Exit_Statement (Loc))))));
9253
9254          Append_To (Stats,
9255            Make_Raise_Program_Error (Loc,
9256              Condition => Make_Op_Eq (Loc,
9257                Left_Opnd  => New_Reference_To (Xnam, Loc),
9258                Right_Opnd =>
9259                  New_Reference_To (RTE (RE_No_Rendezvous), Loc)),
9260              Reason => PE_All_Guards_Closed));
9261
9262          return Stats;
9263       end Accept_Or_Raise;
9264
9265       ----------------
9266       -- Add_Accept --
9267       ----------------
9268
9269       procedure Add_Accept (Alt : Node_Id) is
9270          Acc_Stm   : constant Node_Id    := Accept_Statement (Alt);
9271          Ename     : constant Node_Id    := Entry_Direct_Name (Acc_Stm);
9272          Eloc      : constant Source_Ptr := Sloc (Ename);
9273          Eent      : constant Entity_Id  := Entity (Ename);
9274          Index     : constant Node_Id    := Entry_Index (Acc_Stm);
9275          Null_Body : Node_Id;
9276          Proc_Body : Node_Id;
9277          PB_Ent    : Entity_Id;
9278          Expr      : Node_Id;
9279          Call      : Node_Id;
9280
9281       begin
9282          if No (Ann) then
9283             Ann := Node (Last_Elmt (Accept_Address (Eent)));
9284          end if;
9285
9286          if Present (Condition (Alt)) then
9287             Expr :=
9288               Make_Conditional_Expression (Eloc, New_List (
9289                 Condition (Alt),
9290                 Entry_Index_Expression (Eloc, Eent, Index, Scope (Eent)),
9291                 New_Reference_To (RTE (RE_Null_Task_Entry), Eloc)));
9292          else
9293             Expr :=
9294               Entry_Index_Expression
9295                 (Eloc, Eent, Index, Scope (Eent));
9296          end if;
9297
9298          if Present (Handled_Statement_Sequence (Accept_Statement (Alt))) then
9299             Null_Body := New_Reference_To (Standard_False, Eloc);
9300
9301             if Abort_Allowed then
9302                Call := Make_Procedure_Call_Statement (Eloc,
9303                  Name => New_Reference_To (RTE (RE_Abort_Undefer), Eloc));
9304                Insert_Before (First (Statements (Handled_Statement_Sequence (
9305                  Accept_Statement (Alt)))), Call);
9306                Analyze (Call);
9307             end if;
9308
9309             PB_Ent :=
9310               Make_Defining_Identifier (Eloc,
9311                 New_External_Name (Chars (Ename), 'A', Num_Accept));
9312
9313             if Comes_From_Source (Alt) then
9314                Set_Debug_Info_Needed (PB_Ent);
9315             end if;
9316
9317             Proc_Body :=
9318               Make_Subprogram_Body (Eloc,
9319                 Specification =>
9320                   Make_Procedure_Specification (Eloc,
9321                     Defining_Unit_Name => PB_Ent),
9322                Declarations => Declarations (Acc_Stm),
9323                Handled_Statement_Sequence =>
9324                  Build_Accept_Body (Accept_Statement (Alt)));
9325
9326             --  During the analysis of the body of the accept statement, any
9327             --  zero cost exception handler records were collected in the
9328             --  Accept_Handler_Records field of the N_Accept_Alternative node.
9329             --  This is where we move them to where they belong, namely the
9330             --  newly created procedure.
9331
9332             Set_Handler_Records (PB_Ent, Accept_Handler_Records (Alt));
9333             Append (Proc_Body, Body_List);
9334
9335          else
9336             Null_Body := New_Reference_To (Standard_True,  Eloc);
9337
9338             --  if accept statement has declarations, insert above, given that
9339             --  we are not creating a body for the accept.
9340
9341             if Present (Declarations (Acc_Stm)) then
9342                Insert_Actions (N, Declarations (Acc_Stm));
9343             end if;
9344          end if;
9345
9346          Append_To (Accept_List,
9347            Make_Aggregate (Eloc, Expressions => New_List (Null_Body, Expr)));
9348
9349          Num_Accept := Num_Accept + 1;
9350       end Add_Accept;
9351
9352       ----------------------------
9353       -- Make_And_Declare_Label --
9354       ----------------------------
9355
9356       function Make_And_Declare_Label (Num : Int) return Node_Id is
9357          Lab_Id : Node_Id;
9358
9359       begin
9360          Lab_Id := Make_Identifier (Loc, New_External_Name ('L', Num));
9361          Lab :=
9362            Make_Label (Loc, Lab_Id);
9363
9364          Append_To (Decls,
9365            Make_Implicit_Label_Declaration (Loc,
9366              Defining_Identifier  =>
9367                Make_Defining_Identifier (Loc, Chars (Lab_Id)),
9368              Label_Construct => Lab));
9369
9370          return Lab;
9371       end Make_And_Declare_Label;
9372
9373       ----------------------
9374       -- Make_Select_Call --
9375       ----------------------
9376
9377       function Make_Select_Call (Select_Mode : Entity_Id) return Node_Id is
9378          Params : constant List_Id := New_List;
9379
9380       begin
9381          Append (
9382            Make_Attribute_Reference (Loc,
9383              Prefix => New_Reference_To (Qnam, Loc),
9384              Attribute_Name => Name_Unchecked_Access),
9385            Params);
9386          Append (Select_Mode, Params);
9387          Append (New_Reference_To (Ann, Loc), Params);
9388          Append (New_Reference_To (Xnam, Loc), Params);
9389
9390          return
9391            Make_Procedure_Call_Statement (Loc,
9392              Name => New_Reference_To (RTE (RE_Selective_Wait), Loc),
9393              Parameter_Associations => Params);
9394       end Make_Select_Call;
9395
9396       --------------------------------
9397       -- Process_Accept_Alternative --
9398       --------------------------------
9399
9400       procedure Process_Accept_Alternative
9401         (Alt   : Node_Id;
9402          Index : Int;
9403          Proc  : Node_Id)
9404       is
9405          Choices   : List_Id := No_List;
9406          Alt_Stats : List_Id;
9407
9408       begin
9409          Adjust_Condition (Condition (Alt));
9410          Alt_Stats := No_List;
9411
9412          if Present (Handled_Statement_Sequence (Accept_Statement (Alt))) then
9413             Choices := New_List (
9414               Make_Integer_Literal (Loc, Index));
9415
9416             Alt_Stats := New_List (
9417               Make_Procedure_Call_Statement (Sloc (Proc),
9418                 Name => New_Reference_To (
9419                   Defining_Unit_Name (Specification (Proc)), Sloc (Proc))));
9420          end if;
9421
9422          if Statements (Alt) /= Empty_List then
9423
9424             if No (Alt_Stats) then
9425
9426                --  Accept with no body, followed by trailing statements
9427
9428                Choices := New_List (
9429                  Make_Integer_Literal (Loc, Index));
9430
9431                Alt_Stats := New_List;
9432             end if;
9433
9434             --  After the call, if any, branch to trailing statements. We
9435             --  create a label for each, as well as the corresponding label
9436             --  declaration.
9437
9438             Lab := Make_And_Declare_Label (Index);
9439             Append_To (Alt_Stats,
9440               Make_Goto_Statement (Loc,
9441                 Name => New_Copy (Identifier (Lab))));
9442
9443             Append (Lab, Trailing_List);
9444             Append_List (Statements (Alt), Trailing_List);
9445             Append_To (Trailing_List,
9446               Make_Goto_Statement (Loc,
9447                 Name => New_Copy (Identifier (End_Lab))));
9448          end if;
9449
9450          if Present (Alt_Stats) then
9451
9452             --  Procedure call. and/or trailing statements
9453
9454             Append_To (Alt_List,
9455               Make_Case_Statement_Alternative (Loc,
9456                 Discrete_Choices => Choices,
9457                 Statements => Alt_Stats));
9458          end if;
9459       end Process_Accept_Alternative;
9460
9461       -------------------------------
9462       -- Process_Delay_Alternative --
9463       -------------------------------
9464
9465       procedure Process_Delay_Alternative (Alt : Node_Id; Index : Int) is
9466          Choices   : List_Id;
9467          Cond      : Node_Id;
9468          Delay_Alt : List_Id;
9469
9470       begin
9471          --  Deal with C/Fortran boolean as delay condition
9472
9473          Adjust_Condition (Condition (Alt));
9474
9475          --  Determine the smallest specified delay
9476
9477          --  for each delay alternative generate:
9478
9479          --    if guard-expression then
9480          --       Delay_Val  := delay-expression;
9481          --       Guard_Open := True;
9482          --       if Delay_Val < Delay_Min then
9483          --          Delay_Min   := Delay_Val;
9484          --          Delay_Index := Index;
9485          --       end if;
9486          --    end if;
9487
9488          --  The enclosing if-statement is omitted if there is no guard
9489
9490          if Delay_Count = 1
9491            or else First_Delay
9492          then
9493             First_Delay := False;
9494
9495             Delay_Alt := New_List (
9496               Make_Assignment_Statement (Loc,
9497                 Name => New_Reference_To (Delay_Min, Loc),
9498                 Expression => Expression (Delay_Statement (Alt))));
9499
9500             if Delay_Count > 1 then
9501                Append_To (Delay_Alt,
9502                  Make_Assignment_Statement (Loc,
9503                    Name       => New_Reference_To (Delay_Index, Loc),
9504                    Expression => Make_Integer_Literal (Loc, Index)));
9505             end if;
9506
9507          else
9508             Delay_Alt := New_List (
9509               Make_Assignment_Statement (Loc,
9510                 Name => New_Reference_To (Delay_Val, Loc),
9511                 Expression => Expression (Delay_Statement (Alt))));
9512
9513             if Time_Type = Standard_Duration then
9514                Cond :=
9515                   Make_Op_Lt (Loc,
9516                     Left_Opnd  => New_Reference_To (Delay_Val, Loc),
9517                     Right_Opnd => New_Reference_To (Delay_Min, Loc));
9518
9519             else
9520                --  The scope of the time type must define a comparison
9521                --  operator. The scope itself may not be visible, so we
9522                --  construct a node with entity information to insure that
9523                --  semantic analysis can find the proper operator.
9524
9525                Cond :=
9526                  Make_Function_Call (Loc,
9527                    Name => Make_Selected_Component (Loc,
9528                      Prefix => New_Reference_To (Scope (Time_Type), Loc),
9529                      Selector_Name =>
9530                        Make_Operator_Symbol (Loc,
9531                          Chars => Name_Op_Lt,
9532                          Strval => No_String)),
9533                     Parameter_Associations =>
9534                       New_List (
9535                         New_Reference_To (Delay_Val, Loc),
9536                         New_Reference_To (Delay_Min, Loc)));
9537
9538                Set_Entity (Prefix (Name (Cond)), Scope (Time_Type));
9539             end if;
9540
9541             Append_To (Delay_Alt,
9542               Make_Implicit_If_Statement (N,
9543                 Condition => Cond,
9544                 Then_Statements => New_List (
9545                   Make_Assignment_Statement (Loc,
9546                     Name       => New_Reference_To (Delay_Min, Loc),
9547                     Expression => New_Reference_To (Delay_Val, Loc)),
9548
9549                   Make_Assignment_Statement (Loc,
9550                     Name       => New_Reference_To (Delay_Index, Loc),
9551                     Expression => Make_Integer_Literal (Loc, Index)))));
9552          end if;
9553
9554          if Check_Guard then
9555             Append_To (Delay_Alt,
9556               Make_Assignment_Statement (Loc,
9557                 Name => New_Reference_To (Guard_Open, Loc),
9558                 Expression => New_Reference_To (Standard_True, Loc)));
9559          end if;
9560
9561          if Present (Condition (Alt)) then
9562             Delay_Alt := New_List (
9563               Make_Implicit_If_Statement (N,
9564                 Condition => Condition (Alt),
9565                 Then_Statements => Delay_Alt));
9566          end if;
9567
9568          Append_List (Delay_Alt, Delay_List);
9569
9570          --  If the delay alternative has a statement part, add choice to the
9571          --  case statements for delays.
9572
9573          if Present (Statements (Alt)) then
9574
9575             if Delay_Count = 1 then
9576                Append_List (Statements (Alt), Delay_Alt_List);
9577
9578             else
9579                Choices := New_List (
9580                  Make_Integer_Literal (Loc, Index));
9581
9582                Append_To (Delay_Alt_List,
9583                  Make_Case_Statement_Alternative (Loc,
9584                    Discrete_Choices => Choices,
9585                    Statements => Statements (Alt)));
9586             end if;
9587
9588          elsif Delay_Count = 1 then
9589
9590             --  If the single delay has no trailing statements, add a branch
9591             --  to the exit label to the selective wait.
9592
9593             Delay_Alt_List := New_List (
9594               Make_Goto_Statement (Loc,
9595                 Name => New_Copy (Identifier (End_Lab))));
9596
9597          end if;
9598       end Process_Delay_Alternative;
9599
9600    --  Start of processing for Expand_N_Selective_Accept
9601
9602    begin
9603       --  First insert some declarations before the select. The first is:
9604
9605       --    Ann : Address
9606
9607       --  This variable holds the parameters passed to the accept body. This
9608       --  declaration has already been inserted by the time we get here by
9609       --  a call to Expand_Accept_Declarations made from the semantics when
9610       --  processing the first accept statement contained in the select. We
9611       --  can find this entity as Accept_Address (E), where E is any of the
9612       --  entries references by contained accept statements.
9613
9614       --  The first step is to scan the list of Selective_Accept_Statements
9615       --  to find this entity, and also count the number of accepts, and
9616       --  determine if terminated, delay or else is present:
9617
9618       Num_Alts := 0;
9619
9620       Alt := First (Alts);
9621       while Present (Alt) loop
9622
9623          if Nkind (Alt) = N_Accept_Alternative then
9624             Add_Accept (Alt);
9625
9626          elsif Nkind (Alt) = N_Delay_Alternative then
9627             Delay_Count := Delay_Count + 1;
9628
9629             --  If the delays are relative delays, the delay expressions have
9630             --  type Standard_Duration. Otherwise they must have some time type
9631             --  recognized by GNAT.
9632
9633             if Nkind (Delay_Statement (Alt)) = N_Delay_Relative_Statement then
9634                Time_Type := Standard_Duration;
9635             else
9636                Time_Type := Etype (Expression (Delay_Statement (Alt)));
9637
9638                if Is_RTE (Base_Type (Etype (Time_Type)), RO_CA_Time)
9639                  or else Is_RTE (Base_Type (Etype (Time_Type)), RO_RT_Time)
9640                then
9641                   null;
9642                else
9643                   Error_Msg_NE (
9644                     "& is not a time type (RM 9.6(6))",
9645                        Expression (Delay_Statement (Alt)), Time_Type);
9646                   Time_Type := Standard_Duration;
9647                   Set_Etype (Expression (Delay_Statement (Alt)), Any_Type);
9648                end if;
9649             end if;
9650
9651             if No (Condition (Alt)) then
9652
9653                --  This guard will always be open
9654
9655                Check_Guard := False;
9656             end if;
9657
9658          elsif Nkind (Alt) = N_Terminate_Alternative then
9659             Adjust_Condition (Condition (Alt));
9660             Terminate_Alt := Alt;
9661          end if;
9662
9663          Num_Alts := Num_Alts + 1;
9664          Next (Alt);
9665       end loop;
9666
9667       Else_Present := Present (Else_Statements (N));
9668
9669       --  At the same time (see procedure Add_Accept) we build the accept list:
9670
9671       --    Qnn : Accept_List (1 .. num-select) := (
9672       --          (null-body, entry-index),
9673       --          (null-body, entry-index),
9674       --          ..
9675       --          (null_body, entry-index));
9676
9677       --  In the above declaration, null-body is True if the corresponding
9678       --  accept has no body, and false otherwise. The entry is either the
9679       --  entry index expression if there is no guard, or if a guard is
9680       --  present, then a conditional expression of the form:
9681
9682       --    (if guard then entry-index else Null_Task_Entry)
9683
9684       --  If a guard is statically known to be false, the entry can simply
9685       --  be omitted from the accept list.
9686
9687       Q :=
9688         Make_Object_Declaration (Loc,
9689           Defining_Identifier => Qnam,
9690           Object_Definition =>
9691             New_Reference_To (RTE (RE_Accept_List), Loc),
9692           Aliased_Present => True,
9693
9694           Expression =>
9695              Make_Qualified_Expression (Loc,
9696                Subtype_Mark =>
9697                  New_Reference_To (RTE (RE_Accept_List), Loc),
9698                Expression =>
9699                  Make_Aggregate (Loc, Expressions => Accept_List)));
9700
9701       Append (Q, Decls);
9702
9703       --  Then we declare the variable that holds the index for the accept
9704       --  that will be selected for service:
9705
9706       --    Xnn : Select_Index;
9707
9708       X :=
9709         Make_Object_Declaration (Loc,
9710           Defining_Identifier => Xnam,
9711           Object_Definition =>
9712             New_Reference_To (RTE (RE_Select_Index), Loc),
9713           Expression =>
9714             New_Reference_To (RTE (RE_No_Rendezvous), Loc));
9715
9716       Append (X, Decls);
9717
9718       --  After this follow procedure declarations for each accept body
9719
9720       --    procedure Pnn is
9721       --    begin
9722       --       ...
9723       --    end;
9724
9725       --  where the ... are statements from the corresponding procedure body.
9726       --  No parameters are involved, since the parameters are passed via Ann
9727       --  and the parameter references have already been expanded to be direct
9728       --  references to Ann (see Exp_Ch2.Expand_Entry_Parameter). Furthermore,
9729       --  any embedded tasking statements (which would normally be illegal in
9730       --  procedures), have been converted to calls to the tasking runtime so
9731       --  there is no problem in putting them into procedures.
9732
9733       --  The original accept statement has been expanded into a block in
9734       --  the same fashion as for simple accepts (see Build_Accept_Body).
9735
9736       --  Note: we don't really need to build these procedures for the case
9737       --  where no delay statement is present, but it is just as easy to
9738       --  build them unconditionally, and not significantly inefficient,
9739       --  since if they are short they will be inlined anyway.
9740
9741       --  The procedure declarations have been assembled in Body_List
9742
9743       --  If delays are present, we must compute the required delay.
9744       --  We first generate the declarations:
9745
9746       --    Delay_Index : Boolean := 0;
9747       --    Delay_Min   : Some_Time_Type.Time;
9748       --    Delay_Val   : Some_Time_Type.Time;
9749
9750       --  Delay_Index will be set to the index of the minimum delay, i.e. the
9751       --  active delay that is actually chosen as the basis for the possible
9752       --  delay if an immediate rendez-vous is not possible.
9753
9754       --  In the most common case there is a single delay statement, and this
9755       --  is handled specially.
9756
9757       if Delay_Count > 0 then
9758
9759          --  Generate the required declarations
9760
9761          Delay_Val :=
9762            Make_Defining_Identifier (Loc, New_External_Name ('D', 1));
9763          Delay_Index :=
9764            Make_Defining_Identifier (Loc, New_External_Name ('D', 2));
9765          Delay_Min :=
9766            Make_Defining_Identifier (Loc, New_External_Name ('D', 3));
9767
9768          Append_To (Decls,
9769            Make_Object_Declaration (Loc,
9770              Defining_Identifier => Delay_Val,
9771              Object_Definition   => New_Reference_To (Time_Type, Loc)));
9772
9773          Append_To (Decls,
9774            Make_Object_Declaration (Loc,
9775              Defining_Identifier => Delay_Index,
9776              Object_Definition   => New_Reference_To (Standard_Integer, Loc),
9777              Expression          => Make_Integer_Literal (Loc, 0)));
9778
9779          Append_To (Decls,
9780            Make_Object_Declaration (Loc,
9781              Defining_Identifier => Delay_Min,
9782              Object_Definition   => New_Reference_To (Time_Type, Loc),
9783              Expression          =>
9784                Unchecked_Convert_To (Time_Type,
9785                  Make_Attribute_Reference (Loc,
9786                    Prefix =>
9787                      New_Occurrence_Of (Underlying_Type (Time_Type), Loc),
9788                    Attribute_Name => Name_Last))));
9789
9790          --  Create Duration and Delay_Mode objects used for passing a delay
9791          --  value to RTS
9792
9793          D := Make_Temporary (Loc, 'D');
9794          M := Make_Temporary (Loc, 'M');
9795
9796          declare
9797             Discr : Entity_Id;
9798
9799          begin
9800             --  Note that these values are defined in s-osprim.ads and must
9801             --  be kept in sync:
9802             --
9803             --     Relative          : constant := 0;
9804             --     Absolute_Calendar : constant := 1;
9805             --     Absolute_RT       : constant := 2;
9806
9807             if Time_Type = Standard_Duration then
9808                Discr := Make_Integer_Literal (Loc, 0);
9809
9810             elsif Is_RTE (Base_Type (Etype (Time_Type)), RO_CA_Time) then
9811                Discr := Make_Integer_Literal (Loc, 1);
9812
9813             else
9814                pragma Assert
9815                  (Is_RTE (Base_Type (Etype (Time_Type)), RO_RT_Time));
9816                Discr := Make_Integer_Literal (Loc, 2);
9817             end if;
9818
9819             Append_To (Decls,
9820               Make_Object_Declaration (Loc,
9821                 Defining_Identifier => D,
9822                 Object_Definition =>
9823                   New_Reference_To (Standard_Duration, Loc)));
9824
9825             Append_To (Decls,
9826               Make_Object_Declaration (Loc,
9827                 Defining_Identifier => M,
9828                 Object_Definition   =>
9829                   New_Reference_To (Standard_Integer, Loc),
9830                 Expression          => Discr));
9831          end;
9832
9833          if Check_Guard then
9834             Guard_Open :=
9835               Make_Defining_Identifier (Loc, New_External_Name ('G', 1));
9836
9837             Append_To (Decls,
9838               Make_Object_Declaration (Loc,
9839                  Defining_Identifier => Guard_Open,
9840                  Object_Definition => New_Reference_To (Standard_Boolean, Loc),
9841                  Expression        => New_Reference_To (Standard_False, Loc)));
9842          end if;
9843
9844       --  Delay_Count is zero, don't need M and D set (suppress warning)
9845
9846       else
9847          M := Empty;
9848          D := Empty;
9849       end if;
9850
9851       if Present (Terminate_Alt) then
9852
9853          --  If the terminate alternative guard is False, use
9854          --  Simple_Mode; otherwise use Terminate_Mode.
9855
9856          if Present (Condition (Terminate_Alt)) then
9857             Select_Mode := Make_Conditional_Expression (Loc,
9858               New_List (Condition (Terminate_Alt),
9859                         New_Reference_To (RTE (RE_Terminate_Mode), Loc),
9860                         New_Reference_To (RTE (RE_Simple_Mode), Loc)));
9861          else
9862             Select_Mode := New_Reference_To (RTE (RE_Terminate_Mode), Loc);
9863          end if;
9864
9865       elsif Else_Present or Delay_Count > 0 then
9866          Select_Mode := New_Reference_To (RTE (RE_Else_Mode), Loc);
9867
9868       else
9869          Select_Mode := New_Reference_To (RTE (RE_Simple_Mode), Loc);
9870       end if;
9871
9872       Select_Call := Make_Select_Call (Select_Mode);
9873       Append (Select_Call, Stats);
9874
9875       --  Now generate code to act on the result. There is an entry
9876       --  in this case for each accept statement with a non-null body,
9877       --  followed by a branch to the statements that follow the Accept.
9878       --  In the absence of delay alternatives, we generate:
9879
9880       --    case X is
9881       --      when No_Rendezvous =>  --  omitted if simple mode
9882       --         goto Lab0;
9883
9884       --      when 1 =>
9885       --         P1n;
9886       --         goto Lab1;
9887
9888       --      when 2 =>
9889       --         P2n;
9890       --         goto Lab2;
9891
9892       --      when others =>
9893       --         goto Exit;
9894       --    end case;
9895       --
9896       --    Lab0: Else_Statements;
9897       --    goto exit;
9898
9899       --    Lab1:  Trailing_Statements1;
9900       --    goto Exit;
9901       --
9902       --    Lab2:  Trailing_Statements2;
9903       --    goto Exit;
9904       --    ...
9905       --    Exit:
9906
9907       --  Generate label for common exit
9908
9909       End_Lab := Make_And_Declare_Label (Num_Alts + 1);
9910
9911       --  First entry is the default case, when no rendezvous is possible
9912
9913       Choices := New_List (New_Reference_To (RTE (RE_No_Rendezvous), Loc));
9914
9915       if Else_Present then
9916
9917          --  If no rendezvous is possible, the else part is executed
9918
9919          Lab := Make_And_Declare_Label (0);
9920          Alt_Stats := New_List (
9921            Make_Goto_Statement (Loc,
9922              Name => New_Copy (Identifier (Lab))));
9923
9924          Append (Lab, Trailing_List);
9925          Append_List (Else_Statements (N), Trailing_List);
9926          Append_To (Trailing_List,
9927            Make_Goto_Statement (Loc,
9928              Name => New_Copy (Identifier (End_Lab))));
9929       else
9930          Alt_Stats := New_List (
9931            Make_Goto_Statement (Loc,
9932              Name => New_Copy (Identifier (End_Lab))));
9933       end if;
9934
9935       Append_To (Alt_List,
9936         Make_Case_Statement_Alternative (Loc,
9937           Discrete_Choices => Choices,
9938           Statements => Alt_Stats));
9939
9940       --  We make use of the fact that Accept_Index is an integer type, and
9941       --  generate successive literals for entries for each accept. Only those
9942       --  for which there is a body or trailing statements get a case entry.
9943
9944       Alt := First (Select_Alternatives (N));
9945       Proc := First (Body_List);
9946       while Present (Alt) loop
9947
9948          if Nkind (Alt) = N_Accept_Alternative then
9949             Process_Accept_Alternative (Alt, Index, Proc);
9950             Index := Index + 1;
9951
9952             if Present
9953               (Handled_Statement_Sequence (Accept_Statement (Alt)))
9954             then
9955                Next (Proc);
9956             end if;
9957
9958          elsif Nkind (Alt) = N_Delay_Alternative then
9959             Process_Delay_Alternative (Alt, Delay_Num);
9960             Delay_Num := Delay_Num + 1;
9961          end if;
9962
9963          Next (Alt);
9964       end loop;
9965
9966       --  An others choice is always added to the main case, as well
9967       --  as the delay case (to satisfy the compiler).
9968
9969       Append_To (Alt_List,
9970         Make_Case_Statement_Alternative (Loc,
9971           Discrete_Choices =>
9972             New_List (Make_Others_Choice (Loc)),
9973           Statements       =>
9974             New_List (Make_Goto_Statement (Loc,
9975               Name => New_Copy (Identifier (End_Lab))))));
9976
9977       Accept_Case := New_List (
9978         Make_Case_Statement (Loc,
9979           Expression   => New_Reference_To (Xnam, Loc),
9980           Alternatives => Alt_List));
9981
9982       Append_List (Trailing_List, Accept_Case);
9983       Append (End_Lab, Accept_Case);
9984       Append_List (Body_List, Decls);
9985
9986       --  Construct case statement for trailing statements of delay
9987       --  alternatives, if there are several of them.
9988
9989       if Delay_Count > 1 then
9990          Append_To (Delay_Alt_List,
9991            Make_Case_Statement_Alternative (Loc,
9992              Discrete_Choices =>
9993                New_List (Make_Others_Choice (Loc)),
9994              Statements       =>
9995                New_List (Make_Null_Statement (Loc))));
9996
9997          Delay_Case := New_List (
9998            Make_Case_Statement (Loc,
9999              Expression   => New_Reference_To (Delay_Index, Loc),
10000              Alternatives => Delay_Alt_List));
10001       else
10002          Delay_Case := Delay_Alt_List;
10003       end if;
10004
10005       --  If there are no delay alternatives, we append the case statement
10006       --  to the statement list.
10007
10008       if Delay_Count = 0 then
10009          Append_List (Accept_Case, Stats);
10010
10011       --  Delay alternatives present
10012
10013       else
10014          --  If delay alternatives are present we generate:
10015
10016          --    find minimum delay.
10017          --    DX := minimum delay;
10018          --    M := <delay mode>;
10019          --    Timed_Selective_Wait (Q'Unchecked_Access, Delay_Mode, P,
10020          --      DX, MX, X);
10021          --
10022          --    if X = No_Rendezvous then
10023          --      case statement for delay statements.
10024          --    else
10025          --      case statement for accept alternatives.
10026          --    end if;
10027
10028          declare
10029             Cases : Node_Id;
10030             Stmt  : Node_Id;
10031             Parms : List_Id;
10032             Parm  : Node_Id;
10033             Conv  : Node_Id;
10034
10035          begin
10036             --  The type of the delay expression is known to be legal
10037
10038             if Time_Type = Standard_Duration then
10039                Conv := New_Reference_To (Delay_Min, Loc);
10040
10041             elsif Is_RTE (Base_Type (Etype (Time_Type)), RO_CA_Time) then
10042                Conv := Make_Function_Call (Loc,
10043                  New_Reference_To (RTE (RO_CA_To_Duration), Loc),
10044                  New_List (New_Reference_To (Delay_Min, Loc)));
10045
10046             else
10047                pragma Assert
10048                  (Is_RTE (Base_Type (Etype (Time_Type)), RO_RT_Time));
10049
10050                Conv := Make_Function_Call (Loc,
10051                  New_Reference_To (RTE (RO_RT_To_Duration), Loc),
10052                  New_List (New_Reference_To (Delay_Min, Loc)));
10053             end if;
10054
10055             Stmt := Make_Assignment_Statement (Loc,
10056               Name => New_Reference_To (D, Loc),
10057               Expression => Conv);
10058
10059             --  Change the value for Accept_Modes. (Else_Mode -> Delay_Mode)
10060
10061             Parms := Parameter_Associations (Select_Call);
10062             Parm := First (Parms);
10063
10064             while Present (Parm)
10065               and then Parm /= Select_Mode
10066             loop
10067                Next (Parm);
10068             end loop;
10069
10070             pragma Assert (Present (Parm));
10071             Rewrite (Parm, New_Reference_To (RTE (RE_Delay_Mode), Loc));
10072             Analyze (Parm);
10073
10074             --  Prepare two new parameters of Duration and Delay_Mode type
10075             --  which represent the value and the mode of the minimum delay.
10076
10077             Next (Parm);
10078             Insert_After (Parm, New_Reference_To (M, Loc));
10079             Insert_After (Parm, New_Reference_To (D, Loc));
10080
10081             --  Create a call to RTS
10082
10083             Rewrite (Select_Call,
10084               Make_Procedure_Call_Statement (Loc,
10085                 Name => New_Reference_To (RTE (RE_Timed_Selective_Wait), Loc),
10086                 Parameter_Associations => Parms));
10087
10088             --  This new call should follow the calculation of the minimum
10089             --  delay.
10090
10091             Insert_List_Before (Select_Call, Delay_List);
10092
10093             if Check_Guard then
10094                Stmt :=
10095                  Make_Implicit_If_Statement (N,
10096                    Condition => New_Reference_To (Guard_Open, Loc),
10097                    Then_Statements =>
10098                      New_List (New_Copy_Tree (Stmt),
10099                        New_Copy_Tree (Select_Call)),
10100                    Else_Statements => Accept_Or_Raise);
10101                Rewrite (Select_Call, Stmt);
10102             else
10103                Insert_Before (Select_Call, Stmt);
10104             end if;
10105
10106             Cases :=
10107               Make_Implicit_If_Statement (N,
10108                 Condition => Make_Op_Eq (Loc,
10109                   Left_Opnd  => New_Reference_To (Xnam, Loc),
10110                   Right_Opnd =>
10111                     New_Reference_To (RTE (RE_No_Rendezvous), Loc)),
10112
10113                 Then_Statements => Delay_Case,
10114                 Else_Statements => Accept_Case);
10115
10116             Append (Cases, Stats);
10117          end;
10118       end if;
10119
10120       --  Replace accept statement with appropriate block
10121
10122       Block :=
10123         Make_Block_Statement (Loc,
10124           Declarations => Decls,
10125           Handled_Statement_Sequence =>
10126             Make_Handled_Sequence_Of_Statements (Loc,
10127               Statements => Stats));
10128
10129       Rewrite (N, Block);
10130       Analyze (N);
10131
10132       --  Note: have to worry more about abort deferral in above code ???
10133
10134       --  Final step is to unstack the Accept_Address entries for all accept
10135       --  statements appearing in accept alternatives in the select statement
10136
10137       Alt := First (Alts);
10138       while Present (Alt) loop
10139          if Nkind (Alt) = N_Accept_Alternative then
10140             Remove_Last_Elmt (Accept_Address
10141               (Entity (Entry_Direct_Name (Accept_Statement (Alt)))));
10142          end if;
10143
10144          Next (Alt);
10145       end loop;
10146    end Expand_N_Selective_Accept;
10147
10148    --------------------------------------
10149    -- Expand_N_Single_Task_Declaration --
10150    --------------------------------------
10151
10152    --  Single task declarations should never be present after semantic
10153    --  analysis, since we expect them to be replaced by a declaration of an
10154    --  anonymous task type, followed by a declaration of the task object. We
10155    --  include this routine to make sure that is happening!
10156
10157    procedure Expand_N_Single_Task_Declaration (N : Node_Id) is
10158    begin
10159       raise Program_Error;
10160    end Expand_N_Single_Task_Declaration;
10161
10162    ------------------------
10163    -- Expand_N_Task_Body --
10164    ------------------------
10165
10166    --  Given a task body
10167
10168    --    task body tname is
10169    --       <declarations>
10170    --    begin
10171    --       <statements>
10172    --    end x;
10173
10174    --  This expansion routine converts it into a procedure and sets the
10175    --  elaboration flag for the procedure to true, to represent the fact
10176    --  that the task body is now elaborated:
10177
10178    --    procedure tnameB (_Task : access tnameV) is
10179    --       discriminal : dtype renames _Task.discriminant;
10180
10181    --       procedure _clean is
10182    --       begin
10183    --          Abort_Defer.all;
10184    --          Complete_Task;
10185    --          Abort_Undefer.all;
10186    --          return;
10187    --       end _clean;
10188
10189    --    begin
10190    --       Abort_Undefer.all;
10191    --       <declarations>
10192    --       System.Task_Stages.Complete_Activation;
10193    --       <statements>
10194    --    at end
10195    --       _clean;
10196    --    end tnameB;
10197
10198    --    tnameE := True;
10199
10200    --  In addition, if the task body is an activator, then a call to activate
10201    --  tasks is added at the start of the statements, before the call to
10202    --  Complete_Activation, and if in addition the task is a master then it
10203    --  must be established as a master. These calls are inserted and analyzed
10204    --  in Expand_Cleanup_Actions, when the Handled_Sequence_Of_Statements is
10205    --  expanded.
10206
10207    --  There is one discriminal declaration line generated for each
10208    --  discriminant that is present to provide an easy reference point for
10209    --  discriminant references inside the body (see Exp_Ch2.Expand_Name).
10210
10211    --  Note on relationship to GNARLI definition. In the GNARLI definition,
10212    --  task body procedures have a profile (Arg : System.Address). That is
10213    --  needed because GNARLI has to use the same access-to-subprogram type
10214    --  for all task types. We depend here on knowing that in GNAT, passing
10215    --  an address argument by value is identical to passing a record value
10216    --  by access (in either case a single pointer is passed), so even though
10217    --  this procedure has the wrong profile. In fact it's all OK, since the
10218    --  callings sequence is identical.
10219
10220    procedure Expand_N_Task_Body (N : Node_Id) is
10221       Loc   : constant Source_Ptr := Sloc (N);
10222       Ttyp  : constant Entity_Id  := Corresponding_Spec (N);
10223       Call  : Node_Id;
10224       New_N : Node_Id;
10225
10226       Insert_Nod : Node_Id;
10227       --  Used to determine the proper location of wrapper body insertions
10228
10229    begin
10230       --  Add renaming declarations for discriminals and a declaration for the
10231       --  entry family index (if applicable).
10232
10233       Install_Private_Data_Declarations
10234         (Loc, Task_Body_Procedure (Ttyp), Ttyp, N, Declarations (N));
10235
10236       --  Add a call to Abort_Undefer at the very beginning of the task
10237       --  body since this body is called with abort still deferred.
10238
10239       if Abort_Allowed then
10240          Call := Build_Runtime_Call (Loc, RE_Abort_Undefer);
10241          Insert_Before
10242            (First (Statements (Handled_Statement_Sequence (N))), Call);
10243          Analyze (Call);
10244       end if;
10245
10246       --  The statement part has already been protected with an at_end and
10247       --  cleanup actions. The call to Complete_Activation must be placed
10248       --  at the head of the sequence of statements of that block. The
10249       --  declarations have been merged in this sequence of statements but
10250       --  the first real statement is accessible from the First_Real_Statement
10251       --  field (which was set for exactly this purpose).
10252
10253       if Restricted_Profile then
10254          Call := Build_Runtime_Call (Loc, RE_Complete_Restricted_Activation);
10255       else
10256          Call := Build_Runtime_Call (Loc, RE_Complete_Activation);
10257       end if;
10258
10259       Insert_Before
10260         (First_Real_Statement (Handled_Statement_Sequence (N)), Call);
10261       Analyze (Call);
10262
10263       New_N :=
10264         Make_Subprogram_Body (Loc,
10265           Specification              => Build_Task_Proc_Specification (Ttyp),
10266           Declarations               => Declarations (N),
10267           Handled_Statement_Sequence => Handled_Statement_Sequence (N));
10268
10269       --  If the task contains generic instantiations, cleanup actions are
10270       --  delayed until after instantiation. Transfer the activation chain to
10271       --  the subprogram, to insure that the activation call is properly
10272       --  generated. It the task body contains inner tasks, indicate that the
10273       --  subprogram is a task master.
10274
10275       if Delay_Cleanups (Ttyp) then
10276          Set_Activation_Chain_Entity (New_N, Activation_Chain_Entity (N));
10277          Set_Is_Task_Master  (New_N, Is_Task_Master (N));
10278       end if;
10279
10280       Rewrite (N, New_N);
10281       Analyze (N);
10282
10283       --  Set elaboration flag immediately after task body. If the body is a
10284       --  subunit, the flag is set in the declarative part containing the stub.
10285
10286       if Nkind (Parent (N)) /= N_Subunit then
10287          Insert_After (N,
10288            Make_Assignment_Statement (Loc,
10289              Name =>
10290                Make_Identifier (Loc, New_External_Name (Chars (Ttyp), 'E')),
10291              Expression => New_Reference_To (Standard_True, Loc)));
10292       end if;
10293
10294       --  Ada 2005 (AI-345): Construct the primitive entry wrapper bodies after
10295       --  the task body. At this point all wrapper specs have been created,
10296       --  frozen and included in the dispatch table for the task type.
10297
10298       if Ada_Version >= Ada_2005 then
10299          if Nkind (Parent (N)) = N_Subunit then
10300             Insert_Nod := Corresponding_Stub (Parent (N));
10301          else
10302             Insert_Nod := N;
10303          end if;
10304
10305          Build_Wrapper_Bodies (Loc, Ttyp, Insert_Nod);
10306       end if;
10307    end Expand_N_Task_Body;
10308
10309    ------------------------------------
10310    -- Expand_N_Task_Type_Declaration --
10311    ------------------------------------
10312
10313    --  We have several things to do. First we must create a Boolean flag used
10314    --  to mark if the body is elaborated yet. This variable gets set to True
10315    --  when the body of the task is elaborated (we can't rely on the normal
10316    --  ABE mechanism for the task body, since we need to pass an access to
10317    --  this elaboration boolean to the runtime routines).
10318
10319    --    taskE : aliased Boolean := False;
10320
10321    --  Next a variable is declared to hold the task stack size (either the
10322    --  default : Unspecified_Size, or a value that is set by a pragma
10323    --  Storage_Size). If the value of the pragma Storage_Size is static, then
10324    --  the variable is initialized with this value:
10325
10326    --    taskZ : Size_Type := Unspecified_Size;
10327    --  or
10328    --    taskZ : Size_Type := Size_Type (size_expression);
10329
10330    --  Note: No variable is needed to hold the task relative deadline since
10331    --  its value would never be static because the parameter is of a private
10332    --  type (Ada.Real_Time.Time_Span).
10333
10334    --  Next we create a corresponding record type declaration used to represent
10335    --  values of this task. The general form of this type declaration is
10336
10337    --    type taskV (discriminants) is record
10338    --      _Task_Id     : Task_Id;
10339    --      entry_family : array (bounds) of Void;
10340    --      _Priority    : Integer         := priority_expression;
10341    --      _Size        : Size_Type       := Size_Type (size_expression);
10342    --      _Task_Info   : Task_Info_Type  := task_info_expression;
10343    --      _CPU         : Integer         := cpu_range_expression;
10344    --    end record;
10345
10346    --  The discriminants are present only if the corresponding task type has
10347    --  discriminants, and they exactly mirror the task type discriminants.
10348
10349    --  The Id field is always present. It contains the Task_Id value, as set by
10350    --  the call to Create_Task. Note that although the task is limited, the
10351    --  task value record type is not limited, so there is no problem in passing
10352    --  this field as an out parameter to Create_Task.
10353
10354    --  One entry_family component is present for each entry family in the task
10355    --  definition. The bounds correspond to the bounds of the entry family
10356    --  (which may depend on discriminants). The element type is void, since we
10357    --  only need the bounds information for determining the entry index. Note
10358    --  that the use of an anonymous array would normally be illegal in this
10359    --  context, but this is a parser check, and the semantics is quite prepared
10360    --  to handle such a case.
10361
10362    --  The _Size field is present only if a Storage_Size pragma appears in the
10363    --  task definition. The expression captures the argument that was present
10364    --  in the pragma, and is used to override the task stack size otherwise
10365    --  associated with the task type.
10366
10367    --  The _Priority field is present only if a Priority or Interrupt_Priority
10368    --  pragma appears in the task definition. The expression captures the
10369    --  argument that was present in the pragma, and is used to provide the Size
10370    --  parameter to the call to Create_Task.
10371
10372    --  The _Task_Info field is present only if a Task_Info pragma appears in
10373    --  the task definition. The expression captures the argument that was
10374    --  present in the pragma, and is used to provide the Task_Image parameter
10375    --  to the call to Create_Task.
10376
10377    --  The _CPU field is present only if a CPU pragma appears in the task
10378    --  definition. The expression captures the argument that was present in
10379    --  the pragma, and is used to provide the CPU parameter to the call to
10380    --  Create_Task.
10381
10382    --  The _Relative_Deadline field is present only if a Relative_Deadline
10383    --  pragma appears in the task definition. The expression captures the
10384    --  argument that was present in the pragma, and is used to provide the
10385    --  Relative_Deadline parameter to the call to Create_Task.
10386
10387    --  When a task is declared, an instance of the task value record is
10388    --  created. The elaboration of this declaration creates the correct bounds
10389    --  for the entry families, and also evaluates the size, priority, and
10390    --  task_Info expressions if needed. The initialization routine for the task
10391    --  type itself then calls Create_Task with appropriate parameters to
10392    --  initialize the value of the Task_Id field.
10393
10394    --  Note: the address of this record is passed as the "Discriminants"
10395    --  parameter for Create_Task. Since Create_Task merely passes this onto the
10396    --  body procedure, it does not matter that it does not quite match the
10397    --  GNARLI model of what is being passed (the record contains more than just
10398    --  the discriminants, but the discriminants can be found from the record
10399    --  value).
10400
10401    --  The Entity_Id for this created record type is placed in the
10402    --  Corresponding_Record_Type field of the associated task type entity.
10403
10404    --  Next we create a procedure specification for the task body procedure:
10405
10406    --    procedure taskB (_Task : access taskV);
10407
10408    --  Note that this must come after the record type declaration, since
10409    --  the spec refers to this type. It turns out that the initialization
10410    --  procedure for the value type references the task body spec, but that's
10411    --  fine, since it won't be generated till the freeze point for the type,
10412    --  which is certainly after the task body spec declaration.
10413
10414    --  Finally, we set the task index value field of the entry attribute in
10415    --  the case of a simple entry.
10416
10417    procedure Expand_N_Task_Type_Declaration (N : Node_Id) is
10418       Loc     : constant Source_Ptr := Sloc (N);
10419       Tasktyp : constant Entity_Id  := Etype (Defining_Identifier (N));
10420       Tasknm  : constant Name_Id    := Chars (Tasktyp);
10421       Taskdef : constant Node_Id    := Task_Definition (N);
10422
10423       Proc_Spec  : Node_Id;
10424       Rec_Decl   : Node_Id;
10425       Rec_Ent    : Entity_Id;
10426       Cdecls     : List_Id;
10427       Elab_Decl  : Node_Id;
10428       Size_Decl  : Node_Id;
10429       Body_Decl  : Node_Id;
10430       Task_Size  : Node_Id;
10431       Ent_Stack  : Entity_Id;
10432       Decl_Stack : Node_Id;
10433
10434    begin
10435       --  If already expanded, nothing to do
10436
10437       if Present (Corresponding_Record_Type (Tasktyp)) then
10438          return;
10439       end if;
10440
10441       --  Here we will do the expansion
10442
10443       Rec_Decl := Build_Corresponding_Record (N, Tasktyp, Loc);
10444
10445       Rec_Ent  := Defining_Identifier (Rec_Decl);
10446       Cdecls   := Component_Items (Component_List
10447                                      (Type_Definition (Rec_Decl)));
10448
10449       Qualify_Entity_Names (N);
10450
10451       --  First create the elaboration variable
10452
10453       Elab_Decl :=
10454         Make_Object_Declaration (Loc,
10455           Defining_Identifier =>
10456             Make_Defining_Identifier (Sloc (Tasktyp),
10457               Chars => New_External_Name (Tasknm, 'E')),
10458           Aliased_Present      => True,
10459           Object_Definition    => New_Reference_To (Standard_Boolean, Loc),
10460           Expression           => New_Reference_To (Standard_False, Loc));
10461       Insert_After (N, Elab_Decl);
10462
10463       --  Next create the declaration of the size variable (tasknmZ)
10464
10465       Set_Storage_Size_Variable (Tasktyp,
10466         Make_Defining_Identifier (Sloc (Tasktyp),
10467           Chars => New_External_Name (Tasknm, 'Z')));
10468
10469       if Present (Taskdef) and then Has_Storage_Size_Pragma (Taskdef) and then
10470         Is_Static_Expression (Expression (First (
10471           Pragma_Argument_Associations (Find_Task_Or_Protected_Pragma (
10472             Taskdef, Name_Storage_Size)))))
10473       then
10474          Size_Decl :=
10475            Make_Object_Declaration (Loc,
10476              Defining_Identifier => Storage_Size_Variable (Tasktyp),
10477              Object_Definition => New_Reference_To (RTE (RE_Size_Type), Loc),
10478              Expression =>
10479                Convert_To (RTE (RE_Size_Type),
10480                  Relocate_Node (
10481                    Expression (First (
10482                      Pragma_Argument_Associations (
10483                        Find_Task_Or_Protected_Pragma
10484                          (Taskdef, Name_Storage_Size)))))));
10485
10486       else
10487          Size_Decl :=
10488            Make_Object_Declaration (Loc,
10489              Defining_Identifier => Storage_Size_Variable (Tasktyp),
10490              Object_Definition => New_Reference_To (RTE (RE_Size_Type), Loc),
10491              Expression => New_Reference_To (RTE (RE_Unspecified_Size), Loc));
10492       end if;
10493
10494       Insert_After (Elab_Decl, Size_Decl);
10495
10496       --  Next build the rest of the corresponding record declaration. This is
10497       --  done last, since the corresponding record initialization procedure
10498       --  will reference the previously created entities.
10499
10500       --  Fill in the component declarations -- first the _Task_Id field
10501
10502       Append_To (Cdecls,
10503         Make_Component_Declaration (Loc,
10504           Defining_Identifier =>
10505             Make_Defining_Identifier (Loc, Name_uTask_Id),
10506           Component_Definition =>
10507             Make_Component_Definition (Loc,
10508               Aliased_Present    => False,
10509               Subtype_Indication => New_Reference_To (RTE (RO_ST_Task_Id),
10510                                     Loc))));
10511
10512       --  Declare static ATCB (that is, created by the expander) if we are
10513       --  using the Restricted run time.
10514
10515       if Restricted_Profile then
10516          Append_To (Cdecls,
10517            Make_Component_Declaration (Loc,
10518              Defining_Identifier  =>
10519                Make_Defining_Identifier (Loc, Name_uATCB),
10520
10521              Component_Definition =>
10522                Make_Component_Definition (Loc,
10523                  Aliased_Present     => True,
10524                  Subtype_Indication  => Make_Subtype_Indication (Loc,
10525                    Subtype_Mark => New_Occurrence_Of
10526                      (RTE (RE_Ada_Task_Control_Block), Loc),
10527
10528                    Constraint   =>
10529                      Make_Index_Or_Discriminant_Constraint (Loc,
10530                        Constraints =>
10531                          New_List (Make_Integer_Literal (Loc, 0)))))));
10532
10533       end if;
10534
10535       --  Declare static stack (that is, created by the expander) if we are
10536       --  using the Restricted run time on a bare board configuration.
10537
10538       if Restricted_Profile
10539         and then Preallocated_Stacks_On_Target
10540       then
10541          --  First we need to extract the appropriate stack size
10542
10543          Ent_Stack := Make_Defining_Identifier (Loc, Name_uStack);
10544
10545          if Present (Taskdef) and then Has_Storage_Size_Pragma (Taskdef) then
10546             declare
10547                Expr_N : constant Node_Id :=
10548                           Expression (First (
10549                             Pragma_Argument_Associations (
10550                               Find_Task_Or_Protected_Pragma
10551                                 (Taskdef, Name_Storage_Size))));
10552                Etyp   : constant Entity_Id := Etype (Expr_N);
10553                P      : constant Node_Id   := Parent (Expr_N);
10554
10555             begin
10556                --  The stack is defined inside the corresponding record.
10557                --  Therefore if the size of the stack is set by means of
10558                --  a discriminant, we must reference the discriminant of the
10559                --  corresponding record type.
10560
10561                if Nkind (Expr_N) in N_Has_Entity
10562                  and then Present (Discriminal_Link (Entity (Expr_N)))
10563                then
10564                   Task_Size :=
10565                     New_Reference_To
10566                       (CR_Discriminant (Discriminal_Link (Entity (Expr_N))),
10567                        Loc);
10568                   Set_Parent   (Task_Size, P);
10569                   Set_Etype    (Task_Size, Etyp);
10570                   Set_Analyzed (Task_Size);
10571
10572                else
10573                   Task_Size := Relocate_Node (Expr_N);
10574                end if;
10575             end;
10576
10577          else
10578             Task_Size :=
10579               New_Reference_To (RTE (RE_Default_Stack_Size), Loc);
10580          end if;
10581
10582          Decl_Stack := Make_Component_Declaration (Loc,
10583            Defining_Identifier  => Ent_Stack,
10584
10585            Component_Definition =>
10586              Make_Component_Definition (Loc,
10587                Aliased_Present     => True,
10588                Subtype_Indication  => Make_Subtype_Indication (Loc,
10589                  Subtype_Mark =>
10590                    New_Occurrence_Of (RTE (RE_Storage_Array), Loc),
10591
10592                  Constraint   =>
10593                    Make_Index_Or_Discriminant_Constraint (Loc,
10594                      Constraints  => New_List (Make_Range (Loc,
10595                        Low_Bound  => Make_Integer_Literal (Loc, 1),
10596                        High_Bound => Convert_To (RTE (RE_Storage_Offset),
10597                          Task_Size)))))));
10598
10599          Append_To (Cdecls, Decl_Stack);
10600
10601          --  The appropriate alignment for the stack is ensured by the run-time
10602          --  code in charge of task creation.
10603
10604       end if;
10605
10606       --  Add components for entry families
10607
10608       Collect_Entry_Families (Loc, Cdecls, Size_Decl, Tasktyp);
10609
10610       --  Add the _Priority component if a Priority pragma is present
10611
10612       if Present (Taskdef) and then Has_Pragma_Priority (Taskdef) then
10613          declare
10614             Prag : constant Node_Id :=
10615                      Find_Task_Or_Protected_Pragma (Taskdef, Name_Priority);
10616             Expr : Node_Id;
10617
10618          begin
10619             Expr := First (Pragma_Argument_Associations (Prag));
10620
10621             if Nkind (Expr) = N_Pragma_Argument_Association then
10622                Expr := Expression (Expr);
10623             end if;
10624
10625             Expr := New_Copy_Tree (Expr);
10626
10627             --  Add conversion to proper type to do range check if required
10628             --  Note that for runtime units, we allow out of range interrupt
10629             --  priority values to be used in a priority pragma. This is for
10630             --  the benefit of some versions of System.Interrupts which use
10631             --  a special server task with maximum interrupt priority.
10632
10633             if Pragma_Name (Prag) = Name_Priority
10634               and then not GNAT_Mode
10635             then
10636                Rewrite (Expr, Convert_To (RTE (RE_Priority), Expr));
10637             else
10638                Rewrite (Expr, Convert_To (RTE (RE_Any_Priority), Expr));
10639             end if;
10640
10641             Append_To (Cdecls,
10642               Make_Component_Declaration (Loc,
10643                 Defining_Identifier =>
10644                   Make_Defining_Identifier (Loc, Name_uPriority),
10645                 Component_Definition =>
10646                   Make_Component_Definition (Loc,
10647                     Aliased_Present    => False,
10648                     Subtype_Indication => New_Reference_To (Standard_Integer,
10649                                                             Loc)),
10650                 Expression => Expr));
10651          end;
10652       end if;
10653
10654       --  Add the _Task_Size component if a Storage_Size pragma is present
10655
10656       if Present (Taskdef)
10657         and then Has_Storage_Size_Pragma (Taskdef)
10658       then
10659          Append_To (Cdecls,
10660            Make_Component_Declaration (Loc,
10661              Defining_Identifier =>
10662                Make_Defining_Identifier (Loc, Name_uSize),
10663
10664              Component_Definition =>
10665                Make_Component_Definition (Loc,
10666                  Aliased_Present    => False,
10667                  Subtype_Indication => New_Reference_To (RTE (RE_Size_Type),
10668                                                          Loc)),
10669
10670              Expression =>
10671                Convert_To (RTE (RE_Size_Type),
10672                  Relocate_Node (
10673                    Expression (First (
10674                      Pragma_Argument_Associations (
10675                        Find_Task_Or_Protected_Pragma
10676                          (Taskdef, Name_Storage_Size))))))));
10677       end if;
10678
10679       --  Add the _Task_Info component if a Task_Info pragma is present
10680
10681       if Present (Taskdef) and then Has_Task_Info_Pragma (Taskdef) then
10682          Append_To (Cdecls,
10683            Make_Component_Declaration (Loc,
10684              Defining_Identifier =>
10685                Make_Defining_Identifier (Loc, Name_uTask_Info),
10686
10687              Component_Definition =>
10688                Make_Component_Definition (Loc,
10689                  Aliased_Present    => False,
10690                  Subtype_Indication =>
10691                    New_Reference_To (RTE (RE_Task_Info_Type), Loc)),
10692
10693              Expression => New_Copy (
10694                Expression (First (
10695                  Pragma_Argument_Associations (
10696                    Find_Task_Or_Protected_Pragma
10697                      (Taskdef, Name_Task_Info)))))));
10698       end if;
10699
10700       --  Add the _CPU component if a CPU pragma is present
10701
10702       if Present (Taskdef) and then Has_Pragma_CPU (Taskdef) then
10703          Append_To (Cdecls,
10704            Make_Component_Declaration (Loc,
10705              Defining_Identifier =>
10706                Make_Defining_Identifier (Loc, Name_uCPU),
10707
10708              Component_Definition =>
10709                Make_Component_Definition (Loc,
10710                  Aliased_Present    => False,
10711                  Subtype_Indication =>
10712                    New_Reference_To (RTE (RE_CPU_Range), Loc)),
10713
10714              Expression => New_Copy (
10715                Expression (First (
10716                  Pragma_Argument_Associations (
10717                    Find_Task_Or_Protected_Pragma
10718                      (Taskdef, Name_CPU)))))));
10719       end if;
10720
10721       --  Add the _Relative_Deadline component if a Relative_Deadline pragma is
10722       --  present. If we are using a restricted run time this component will
10723       --  not be added (deadlines are not allowed by the Ravenscar profile).
10724
10725       if not Restricted_Profile
10726         and then Present (Taskdef)
10727         and then Has_Relative_Deadline_Pragma (Taskdef)
10728       then
10729          Append_To (Cdecls,
10730            Make_Component_Declaration (Loc,
10731              Defining_Identifier =>
10732                Make_Defining_Identifier (Loc, Name_uRelative_Deadline),
10733
10734              Component_Definition =>
10735                Make_Component_Definition (Loc,
10736                  Aliased_Present    => False,
10737                  Subtype_Indication =>
10738                    New_Reference_To (RTE (RE_Time_Span), Loc)),
10739
10740              Expression =>
10741                Convert_To (RTE (RE_Time_Span),
10742                  Relocate_Node (
10743                    Expression (First (
10744                      Pragma_Argument_Associations (
10745                        Find_Task_Or_Protected_Pragma
10746                          (Taskdef, Name_Relative_Deadline))))))));
10747       end if;
10748
10749       Insert_After (Size_Decl, Rec_Decl);
10750
10751       --  Analyze the record declaration immediately after construction,
10752       --  because the initialization procedure is needed for single task
10753       --  declarations before the next entity is analyzed.
10754
10755       Analyze (Rec_Decl);
10756
10757       --  Create the declaration of the task body procedure
10758
10759       Proc_Spec := Build_Task_Proc_Specification (Tasktyp);
10760       Body_Decl :=
10761         Make_Subprogram_Declaration (Loc,
10762           Specification => Proc_Spec);
10763
10764       Insert_After (Rec_Decl, Body_Decl);
10765
10766       --  The subprogram does not comes from source, so we have to indicate the
10767       --  need for debugging information explicitly.
10768
10769       if Comes_From_Source (Original_Node (N)) then
10770          Set_Debug_Info_Needed (Defining_Entity (Proc_Spec));
10771       end if;
10772
10773       --  Ada 2005 (AI-345): Construct the primitive entry wrapper specs before
10774       --  the corresponding record has been frozen.
10775
10776       if Ada_Version >= Ada_2005 then
10777          Build_Wrapper_Specs (Loc, Tasktyp, Rec_Decl);
10778       end if;
10779
10780       --  Ada 2005 (AI-345): We must defer freezing to allow further
10781       --  declaration of primitive subprograms covering task interfaces
10782
10783       if Ada_Version <= Ada_95 then
10784
10785          --  Now we can freeze the corresponding record. This needs manually
10786          --  freezing, since it is really part of the task type, and the task
10787          --  type is frozen at this stage. We of course need the initialization
10788          --  procedure for this corresponding record type and we won't get it
10789          --  in time if we don't freeze now.
10790
10791          declare
10792             L : constant List_Id := Freeze_Entity (Rec_Ent, N);
10793          begin
10794             if Is_Non_Empty_List (L) then
10795                Insert_List_After (Body_Decl, L);
10796             end if;
10797          end;
10798       end if;
10799
10800       --  Complete the expansion of access types to the current task type, if
10801       --  any were declared.
10802
10803       Expand_Previous_Access_Type (Tasktyp);
10804
10805       --  Create wrappers for entries that have pre/postconditions
10806
10807       declare
10808          Ent : Entity_Id;
10809
10810       begin
10811          Ent := First_Entity (Tasktyp);
10812          while Present (Ent) loop
10813             if Ekind_In (Ent, E_Entry, E_Entry_Family)
10814               and then Present (Spec_PPC_List (Ent))
10815             then
10816                Build_PPC_Wrapper (Ent, N);
10817             end if;
10818
10819             Next_Entity (Ent);
10820          end loop;
10821       end;
10822    end Expand_N_Task_Type_Declaration;
10823
10824    -------------------------------
10825    -- Expand_N_Timed_Entry_Call --
10826    -------------------------------
10827
10828    --  A timed entry call in normal case is not implemented using ATC mechanism
10829    --  anymore for efficiency reason.
10830
10831    --     select
10832    --        T.E;
10833    --        S1;
10834    --     or
10835    --        Delay D;
10836    --        S2;
10837    --     end select;
10838
10839    --  is expanded as follow:
10840
10841    --  1) When T.E is a task entry_call;
10842
10843    --    declare
10844    --       B  : Boolean;
10845    --       X  : Task_Entry_Index := <entry index>;
10846    --       DX : Duration := To_Duration (D);
10847    --       M  : Delay_Mode := <discriminant>;
10848    --       P  : parms := (parm, parm, parm);
10849
10850    --    begin
10851    --       Timed_Protected_Entry_Call
10852    --         (<acceptor-task>, X, P'Address, DX, M, B);
10853    --       if B then
10854    --          S1;
10855    --       else
10856    --          S2;
10857    --       end if;
10858    --    end;
10859
10860    --  2) When T.E is a protected entry_call;
10861
10862    --    declare
10863    --       B  : Boolean;
10864    --       X  : Protected_Entry_Index := <entry index>;
10865    --       DX : Duration := To_Duration (D);
10866    --       M  : Delay_Mode := <discriminant>;
10867    --       P  : parms := (parm, parm, parm);
10868
10869    --    begin
10870    --       Timed_Protected_Entry_Call
10871    --         (<object>'unchecked_access, X, P'Address, DX, M, B);
10872    --       if B then
10873    --          S1;
10874    --       else
10875    --          S2;
10876    --       end if;
10877    --    end;
10878
10879    --  3) Ada 2005 (AI-345): When T.E is a dispatching procedure call;
10880
10881    --    declare
10882    --       B  : Boolean := False;
10883    --       C  : Ada.Tags.Prim_Op_Kind;
10884    --       DX : Duration := To_Duration (D)
10885    --       K  : Ada.Tags.Tagged_Kind :=
10886    --              Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag (<object>));
10887    --       M  : Integer :=...;
10888    --       P  : Parameters := (Param1 .. ParamN);
10889    --       S  : Iteger;
10890
10891    --    begin
10892    --       if K = Ada.Tags.TK_Limited_Tagged then
10893    --          <dispatching-call>;
10894    --          <triggering-statements>
10895
10896    --       else
10897    --          S :=
10898    --            Ada.Tags.Get_Offset_Index
10899    --              (Ada.Tags.Tag (<object>), DT_Position (<dispatching-call>));
10900
10901    --          _Disp_Timed_Select (<object>, S, P'Address, DX, M, C, B);
10902
10903    --          if C = POK_Protected_Entry
10904    --            or else C = POK_Task_Entry
10905    --          then
10906    --             Param1 := P.Param1;
10907    --             ...
10908    --             ParamN := P.ParamN;
10909    --          end if;
10910
10911    --          if B then
10912    --             if C = POK_Procedure
10913    --               or else C = POK_Protected_Procedure
10914    --               or else C = POK_Task_Procedure
10915    --             then
10916    --                <dispatching-call>;
10917    --             end if;
10918
10919    --             <triggering-statements>
10920    --          else
10921    --             <timed-statements>
10922    --          end if;
10923    --       end if;
10924    --    end;
10925
10926    procedure Expand_N_Timed_Entry_Call (N : Node_Id) is
10927       Loc : constant Source_Ptr := Sloc (N);
10928
10929       E_Call  : Node_Id :=
10930                   Entry_Call_Statement (Entry_Call_Alternative (N));
10931       E_Stats : constant List_Id :=
10932                   Statements (Entry_Call_Alternative (N));
10933       D_Stat  : Node_Id :=
10934                   Delay_Statement (Delay_Alternative (N));
10935       D_Stats : constant List_Id :=
10936                   Statements (Delay_Alternative (N));
10937
10938       Actuals        : List_Id;
10939       Blk_Typ        : Entity_Id;
10940       Call           : Node_Id;
10941       Call_Ent       : Entity_Id;
10942       Conc_Typ_Stmts : List_Id;
10943       Concval        : Node_Id;
10944       D_Conv         : Node_Id;
10945       D_Disc         : Node_Id;
10946       D_Type         : Entity_Id;
10947       Decls          : List_Id;
10948       Dummy          : Node_Id;
10949       Ename          : Node_Id;
10950       Formals        : List_Id;
10951       Index          : Node_Id;
10952       Is_Disp_Select : Boolean;
10953       Lim_Typ_Stmts  : List_Id;
10954       N_Stats        : List_Id;
10955       Obj            : Entity_Id;
10956       Param          : Node_Id;
10957       Params         : List_Id;
10958       Stmt           : Node_Id;
10959       Stmts          : List_Id;
10960       Unpack         : List_Id;
10961
10962       B : Entity_Id;  --  Call status flag
10963       C : Entity_Id;  --  Call kind
10964       D : Entity_Id;  --  Delay
10965       K : Entity_Id;  --  Tagged kind
10966       M : Entity_Id;  --  Delay mode
10967       P : Entity_Id;  --  Parameter block
10968       S : Entity_Id;  --  Primitive operation slot
10969
10970    begin
10971       --  Under the Ravenscar profile, timed entry calls are excluded. An error
10972       --  was already reported on spec, so do not attempt to expand the call.
10973
10974       if Restriction_Active (No_Select_Statements) then
10975          return;
10976       end if;
10977
10978       --  The arguments in the call may require dynamic allocation, and the
10979       --  call statement may have been transformed into a block. The block
10980       --  may contain additional declarations for internal entities, and the
10981       --  original call is found by sequential search.
10982
10983       if Nkind (E_Call) = N_Block_Statement then
10984          E_Call := First (Statements (Handled_Statement_Sequence (E_Call)));
10985          while not Nkind_In (E_Call, N_Procedure_Call_Statement,
10986                                      N_Entry_Call_Statement)
10987          loop
10988             Next (E_Call);
10989          end loop;
10990       end if;
10991
10992       Is_Disp_Select :=
10993         Ada_Version >= Ada_2005
10994           and then Nkind (E_Call) = N_Procedure_Call_Statement;
10995
10996       if Is_Disp_Select then
10997          Extract_Dispatching_Call (E_Call, Call_Ent, Obj, Actuals, Formals);
10998
10999          Decls := New_List;
11000          Stmts := New_List;
11001
11002          --  Generate:
11003          --    B : Boolean := False;
11004
11005          B := Build_B (Loc, Decls);
11006
11007          --  Generate:
11008          --    C : Ada.Tags.Prim_Op_Kind;
11009
11010          C := Build_C (Loc, Decls);
11011
11012          --  Because the analysis of all statements was disabled, manually
11013          --  analyze the delay statement.
11014
11015          Analyze (D_Stat);
11016          D_Stat := Original_Node (D_Stat);
11017
11018       else
11019          --  Build an entry call using Simple_Entry_Call
11020
11021          Extract_Entry (E_Call, Concval, Ename, Index);
11022          Build_Simple_Entry_Call (E_Call, Concval, Ename, Index);
11023
11024          Decls := Declarations (E_Call);
11025          Stmts := Statements (Handled_Statement_Sequence (E_Call));
11026
11027          if No (Decls) then
11028             Decls := New_List;
11029          end if;
11030
11031          --  Generate:
11032          --    B : Boolean;
11033
11034          B := Make_Defining_Identifier (Loc, Name_uB);
11035
11036          Prepend_To (Decls,
11037            Make_Object_Declaration (Loc,
11038              Defining_Identifier =>
11039                B,
11040              Object_Definition =>
11041                New_Reference_To (Standard_Boolean, Loc)));
11042       end if;
11043
11044       --  Duration and mode processing
11045
11046       D_Type := Base_Type (Etype (Expression (D_Stat)));
11047
11048       --  Use the type of the delay expression (Calendar or Real_Time) to
11049       --  generate the appropriate conversion.
11050
11051       if Nkind (D_Stat) = N_Delay_Relative_Statement then
11052          D_Disc := Make_Integer_Literal (Loc, 0);
11053          D_Conv := Relocate_Node (Expression (D_Stat));
11054
11055       elsif Is_RTE (D_Type, RO_CA_Time) then
11056          D_Disc := Make_Integer_Literal (Loc, 1);
11057          D_Conv := Make_Function_Call (Loc,
11058            New_Reference_To (RTE (RO_CA_To_Duration), Loc),
11059            New_List (New_Copy (Expression (D_Stat))));
11060
11061       else pragma Assert (Is_RTE (D_Type, RO_RT_Time));
11062          D_Disc := Make_Integer_Literal (Loc, 2);
11063          D_Conv := Make_Function_Call (Loc,
11064            New_Reference_To (RTE (RO_RT_To_Duration), Loc),
11065            New_List (New_Copy (Expression (D_Stat))));
11066       end if;
11067
11068       D := Make_Temporary (Loc, 'D');
11069
11070       --  Generate:
11071       --    D : Duration;
11072
11073       Append_To (Decls,
11074         Make_Object_Declaration (Loc,
11075           Defining_Identifier =>
11076             D,
11077           Object_Definition =>
11078             New_Reference_To (Standard_Duration, Loc)));
11079
11080       M := Make_Temporary (Loc, 'M');
11081
11082       --  Generate:
11083       --    M : Integer := (0 | 1 | 2);
11084
11085       Append_To (Decls,
11086         Make_Object_Declaration (Loc,
11087           Defining_Identifier =>
11088             M,
11089           Object_Definition =>
11090             New_Reference_To (Standard_Integer, Loc),
11091           Expression =>
11092             D_Disc));
11093
11094       --  Do the assignment at this stage only because the evaluation of the
11095       --  expression must not occur before (see ACVC C97302A).
11096
11097       Append_To (Stmts,
11098         Make_Assignment_Statement (Loc,
11099           Name =>
11100             New_Reference_To (D, Loc),
11101           Expression =>
11102             D_Conv));
11103
11104       --  Parameter block processing
11105
11106       --  Manually create the parameter block for dispatching calls. In the
11107       --  case of entries, the block has already been created during the call
11108       --  to Build_Simple_Entry_Call.
11109
11110       if Is_Disp_Select then
11111
11112          --  Tagged kind processing, generate:
11113          --    K : Ada.Tags.Tagged_Kind :=
11114          --          Ada.Tags.Get_Tagged_Kind (Ada.Tags.Tag <object>));
11115
11116          K := Build_K (Loc, Decls, Obj);
11117
11118          Blk_Typ := Build_Parameter_Block (Loc, Actuals, Formals, Decls);
11119          P := Parameter_Block_Pack
11120                 (Loc, Blk_Typ, Actuals, Formals, Decls, Stmts);
11121
11122          --  Dispatch table slot processing, generate:
11123          --    S : Integer;
11124
11125          S := Build_S (Loc, Decls);
11126
11127          --  Generate:
11128          --    S := Ada.Tags.Get_Offset_Index
11129          --           (Ada.Tags.Tag (<object>), DT_Position (Call_Ent));
11130
11131          Conc_Typ_Stmts :=
11132            New_List (Build_S_Assignment (Loc, S, Obj, Call_Ent));
11133
11134          --  Generate:
11135          --    _Disp_Timed_Select (<object>, S, P'Address, D, M, C, B);
11136
11137          --  where Obj is the controlling formal parameter, S is the dispatch
11138          --  table slot number of the dispatching operation, P is the wrapped
11139          --  parameter block, D is the duration, M is the duration mode, C is
11140          --  the call kind and B is the call status.
11141
11142          Params := New_List;
11143
11144          Append_To (Params, New_Copy_Tree (Obj));
11145          Append_To (Params, New_Reference_To (S, Loc));
11146          Append_To (Params, Make_Attribute_Reference (Loc,
11147                               Prefix => New_Reference_To (P, Loc),
11148                               Attribute_Name => Name_Address));
11149          Append_To (Params, New_Reference_To (D, Loc));
11150          Append_To (Params, New_Reference_To (M, Loc));
11151          Append_To (Params, New_Reference_To (C, Loc));
11152          Append_To (Params, New_Reference_To (B, Loc));
11153
11154          Append_To (Conc_Typ_Stmts,
11155            Make_Procedure_Call_Statement (Loc,
11156              Name =>
11157                New_Reference_To (
11158                  Find_Prim_Op (Etype (Etype (Obj)),
11159                    Name_uDisp_Timed_Select),
11160                  Loc),
11161              Parameter_Associations =>
11162                Params));
11163
11164          --  Generate:
11165          --    if C = POK_Protected_Entry
11166          --      or else C = POK_Task_Entry
11167          --    then
11168          --       Param1 := P.Param1;
11169          --       ...
11170          --       ParamN := P.ParamN;
11171          --    end if;
11172
11173          Unpack := Parameter_Block_Unpack (Loc, P, Actuals, Formals);
11174
11175          --  Generate the if statement only when the packed parameters need
11176          --  explicit assignments to their corresponding actuals.
11177
11178          if Present (Unpack) then
11179             Append_To (Conc_Typ_Stmts,
11180               Make_If_Statement (Loc,
11181
11182                 Condition =>
11183                   Make_Or_Else (Loc,
11184                     Left_Opnd =>
11185                       Make_Op_Eq (Loc,
11186                         Left_Opnd =>
11187                           New_Reference_To (C, Loc),
11188                         Right_Opnd =>
11189                           New_Reference_To (RTE (
11190                             RE_POK_Protected_Entry), Loc)),
11191                     Right_Opnd =>
11192                       Make_Op_Eq (Loc,
11193                         Left_Opnd =>
11194                           New_Reference_To (C, Loc),
11195                         Right_Opnd =>
11196                           New_Reference_To (RTE (RE_POK_Task_Entry), Loc))),
11197
11198                 Then_Statements =>
11199                   Unpack));
11200          end if;
11201
11202          --  Generate:
11203
11204          --    if B then
11205          --       if C = POK_Procedure
11206          --         or else C = POK_Protected_Procedure
11207          --         or else C = POK_Task_Procedure
11208          --       then
11209          --          <dispatching-call>
11210          --       end if;
11211          --       <triggering-statements>
11212          --    else
11213          --       <timed-statements>
11214          --    end if;
11215
11216          N_Stats := New_Copy_List_Tree (E_Stats);
11217
11218          Prepend_To (N_Stats,
11219            Make_If_Statement (Loc,
11220
11221              Condition =>
11222                Make_Or_Else (Loc,
11223                  Left_Opnd =>
11224                    Make_Op_Eq (Loc,
11225                      Left_Opnd =>
11226                        New_Reference_To (C, Loc),
11227                      Right_Opnd =>
11228                        New_Reference_To (RTE (RE_POK_Procedure), Loc)),
11229                  Right_Opnd =>
11230                    Make_Or_Else (Loc,
11231                      Left_Opnd =>
11232                        Make_Op_Eq (Loc,
11233                          Left_Opnd =>
11234                            New_Reference_To (C, Loc),
11235                          Right_Opnd =>
11236                            New_Reference_To (RTE (
11237                              RE_POK_Protected_Procedure), Loc)),
11238                      Right_Opnd =>
11239                        Make_Op_Eq (Loc,
11240                          Left_Opnd =>
11241                            New_Reference_To (C, Loc),
11242                          Right_Opnd =>
11243                            New_Reference_To (RTE (
11244                              RE_POK_Task_Procedure), Loc)))),
11245
11246              Then_Statements =>
11247                New_List (E_Call)));
11248
11249          Append_To (Conc_Typ_Stmts,
11250            Make_If_Statement (Loc,
11251              Condition => New_Reference_To (B, Loc),
11252              Then_Statements => N_Stats,
11253              Else_Statements => D_Stats));
11254
11255          --  Generate:
11256          --    <dispatching-call>;
11257          --    <triggering-statements>
11258
11259          Lim_Typ_Stmts := New_Copy_List_Tree (E_Stats);
11260          Prepend_To (Lim_Typ_Stmts, New_Copy_Tree (E_Call));
11261
11262          --  Generate:
11263          --    if K = Ada.Tags.TK_Limited_Tagged then
11264          --       Lim_Typ_Stmts
11265          --    else
11266          --       Conc_Typ_Stmts
11267          --    end if;
11268
11269          Append_To (Stmts,
11270            Make_If_Statement (Loc,
11271              Condition =>
11272                Make_Op_Eq (Loc,
11273                  Left_Opnd =>
11274                    New_Reference_To (K, Loc),
11275                  Right_Opnd =>
11276                    New_Reference_To (RTE (RE_TK_Limited_Tagged), Loc)),
11277
11278              Then_Statements =>
11279                Lim_Typ_Stmts,
11280
11281              Else_Statements =>
11282                Conc_Typ_Stmts));
11283
11284       else
11285          --  Skip assignments to temporaries created for in-out parameters.
11286          --  This makes unwarranted assumptions about the shape of the expanded
11287          --  tree for the call, and should be cleaned up ???
11288
11289          Stmt := First (Stmts);
11290          while Nkind (Stmt) /= N_Procedure_Call_Statement loop
11291             Next (Stmt);
11292          end loop;
11293
11294          --  Do the assignment at this stage only because the evaluation
11295          --  of the expression must not occur before (see ACVC C97302A).
11296
11297          Insert_Before (Stmt,
11298            Make_Assignment_Statement (Loc,
11299              Name => New_Reference_To (D, Loc),
11300              Expression => D_Conv));
11301
11302          Call   := Stmt;
11303          Params := Parameter_Associations (Call);
11304
11305          --  For a protected type, we build a Timed_Protected_Entry_Call
11306
11307          if Is_Protected_Type (Etype (Concval)) then
11308
11309             --  Create a new call statement
11310
11311             Param := First (Params);
11312             while Present (Param)
11313               and then not Is_RTE (Etype (Param), RE_Call_Modes)
11314             loop
11315                Next (Param);
11316             end loop;
11317
11318             Dummy := Remove_Next (Next (Param));
11319
11320             --  Remove garbage is following the Cancel_Param if present
11321
11322             Dummy := Next (Param);
11323
11324             --  Remove the mode of the Protected_Entry_Call call, then remove
11325             --  the Communication_Block of the Protected_Entry_Call call, and
11326             --  finally add Duration and a Delay_Mode parameter
11327
11328             pragma Assert (Present (Param));
11329             Rewrite (Param, New_Reference_To (D, Loc));
11330
11331             Rewrite (Dummy, New_Reference_To (M, Loc));
11332
11333             --  Add a Boolean flag for successful entry call
11334
11335             Append_To (Params, New_Reference_To (B, Loc));
11336
11337             case Corresponding_Runtime_Package (Etype (Concval)) is
11338                when System_Tasking_Protected_Objects_Entries =>
11339                   Rewrite (Call,
11340                     Make_Procedure_Call_Statement (Loc,
11341                       Name =>
11342                         New_Reference_To
11343                           (RTE (RE_Timed_Protected_Entry_Call), Loc),
11344                       Parameter_Associations => Params));
11345
11346                when System_Tasking_Protected_Objects_Single_Entry =>
11347                   Param := First (Params);
11348                   while Present (Param)
11349                     and then not
11350                       Is_RTE (Etype (Param), RE_Protected_Entry_Index)
11351                   loop
11352                      Next (Param);
11353                   end loop;
11354
11355                   Remove (Param);
11356
11357                   Rewrite (Call,
11358                     Make_Procedure_Call_Statement (Loc,
11359                       Name => New_Reference_To (
11360                         RTE (RE_Timed_Protected_Single_Entry_Call), Loc),
11361                       Parameter_Associations => Params));
11362
11363                when others =>
11364                   raise Program_Error;
11365             end case;
11366
11367          --  For the task case, build a Timed_Task_Entry_Call
11368
11369          else
11370             --  Create a new call statement
11371
11372             Append_To (Params, New_Reference_To (D, Loc));
11373             Append_To (Params, New_Reference_To (M, Loc));
11374             Append_To (Params, New_Reference_To (B, Loc));
11375
11376             Rewrite (Call,
11377               Make_Procedure_Call_Statement (Loc,
11378                 Name =>
11379                   New_Reference_To (RTE (RE_Timed_Task_Entry_Call), Loc),
11380                 Parameter_Associations => Params));
11381          end if;
11382
11383          Append_To (Stmts,
11384            Make_Implicit_If_Statement (N,
11385              Condition => New_Reference_To (B, Loc),
11386              Then_Statements => E_Stats,
11387              Else_Statements => D_Stats));
11388       end if;
11389
11390       Rewrite (N,
11391         Make_Block_Statement (Loc,
11392           Declarations => Decls,
11393           Handled_Statement_Sequence =>
11394             Make_Handled_Sequence_Of_Statements (Loc, Stmts)));
11395
11396       Analyze (N);
11397    end Expand_N_Timed_Entry_Call;
11398
11399    ----------------------------------------
11400    -- Expand_Protected_Body_Declarations --
11401    ----------------------------------------
11402
11403    procedure Expand_Protected_Body_Declarations
11404      (N       : Node_Id;
11405       Spec_Id : Entity_Id)
11406    is
11407    begin
11408       if No_Run_Time_Mode then
11409          Error_Msg_CRT ("protected body", N);
11410          return;
11411
11412       elsif Expander_Active then
11413
11414          --  Associate discriminals with the first subprogram or entry body to
11415          --  be expanded.
11416
11417          if Present (First_Protected_Operation (Declarations (N))) then
11418             Set_Discriminals (Parent (Spec_Id));
11419          end if;
11420       end if;
11421    end Expand_Protected_Body_Declarations;
11422
11423    -------------------------
11424    -- External_Subprogram --
11425    -------------------------
11426
11427    function External_Subprogram (E : Entity_Id) return Entity_Id is
11428       Subp : constant Entity_Id := Protected_Body_Subprogram (E);
11429
11430    begin
11431       --  The internal and external subprograms follow each other on the entity
11432       --  chain. Note that previously private operations had no separate
11433       --  external subprogram. We now create one in all cases, because a
11434       --  private operation may actually appear in an external call, through
11435       --  a 'Access reference used for a callback.
11436
11437       --  If the operation is a function that returns an anonymous access type,
11438       --  the corresponding itype appears before the operation, and must be
11439       --  skipped.
11440
11441       --  This mechanism is fragile, there should be a real link between the
11442       --  two versions of the operation, but there is no place to put it ???
11443
11444       if Is_Access_Type (Next_Entity (Subp)) then
11445          return Next_Entity (Next_Entity (Subp));
11446       else
11447          return Next_Entity (Subp);
11448       end if;
11449    end External_Subprogram;
11450
11451    ------------------------------
11452    -- Extract_Dispatching_Call --
11453    ------------------------------
11454
11455    procedure Extract_Dispatching_Call
11456      (N        : Node_Id;
11457       Call_Ent : out Entity_Id;
11458       Object   : out Entity_Id;
11459       Actuals  : out List_Id;
11460       Formals  : out List_Id)
11461    is
11462       Call_Nam : Node_Id;
11463
11464    begin
11465       pragma Assert (Nkind (N) = N_Procedure_Call_Statement);
11466
11467       if Present (Original_Node (N)) then
11468          Call_Nam := Name (Original_Node (N));
11469       else
11470          Call_Nam := Name (N);
11471       end if;
11472
11473       --  Retrieve the name of the dispatching procedure. It contains the
11474       --  dispatch table slot number.
11475
11476       loop
11477          case Nkind (Call_Nam) is
11478             when N_Identifier =>
11479                exit;
11480
11481             when N_Selected_Component =>
11482                Call_Nam := Selector_Name (Call_Nam);
11483
11484             when others =>
11485                raise Program_Error;
11486
11487          end case;
11488       end loop;
11489
11490       Actuals  := Parameter_Associations (N);
11491       Call_Ent := Entity (Call_Nam);
11492       Formals  := Parameter_Specifications (Parent (Call_Ent));
11493       Object   := First (Actuals);
11494
11495       if Present (Original_Node (Object)) then
11496          Object := Original_Node (Object);
11497       end if;
11498    end Extract_Dispatching_Call;
11499
11500    -------------------
11501    -- Extract_Entry --
11502    -------------------
11503
11504    procedure Extract_Entry
11505      (N       : Node_Id;
11506       Concval : out Node_Id;
11507       Ename   : out Node_Id;
11508       Index   : out Node_Id)
11509    is
11510       Nam : constant Node_Id := Name (N);
11511
11512    begin
11513       --  For a simple entry, the name is a selected component, with the
11514       --  prefix being the task value, and the selector being the entry.
11515
11516       if Nkind (Nam) = N_Selected_Component then
11517          Concval := Prefix (Nam);
11518          Ename   := Selector_Name (Nam);
11519          Index   := Empty;
11520
11521       --  For a member of an entry family, the name is an indexed component
11522       --  where the prefix is a selected component, whose prefix in turn is
11523       --  the task value, and whose selector is the entry family. The single
11524       --  expression in the expressions list of the indexed component is the
11525       --  subscript for the family.
11526
11527       else pragma Assert (Nkind (Nam) = N_Indexed_Component);
11528          Concval := Prefix (Prefix (Nam));
11529          Ename   := Selector_Name (Prefix (Nam));
11530          Index   := First (Expressions (Nam));
11531       end if;
11532    end Extract_Entry;
11533
11534    -------------------
11535    -- Family_Offset --
11536    -------------------
11537
11538    function Family_Offset
11539      (Loc  : Source_Ptr;
11540       Hi   : Node_Id;
11541       Lo   : Node_Id;
11542       Ttyp : Entity_Id;
11543       Cap  : Boolean) return Node_Id
11544    is
11545       Ityp : Entity_Id;
11546       Real_Hi : Node_Id;
11547       Real_Lo : Node_Id;
11548
11549       function Convert_Discriminant_Ref (Bound : Node_Id) return Node_Id;
11550       --  If one of the bounds is a reference to a discriminant, replace with
11551       --  corresponding discriminal of type. Within the body of a task retrieve
11552       --  the renamed discriminant by simple visibility, using its generated
11553       --  name. Within a protected object, find the original discriminant and
11554       --  replace it with the discriminal of the current protected operation.
11555
11556       ------------------------------
11557       -- Convert_Discriminant_Ref --
11558       ------------------------------
11559
11560       function Convert_Discriminant_Ref (Bound : Node_Id) return Node_Id is
11561          Loc : constant Source_Ptr := Sloc (Bound);
11562          B   : Node_Id;
11563          D   : Entity_Id;
11564
11565       begin
11566          if Is_Entity_Name (Bound)
11567            and then Ekind (Entity (Bound)) = E_Discriminant
11568          then
11569             if Is_Task_Type (Ttyp)
11570               and then Has_Completion (Ttyp)
11571             then
11572                B := Make_Identifier (Loc, Chars (Entity (Bound)));
11573                Find_Direct_Name (B);
11574
11575             elsif Is_Protected_Type (Ttyp) then
11576                D := First_Discriminant (Ttyp);
11577                while Chars (D) /= Chars (Entity (Bound)) loop
11578                   Next_Discriminant (D);
11579                end loop;
11580
11581                B := New_Reference_To  (Discriminal (D), Loc);
11582
11583             else
11584                B := New_Reference_To (Discriminal (Entity (Bound)), Loc);
11585             end if;
11586
11587          elsif Nkind (Bound) = N_Attribute_Reference then
11588             return Bound;
11589
11590          else
11591             B := New_Copy_Tree (Bound);
11592          end if;
11593
11594          return
11595            Make_Attribute_Reference (Loc,
11596              Attribute_Name => Name_Pos,
11597              Prefix => New_Occurrence_Of (Etype (Bound), Loc),
11598              Expressions    => New_List (B));
11599       end Convert_Discriminant_Ref;
11600
11601    --  Start of processing for Family_Offset
11602
11603    begin
11604       Real_Hi := Convert_Discriminant_Ref (Hi);
11605       Real_Lo := Convert_Discriminant_Ref (Lo);
11606
11607       if Cap then
11608          if Is_Task_Type (Ttyp) then
11609             Ityp := RTE (RE_Task_Entry_Index);
11610          else
11611             Ityp := RTE (RE_Protected_Entry_Index);
11612          end if;
11613
11614          Real_Hi :=
11615            Make_Attribute_Reference (Loc,
11616              Prefix         => New_Reference_To (Ityp, Loc),
11617              Attribute_Name => Name_Min,
11618              Expressions    => New_List (
11619                Real_Hi,
11620                Make_Integer_Literal (Loc, Entry_Family_Bound - 1)));
11621
11622          Real_Lo :=
11623            Make_Attribute_Reference (Loc,
11624              Prefix         => New_Reference_To (Ityp, Loc),
11625              Attribute_Name => Name_Max,
11626              Expressions    => New_List (
11627                Real_Lo,
11628                Make_Integer_Literal (Loc, -Entry_Family_Bound)));
11629       end if;
11630
11631       return Make_Op_Subtract (Loc, Real_Hi, Real_Lo);
11632    end Family_Offset;
11633
11634    -----------------
11635    -- Family_Size --
11636    -----------------
11637
11638    function Family_Size
11639      (Loc  : Source_Ptr;
11640       Hi   : Node_Id;
11641       Lo   : Node_Id;
11642       Ttyp : Entity_Id;
11643       Cap  : Boolean) return Node_Id
11644    is
11645       Ityp : Entity_Id;
11646
11647    begin
11648       if Is_Task_Type (Ttyp) then
11649          Ityp := RTE (RE_Task_Entry_Index);
11650       else
11651          Ityp := RTE (RE_Protected_Entry_Index);
11652       end if;
11653
11654       return
11655         Make_Attribute_Reference (Loc,
11656           Prefix         => New_Reference_To (Ityp, Loc),
11657           Attribute_Name => Name_Max,
11658           Expressions    => New_List (
11659             Make_Op_Add (Loc,
11660               Left_Opnd  =>
11661                 Family_Offset (Loc, Hi, Lo, Ttyp, Cap),
11662               Right_Opnd =>
11663                 Make_Integer_Literal (Loc, 1)),
11664             Make_Integer_Literal (Loc, 0)));
11665    end Family_Size;
11666
11667    -----------------------
11668    -- Find_Master_Scope --
11669    -----------------------
11670
11671    function Find_Master_Scope (E : Entity_Id) return Entity_Id is
11672       S : Entity_Id;
11673
11674    begin
11675       --  In Ada2005, the master is the innermost enclosing scope that is not
11676       --  transient. If the enclosing block is the rewriting of a call or the
11677       --  scope is an extended return statement this is valid master. The
11678       --  master in an extended return is only used within the return, and is
11679       --  subsequently overwritten in Move_Activation_Chain, but it must exist
11680       --  now before that overwriting occurs.
11681
11682       S := Scope (E);
11683
11684       if Ada_Version >= Ada_2005 then
11685          while Is_Internal (S) loop
11686             if Nkind (Parent (S)) = N_Block_Statement
11687               and then
11688                 Nkind (Original_Node (Parent (S))) = N_Procedure_Call_Statement
11689             then
11690                exit;
11691
11692             elsif Ekind (S) = E_Return_Statement then
11693                exit;
11694
11695             else
11696                S := Scope (S);
11697             end if;
11698          end loop;
11699       end if;
11700
11701       return S;
11702    end Find_Master_Scope;
11703
11704    -----------------------------------
11705    -- Find_Task_Or_Protected_Pragma --
11706    -----------------------------------
11707
11708    function Find_Task_Or_Protected_Pragma
11709      (T : Node_Id;
11710       P : Name_Id) return Node_Id
11711    is
11712       N : Node_Id;
11713
11714    begin
11715       N := First (Visible_Declarations (T));
11716       while Present (N) loop
11717          if Nkind (N) = N_Pragma then
11718             if Pragma_Name (N) = P then
11719                return N;
11720
11721             elsif P = Name_Priority
11722               and then Pragma_Name (N) = Name_Interrupt_Priority
11723             then
11724                return N;
11725
11726             else
11727                Next (N);
11728             end if;
11729
11730          else
11731             Next (N);
11732          end if;
11733       end loop;
11734
11735       N := First (Private_Declarations (T));
11736       while Present (N) loop
11737          if Nkind (N) = N_Pragma then
11738             if Pragma_Name (N) = P then
11739                return N;
11740
11741             elsif P = Name_Priority
11742               and then Pragma_Name (N) = Name_Interrupt_Priority
11743             then
11744                return N;
11745
11746             else
11747                Next (N);
11748             end if;
11749
11750          else
11751             Next (N);
11752          end if;
11753       end loop;
11754
11755       raise Program_Error;
11756    end Find_Task_Or_Protected_Pragma;
11757
11758    -------------------------------
11759    -- First_Protected_Operation --
11760    -------------------------------
11761
11762    function First_Protected_Operation (D : List_Id) return Node_Id is
11763       First_Op : Node_Id;
11764
11765    begin
11766       First_Op := First (D);
11767       while Present (First_Op)
11768         and then not Nkind_In (First_Op, N_Subprogram_Body, N_Entry_Body)
11769       loop
11770          Next (First_Op);
11771       end loop;
11772
11773       return First_Op;
11774    end First_Protected_Operation;
11775
11776    ---------------------------------------
11777    -- Install_Private_Data_Declarations --
11778    ---------------------------------------
11779
11780    procedure Install_Private_Data_Declarations
11781      (Loc      : Source_Ptr;
11782       Spec_Id  : Entity_Id;
11783       Conc_Typ : Entity_Id;
11784       Body_Nod : Node_Id;
11785       Decls    : List_Id;
11786       Barrier  : Boolean := False;
11787       Family   : Boolean := False)
11788    is
11789       Is_Protected : constant Boolean := Is_Protected_Type (Conc_Typ);
11790       Decl         : Node_Id;
11791       Def          : Node_Id;
11792       Insert_Node  : Node_Id := Empty;
11793       Obj_Ent      : Entity_Id;
11794
11795       procedure Add (Decl : Node_Id);
11796       --  Add a single declaration after Insert_Node. If this is the first
11797       --  addition, Decl is added to the front of Decls and it becomes the
11798       --  insertion node.
11799
11800       function Replace_Bound (Bound : Node_Id) return Node_Id;
11801       --  The bounds of an entry index may depend on discriminants, create a
11802       --  reference to the corresponding prival. Otherwise return a duplicate
11803       --  of the original bound.
11804
11805       ---------
11806       -- Add --
11807       ---------
11808
11809       procedure Add (Decl : Node_Id) is
11810       begin
11811          if No (Insert_Node) then
11812             Prepend_To (Decls, Decl);
11813          else
11814             Insert_After (Insert_Node, Decl);
11815          end if;
11816
11817          Insert_Node := Decl;
11818       end Add;
11819
11820       --------------------------
11821       -- Replace_Discriminant --
11822       --------------------------
11823
11824       function Replace_Bound (Bound : Node_Id) return Node_Id is
11825       begin
11826          if Nkind (Bound) = N_Identifier
11827            and then Is_Discriminal (Entity (Bound))
11828          then
11829             return Make_Identifier (Loc, Chars (Entity (Bound)));
11830          else
11831             return Duplicate_Subexpr (Bound);
11832          end if;
11833       end Replace_Bound;
11834
11835    --  Start of processing for Install_Private_Data_Declarations
11836
11837    begin
11838       --  Step 1: Retrieve the concurrent object entity. Obj_Ent can denote
11839       --  formal parameter _O, _object or _task depending on the context.
11840
11841       Obj_Ent := Concurrent_Object (Spec_Id, Conc_Typ);
11842
11843       --  Special processing of _O for barrier functions, protected entries
11844       --  and families.
11845
11846       if Barrier
11847         or else
11848           (Is_Protected
11849              and then
11850                (Ekind (Spec_Id) = E_Entry
11851                   or else Ekind (Spec_Id) = E_Entry_Family))
11852       then
11853          declare
11854             Conc_Rec : constant Entity_Id :=
11855                          Corresponding_Record_Type (Conc_Typ);
11856             Typ_Id   : constant Entity_Id :=
11857                          Make_Defining_Identifier (Loc,
11858                            New_External_Name (Chars (Conc_Rec), 'P'));
11859          begin
11860             --  Generate:
11861             --    type prot_typVP is access prot_typV;
11862
11863             Decl :=
11864               Make_Full_Type_Declaration (Loc,
11865                 Defining_Identifier => Typ_Id,
11866                 Type_Definition     =>
11867                   Make_Access_To_Object_Definition (Loc,
11868                     Subtype_Indication =>
11869                       New_Reference_To (Conc_Rec, Loc)));
11870             Add (Decl);
11871
11872             --  Generate:
11873             --    _object : prot_typVP := prot_typV (_O);
11874
11875             Decl :=
11876               Make_Object_Declaration (Loc,
11877                 Defining_Identifier =>
11878                   Make_Defining_Identifier (Loc, Name_uObject),
11879                 Object_Definition   => New_Reference_To (Typ_Id, Loc),
11880                 Expression          =>
11881                   Unchecked_Convert_To (Typ_Id,
11882                     New_Reference_To (Obj_Ent, Loc)));
11883             Add (Decl);
11884
11885             --  Set the reference to the concurrent object
11886
11887             Obj_Ent := Defining_Identifier (Decl);
11888          end;
11889       end if;
11890
11891       --  Step 2: Create the Protection object and build its declaration for
11892       --  any protected entry (family) of subprogram.
11893
11894       if Is_Protected then
11895          declare
11896             Prot_Ent : constant Entity_Id := Make_Temporary (Loc, 'R');
11897             Prot_Typ : RE_Id;
11898
11899          begin
11900             Set_Protection_Object (Spec_Id, Prot_Ent);
11901
11902             --  Determine the proper protection type
11903
11904             if Has_Attach_Handler (Conc_Typ)
11905               and then not Restricted_Profile
11906             then
11907                Prot_Typ := RE_Static_Interrupt_Protection;
11908
11909             elsif Has_Interrupt_Handler (Conc_Typ) then
11910                Prot_Typ := RE_Dynamic_Interrupt_Protection;
11911
11912             --  The type has explicit entries or generated primitive entry
11913             --  wrappers.
11914
11915             elsif Has_Entries (Conc_Typ)
11916               or else
11917                 (Ada_Version >= Ada_2005
11918                    and then Present (Interface_List (Parent (Conc_Typ))))
11919             then
11920                case Corresponding_Runtime_Package (Conc_Typ) is
11921                   when System_Tasking_Protected_Objects_Entries =>
11922                      Prot_Typ := RE_Protection_Entries;
11923
11924                   when System_Tasking_Protected_Objects_Single_Entry =>
11925                      Prot_Typ := RE_Protection_Entry;
11926
11927                   when others =>
11928                      raise Program_Error;
11929                end case;
11930
11931             else
11932                Prot_Typ := RE_Protection;
11933             end if;
11934
11935             --  Generate:
11936             --    conc_typR : protection_typ renames _object._object;
11937
11938             Decl :=
11939               Make_Object_Renaming_Declaration (Loc,
11940                 Defining_Identifier => Prot_Ent,
11941                 Subtype_Mark =>
11942                   New_Reference_To (RTE (Prot_Typ), Loc),
11943                 Name =>
11944                   Make_Selected_Component (Loc,
11945                     Prefix =>
11946                       New_Reference_To (Obj_Ent, Loc),
11947                     Selector_Name =>
11948                       Make_Identifier (Loc, Name_uObject)));
11949             Add (Decl);
11950          end;
11951       end if;
11952
11953       --  Step 3: Add discriminant renamings (if any)
11954
11955       if Has_Discriminants (Conc_Typ) then
11956          declare
11957             D : Entity_Id;
11958
11959          begin
11960             D := First_Discriminant (Conc_Typ);
11961             while Present (D) loop
11962
11963                --  Adjust the source location
11964
11965                Set_Sloc (Discriminal (D), Loc);
11966
11967                --  Generate:
11968                --    discr_name : discr_typ renames _object.discr_name;
11969                --      or
11970                --    discr_name : discr_typ renames _task.discr_name;
11971
11972                Decl :=
11973                  Make_Object_Renaming_Declaration (Loc,
11974                    Defining_Identifier => Discriminal (D),
11975                    Subtype_Mark        => New_Reference_To (Etype (D), Loc),
11976                    Name                =>
11977                      Make_Selected_Component (Loc,
11978                        Prefix        => New_Reference_To (Obj_Ent, Loc),
11979                        Selector_Name => Make_Identifier (Loc, Chars (D))));
11980                Add (Decl);
11981
11982                Next_Discriminant (D);
11983             end loop;
11984          end;
11985       end if;
11986
11987       --  Step 4: Add private component renamings (if any)
11988
11989       if Is_Protected then
11990          Def := Protected_Definition (Parent (Conc_Typ));
11991
11992          if Present (Private_Declarations (Def)) then
11993             declare
11994                Comp    : Node_Id;
11995                Comp_Id : Entity_Id;
11996                Decl_Id : Entity_Id;
11997
11998             begin
11999                Comp := First (Private_Declarations (Def));
12000                while Present (Comp) loop
12001                   if Nkind (Comp) = N_Component_Declaration then
12002                      Comp_Id := Defining_Identifier (Comp);
12003                      Decl_Id :=
12004                        Make_Defining_Identifier (Loc, Chars (Comp_Id));
12005
12006                      --  Minimal decoration
12007
12008                      if Ekind (Spec_Id) = E_Function then
12009                         Set_Ekind (Decl_Id, E_Constant);
12010                      else
12011                         Set_Ekind (Decl_Id, E_Variable);
12012                      end if;
12013
12014                      Set_Prival      (Comp_Id, Decl_Id);
12015                      Set_Prival_Link (Decl_Id, Comp_Id);
12016                      Set_Is_Aliased  (Decl_Id, Is_Aliased (Comp_Id));
12017
12018                      --  Generate:
12019                      --    comp_name : comp_typ renames _object.comp_name;
12020
12021                      Decl :=
12022                        Make_Object_Renaming_Declaration (Loc,
12023                          Defining_Identifier => Decl_Id,
12024                          Subtype_Mark =>
12025                            New_Reference_To (Etype (Comp_Id), Loc),
12026                          Name =>
12027                            Make_Selected_Component (Loc,
12028                              Prefix =>
12029                                New_Reference_To (Obj_Ent, Loc),
12030                              Selector_Name =>
12031                                Make_Identifier (Loc, Chars (Comp_Id))));
12032                      Add (Decl);
12033                   end if;
12034
12035                   Next (Comp);
12036                end loop;
12037             end;
12038          end if;
12039       end if;
12040
12041       --  Step 5: Add the declaration of the entry index and the associated
12042       --  type for barrier functions and entry families.
12043
12044       if (Barrier and then Family)
12045         or else Ekind (Spec_Id) = E_Entry_Family
12046       then
12047          declare
12048             E         : constant Entity_Id := Index_Object (Spec_Id);
12049             Index     : constant Entity_Id :=
12050                           Defining_Identifier (
12051                             Entry_Index_Specification (
12052                               Entry_Body_Formal_Part (Body_Nod)));
12053             Index_Con : constant Entity_Id :=
12054                           Make_Defining_Identifier (Loc, Chars (Index));
12055             High      : Node_Id;
12056             Index_Typ : Entity_Id;
12057             Low       : Node_Id;
12058
12059          begin
12060             --  Minimal decoration
12061
12062             Set_Ekind                (Index_Con, E_Constant);
12063             Set_Entry_Index_Constant (Index, Index_Con);
12064             Set_Discriminal_Link     (Index_Con, Index);
12065
12066             --  Retrieve the bounds of the entry family
12067
12068             High := Type_High_Bound (Etype (Index));
12069             Low  := Type_Low_Bound  (Etype (Index));
12070
12071             --  In the simple case the entry family is given by a subtype
12072             --  mark and the index constant has the same type.
12073
12074             if Is_Entity_Name (Original_Node (
12075                  Discrete_Subtype_Definition (Parent (Index))))
12076             then
12077                Index_Typ := Etype (Index);
12078
12079             --  Otherwise a new subtype declaration is required
12080
12081             else
12082                High := Replace_Bound (High);
12083                Low  := Replace_Bound (Low);
12084
12085                Index_Typ := Make_Temporary (Loc, 'J');
12086
12087                --  Generate:
12088                --    subtype Jnn is <Etype of Index> range Low .. High;
12089
12090                Decl :=
12091                  Make_Subtype_Declaration (Loc,
12092                    Defining_Identifier => Index_Typ,
12093                    Subtype_Indication =>
12094                      Make_Subtype_Indication (Loc,
12095                        Subtype_Mark =>
12096                          New_Reference_To (Base_Type (Etype (Index)), Loc),
12097                        Constraint =>
12098                          Make_Range_Constraint (Loc,
12099                            Range_Expression =>
12100                              Make_Range (Loc, Low, High))));
12101                Add (Decl);
12102             end if;
12103
12104             Set_Etype (Index_Con, Index_Typ);
12105
12106             --  Create the object which designates the index:
12107             --    J : constant Jnn :=
12108             --          Jnn'Val (_E - <index expr> + Jnn'Pos (Jnn'First));
12109             --
12110             --  where Jnn is the subtype created above or the original type of
12111             --  the index, _E is a formal of the protected body subprogram and
12112             --  <index expr> is the index of the first family member.
12113
12114             Decl :=
12115               Make_Object_Declaration (Loc,
12116                 Defining_Identifier => Index_Con,
12117                 Constant_Present => True,
12118                 Object_Definition =>
12119                   New_Reference_To (Index_Typ, Loc),
12120
12121                 Expression =>
12122                   Make_Attribute_Reference (Loc,
12123                     Prefix =>
12124                       New_Reference_To (Index_Typ, Loc),
12125                     Attribute_Name => Name_Val,
12126
12127                     Expressions => New_List (
12128
12129                       Make_Op_Add (Loc,
12130                         Left_Opnd =>
12131                           Make_Op_Subtract (Loc,
12132                             Left_Opnd =>
12133                               New_Reference_To (E, Loc),
12134                             Right_Opnd =>
12135                               Entry_Index_Expression (Loc,
12136                                 Defining_Identifier (Body_Nod),
12137                                 Empty, Conc_Typ)),
12138
12139                         Right_Opnd =>
12140                           Make_Attribute_Reference (Loc,
12141                             Prefix =>
12142                               New_Reference_To (Index_Typ, Loc),
12143                             Attribute_Name => Name_Pos,
12144                             Expressions => New_List (
12145                               Make_Attribute_Reference (Loc,
12146                                 Prefix =>
12147                                   New_Reference_To (Index_Typ, Loc),
12148                                 Attribute_Name => Name_First)))))));
12149             Add (Decl);
12150          end;
12151       end if;
12152    end Install_Private_Data_Declarations;
12153
12154    ---------------------------------
12155    -- Is_Potentially_Large_Family --
12156    ---------------------------------
12157
12158    function Is_Potentially_Large_Family
12159      (Base_Index : Entity_Id;
12160       Conctyp    : Entity_Id;
12161       Lo         : Node_Id;
12162       Hi         : Node_Id) return Boolean
12163    is
12164    begin
12165       return Scope (Base_Index) = Standard_Standard
12166         and then Base_Index = Base_Type (Standard_Integer)
12167         and then Has_Discriminants (Conctyp)
12168         and then Present
12169           (Discriminant_Default_Value (First_Discriminant (Conctyp)))
12170         and then
12171           (Denotes_Discriminant (Lo, True)
12172             or else Denotes_Discriminant (Hi, True));
12173    end Is_Potentially_Large_Family;
12174
12175    -------------------------------------
12176    -- Is_Private_Primitive_Subprogram --
12177    -------------------------------------
12178
12179    function Is_Private_Primitive_Subprogram (Id : Entity_Id) return Boolean is
12180    begin
12181       return
12182         (Ekind (Id) = E_Function or else Ekind (Id) = E_Procedure)
12183           and then Is_Private_Primitive (Id);
12184    end Is_Private_Primitive_Subprogram;
12185
12186    ------------------
12187    -- Index_Object --
12188    ------------------
12189
12190    function Index_Object (Spec_Id : Entity_Id) return Entity_Id is
12191       Bod_Subp : constant Entity_Id := Protected_Body_Subprogram (Spec_Id);
12192       Formal   : Entity_Id;
12193
12194    begin
12195       Formal := First_Formal (Bod_Subp);
12196       while Present (Formal) loop
12197
12198          --  Look for formal parameter _E
12199
12200          if Chars (Formal) = Name_uE then
12201             return Formal;
12202          end if;
12203
12204          Next_Formal (Formal);
12205       end loop;
12206
12207       --  A protected body subprogram should always have the parameter in
12208       --  question.
12209
12210       raise Program_Error;
12211    end Index_Object;
12212
12213    --------------------------------
12214    -- Make_Initialize_Protection --
12215    --------------------------------
12216
12217    function Make_Initialize_Protection
12218      (Protect_Rec : Entity_Id) return List_Id
12219    is
12220       Loc         : constant Source_Ptr := Sloc (Protect_Rec);
12221       P_Arr       : Entity_Id;
12222       Pdef        : Node_Id;
12223       Pdec        : Node_Id;
12224       Ptyp        : constant Node_Id :=
12225                       Corresponding_Concurrent_Type (Protect_Rec);
12226       Args        : List_Id;
12227       L           : constant List_Id := New_List;
12228       Has_Entry   : constant Boolean := Has_Entries (Ptyp);
12229       Restricted  : constant Boolean := Restricted_Profile;
12230
12231    begin
12232       --  We may need two calls to properly initialize the object, one to
12233       --  Initialize_Protection, and possibly one to Install_Handlers if we
12234       --  have a pragma Attach_Handler.
12235
12236       --  Get protected declaration. In the case of a task type declaration,
12237       --  this is simply the parent of the protected type entity. In the single
12238       --  protected object declaration, this parent will be the implicit type,
12239       --  and we can find the corresponding single protected object declaration
12240       --  by searching forward in the declaration list in the tree.
12241
12242       --  Is the test for N_Single_Protected_Declaration needed here??? Nodes
12243       --  of this type should have been removed during semantic analysis.
12244
12245       Pdec := Parent (Ptyp);
12246       while not Nkind_In (Pdec, N_Protected_Type_Declaration,
12247                                 N_Single_Protected_Declaration)
12248       loop
12249          Next (Pdec);
12250       end loop;
12251
12252       --  Now we can find the object definition from this declaration
12253
12254       Pdef := Protected_Definition (Pdec);
12255
12256       --  Build the parameter list for the call. Note that _Init is the name
12257       --  of the formal for the object to be initialized, which is the task
12258       --  value record itself.
12259
12260       Args := New_List;
12261
12262       --  Object parameter. This is a pointer to the object of type
12263       --  Protection used by the GNARL to control the protected object.
12264
12265       Append_To (Args,
12266         Make_Attribute_Reference (Loc,
12267           Prefix =>
12268             Make_Selected_Component (Loc,
12269               Prefix => Make_Identifier (Loc, Name_uInit),
12270               Selector_Name => Make_Identifier (Loc, Name_uObject)),
12271           Attribute_Name => Name_Unchecked_Access));
12272
12273       --  Priority parameter. Set to Unspecified_Priority unless there is a
12274       --  priority pragma, in which case we take the value from the pragma,
12275       --  or there is an interrupt pragma and no priority pragma, and we
12276       --  set the ceiling to Interrupt_Priority'Last, an implementation-
12277       --  defined value, see D.3(10).
12278
12279       if Present (Pdef)
12280         and then Has_Pragma_Priority (Pdef)
12281       then
12282          declare
12283             Prio : constant Node_Id :=
12284                      Expression
12285                        (First
12286                           (Pragma_Argument_Associations
12287                              (Find_Task_Or_Protected_Pragma
12288                                 (Pdef, Name_Priority))));
12289             Temp : Entity_Id;
12290
12291          begin
12292             --  If priority is a static expression, then we can duplicate it
12293             --  with no problem and simply append it to the argument list.
12294
12295             if Is_Static_Expression (Prio) then
12296                Append_To (Args,
12297                           Duplicate_Subexpr_No_Checks (Prio));
12298
12299             --  Otherwise, the priority may be a per-object expression, if it
12300             --  depends on a discriminant of the type. In this case, create
12301             --  local variable to capture the expression. Note that it is
12302             --  really necessary to create this variable explicitly. It might
12303             --  be thought that removing side effects would the appropriate
12304             --  approach, but that could generate declarations improperly
12305             --  placed in the enclosing scope.
12306
12307             --  Note: Use System.Any_Priority as the expected type for the
12308             --  non-static priority expression, in case the expression has not
12309             --  been analyzed yet (as occurs for example with pragma
12310             --  Interrupt_Priority).
12311
12312             else
12313                Temp := Make_Temporary (Loc, 'R', Prio);
12314                Append_To (L,
12315                   Make_Object_Declaration (Loc,
12316                      Defining_Identifier => Temp,
12317                      Object_Definition   =>
12318                        New_Occurrence_Of (RTE (RE_Any_Priority), Loc),
12319                      Expression          => Relocate_Node (Prio)));
12320
12321                Append_To (Args, New_Occurrence_Of (Temp, Loc));
12322             end if;
12323          end;
12324
12325       --  When no priority is specified but an xx_Handler pragma is, we default
12326       --  to System.Interrupts.Default_Interrupt_Priority, see D.3(10).
12327
12328       elsif Has_Interrupt_Handler (Ptyp)
12329         or else Has_Attach_Handler (Ptyp)
12330       then
12331          Append_To (Args,
12332            New_Reference_To (RTE (RE_Default_Interrupt_Priority), Loc));
12333
12334       --  Normal case, no priority or xx_Handler specified, default priority
12335
12336       else
12337          Append_To (Args,
12338            New_Reference_To (RTE (RE_Unspecified_Priority), Loc));
12339       end if;
12340
12341       --  Test for Compiler_Info parameter. This parameter allows entry body
12342       --  procedures and barrier functions to be called from the runtime. It
12343       --  is a pointer to the record generated by the compiler to represent
12344       --  the protected object.
12345
12346       if Has_Entry
12347         or else Has_Interrupt_Handler (Ptyp)
12348         or else Has_Attach_Handler (Ptyp)
12349         or else Has_Interfaces (Protect_Rec)
12350       then
12351          declare
12352             Pkg_Id      : constant RTU_Id  :=
12353                             Corresponding_Runtime_Package (Ptyp);
12354             Called_Subp : RE_Id;
12355
12356          begin
12357             case Pkg_Id is
12358                when System_Tasking_Protected_Objects_Entries =>
12359                   Called_Subp := RE_Initialize_Protection_Entries;
12360
12361                when System_Tasking_Protected_Objects =>
12362                   Called_Subp := RE_Initialize_Protection;
12363
12364                when System_Tasking_Protected_Objects_Single_Entry =>
12365                   Called_Subp := RE_Initialize_Protection_Entry;
12366
12367                when others =>
12368                   raise Program_Error;
12369             end case;
12370
12371             if Has_Entry or else not Restricted then
12372                Append_To (Args,
12373                  Make_Attribute_Reference (Loc,
12374                    Prefix => Make_Identifier (Loc, Name_uInit),
12375                    Attribute_Name => Name_Address));
12376             end if;
12377
12378             --  Entry_Bodies parameter. This is a pointer to an array of
12379             --  pointers to the entry body procedures and barrier functions of
12380             --  the object. If the protected type has no entries this object
12381             --  will not exist, in this case, pass a null.
12382
12383             if Has_Entry then
12384                P_Arr := Entry_Bodies_Array (Ptyp);
12385
12386                Append_To (Args,
12387                  Make_Attribute_Reference (Loc,
12388                    Prefix => New_Reference_To (P_Arr, Loc),
12389                    Attribute_Name => Name_Unrestricted_Access));
12390
12391                if Pkg_Id = System_Tasking_Protected_Objects_Entries then
12392
12393                   --  Find index mapping function (clumsy but ok for now)
12394
12395                   while Ekind (P_Arr) /= E_Function loop
12396                      Next_Entity (P_Arr);
12397                   end loop;
12398
12399                   Append_To (Args,
12400                     Make_Attribute_Reference (Loc,
12401                       Prefix =>
12402                         New_Reference_To (P_Arr, Loc),
12403                       Attribute_Name => Name_Unrestricted_Access));
12404
12405                   --  Build_Entry_Names generation flag. When set to true, the
12406                   --  runtime will allocate an array to hold the string names
12407                   --  of protected entries.
12408
12409                   if not Restricted_Profile then
12410                      if Entry_Names_OK then
12411                         Append_To (Args,
12412                           New_Reference_To (Standard_True, Loc));
12413                      else
12414                         Append_To (Args,
12415                           New_Reference_To (Standard_False, Loc));
12416                      end if;
12417                   end if;
12418                end if;
12419
12420             elsif Pkg_Id = System_Tasking_Protected_Objects_Single_Entry then
12421                Append_To (Args, Make_Null (Loc));
12422
12423             elsif Pkg_Id = System_Tasking_Protected_Objects_Entries then
12424                Append_To (Args, Make_Null (Loc));
12425                Append_To (Args, Make_Null (Loc));
12426                Append_To (Args, New_Reference_To (Standard_False, Loc));
12427             end if;
12428
12429             Append_To (L,
12430               Make_Procedure_Call_Statement (Loc,
12431                 Name => New_Reference_To (RTE (Called_Subp), Loc),
12432                 Parameter_Associations => Args));
12433          end;
12434       else
12435          Append_To (L,
12436            Make_Procedure_Call_Statement (Loc,
12437              Name => New_Reference_To (RTE (RE_Initialize_Protection), Loc),
12438              Parameter_Associations => Args));
12439       end if;
12440
12441       if Has_Attach_Handler (Ptyp) then
12442
12443          --  We have a list of N Attach_Handler (ProcI, ExprI), and we have to
12444          --  make the following call:
12445
12446          --  Install_Handlers (_object,
12447          --    ((Expr1, Proc1'access), ...., (ExprN, ProcN'access));
12448
12449          --  or, in the case of Ravenscar:
12450
12451          --  Install_Restricted_Handlers
12452          --    ((Expr1, Proc1'access), ...., (ExprN, ProcN'access));
12453
12454          declare
12455             Args  : constant List_Id := New_List;
12456             Table : constant List_Id := New_List;
12457             Ritem : Node_Id          := First_Rep_Item (Ptyp);
12458
12459          begin
12460             --  Build the Attach_Handler table argument
12461
12462             while Present (Ritem) loop
12463                if Nkind (Ritem) = N_Pragma
12464                  and then Pragma_Name (Ritem) = Name_Attach_Handler
12465                then
12466                   declare
12467                      Handler : constant Node_Id :=
12468                                  First (Pragma_Argument_Associations (Ritem));
12469
12470                      Interrupt : constant Node_Id := Next (Handler);
12471                      Expr      : constant Node_Id := Expression (Interrupt);
12472
12473                   begin
12474                      Append_To (Table,
12475                        Make_Aggregate (Loc, Expressions => New_List (
12476                          Unchecked_Convert_To
12477                           (RTE (RE_System_Interrupt_Id), Expr),
12478                          Make_Attribute_Reference (Loc,
12479                            Prefix => Make_Selected_Component (Loc,
12480                               Make_Identifier (Loc, Name_uInit),
12481                               Duplicate_Subexpr_No_Checks
12482                                 (Expression (Handler))),
12483                            Attribute_Name => Name_Access))));
12484                   end;
12485                end if;
12486
12487                Next_Rep_Item (Ritem);
12488             end loop;
12489
12490             --  Append the table argument we just built
12491
12492             Append_To (Args, Make_Aggregate (Loc, Table));
12493
12494             --  Append the Install_Handlers (or Install_Restricted_Handlers)
12495             --  call to the statements.
12496
12497             if Restricted then
12498                --  Call a simplified version of Install_Handlers to be used
12499                --  when the Ravenscar restrictions are in effect
12500                --  (Install_Restricted_Handlers).
12501
12502                Append_To (L,
12503                  Make_Procedure_Call_Statement (Loc,
12504                    Name =>
12505                      New_Reference_To
12506                         (RTE (RE_Install_Restricted_Handlers), Loc),
12507                    Parameter_Associations => Args));
12508
12509             else
12510                --  First, prepends the _object argument
12511
12512                Prepend_To (Args,
12513                  Make_Attribute_Reference (Loc,
12514                    Prefix =>
12515                      Make_Selected_Component (Loc,
12516                        Prefix => Make_Identifier (Loc, Name_uInit),
12517                        Selector_Name => Make_Identifier (Loc, Name_uObject)),
12518                    Attribute_Name => Name_Unchecked_Access));
12519
12520                --  Then, insert call to Install_Handlers
12521
12522                Append_To (L,
12523                  Make_Procedure_Call_Statement (Loc,
12524                    Name => New_Reference_To (RTE (RE_Install_Handlers), Loc),
12525                    Parameter_Associations => Args));
12526             end if;
12527          end;
12528       end if;
12529
12530       return L;
12531    end Make_Initialize_Protection;
12532
12533    ---------------------------
12534    -- Make_Task_Create_Call --
12535    ---------------------------
12536
12537    function Make_Task_Create_Call (Task_Rec : Entity_Id) return Node_Id is
12538       Loc    : constant Source_Ptr := Sloc (Task_Rec);
12539       Args   : List_Id;
12540       Ecount : Node_Id;
12541       Name   : Node_Id;
12542       Tdec   : Node_Id;
12543       Tdef   : Node_Id;
12544       Tnam   : Name_Id;
12545       Ttyp   : Node_Id;
12546
12547    begin
12548       Ttyp := Corresponding_Concurrent_Type (Task_Rec);
12549       Tnam := Chars (Ttyp);
12550
12551       --  Get task declaration. In the case of a task type declaration, this is
12552       --  simply the parent of the task type entity. In the single task
12553       --  declaration, this parent will be the implicit type, and we can find
12554       --  the corresponding single task declaration by searching forward in the
12555       --  declaration list in the tree.
12556
12557       --  Is the test for N_Single_Task_Declaration needed here??? Nodes of
12558       --  this type should have been removed during semantic analysis.
12559
12560       Tdec := Parent (Ttyp);
12561       while not Nkind_In (Tdec, N_Task_Type_Declaration,
12562                                 N_Single_Task_Declaration)
12563       loop
12564          Next (Tdec);
12565       end loop;
12566
12567       --  Now we can find the task definition from this declaration
12568
12569       Tdef := Task_Definition (Tdec);
12570
12571       --  Build the parameter list for the call. Note that _Init is the name
12572       --  of the formal for the object to be initialized, which is the task
12573       --  value record itself.
12574
12575       Args := New_List;
12576
12577       --  Priority parameter. Set to Unspecified_Priority unless there is a
12578       --  priority pragma, in which case we take the value from the pragma.
12579
12580       if Present (Tdef) and then Has_Pragma_Priority (Tdef) then
12581          Append_To (Args,
12582            Make_Selected_Component (Loc,
12583              Prefix => Make_Identifier (Loc, Name_uInit),
12584              Selector_Name => Make_Identifier (Loc, Name_uPriority)));
12585       else
12586          Append_To (Args,
12587            New_Reference_To (RTE (RE_Unspecified_Priority), Loc));
12588       end if;
12589
12590       --  Optional Stack parameter
12591
12592       if Restricted_Profile then
12593
12594          --  If the stack has been preallocated by the expander then
12595          --  pass its address. Otherwise, pass a null address.
12596
12597          if Preallocated_Stacks_On_Target then
12598             Append_To (Args,
12599               Make_Attribute_Reference (Loc,
12600                 Prefix         => Make_Selected_Component (Loc,
12601                   Prefix        => Make_Identifier (Loc, Name_uInit),
12602                   Selector_Name =>
12603                     Make_Identifier (Loc, Name_uStack)),
12604                 Attribute_Name => Name_Address));
12605
12606          else
12607             Append_To (Args,
12608               New_Reference_To (RTE (RE_Null_Address), Loc));
12609          end if;
12610       end if;
12611
12612       --  Size parameter. If no Storage_Size pragma is present, then
12613       --  the size is taken from the taskZ variable for the type, which
12614       --  is either Unspecified_Size, or has been reset by the use of
12615       --  a Storage_Size attribute definition clause. If a pragma is
12616       --  present, then the size is taken from the _Size field of the
12617       --  task value record, which was set from the pragma value.
12618
12619       if Present (Tdef)
12620         and then Has_Storage_Size_Pragma (Tdef)
12621       then
12622          Append_To (Args,
12623            Make_Selected_Component (Loc,
12624              Prefix => Make_Identifier (Loc, Name_uInit),
12625              Selector_Name => Make_Identifier (Loc, Name_uSize)));
12626
12627       else
12628          Append_To (Args,
12629            New_Reference_To (Storage_Size_Variable (Ttyp), Loc));
12630       end if;
12631
12632       --  Task_Info parameter. Set to Unspecified_Task_Info unless there is a
12633       --  Task_Info pragma, in which case we take the value from the pragma.
12634
12635       if Present (Tdef)
12636         and then Has_Task_Info_Pragma (Tdef)
12637       then
12638          Append_To (Args,
12639            Make_Selected_Component (Loc,
12640              Prefix => Make_Identifier (Loc, Name_uInit),
12641              Selector_Name => Make_Identifier (Loc, Name_uTask_Info)));
12642
12643       else
12644          Append_To (Args,
12645            New_Reference_To (RTE (RE_Unspecified_Task_Info), Loc));
12646       end if;
12647
12648       --  CPU parameter. Set to Unspecified_CPU unless there is a CPU pragma,
12649       --  in which case we take the value from the pragma. The parameter is
12650       --  passed as an Integer because in the case of unspecified CPU the
12651       --  value is not in the range of CPU_Range.
12652
12653       if Present (Tdef) and then Has_Pragma_CPU (Tdef) then
12654          Append_To (Args,
12655            Convert_To (Standard_Integer,
12656              Make_Selected_Component (Loc,
12657                Prefix => Make_Identifier (Loc, Name_uInit),
12658                Selector_Name => Make_Identifier (Loc, Name_uCPU))));
12659
12660       else
12661          Append_To (Args,
12662            New_Reference_To (RTE (RE_Unspecified_CPU), Loc));
12663       end if;
12664
12665       if not Restricted_Profile then
12666
12667          --  Deadline parameter. If no Relative_Deadline pragma is present,
12668          --  then the deadline is Time_Span_Zero. If a pragma is present, then
12669          --  the deadline is taken from the _Relative_Deadline field of the
12670          --  task value record, which was set from the pragma value. Note that
12671          --  this parameter must not be generated for the restricted profiles
12672          --  since Ravenscar does not allow deadlines.
12673
12674          --  Case where pragma Relative_Deadline applies: use given value
12675
12676          if Present (Tdef) and then Has_Relative_Deadline_Pragma (Tdef) then
12677             Append_To (Args,
12678               Make_Selected_Component (Loc,
12679                 Prefix => Make_Identifier (Loc, Name_uInit),
12680                 Selector_Name =>
12681                   Make_Identifier (Loc, Name_uRelative_Deadline)));
12682
12683          --  No pragma Relative_Deadline apply to the task
12684
12685          else
12686             Append_To (Args,
12687               New_Reference_To (RTE (RE_Time_Span_Zero), Loc));
12688          end if;
12689
12690          --  Number of entries. This is an expression of the form:
12691
12692          --    n + _Init.a'Length + _Init.a'B'Length + ...
12693
12694          --  where a,b... are the entry family names for the task definition
12695
12696          Ecount :=
12697            Build_Entry_Count_Expression
12698              (Ttyp,
12699               Component_Items
12700                 (Component_List
12701                    (Type_Definition
12702                       (Parent (Corresponding_Record_Type (Ttyp))))),
12703               Loc);
12704          Append_To (Args, Ecount);
12705
12706          --  Master parameter. This is a reference to the _Master parameter of
12707          --  the initialization procedure, except in the case of the pragma
12708          --  Restrictions (No_Task_Hierarchy) where the value is fixed to
12709          --  System.Tasking.Library_Task_Level.
12710
12711          if Restriction_Active (No_Task_Hierarchy) = False then
12712             Append_To (Args, Make_Identifier (Loc, Name_uMaster));
12713          else
12714             Append_To (Args,
12715               New_Occurrence_Of (RTE (RE_Library_Task_Level), Loc));
12716          end if;
12717       end if;
12718
12719       --  State parameter. This is a pointer to the task body procedure. The
12720       --  required value is obtained by taking 'Unrestricted_Access of the task
12721       --  body procedure and converting it (with an unchecked conversion) to
12722       --  the type required by the task kernel. For further details, see the
12723       --  description of Expand_N_Task_Body. We use 'Unrestricted_Access rather
12724       --  than 'Address in order to avoid creating trampolines.
12725
12726       declare
12727          Body_Proc    : constant Node_Id := Get_Task_Body_Procedure (Ttyp);
12728          Subp_Ptr_Typ : constant Node_Id :=
12729                           Create_Itype (E_Access_Subprogram_Type, Tdec);
12730          Ref          : constant Node_Id := Make_Itype_Reference (Loc);
12731
12732       begin
12733          Set_Directly_Designated_Type (Subp_Ptr_Typ, Body_Proc);
12734          Set_Etype (Subp_Ptr_Typ, Subp_Ptr_Typ);
12735
12736          --  Be sure to freeze a reference to the access-to-subprogram type,
12737          --  otherwise gigi will complain that it's in the wrong scope, because
12738          --  it's actually inside the init procedure for the record type that
12739          --  corresponds to the task type.
12740
12741          --  This processing is causing a crash in the .NET/JVM back ends that
12742          --  is not yet understood, so skip it in these cases ???
12743
12744          if VM_Target = No_VM then
12745             Set_Itype (Ref, Subp_Ptr_Typ);
12746             Append_Freeze_Action (Task_Rec, Ref);
12747
12748             Append_To (Args,
12749               Unchecked_Convert_To (RTE (RE_Task_Procedure_Access),
12750                 Make_Qualified_Expression (Loc,
12751                   Subtype_Mark => New_Reference_To (Subp_Ptr_Typ, Loc),
12752                   Expression   =>
12753                     Make_Attribute_Reference (Loc,
12754                       Prefix =>
12755                         New_Occurrence_Of (Body_Proc, Loc),
12756                       Attribute_Name => Name_Unrestricted_Access))));
12757
12758          --  For the .NET/JVM cases revert to the original code below ???
12759
12760          else
12761             Append_To (Args,
12762               Unchecked_Convert_To (RTE (RE_Task_Procedure_Access),
12763                 Make_Attribute_Reference (Loc,
12764                   Prefix =>
12765                     New_Occurrence_Of (Body_Proc, Loc),
12766                   Attribute_Name => Name_Address)));
12767          end if;
12768       end;
12769
12770       --  Discriminants parameter. This is just the address of the task
12771       --  value record itself (which contains the discriminant values
12772
12773       Append_To (Args,
12774         Make_Attribute_Reference (Loc,
12775           Prefix => Make_Identifier (Loc, Name_uInit),
12776           Attribute_Name => Name_Address));
12777
12778       --  Elaborated parameter. This is an access to the elaboration Boolean
12779
12780       Append_To (Args,
12781         Make_Attribute_Reference (Loc,
12782           Prefix => Make_Identifier (Loc, New_External_Name (Tnam, 'E')),
12783           Attribute_Name => Name_Unchecked_Access));
12784
12785       --  Chain parameter. This is a reference to the _Chain parameter of
12786       --  the initialization procedure.
12787
12788       Append_To (Args, Make_Identifier (Loc, Name_uChain));
12789
12790       --  Task name parameter. Take this from the _Task_Id parameter to the
12791       --  init call unless there is a Task_Name pragma, in which case we take
12792       --  the value from the pragma.
12793
12794       if Present (Tdef)
12795         and then Has_Task_Name_Pragma (Tdef)
12796       then
12797          --  Copy expression in full, because it may be dynamic and have
12798          --  side effects.
12799
12800          Append_To (Args,
12801            New_Copy_Tree
12802              (Expression (First
12803                            (Pragma_Argument_Associations
12804                              (Find_Task_Or_Protected_Pragma
12805                                (Tdef, Name_Task_Name))))));
12806
12807       else
12808          Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
12809       end if;
12810
12811       --  Created_Task parameter. This is the _Task_Id field of the task
12812       --  record value
12813
12814       Append_To (Args,
12815         Make_Selected_Component (Loc,
12816           Prefix => Make_Identifier (Loc, Name_uInit),
12817           Selector_Name => Make_Identifier (Loc, Name_uTask_Id)));
12818
12819       --  Build_Entry_Names generation flag. When set to true, the runtime
12820       --  will allocate an array to hold the string names of task entries.
12821
12822       if not Restricted_Profile then
12823          if Has_Entries (Ttyp)
12824            and then Entry_Names_OK
12825          then
12826             Append_To (Args, New_Reference_To (Standard_True, Loc));
12827          else
12828             Append_To (Args, New_Reference_To (Standard_False, Loc));
12829          end if;
12830       end if;
12831
12832       if Restricted_Profile then
12833          Name := New_Reference_To (RTE (RE_Create_Restricted_Task), Loc);
12834       else
12835          Name := New_Reference_To (RTE (RE_Create_Task), Loc);
12836       end if;
12837
12838       return
12839         Make_Procedure_Call_Statement (Loc,
12840           Name => Name,
12841           Parameter_Associations => Args);
12842    end Make_Task_Create_Call;
12843
12844    ------------------------------
12845    -- Next_Protected_Operation --
12846    ------------------------------
12847
12848    function Next_Protected_Operation (N : Node_Id) return Node_Id is
12849       Next_Op : Node_Id;
12850
12851    begin
12852       Next_Op := Next (N);
12853       while Present (Next_Op)
12854         and then not Nkind_In (Next_Op, N_Subprogram_Body, N_Entry_Body)
12855       loop
12856          Next (Next_Op);
12857       end loop;
12858
12859       return Next_Op;
12860    end Next_Protected_Operation;
12861
12862    ---------------------
12863    -- Null_Statements --
12864    ---------------------
12865
12866    function Null_Statements (Stats : List_Id) return Boolean is
12867       Stmt : Node_Id;
12868
12869    begin
12870       Stmt := First (Stats);
12871       while Nkind (Stmt) /= N_Empty
12872         and then (Nkind_In (Stmt, N_Null_Statement, N_Label)
12873                     or else
12874                       (Nkind (Stmt) = N_Pragma
12875                          and then (Pragma_Name (Stmt) = Name_Unreferenced
12876                                      or else
12877                                    Pragma_Name (Stmt) = Name_Unmodified
12878                                      or else
12879                                    Pragma_Name (Stmt) = Name_Warnings)))
12880       loop
12881          Next (Stmt);
12882       end loop;
12883
12884       return Nkind (Stmt) = N_Empty;
12885    end Null_Statements;
12886
12887    --------------------------
12888    -- Parameter_Block_Pack --
12889    --------------------------
12890
12891    function Parameter_Block_Pack
12892      (Loc     : Source_Ptr;
12893       Blk_Typ : Entity_Id;
12894       Actuals : List_Id;
12895       Formals : List_Id;
12896       Decls   : List_Id;
12897       Stmts   : List_Id) return Node_Id
12898    is
12899       Actual    : Entity_Id;
12900       Expr      : Node_Id := Empty;
12901       Formal    : Entity_Id;
12902       Has_Param : Boolean := False;
12903       P         : Entity_Id;
12904       Params    : List_Id;
12905       Temp_Asn  : Node_Id;
12906       Temp_Nam  : Node_Id;
12907
12908    begin
12909       Actual := First (Actuals);
12910       Formal := Defining_Identifier (First (Formals));
12911       Params := New_List;
12912
12913       while Present (Actual) loop
12914          if Is_By_Copy_Type (Etype (Actual)) then
12915             --  Generate:
12916             --    Jnn : aliased <formal-type>
12917
12918             Temp_Nam := Make_Temporary (Loc, 'J');
12919
12920             Append_To (Decls,
12921               Make_Object_Declaration (Loc,
12922                 Aliased_Present =>
12923                   True,
12924                 Defining_Identifier =>
12925                   Temp_Nam,
12926                 Object_Definition =>
12927                   New_Reference_To (Etype (Formal), Loc)));
12928
12929             if Ekind (Formal) /= E_Out_Parameter then
12930
12931                --  Generate:
12932                --    Jnn := <actual>
12933
12934                Temp_Asn :=
12935                  New_Reference_To (Temp_Nam, Loc);
12936
12937                Set_Assignment_OK (Temp_Asn);
12938
12939                Append_To (Stmts,
12940                  Make_Assignment_Statement (Loc,
12941                    Name =>
12942                      Temp_Asn,
12943                    Expression =>
12944                      New_Copy_Tree (Actual)));
12945             end if;
12946
12947             --  Generate:
12948             --    Jnn'unchecked_access
12949
12950             Append_To (Params,
12951               Make_Attribute_Reference (Loc,
12952                 Attribute_Name =>
12953                   Name_Unchecked_Access,
12954                 Prefix =>
12955                   New_Reference_To (Temp_Nam, Loc)));
12956
12957             Has_Param := True;
12958
12959          --  The controlling parameter is omitted
12960
12961          else
12962             if not Is_Controlling_Actual (Actual) then
12963                Append_To (Params,
12964                  Make_Reference (Loc, New_Copy_Tree (Actual)));
12965
12966                Has_Param := True;
12967             end if;
12968          end if;
12969
12970          Next_Actual (Actual);
12971          Next_Formal_With_Extras (Formal);
12972       end loop;
12973
12974       if Has_Param then
12975          Expr := Make_Aggregate (Loc, Params);
12976       end if;
12977
12978       --  Generate:
12979       --    P : Ann := (
12980       --      J1'unchecked_access;
12981       --      <actual2>'reference;
12982       --      ...);
12983
12984       P := Make_Temporary (Loc, 'P');
12985
12986       Append_To (Decls,
12987         Make_Object_Declaration (Loc,
12988           Defining_Identifier =>
12989             P,
12990           Object_Definition =>
12991             New_Reference_To (Blk_Typ, Loc),
12992           Expression =>
12993             Expr));
12994
12995       return P;
12996    end Parameter_Block_Pack;
12997
12998    ----------------------------
12999    -- Parameter_Block_Unpack --
13000    ----------------------------
13001
13002    function Parameter_Block_Unpack
13003      (Loc     : Source_Ptr;
13004       P       : Entity_Id;
13005       Actuals : List_Id;
13006       Formals : List_Id) return List_Id
13007    is
13008       Actual    : Entity_Id;
13009       Asnmt     : Node_Id;
13010       Formal    : Entity_Id;
13011       Has_Asnmt : Boolean := False;
13012       Result    : constant List_Id := New_List;
13013
13014    begin
13015       Actual := First (Actuals);
13016       Formal := Defining_Identifier (First (Formals));
13017       while Present (Actual) loop
13018          if Is_By_Copy_Type (Etype (Actual))
13019            and then Ekind (Formal) /= E_In_Parameter
13020          then
13021             --  Generate:
13022             --    <actual> := P.<formal>;
13023
13024             Asnmt :=
13025               Make_Assignment_Statement (Loc,
13026                 Name =>
13027                   New_Copy (Actual),
13028                 Expression =>
13029                   Make_Explicit_Dereference (Loc,
13030                     Make_Selected_Component (Loc,
13031                       Prefix =>
13032                         New_Reference_To (P, Loc),
13033                       Selector_Name =>
13034                         Make_Identifier (Loc, Chars (Formal)))));
13035
13036             Set_Assignment_OK (Name (Asnmt));
13037             Append_To (Result, Asnmt);
13038
13039             Has_Asnmt := True;
13040          end if;
13041
13042          Next_Actual (Actual);
13043          Next_Formal_With_Extras (Formal);
13044       end loop;
13045
13046       if Has_Asnmt then
13047          return Result;
13048       else
13049          return New_List (Make_Null_Statement (Loc));
13050       end if;
13051    end Parameter_Block_Unpack;
13052
13053    ----------------------
13054    -- Set_Discriminals --
13055    ----------------------
13056
13057    procedure Set_Discriminals (Dec : Node_Id) is
13058       D       : Entity_Id;
13059       Pdef    : Entity_Id;
13060       D_Minal : Entity_Id;
13061
13062    begin
13063       pragma Assert (Nkind (Dec) = N_Protected_Type_Declaration);
13064       Pdef := Defining_Identifier (Dec);
13065
13066       if Has_Discriminants (Pdef) then
13067          D := First_Discriminant (Pdef);
13068          while Present (D) loop
13069             D_Minal :=
13070               Make_Defining_Identifier (Sloc (D),
13071                 Chars => New_External_Name (Chars (D), 'D'));
13072
13073             Set_Ekind (D_Minal, E_Constant);
13074             Set_Etype (D_Minal, Etype (D));
13075             Set_Scope (D_Minal, Pdef);
13076             Set_Discriminal (D, D_Minal);
13077             Set_Discriminal_Link (D_Minal, D);
13078
13079             Next_Discriminant (D);
13080          end loop;
13081       end if;
13082    end Set_Discriminals;
13083
13084    -----------------------
13085    -- Trivial_Accept_OK --
13086    -----------------------
13087
13088    function Trivial_Accept_OK return Boolean is
13089    begin
13090       case Opt.Task_Dispatching_Policy is
13091
13092          --  If we have the default task dispatching policy in effect, we can
13093          --  definitely do the optimization (one way of looking at this is to
13094          --  think of the formal definition of the default policy being allowed
13095          --  to run any task it likes after a rendezvous, so even if notionally
13096          --  a full rescheduling occurs, we can say that our dispatching policy
13097          --  (i.e. the default dispatching policy) reorders the queue to be the
13098          --  same as just before the call.
13099
13100          when ' ' =>
13101             return True;
13102
13103          --  FIFO_Within_Priorities certainly does not permit this
13104          --  optimization since the Rendezvous is a scheduling action that may
13105          --  require some other task to be run.
13106
13107          when 'F' =>
13108             return False;
13109
13110          --  For now, disallow the optimization for all other policies. This
13111          --  may be over-conservative, but it is certainly not incorrect.
13112
13113          when others =>
13114             return False;
13115
13116       end case;
13117    end Trivial_Accept_OK;
13118
13119 end Exp_Ch9;