OSDN Git Service

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