OSDN Git Service

2005-11-14 Hristian Kirtchev <kirtchev@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / exp_ch6.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                              E X P _ C H 6                               --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2005, 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 2,  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 COPYING.  If not, write --
19 -- to  the  Free Software Foundation,  51  Franklin  Street,  Fifth  Floor, --
20 -- Boston, MA 02110-1301, USA.                                              --
21 --                                                                          --
22 -- GNAT was originally developed  by the GNAT team at  New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
24 --                                                                          --
25 ------------------------------------------------------------------------------
26
27 with Atree;    use Atree;
28 with Checks;   use Checks;
29 with Debug;    use Debug;
30 with Einfo;    use Einfo;
31 with Errout;   use Errout;
32 with Elists;   use Elists;
33 with Exp_Ch2;  use Exp_Ch2;
34 with Exp_Ch3;  use Exp_Ch3;
35 with Exp_Ch7;  use Exp_Ch7;
36 with Exp_Ch9;  use Exp_Ch9;
37 with Exp_Dbug; use Exp_Dbug;
38 with Exp_Disp; use Exp_Disp;
39 with Exp_Dist; use Exp_Dist;
40 with Exp_Intr; use Exp_Intr;
41 with Exp_Pakd; use Exp_Pakd;
42 with Exp_Tss;  use Exp_Tss;
43 with Exp_Util; use Exp_Util;
44 with Fname;    use Fname;
45 with Freeze;   use Freeze;
46 with Hostparm; use Hostparm;
47 with Inline;   use Inline;
48 with Lib;      use Lib;
49 with Nlists;   use Nlists;
50 with Nmake;    use Nmake;
51 with Opt;      use Opt;
52 with Restrict; use Restrict;
53 with Rident;   use Rident;
54 with Rtsfind;  use Rtsfind;
55 with Sem;      use Sem;
56 with Sem_Ch6;  use Sem_Ch6;
57 with Sem_Ch8;  use Sem_Ch8;
58 with Sem_Ch12; use Sem_Ch12;
59 with Sem_Ch13; use Sem_Ch13;
60 with Sem_Disp; use Sem_Disp;
61 with Sem_Dist; use Sem_Dist;
62 with Sem_Mech; use Sem_Mech;
63 with Sem_Res;  use Sem_Res;
64 with Sem_Util; use Sem_Util;
65 with Sinfo;    use Sinfo;
66 with Snames;   use Snames;
67 with Stand;    use Stand;
68 with Tbuild;   use Tbuild;
69 with Ttypes;   use Ttypes;
70 with Uintp;    use Uintp;
71 with Validsw;  use Validsw;
72
73 package body Exp_Ch6 is
74
75    -----------------------
76    -- Local Subprograms --
77    -----------------------
78
79    procedure Check_Overriding_Operation (Subp : Entity_Id);
80    --  Subp is a dispatching operation. Check whether it may override an
81    --  inherited private operation, in which case its DT entry is that of
82    --  the hidden operation, not the one it may have received earlier.
83    --  This must be done before emitting the code to set the corresponding
84    --  DT to the address of the subprogram. The actual placement of Subp in
85    --  the proper place in the list of primitive operations is done in
86    --  Declare_Inherited_Private_Subprograms, which also has to deal with
87    --  implicit operations. This duplication is unavoidable for now???
88
89    procedure Detect_Infinite_Recursion (N : Node_Id; Spec : Entity_Id);
90    --  This procedure is called only if the subprogram body N, whose spec
91    --  has the given entity Spec, contains a parameterless recursive call.
92    --  It attempts to generate runtime code to detect if this a case of
93    --  infinite recursion.
94    --
95    --  The body is scanned to determine dependencies. If the only external
96    --  dependencies are on a small set of scalar variables, then the values
97    --  of these variables are captured on entry to the subprogram, and if
98    --  the values are not changed for the call, we know immediately that
99    --  we have an infinite recursion.
100
101    procedure Expand_Actuals (N : Node_Id; Subp : Entity_Id);
102    --  For each actual of an in-out or out parameter which is a numeric
103    --  (view) conversion of the form T (A), where A denotes a variable,
104    --  we insert the declaration:
105    --
106    --    Temp : T[ := T (A)];
107    --
108    --  prior to the call. Then we replace the actual with a reference to Temp,
109    --  and append the assignment:
110    --
111    --    A := TypeA (Temp);
112    --
113    --  after the call. Here TypeA is the actual type of variable A.
114    --  For out parameters, the initial declaration has no expression.
115    --  If A is not an entity name, we generate instead:
116    --
117    --    Var  : TypeA renames A;
118    --    Temp : T := Var;       --  omitting expression for out parameter.
119    --    ...
120    --    Var := TypeA (Temp);
121    --
122    --  For other in-out parameters, we emit the required constraint checks
123    --  before and/or after the call.
124    --
125    --  For all parameter modes, actuals that denote components and slices
126    --  of packed arrays are expanded into suitable temporaries.
127    --
128    --  For non-scalar objects that are possibly unaligned, add call by copy
129    --  code (copy in for IN and IN OUT, copy out for OUT and IN OUT).
130
131    procedure Expand_Inlined_Call
132     (N         : Node_Id;
133      Subp      : Entity_Id;
134      Orig_Subp : Entity_Id);
135    --  If called subprogram can be inlined by the front-end, retrieve the
136    --  analyzed body, replace formals with actuals and expand call in place.
137    --  Generate thunks for actuals that are expressions, and insert the
138    --  corresponding constant declarations before the call. If the original
139    --  call is to a derived operation, the return type is the one of the
140    --  derived operation, but the body is that of the original, so return
141    --  expressions in the body must be converted to the desired type (which
142    --  is simply not noted in the tree without inline expansion).
143
144    function Expand_Protected_Object_Reference
145      (N    : Node_Id;
146       Scop : Entity_Id)
147       return Node_Id;
148
149    procedure Expand_Protected_Subprogram_Call
150      (N    : Node_Id;
151       Subp : Entity_Id;
152       Scop : Entity_Id);
153    --  A call to a protected subprogram within the protected object may appear
154    --  as a regular call. The list of actuals must be expanded to contain a
155    --  reference to the object itself, and the call becomes a call to the
156    --  corresponding protected subprogram.
157
158    --------------------------------
159    -- Check_Overriding_Operation --
160    --------------------------------
161
162    procedure Check_Overriding_Operation (Subp : Entity_Id) is
163       Typ     : constant Entity_Id := Find_Dispatching_Type (Subp);
164       Op_List : constant Elist_Id  := Primitive_Operations (Typ);
165       Op_Elmt : Elmt_Id;
166       Prim_Op : Entity_Id;
167       Par_Op  : Entity_Id;
168
169    begin
170       if Is_Derived_Type (Typ)
171         and then not Is_Private_Type (Typ)
172         and then In_Open_Scopes (Scope (Etype (Typ)))
173         and then Typ = Base_Type (Typ)
174       then
175          --  Subp overrides an inherited private operation if there is an
176          --  inherited operation with a different name than Subp (see
177          --  Derive_Subprogram) whose Alias is a hidden subprogram with the
178          --  same name as Subp.
179
180          Op_Elmt := First_Elmt (Op_List);
181          while Present (Op_Elmt) loop
182             Prim_Op := Node (Op_Elmt);
183             Par_Op  := Alias (Prim_Op);
184
185             if Present (Par_Op)
186               and then not Comes_From_Source (Prim_Op)
187               and then Chars (Prim_Op) /= Chars (Par_Op)
188               and then Chars (Par_Op) = Chars (Subp)
189               and then Is_Hidden (Par_Op)
190               and then Type_Conformant (Prim_Op, Subp)
191             then
192                Set_DT_Position (Subp, DT_Position (Prim_Op));
193             end if;
194
195             Next_Elmt (Op_Elmt);
196          end loop;
197       end if;
198    end Check_Overriding_Operation;
199
200    -------------------------------
201    -- Detect_Infinite_Recursion --
202    -------------------------------
203
204    procedure Detect_Infinite_Recursion (N : Node_Id; Spec : Entity_Id) is
205       Loc : constant Source_Ptr := Sloc (N);
206
207       Var_List : constant Elist_Id := New_Elmt_List;
208       --  List of globals referenced by body of procedure
209
210       Call_List : constant Elist_Id := New_Elmt_List;
211       --  List of recursive calls in body of procedure
212
213       Shad_List : constant Elist_Id := New_Elmt_List;
214       --  List of entity id's for entities created to capture the value of
215       --  referenced globals on entry to the procedure.
216
217       Scop : constant Uint := Scope_Depth (Spec);
218       --  This is used to record the scope depth of the current procedure, so
219       --  that we can identify global references.
220
221       Max_Vars : constant := 4;
222       --  Do not test more than four global variables
223
224       Count_Vars : Natural := 0;
225       --  Count variables found so far
226
227       Var  : Entity_Id;
228       Elm  : Elmt_Id;
229       Ent  : Entity_Id;
230       Call : Elmt_Id;
231       Decl : Node_Id;
232       Test : Node_Id;
233       Elm1 : Elmt_Id;
234       Elm2 : Elmt_Id;
235       Last : Node_Id;
236
237       function Process (Nod : Node_Id) return Traverse_Result;
238       --  Function to traverse the subprogram body (using Traverse_Func)
239
240       -------------
241       -- Process --
242       -------------
243
244       function Process (Nod : Node_Id) return Traverse_Result is
245       begin
246          --  Procedure call
247
248          if Nkind (Nod) = N_Procedure_Call_Statement then
249
250             --  Case of one of the detected recursive calls
251
252             if Is_Entity_Name (Name (Nod))
253               and then Has_Recursive_Call (Entity (Name (Nod)))
254               and then Entity (Name (Nod)) = Spec
255             then
256                Append_Elmt (Nod, Call_List);
257                return Skip;
258
259             --  Any other procedure call may have side effects
260
261             else
262                return Abandon;
263             end if;
264
265          --  A call to a pure function can always be ignored
266
267          elsif Nkind (Nod) = N_Function_Call
268            and then Is_Entity_Name (Name (Nod))
269            and then Is_Pure (Entity (Name (Nod)))
270          then
271             return Skip;
272
273          --  Case of an identifier reference
274
275          elsif Nkind (Nod) = N_Identifier then
276             Ent := Entity (Nod);
277
278             --  If no entity, then ignore the reference
279
280             --  Not clear why this can happen. To investigate, remove this
281             --  test and look at the crash that occurs here in 3401-004 ???
282
283             if No (Ent) then
284                return Skip;
285
286             --  Ignore entities with no Scope, again not clear how this
287             --  can happen, to investigate, look at 4108-008 ???
288
289             elsif No (Scope (Ent)) then
290                return Skip;
291
292             --  Ignore the reference if not to a more global object
293
294             elsif Scope_Depth (Scope (Ent)) >= Scop then
295                return Skip;
296
297             --  References to types, exceptions and constants are always OK
298
299             elsif Is_Type (Ent)
300               or else Ekind (Ent) = E_Exception
301               or else Ekind (Ent) = E_Constant
302             then
303                return Skip;
304
305             --  If other than a non-volatile scalar variable, we have some
306             --  kind of global reference (e.g. to a function) that we cannot
307             --  deal with so we forget the attempt.
308
309             elsif Ekind (Ent) /= E_Variable
310               or else not Is_Scalar_Type (Etype (Ent))
311               or else Treat_As_Volatile (Ent)
312             then
313                return Abandon;
314
315             --  Otherwise we have a reference to a global scalar
316
317             else
318                --  Loop through global entities already detected
319
320                Elm := First_Elmt (Var_List);
321                loop
322                   --  If not detected before, record this new global reference
323
324                   if No (Elm) then
325                      Count_Vars := Count_Vars + 1;
326
327                      if Count_Vars <= Max_Vars then
328                         Append_Elmt (Entity (Nod), Var_List);
329                      else
330                         return Abandon;
331                      end if;
332
333                      exit;
334
335                   --  If recorded before, ignore
336
337                   elsif Node (Elm) = Entity (Nod) then
338                      return Skip;
339
340                   --  Otherwise keep looking
341
342                   else
343                      Next_Elmt (Elm);
344                   end if;
345                end loop;
346
347                return Skip;
348             end if;
349
350          --  For all other node kinds, recursively visit syntactic children
351
352          else
353             return OK;
354          end if;
355       end Process;
356
357       function Traverse_Body is new Traverse_Func;
358
359    --  Start of processing for Detect_Infinite_Recursion
360
361    begin
362       --  Do not attempt detection in No_Implicit_Conditional mode, since we
363       --  won't be able to generate the code to handle the recursion in any
364       --  case.
365
366       if Restriction_Active (No_Implicit_Conditionals) then
367          return;
368       end if;
369
370       --  Otherwise do traversal and quit if we get abandon signal
371
372       if Traverse_Body (N) = Abandon then
373          return;
374
375       --  We must have a call, since Has_Recursive_Call was set. If not just
376       --  ignore (this is only an error check, so if we have a funny situation,
377       --  due to bugs or errors, we do not want to bomb!)
378
379       elsif Is_Empty_Elmt_List (Call_List) then
380          return;
381       end if;
382
383       --  Here is the case where we detect recursion at compile time
384
385       --  Push our current scope for analyzing the declarations and code that
386       --  we will insert for the checking.
387
388       New_Scope (Spec);
389
390       --  This loop builds temporary variables for each of the referenced
391       --  globals, so that at the end of the loop the list Shad_List contains
392       --  these temporaries in one-to-one correspondence with the elements in
393       --  Var_List.
394
395       Last := Empty;
396       Elm := First_Elmt (Var_List);
397       while Present (Elm) loop
398          Var := Node (Elm);
399          Ent :=
400            Make_Defining_Identifier (Loc,
401              Chars => New_Internal_Name ('S'));
402          Append_Elmt (Ent, Shad_List);
403
404          --  Insert a declaration for this temporary at the start of the
405          --  declarations for the procedure. The temporaries are declared as
406          --  constant objects initialized to the current values of the
407          --  corresponding temporaries.
408
409          Decl :=
410            Make_Object_Declaration (Loc,
411              Defining_Identifier => Ent,
412              Object_Definition   => New_Occurrence_Of (Etype (Var), Loc),
413              Constant_Present    => True,
414              Expression          => New_Occurrence_Of (Var, Loc));
415
416          if No (Last) then
417             Prepend (Decl, Declarations (N));
418          else
419             Insert_After (Last, Decl);
420          end if;
421
422          Last := Decl;
423          Analyze (Decl);
424          Next_Elmt (Elm);
425       end loop;
426
427       --  Loop through calls
428
429       Call := First_Elmt (Call_List);
430       while Present (Call) loop
431
432          --  Build a predicate expression of the form
433
434          --    True
435          --      and then global1 = temp1
436          --      and then global2 = temp2
437          --      ...
438
439          --  This predicate determines if any of the global values
440          --  referenced by the procedure have changed since the
441          --  current call, if not an infinite recursion is assured.
442
443          Test := New_Occurrence_Of (Standard_True, Loc);
444
445          Elm1 := First_Elmt (Var_List);
446          Elm2 := First_Elmt (Shad_List);
447          while Present (Elm1) loop
448             Test :=
449               Make_And_Then (Loc,
450                 Left_Opnd  => Test,
451                 Right_Opnd =>
452                   Make_Op_Eq (Loc,
453                     Left_Opnd  => New_Occurrence_Of (Node (Elm1), Loc),
454                     Right_Opnd => New_Occurrence_Of (Node (Elm2), Loc)));
455
456             Next_Elmt (Elm1);
457             Next_Elmt (Elm2);
458          end loop;
459
460          --  Now we replace the call with the sequence
461
462          --    if no-changes (see above) then
463          --       raise Storage_Error;
464          --    else
465          --       original-call
466          --    end if;
467
468          Rewrite (Node (Call),
469            Make_If_Statement (Loc,
470              Condition       => Test,
471              Then_Statements => New_List (
472                Make_Raise_Storage_Error (Loc,
473                  Reason => SE_Infinite_Recursion)),
474
475              Else_Statements => New_List (
476                Relocate_Node (Node (Call)))));
477
478          Analyze (Node (Call));
479
480          Next_Elmt (Call);
481       end loop;
482
483       --  Remove temporary scope stack entry used for analysis
484
485       Pop_Scope;
486    end Detect_Infinite_Recursion;
487
488    --------------------
489    -- Expand_Actuals --
490    --------------------
491
492    procedure Expand_Actuals (N : Node_Id; Subp : Entity_Id) is
493       Loc       : constant Source_Ptr := Sloc (N);
494       Actual    : Node_Id;
495       Formal    : Entity_Id;
496       N_Node    : Node_Id;
497       Post_Call : List_Id;
498       E_Formal  : Entity_Id;
499
500       procedure Add_Call_By_Copy_Code;
501       --  For cases where the parameter must be passed by copy, this routine
502       --  generates a temporary variable into which the actual is copied and
503       --  then passes this as the parameter. For an OUT or IN OUT parameter,
504       --  an assignment is also generated to copy the result back. The call
505       --  also takes care of any constraint checks required for the type
506       --  conversion case (on both the way in and the way out).
507
508       procedure Add_Simple_Call_By_Copy_Code;
509       --  This is similar to the above, but is used in cases where we know
510       --  that all that is needed is to simply create a temporary and copy
511       --  the value in and out of the temporary.
512
513       procedure Check_Fortran_Logical;
514       --  A value of type Logical that is passed through a formal parameter
515       --  must be normalized because .TRUE. usually does not have the same
516       --  representation as True. We assume that .FALSE. = False = 0.
517       --  What about functions that return a logical type ???
518
519       function Is_Legal_Copy return Boolean;
520       --  Check that an actual can be copied before generating the temporary
521       --  to be used in the call. If the actual is of a by_reference type then
522       --  the program is illegal (this can only happen in the presence of
523       --  rep. clauses that force an incorrect alignment). If the formal is
524       --  a by_reference parameter imposed by a DEC pragma, emit a warning to
525       --  the effect that this might lead to unaligned arguments.
526
527       function Make_Var (Actual : Node_Id) return Entity_Id;
528       --  Returns an entity that refers to the given actual parameter,
529       --  Actual (not including any type conversion). If Actual is an
530       --  entity name, then this entity is returned unchanged, otherwise
531       --  a renaming is created to provide an entity for the actual.
532
533       procedure Reset_Packed_Prefix;
534       --  The expansion of a packed array component reference is delayed in
535       --  the context of a call. Now we need to complete the expansion, so we
536       --  unmark the analyzed bits in all prefixes.
537
538       ---------------------------
539       -- Add_Call_By_Copy_Code --
540       ---------------------------
541
542       procedure Add_Call_By_Copy_Code is
543          Expr  : Node_Id;
544          Init  : Node_Id;
545          Temp  : Entity_Id;
546          Indic : Node_Id;
547          Var   : Entity_Id;
548          F_Typ : constant Entity_Id := Etype (Formal);
549          V_Typ : Entity_Id;
550          Crep  : Boolean;
551
552       begin
553          if not Is_Legal_Copy then
554             return;
555          end if;
556
557          Temp := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
558
559          --  Use formal type for temp, unless formal type is an unconstrained
560          --  array, in which case we don't have to worry about bounds checks,
561          --  and we use the actual type, since that has appropriate bounds.
562
563          if Is_Array_Type (F_Typ) and then not Is_Constrained (F_Typ) then
564             Indic := New_Occurrence_Of (Etype (Actual), Loc);
565          else
566             Indic := New_Occurrence_Of (Etype (Formal), Loc);
567          end if;
568
569          if Nkind (Actual) = N_Type_Conversion then
570             V_Typ := Etype (Expression (Actual));
571
572             --  If the formal is an (in-)out parameter, capture the name
573             --  of the variable in order to build the post-call assignment.
574
575             Var := Make_Var (Expression (Actual));
576
577             Crep := not Same_Representation
578                           (F_Typ, Etype (Expression (Actual)));
579
580          else
581             V_Typ := Etype (Actual);
582             Var   := Make_Var (Actual);
583             Crep  := False;
584          end if;
585
586          --  Setup initialization for case of in out parameter, or an out
587          --  parameter where the formal is an unconstrained array (in the
588          --  latter case, we have to pass in an object with bounds).
589
590          --  If this is an out parameter, the initial copy is wasteful, so as
591          --  an optimization for the one-dimensional case we extract the
592          --  bounds of the actual and build an uninitialized temporary of the
593          --  right size.
594
595          if Ekind (Formal) = E_In_Out_Parameter
596            or else (Is_Array_Type (F_Typ) and then not Is_Constrained (F_Typ))
597          then
598             if Nkind (Actual) = N_Type_Conversion then
599                if Conversion_OK (Actual) then
600                   Init := OK_Convert_To (F_Typ, New_Occurrence_Of (Var, Loc));
601                else
602                   Init := Convert_To (F_Typ, New_Occurrence_Of (Var, Loc));
603                end if;
604
605             elsif Ekind (Formal) = E_Out_Parameter
606               and then Is_Array_Type (F_Typ)
607               and then Number_Dimensions (F_Typ) = 1
608               and then not Has_Non_Null_Base_Init_Proc (F_Typ)
609             then
610                --  Actual is a one-dimensional array or slice, and the type
611                --  requires no initialization. Create a temporary of the
612                --  right size, but do not copy actual into it (optimization).
613
614                Init := Empty;
615                Indic :=
616                  Make_Subtype_Indication (Loc,
617                    Subtype_Mark =>
618                      New_Occurrence_Of (F_Typ, Loc),
619                    Constraint   =>
620                      Make_Index_Or_Discriminant_Constraint (Loc,
621                        Constraints => New_List (
622                          Make_Range (Loc,
623                            Low_Bound  =>
624                              Make_Attribute_Reference (Loc,
625                                Prefix => New_Occurrence_Of (Var, Loc),
626                                Attribute_name => Name_First),
627                            High_Bound =>
628                              Make_Attribute_Reference (Loc,
629                                Prefix => New_Occurrence_Of (Var, Loc),
630                                Attribute_Name => Name_Last)))));
631
632             else
633                Init := New_Occurrence_Of (Var, Loc);
634             end if;
635
636          --  An initialization is created for packed conversions as
637          --  actuals for out parameters to enable Make_Object_Declaration
638          --  to determine the proper subtype for N_Node. Note that this
639          --  is wasteful because the extra copying on the call side is
640          --  not required for such out parameters. ???
641
642          elsif Ekind (Formal) = E_Out_Parameter
643            and then Nkind (Actual) = N_Type_Conversion
644            and then (Is_Bit_Packed_Array (F_Typ)
645                        or else
646                      Is_Bit_Packed_Array (Etype (Expression (Actual))))
647          then
648             if Conversion_OK (Actual) then
649                Init := OK_Convert_To (F_Typ, New_Occurrence_Of (Var, Loc));
650             else
651                Init := Convert_To (F_Typ, New_Occurrence_Of (Var, Loc));
652             end if;
653
654          elsif Ekind (Formal) = E_In_Parameter then
655             Init := New_Occurrence_Of (Var, Loc);
656
657          else
658             Init := Empty;
659          end if;
660
661          N_Node :=
662            Make_Object_Declaration (Loc,
663              Defining_Identifier => Temp,
664              Object_Definition   => Indic,
665              Expression          => Init);
666          Set_Assignment_OK (N_Node);
667          Insert_Action (N, N_Node);
668
669          --  Now, normally the deal here is that we use the defining
670          --  identifier created by that object declaration. There is
671          --  one exception to this. In the change of representation case
672          --  the above declaration will end up looking like:
673
674          --    temp : type := identifier;
675
676          --  And in this case we might as well use the identifier directly
677          --  and eliminate the temporary. Note that the analysis of the
678          --  declaration was not a waste of time in that case, since it is
679          --  what generated the necessary change of representation code. If
680          --  the change of representation introduced additional code, as in
681          --  a fixed-integer conversion, the expression is not an identifier
682          --  and must be kept.
683
684          if Crep
685            and then Present (Expression (N_Node))
686            and then Is_Entity_Name (Expression (N_Node))
687          then
688             Temp := Entity (Expression (N_Node));
689             Rewrite (N_Node, Make_Null_Statement (Loc));
690          end if;
691
692          --  For IN parameter, all we do is to replace the actual
693
694          if Ekind (Formal) = E_In_Parameter then
695             Rewrite (Actual, New_Reference_To (Temp, Loc));
696             Analyze (Actual);
697
698          --  Processing for OUT or IN OUT parameter
699
700          else
701             --  If type conversion, use reverse conversion on exit
702
703             if Nkind (Actual) = N_Type_Conversion then
704                if Conversion_OK (Actual) then
705                   Expr := OK_Convert_To (V_Typ, New_Occurrence_Of (Temp, Loc));
706                else
707                   Expr := Convert_To (V_Typ, New_Occurrence_Of (Temp, Loc));
708                end if;
709             else
710                Expr := New_Occurrence_Of (Temp, Loc);
711             end if;
712
713             Rewrite (Actual, New_Reference_To (Temp, Loc));
714             Analyze (Actual);
715
716             Append_To (Post_Call,
717               Make_Assignment_Statement (Loc,
718                 Name       => New_Occurrence_Of (Var, Loc),
719                 Expression => Expr));
720
721             Set_Assignment_OK (Name (Last (Post_Call)));
722          end if;
723       end Add_Call_By_Copy_Code;
724
725       ----------------------------------
726       -- Add_Simple_Call_By_Copy_Code --
727       ----------------------------------
728
729       procedure Add_Simple_Call_By_Copy_Code is
730          Temp   : Entity_Id;
731          Decl   : Node_Id;
732          Incod  : Node_Id;
733          Outcod : Node_Id;
734          Lhs    : Node_Id;
735          Rhs    : Node_Id;
736          Indic  : Node_Id;
737          F_Typ  : constant Entity_Id := Etype (Formal);
738
739       begin
740          if not Is_Legal_Copy then
741             return;
742          end if;
743
744          --  Use formal type for temp, unless formal type is an unconstrained
745          --  array, in which case we don't have to worry about bounds checks,
746          --  and we use the actual type, since that has appropriate bounds.
747
748          if Is_Array_Type (F_Typ) and then not Is_Constrained (F_Typ) then
749             Indic := New_Occurrence_Of (Etype (Actual), Loc);
750          else
751             Indic := New_Occurrence_Of (Etype (Formal), Loc);
752          end if;
753
754          --  Prepare to generate code
755
756          Reset_Packed_Prefix;
757
758          Temp := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
759          Incod  := Relocate_Node (Actual);
760          Outcod := New_Copy_Tree (Incod);
761
762          --  Generate declaration of temporary variable, initializing it
763          --  with the input parameter unless we have an OUT formal or
764          --  this is an initialization call.
765
766          --  If the formal is an out parameter with discriminants, the
767          --  discriminants must be captured even if the rest of the object
768          --  is in principle uninitialized, because the discriminants may
769          --  be read by the called subprogram.
770
771          if Ekind (Formal) = E_Out_Parameter then
772             Incod := Empty;
773
774             if Has_Discriminants (Etype (Formal)) then
775                Indic := New_Occurrence_Of (Etype (Actual), Loc);
776             end if;
777
778          elsif Inside_Init_Proc then
779
780             --  Could use a comment here to match comment below ???
781
782             if Nkind (Actual) /= N_Selected_Component
783               or else
784                 not Has_Discriminant_Dependent_Constraint
785                   (Entity (Selector_Name (Actual)))
786             then
787                Incod := Empty;
788
789             --  Otherwise, keep the component in order to generate the proper
790             --  actual subtype, that depends on enclosing discriminants.
791
792             else
793                null;
794             end if;
795          end if;
796
797          Decl :=
798            Make_Object_Declaration (Loc,
799              Defining_Identifier => Temp,
800              Object_Definition   => Indic,
801              Expression          => Incod);
802
803          if Inside_Init_Proc
804            and then No (Incod)
805          then
806             --  If the call is to initialize a component of a composite type,
807             --  and the component does not depend on discriminants, use the
808             --  actual type of the component. This is required in case the
809             --  component is constrained, because in general the formal of the
810             --  initialization procedure will be unconstrained. Note that if
811             --  the component being initialized is constrained by an enclosing
812             --  discriminant, the presence of the initialization in the
813             --  declaration will generate an expression for the actual subtype.
814
815             Set_No_Initialization (Decl);
816             Set_Object_Definition (Decl,
817               New_Occurrence_Of (Etype (Actual), Loc));
818          end if;
819
820          Insert_Action (N, Decl);
821
822          --  The actual is simply a reference to the temporary
823
824          Rewrite (Actual, New_Occurrence_Of (Temp, Loc));
825
826          --  Generate copy out if OUT or IN OUT parameter
827
828          if Ekind (Formal) /= E_In_Parameter then
829             Lhs := Outcod;
830             Rhs := New_Occurrence_Of (Temp, Loc);
831
832             --  Deal with conversion
833
834             if Nkind (Lhs) = N_Type_Conversion then
835                Lhs := Expression (Lhs);
836                Rhs := Convert_To (Etype (Actual), Rhs);
837             end if;
838
839             Append_To (Post_Call,
840               Make_Assignment_Statement (Loc,
841                 Name       => Lhs,
842                 Expression => Rhs));
843             Set_Assignment_OK (Name (Last (Post_Call)));
844          end if;
845       end Add_Simple_Call_By_Copy_Code;
846
847       ---------------------------
848       -- Check_Fortran_Logical --
849       ---------------------------
850
851       procedure Check_Fortran_Logical is
852          Logical : constant Entity_Id := Etype (Formal);
853          Var     : Entity_Id;
854
855       --  Note: this is very incomplete, e.g. it does not handle arrays
856       --  of logical values. This is really not the right approach at all???)
857
858       begin
859          if Convention (Subp) = Convention_Fortran
860            and then Root_Type (Etype (Formal)) = Standard_Boolean
861            and then Ekind (Formal) /= E_In_Parameter
862          then
863             Var := Make_Var (Actual);
864             Append_To (Post_Call,
865               Make_Assignment_Statement (Loc,
866                 Name => New_Occurrence_Of (Var, Loc),
867                 Expression =>
868                   Unchecked_Convert_To (
869                     Logical,
870                     Make_Op_Ne (Loc,
871                       Left_Opnd  => New_Occurrence_Of (Var, Loc),
872                       Right_Opnd =>
873                         Unchecked_Convert_To (
874                           Logical,
875                           New_Occurrence_Of (Standard_False, Loc))))));
876          end if;
877       end Check_Fortran_Logical;
878
879       -------------------
880       -- Is_Legal_Copy --
881       -------------------
882
883       function Is_Legal_Copy return Boolean is
884       begin
885          --  An attempt to copy a value of such a type can only occur if
886          --  representation clauses give the actual a misaligned address.
887
888          if Is_By_Reference_Type (Etype (Formal)) then
889             Error_Msg_N
890               ("misaligned actual cannot be passed by reference", Actual);
891             return False;
892
893          --  For users of Starlet, we assume that the specification of by-
894          --  reference mechanism is mandatory. This may lead to unligned
895          --  objects but at least for DEC legacy code it is known to work.
896          --  The warning will alert users of this code that a problem may
897          --  be lurking.
898
899          elsif Mechanism (Formal) = By_Reference
900            and then Is_Valued_Procedure (Scope (Formal))
901          then
902             Error_Msg_N
903               ("by_reference actual may be misaligned?", Actual);
904             return False;
905
906          else
907             return True;
908          end if;
909       end Is_Legal_Copy;
910
911       --------------
912       -- Make_Var --
913       --------------
914
915       function Make_Var (Actual : Node_Id) return Entity_Id is
916          Var : Entity_Id;
917
918       begin
919          if Is_Entity_Name (Actual) then
920             return Entity (Actual);
921
922          else
923             Var := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
924
925             N_Node :=
926               Make_Object_Renaming_Declaration (Loc,
927                 Defining_Identifier => Var,
928                 Subtype_Mark        =>
929                   New_Occurrence_Of (Etype (Actual), Loc),
930                 Name                => Relocate_Node (Actual));
931
932             Insert_Action (N, N_Node);
933             return Var;
934          end if;
935       end Make_Var;
936
937       -------------------------
938       -- Reset_Packed_Prefix --
939       -------------------------
940
941       procedure Reset_Packed_Prefix is
942          Pfx : Node_Id := Actual;
943       begin
944          loop
945             Set_Analyzed (Pfx, False);
946             exit when Nkind (Pfx) /= N_Selected_Component
947               and then Nkind (Pfx) /= N_Indexed_Component;
948             Pfx := Prefix (Pfx);
949          end loop;
950       end Reset_Packed_Prefix;
951
952    --  Start of processing for Expand_Actuals
953
954    begin
955       Post_Call := New_List;
956
957       Formal := First_Formal (Subp);
958       Actual := First_Actual (N);
959       while Present (Formal) loop
960          E_Formal := Etype (Formal);
961
962          if Is_Scalar_Type (E_Formal)
963            or else Nkind (Actual) = N_Slice
964          then
965             Check_Fortran_Logical;
966
967          --  RM 6.4.1 (11)
968
969          elsif Ekind (Formal) /= E_Out_Parameter then
970
971             --  The unusual case of the current instance of a protected type
972             --  requires special handling. This can only occur in the context
973             --  of a call within the body of a protected operation.
974
975             if Is_Entity_Name (Actual)
976               and then Ekind (Entity (Actual)) = E_Protected_Type
977               and then In_Open_Scopes (Entity (Actual))
978             then
979                if Scope (Subp) /= Entity (Actual) then
980                   Error_Msg_N ("operation outside protected type may not "
981                     & "call back its protected operations?", Actual);
982                end if;
983
984                Rewrite (Actual,
985                  Expand_Protected_Object_Reference (N, Entity (Actual)));
986             end if;
987
988             Apply_Constraint_Check (Actual, E_Formal);
989
990          --  Out parameter case. No constraint checks on access type
991          --  RM 6.4.1 (13)
992
993          elsif Is_Access_Type (E_Formal) then
994             null;
995
996          --  RM 6.4.1 (14)
997
998          elsif Has_Discriminants (Base_Type (E_Formal))
999            or else Has_Non_Null_Base_Init_Proc (E_Formal)
1000          then
1001             Apply_Constraint_Check (Actual, E_Formal);
1002
1003          --  RM 6.4.1 (15)
1004
1005          else
1006             Apply_Constraint_Check (Actual, Base_Type (E_Formal));
1007          end if;
1008
1009          --  Processing for IN-OUT and OUT parameters
1010
1011          if Ekind (Formal) /= E_In_Parameter then
1012
1013             --  For type conversions of arrays, apply length/range checks
1014
1015             if Is_Array_Type (E_Formal)
1016               and then Nkind (Actual) = N_Type_Conversion
1017             then
1018                if Is_Constrained (E_Formal) then
1019                   Apply_Length_Check (Expression (Actual), E_Formal);
1020                else
1021                   Apply_Range_Check (Expression (Actual), E_Formal);
1022                end if;
1023             end if;
1024
1025             --  If argument is a type conversion for a type that is passed
1026             --  by copy, then we must pass the parameter by copy.
1027
1028             if Nkind (Actual) = N_Type_Conversion
1029               and then
1030                 (Is_Numeric_Type (E_Formal)
1031                   or else Is_Access_Type (E_Formal)
1032                   or else Is_Enumeration_Type (E_Formal)
1033                   or else Is_Bit_Packed_Array (Etype (Formal))
1034                   or else Is_Bit_Packed_Array (Etype (Expression (Actual)))
1035
1036                   --  Also pass by copy if change of representation
1037
1038                   or else not Same_Representation
1039                                (Etype (Formal),
1040                                 Etype (Expression (Actual))))
1041             then
1042                Add_Call_By_Copy_Code;
1043
1044             --  References to components of bit packed arrays are expanded
1045             --  at this point, rather than at the point of analysis of the
1046             --  actuals, to handle the expansion of the assignment to
1047             --  [in] out parameters.
1048
1049             elsif Is_Ref_To_Bit_Packed_Array (Actual) then
1050                Add_Simple_Call_By_Copy_Code;
1051
1052             --  If a non-scalar actual is possibly unaligned, we need a copy
1053
1054             elsif Is_Possibly_Unaligned_Object (Actual)
1055               and then not Represented_As_Scalar (Etype (Formal))
1056             then
1057                Add_Simple_Call_By_Copy_Code;
1058
1059             --  References to slices of bit packed arrays are expanded
1060
1061             elsif Is_Ref_To_Bit_Packed_Slice (Actual) then
1062                Add_Call_By_Copy_Code;
1063
1064             --  References to possibly unaligned slices of arrays are expanded
1065
1066             elsif Is_Possibly_Unaligned_Slice (Actual) then
1067                Add_Call_By_Copy_Code;
1068
1069             --  Deal with access types where the actual subtpe and the
1070             --  formal subtype are not the same, requiring a check.
1071
1072             --  It is necessary to exclude tagged types because of "downward
1073             --  conversion" errors and a strange assertion error in namet
1074             --  from gnatf in bug 1215-001 ???
1075
1076             elsif Is_Access_Type (E_Formal)
1077               and then not Same_Type (E_Formal, Etype (Actual))
1078               and then not Is_Tagged_Type (Designated_Type (E_Formal))
1079             then
1080                Add_Call_By_Copy_Code;
1081
1082             --  If the actual is not a scalar and is marked for volatile
1083             --  treatment, whereas the formal is not volatile, then pass
1084             --  by copy unless it is a by-reference type.
1085
1086             elsif Is_Entity_Name (Actual)
1087               and then Treat_As_Volatile (Entity (Actual))
1088               and then not Is_By_Reference_Type (Etype (Actual))
1089               and then not Is_Scalar_Type (Etype (Entity (Actual)))
1090               and then not Treat_As_Volatile (E_Formal)
1091             then
1092                Add_Call_By_Copy_Code;
1093
1094             elsif Nkind (Actual) = N_Indexed_Component
1095               and then Is_Entity_Name (Prefix (Actual))
1096               and then Has_Volatile_Components (Entity (Prefix (Actual)))
1097             then
1098                Add_Call_By_Copy_Code;
1099             end if;
1100
1101          --  Processing for IN parameters
1102
1103          else
1104             --  For IN parameters is in the packed array case, we expand an
1105             --  indexed component (the circuit in Exp_Ch4 deliberately left
1106             --  indexed components appearing as actuals untouched, so that
1107             --  the special processing above for the OUT and IN OUT cases
1108             --  could be performed. We could make the test in Exp_Ch4 more
1109             --  complex and have it detect the parameter mode, but it is
1110             --  easier simply to handle all cases here.)
1111
1112             if Nkind (Actual) = N_Indexed_Component
1113               and then Is_Packed (Etype (Prefix (Actual)))
1114             then
1115                Reset_Packed_Prefix;
1116                Expand_Packed_Element_Reference (Actual);
1117
1118             --  If we have a reference to a bit packed array, we copy it,
1119             --  since the actual must be byte aligned.
1120
1121             --  Is this really necessary in all cases???
1122
1123             elsif Is_Ref_To_Bit_Packed_Array (Actual) then
1124                Add_Simple_Call_By_Copy_Code;
1125
1126             --  If a non-scalar actual is possibly unaligned, we need a copy
1127
1128             elsif Is_Possibly_Unaligned_Object (Actual)
1129               and then not Represented_As_Scalar (Etype (Formal))
1130             then
1131                Add_Simple_Call_By_Copy_Code;
1132
1133             --  Similarly, we have to expand slices of packed arrays here
1134             --  because the result must be byte aligned.
1135
1136             elsif Is_Ref_To_Bit_Packed_Slice (Actual) then
1137                Add_Call_By_Copy_Code;
1138
1139             --  Only processing remaining is to pass by copy if this is a
1140             --  reference to a possibly unaligned slice, since the caller
1141             --  expects an appropriately aligned argument.
1142
1143             elsif Is_Possibly_Unaligned_Slice (Actual) then
1144                Add_Call_By_Copy_Code;
1145             end if;
1146          end if;
1147
1148          Next_Formal (Formal);
1149          Next_Actual (Actual);
1150       end loop;
1151
1152       --  Find right place to put post call stuff if it is present
1153
1154       if not Is_Empty_List (Post_Call) then
1155
1156          --  If call is not a list member, it must be the triggering statement
1157          --  of a triggering alternative or an entry call alternative, and we
1158          --  can add the post call stuff to the corresponding statement list.
1159
1160          if not Is_List_Member (N) then
1161             declare
1162                P : constant Node_Id := Parent (N);
1163
1164             begin
1165                pragma Assert (Nkind (P) = N_Triggering_Alternative
1166                  or else Nkind (P) = N_Entry_Call_Alternative);
1167
1168                if Is_Non_Empty_List (Statements (P)) then
1169                   Insert_List_Before_And_Analyze
1170                     (First (Statements (P)), Post_Call);
1171                else
1172                   Set_Statements (P, Post_Call);
1173                end if;
1174             end;
1175
1176          --  Otherwise, normal case where N is in a statement sequence,
1177          --  just put the post-call stuff after the call statement.
1178
1179          else
1180             Insert_Actions_After (N, Post_Call);
1181          end if;
1182       end if;
1183
1184       --  The call node itself is re-analyzed in Expand_Call
1185
1186    end Expand_Actuals;
1187
1188    -----------------
1189    -- Expand_Call --
1190    -----------------
1191
1192    --  This procedure handles expansion of function calls and procedure call
1193    --  statements (i.e. it serves as the body for Expand_N_Function_Call and
1194    --  Expand_N_Procedure_Call_Statement. Processing for calls includes:
1195
1196    --    Replace call to Raise_Exception by Raise_Exception always if possible
1197    --    Provide values of actuals for all formals in Extra_Formals list
1198    --    Replace "call" to enumeration literal function by literal itself
1199    --    Rewrite call to predefined operator as operator
1200    --    Replace actuals to in-out parameters that are numeric conversions,
1201    --     with explicit assignment to temporaries before and after the call.
1202    --    Remove optional actuals if First_Optional_Parameter specified.
1203
1204    --   Note that the list of actuals has been filled with default expressions
1205    --   during semantic analysis of the call. Only the extra actuals required
1206    --   for the 'Constrained attribute and for accessibility checks are added
1207    --   at this point.
1208
1209    procedure Expand_Call (N : Node_Id) is
1210       Loc           : constant Source_Ptr := Sloc (N);
1211       Remote        : constant Boolean    := Is_Remote_Call (N);
1212       Subp          : Entity_Id;
1213       Orig_Subp     : Entity_Id := Empty;
1214       Parent_Subp   : Entity_Id;
1215       Parent_Formal : Entity_Id;
1216       Actual        : Node_Id;
1217       Formal        : Entity_Id;
1218       Prev          : Node_Id := Empty;
1219
1220       Prev_Orig : Node_Id;
1221       --  Original node for an actual, which may have been rewritten. If the
1222       --  actual is a function call that has been transformed from a selected
1223       --  component, the original node is unanalyzed. Otherwise, it carries
1224       --  semantic information used to generate additional actuals.
1225
1226       Scop          : Entity_Id;
1227       Extra_Actuals : List_Id := No_List;
1228
1229       CW_Interface_Formals_Present : Boolean := False;
1230
1231       procedure Add_Actual_Parameter (Insert_Param : Node_Id);
1232       --  Adds one entry to the end of the actual parameter list. Used for
1233       --  default parameters and for extra actuals (for Extra_Formals). The
1234       --  argument is an N_Parameter_Association node.
1235
1236       procedure Add_Extra_Actual (Expr : Node_Id; EF : Entity_Id);
1237       --  Adds an extra actual to the list of extra actuals. Expr is the
1238       --  expression for the value of the actual, EF is the entity for the
1239       --  extra formal.
1240
1241       function Inherited_From_Formal (S : Entity_Id) return Entity_Id;
1242       --  Within an instance, a type derived from a non-tagged formal derived
1243       --  type inherits from the original parent, not from the actual. This is
1244       --  tested in 4723-003. The current derivation mechanism has the derived
1245       --  type inherit from the actual, which is only correct outside of the
1246       --  instance. If the subprogram is inherited, we test for this particular
1247       --  case through a convoluted tree traversal before setting the proper
1248       --  subprogram to be called.
1249
1250       --------------------------
1251       -- Add_Actual_Parameter --
1252       --------------------------
1253
1254       procedure Add_Actual_Parameter (Insert_Param : Node_Id) is
1255          Actual_Expr : constant Node_Id :=
1256                          Explicit_Actual_Parameter (Insert_Param);
1257
1258       begin
1259          --  Case of insertion is first named actual
1260
1261          if No (Prev) or else
1262             Nkind (Parent (Prev)) /= N_Parameter_Association
1263          then
1264             Set_Next_Named_Actual (Insert_Param, First_Named_Actual (N));
1265             Set_First_Named_Actual (N, Actual_Expr);
1266
1267             if No (Prev) then
1268                if not Present (Parameter_Associations (N)) then
1269                   Set_Parameter_Associations (N, New_List);
1270                   Append (Insert_Param, Parameter_Associations (N));
1271                end if;
1272             else
1273                Insert_After (Prev, Insert_Param);
1274             end if;
1275
1276          --  Case of insertion is not first named actual
1277
1278          else
1279             Set_Next_Named_Actual
1280               (Insert_Param, Next_Named_Actual (Parent (Prev)));
1281             Set_Next_Named_Actual (Parent (Prev), Actual_Expr);
1282             Append (Insert_Param, Parameter_Associations (N));
1283          end if;
1284
1285          Prev := Actual_Expr;
1286       end Add_Actual_Parameter;
1287
1288       ----------------------
1289       -- Add_Extra_Actual --
1290       ----------------------
1291
1292       procedure Add_Extra_Actual (Expr : Node_Id; EF : Entity_Id) is
1293          Loc : constant Source_Ptr := Sloc (Expr);
1294
1295       begin
1296          if Extra_Actuals = No_List then
1297             Extra_Actuals := New_List;
1298             Set_Parent (Extra_Actuals, N);
1299          end if;
1300
1301          Append_To (Extra_Actuals,
1302            Make_Parameter_Association (Loc,
1303              Explicit_Actual_Parameter => Expr,
1304              Selector_Name =>
1305                Make_Identifier (Loc, Chars (EF))));
1306
1307          Analyze_And_Resolve (Expr, Etype (EF));
1308       end Add_Extra_Actual;
1309
1310       ---------------------------
1311       -- Inherited_From_Formal --
1312       ---------------------------
1313
1314       function Inherited_From_Formal (S : Entity_Id) return Entity_Id is
1315          Par      : Entity_Id;
1316          Gen_Par  : Entity_Id;
1317          Gen_Prim : Elist_Id;
1318          Elmt     : Elmt_Id;
1319          Indic    : Node_Id;
1320
1321       begin
1322          --  If the operation is inherited, it is attached to the corresponding
1323          --  type derivation. If the parent in the derivation is a generic
1324          --  actual, it is a subtype of the actual, and we have to recover the
1325          --  original derived type declaration to find the proper parent.
1326
1327          if Nkind (Parent (S)) /= N_Full_Type_Declaration
1328            or else not Is_Derived_Type (Defining_Identifier (Parent (S)))
1329            or else Nkind (Type_Definition (Original_Node (Parent (S)))) /=
1330                                                    N_Derived_Type_Definition
1331            or else not In_Instance
1332          then
1333             return Empty;
1334
1335          else
1336             Indic :=
1337               (Subtype_Indication
1338                 (Type_Definition (Original_Node (Parent (S)))));
1339
1340             if Nkind (Indic) = N_Subtype_Indication then
1341                Par := Entity (Subtype_Mark (Indic));
1342             else
1343                Par := Entity (Indic);
1344             end if;
1345          end if;
1346
1347          if not Is_Generic_Actual_Type (Par)
1348            or else Is_Tagged_Type (Par)
1349            or else Nkind (Parent (Par)) /= N_Subtype_Declaration
1350            or else not In_Open_Scopes (Scope (Par))
1351          then
1352             return Empty;
1353
1354          else
1355             Gen_Par := Generic_Parent_Type (Parent (Par));
1356          end if;
1357
1358          --  If the generic parent type is still the generic type, this is a
1359          --  private formal, not a derived formal, and there are no operations
1360          --  inherited from the formal.
1361
1362          if Nkind (Parent (Gen_Par)) = N_Formal_Type_Declaration then
1363             return Empty;
1364          end if;
1365
1366          Gen_Prim := Collect_Primitive_Operations (Gen_Par);
1367
1368          Elmt := First_Elmt (Gen_Prim);
1369          while Present (Elmt) loop
1370             if Chars (Node (Elmt)) = Chars (S) then
1371                declare
1372                   F1 : Entity_Id;
1373                   F2 : Entity_Id;
1374
1375                begin
1376                   F1 := First_Formal (S);
1377                   F2 := First_Formal (Node (Elmt));
1378                   while Present (F1)
1379                     and then Present (F2)
1380                   loop
1381                      if Etype (F1) = Etype (F2)
1382                        or else Etype (F2) = Gen_Par
1383                      then
1384                         Next_Formal (F1);
1385                         Next_Formal (F2);
1386                      else
1387                         Next_Elmt (Elmt);
1388                         exit;   --  not the right subprogram
1389                      end if;
1390
1391                      return Node (Elmt);
1392                   end loop;
1393                end;
1394
1395             else
1396                Next_Elmt (Elmt);
1397             end if;
1398          end loop;
1399
1400          raise Program_Error;
1401       end Inherited_From_Formal;
1402
1403    --  Start of processing for Expand_Call
1404
1405    begin
1406       --  Ignore if previous error
1407
1408       if Nkind (N) in N_Has_Etype and then Etype (N) = Any_Type then
1409          return;
1410       end if;
1411
1412       --  Call using access to subprogram with explicit dereference
1413
1414       if Nkind (Name (N)) = N_Explicit_Dereference then
1415          Subp        := Etype (Name (N));
1416          Parent_Subp := Empty;
1417
1418       --  Case of call to simple entry, where the Name is a selected component
1419       --  whose prefix is the task, and whose selector name is the entry name
1420
1421       elsif Nkind (Name (N)) = N_Selected_Component then
1422          Subp        := Entity (Selector_Name (Name (N)));
1423          Parent_Subp := Empty;
1424
1425       --  Case of call to member of entry family, where Name is an indexed
1426       --  component, with the prefix being a selected component giving the
1427       --  task and entry family name, and the index being the entry index.
1428
1429       elsif Nkind (Name (N)) = N_Indexed_Component then
1430          Subp        := Entity (Selector_Name (Prefix (Name (N))));
1431          Parent_Subp := Empty;
1432
1433       --  Normal case
1434
1435       else
1436          Subp        := Entity (Name (N));
1437          Parent_Subp := Alias (Subp);
1438
1439          --  Replace call to Raise_Exception by call to Raise_Exception_Always
1440          --  if we can tell that the first parameter cannot possibly be null.
1441          --  This helps optimization and also generation of warnings.
1442
1443          if not Restriction_Active (No_Exception_Handlers)
1444            and then Is_RTE (Subp, RE_Raise_Exception)
1445          then
1446             declare
1447                FA : constant Node_Id := Original_Node (First_Actual (N));
1448
1449             begin
1450                --  The case we catch is where the first argument is obtained
1451                --  using the Identity attribute (which must always be
1452                --  non-null).
1453
1454                if Nkind (FA) = N_Attribute_Reference
1455                  and then Attribute_Name (FA) = Name_Identity
1456                then
1457                   Subp := RTE (RE_Raise_Exception_Always);
1458                   Set_Entity (Name (N), Subp);
1459                end if;
1460             end;
1461          end if;
1462
1463          if Ekind (Subp) = E_Entry then
1464             Parent_Subp := Empty;
1465          end if;
1466       end if;
1467
1468       --  Ada 2005 (AI-345): We have a procedure call as a triggering
1469       --  alternative in an asynchronous select or as an entry call in
1470       --  a conditional or timed select. Check whether the procedure call
1471       --  is a renaming of an entry and rewrite it as an entry call.
1472
1473       if Ada_Version >= Ada_05
1474         and then Nkind (N) = N_Procedure_Call_Statement
1475         and then
1476            ((Nkind (Parent (N)) = N_Triggering_Alternative
1477                and then Triggering_Statement (Parent (N)) = N)
1478           or else
1479             (Nkind (Parent (N)) = N_Entry_Call_Alternative
1480                and then Entry_Call_Statement (Parent (N)) = N))
1481       then
1482          declare
1483             Ren_Decl : Node_Id;
1484             Ren_Root : Entity_Id := Subp;
1485
1486          begin
1487             --  This may be a chain of renamings, find the root
1488
1489             if Present (Alias (Ren_Root)) then
1490                Ren_Root := Alias (Ren_Root);
1491             end if;
1492
1493             if Present (Original_Node (Parent (Parent (Ren_Root)))) then
1494                Ren_Decl := Original_Node (Parent (Parent (Ren_Root)));
1495
1496                if Nkind (Ren_Decl) = N_Subprogram_Renaming_Declaration then
1497                   Rewrite (N,
1498                     Make_Entry_Call_Statement (Loc,
1499                       Name =>
1500                         New_Copy_Tree (Name (Ren_Decl)),
1501                       Parameter_Associations =>
1502                         New_Copy_List_Tree (Parameter_Associations (N))));
1503
1504                   return;
1505                end if;
1506             end if;
1507          end;
1508       end if;
1509
1510       --  First step, compute extra actuals, corresponding to any
1511       --  Extra_Formals present. Note that we do not access Extra_Formals
1512       --  directly, instead we simply note the presence of the extra
1513       --  formals as we process the regular formals and collect the
1514       --  corresponding actuals in Extra_Actuals.
1515
1516       --  We also generate any required range checks for actuals as we go
1517       --  through the loop, since this is a convenient place to do this.
1518
1519       Formal := First_Formal (Subp);
1520       Actual := First_Actual (N);
1521       while Present (Formal) loop
1522
1523          --  Generate range check if required (not activated yet ???)
1524
1525 --         if Do_Range_Check (Actual) then
1526 --            Set_Do_Range_Check (Actual, False);
1527 --            Generate_Range_Check
1528 --              (Actual, Etype (Formal), CE_Range_Check_Failed);
1529 --         end if;
1530
1531          --  Prepare to examine current entry
1532
1533          Prev := Actual;
1534          Prev_Orig := Original_Node (Prev);
1535
1536          if not Analyzed (Prev_Orig)
1537            and then Nkind (Actual) = N_Function_Call
1538          then
1539             Prev_Orig := Prev;
1540          end if;
1541
1542          --  Ada 2005 (AI-251): Check if any formal is a class-wide interface
1543          --  to expand it in a further round.
1544
1545          CW_Interface_Formals_Present :=
1546            CW_Interface_Formals_Present
1547              or else
1548                (Ekind (Etype (Formal)) = E_Class_Wide_Type
1549                   and then Is_Interface (Etype (Etype (Formal))))
1550              or else
1551                (Ekind (Etype (Formal)) = E_Anonymous_Access_Type
1552                  and then Is_Interface (Directly_Designated_Type
1553                                          (Etype (Etype (Formal)))));
1554
1555          --  Create possible extra actual for constrained case. Usually, the
1556          --  extra actual is of the form actual'constrained, but since this
1557          --  attribute is only available for unconstrained records, TRUE is
1558          --  expanded if the type of the formal happens to be constrained (for
1559          --  instance when this procedure is inherited from an unconstrained
1560          --  record to a constrained one) or if the actual has no discriminant
1561          --  (its type is constrained). An exception to this is the case of a
1562          --  private type without discriminants. In this case we pass FALSE
1563          --  because the object has underlying discriminants with defaults.
1564
1565          if Present (Extra_Constrained (Formal)) then
1566             if Ekind (Etype (Prev)) in Private_Kind
1567               and then not Has_Discriminants (Base_Type (Etype (Prev)))
1568             then
1569                Add_Extra_Actual (
1570                  New_Occurrence_Of (Standard_False, Loc),
1571                  Extra_Constrained (Formal));
1572
1573             elsif Is_Constrained (Etype (Formal))
1574               or else not Has_Discriminants (Etype (Prev))
1575             then
1576                Add_Extra_Actual (
1577                  New_Occurrence_Of (Standard_True, Loc),
1578                  Extra_Constrained (Formal));
1579
1580             --  Do not produce extra actuals for Unchecked_Union parameters.
1581             --  Jump directly to the end of the loop.
1582
1583             elsif Is_Unchecked_Union (Base_Type (Etype (Actual))) then
1584                goto Skip_Extra_Actual_Generation;
1585
1586             else
1587                --  If the actual is a type conversion, then the constrained
1588                --  test applies to the actual, not the target type.
1589
1590                declare
1591                   Act_Prev : Node_Id;
1592
1593                begin
1594                   --  Test for unchecked conversions as well, which can occur
1595                   --  as out parameter actuals on calls to stream procedures.
1596
1597                   Act_Prev := Prev;
1598                   while Nkind (Act_Prev) = N_Type_Conversion
1599                     or else Nkind (Act_Prev) = N_Unchecked_Type_Conversion
1600                   loop
1601                      Act_Prev := Expression (Act_Prev);
1602                   end loop;
1603
1604                   --  If the expression is a conversion of a dereference,
1605                   --  this is internally generated code that manipulates
1606                   --  addresses, e.g. when building interface tables. No
1607                   --  check should occur in this case, and the discriminated
1608                   --  object is not directly a hand.
1609
1610                   if not Comes_From_Source (Actual)
1611                     and then Nkind (Actual) = N_Unchecked_Type_Conversion
1612                     and then Nkind (Act_Prev) = N_Explicit_Dereference
1613                   then
1614                      Add_Extra_Actual
1615                        (New_Occurrence_Of (Standard_False, Loc),
1616                         Extra_Constrained (Formal));
1617
1618                   else
1619                      Add_Extra_Actual
1620                        (Make_Attribute_Reference (Sloc (Prev),
1621                         Prefix =>
1622                           Duplicate_Subexpr_No_Checks
1623                             (Act_Prev, Name_Req => True),
1624                         Attribute_Name => Name_Constrained),
1625                         Extra_Constrained (Formal));
1626                   end if;
1627                end;
1628             end if;
1629          end if;
1630
1631          --  Create possible extra actual for accessibility level
1632
1633          if Present (Extra_Accessibility (Formal)) then
1634             if Is_Entity_Name (Prev_Orig) then
1635
1636                --  When passing an access parameter as the actual to another
1637                --  access parameter we need to pass along the actual's own
1638                --  associated access level parameter. This is done if we are
1639                --  in the scope of the formal access parameter (if this is an
1640                --  inlined body the extra formal is irrelevant).
1641
1642                if Ekind (Entity (Prev_Orig)) in Formal_Kind
1643                  and then Ekind (Etype (Prev_Orig)) = E_Anonymous_Access_Type
1644                  and then In_Open_Scopes (Scope (Entity (Prev_Orig)))
1645                then
1646                   declare
1647                      Parm_Ent : constant Entity_Id := Param_Entity (Prev_Orig);
1648
1649                   begin
1650                      pragma Assert (Present (Parm_Ent));
1651
1652                      if Present (Extra_Accessibility (Parm_Ent)) then
1653                         Add_Extra_Actual
1654                           (New_Occurrence_Of
1655                              (Extra_Accessibility (Parm_Ent), Loc),
1656                            Extra_Accessibility (Formal));
1657
1658                      --  If the actual access parameter does not have an
1659                      --  associated extra formal providing its scope level,
1660                      --  then treat the actual as having library-level
1661                      --  accessibility.
1662
1663                      else
1664                         Add_Extra_Actual
1665                           (Make_Integer_Literal (Loc,
1666                            Intval => Scope_Depth (Standard_Standard)),
1667                            Extra_Accessibility (Formal));
1668                      end if;
1669                   end;
1670
1671                --  The actual is a normal access value, so just pass the
1672                --  level of the actual's access type.
1673
1674                else
1675                   Add_Extra_Actual
1676                     (Make_Integer_Literal (Loc,
1677                      Intval => Type_Access_Level (Etype (Prev_Orig))),
1678                      Extra_Accessibility (Formal));
1679                end if;
1680
1681             else
1682                case Nkind (Prev_Orig) is
1683
1684                   when N_Attribute_Reference =>
1685
1686                      case Get_Attribute_Id (Attribute_Name (Prev_Orig)) is
1687
1688                         --  For X'Access, pass on the level of the prefix X
1689
1690                         when Attribute_Access =>
1691                            Add_Extra_Actual (
1692                              Make_Integer_Literal (Loc,
1693                                Intval =>
1694                                  Object_Access_Level (Prefix (Prev_Orig))),
1695                              Extra_Accessibility (Formal));
1696
1697                         --  Treat the unchecked attributes as library-level
1698
1699                         when Attribute_Unchecked_Access |
1700                            Attribute_Unrestricted_Access =>
1701                            Add_Extra_Actual (
1702                              Make_Integer_Literal (Loc,
1703                                Intval => Scope_Depth (Standard_Standard)),
1704                              Extra_Accessibility (Formal));
1705
1706                         --  No other cases of attributes returning access
1707                         --  values that can be passed to access parameters
1708
1709                         when others =>
1710                            raise Program_Error;
1711
1712                      end case;
1713
1714                   --  For allocators we pass the level of the execution of
1715                   --  the called subprogram, which is one greater than the
1716                   --  current scope level.
1717
1718                   when N_Allocator =>
1719                      Add_Extra_Actual (
1720                        Make_Integer_Literal (Loc,
1721                         Scope_Depth (Current_Scope) + 1),
1722                        Extra_Accessibility (Formal));
1723
1724                   --  For other cases we simply pass the level of the
1725                   --  actual's access type.
1726
1727                   when others =>
1728                      Add_Extra_Actual (
1729                        Make_Integer_Literal (Loc,
1730                          Intval => Type_Access_Level (Etype (Prev_Orig))),
1731                        Extra_Accessibility (Formal));
1732
1733                end case;
1734             end if;
1735          end if;
1736
1737          --  Perform the check of 4.6(49) that prevents a null value from being
1738          --  passed as an actual to an access parameter. Note that the check is
1739          --  elided in the common cases of passing an access attribute or
1740          --  access parameter as an actual. Also, we currently don't enforce
1741          --  this check for expander-generated actuals and when -gnatdj is set.
1742
1743          if Ada_Version >= Ada_05 then
1744
1745             --  Ada 2005 (AI-231): Check null-excluding access types
1746
1747             if Is_Access_Type (Etype (Formal))
1748               and then Can_Never_Be_Null (Etype (Formal))
1749               and then Nkind (Prev) /= N_Raise_Constraint_Error
1750               and then (Nkind (Prev) = N_Null
1751                           or else not Can_Never_Be_Null (Etype (Prev)))
1752             then
1753                Install_Null_Excluding_Check (Prev);
1754             end if;
1755
1756          --  Ada_Version < Ada_05
1757
1758          else
1759             if Ekind (Etype (Formal)) /= E_Anonymous_Access_Type
1760               or else Access_Checks_Suppressed (Subp)
1761             then
1762                null;
1763
1764             elsif Debug_Flag_J then
1765                null;
1766
1767             elsif not Comes_From_Source (Prev) then
1768                null;
1769
1770             elsif Is_Entity_Name (Prev)
1771               and then Ekind (Etype (Prev)) = E_Anonymous_Access_Type
1772             then
1773                null;
1774
1775             elsif Nkind (Prev) = N_Allocator
1776               or else Nkind (Prev) = N_Attribute_Reference
1777             then
1778                null;
1779
1780             --  Suppress null checks when passing to access parameters of Java
1781             --  subprograms. (Should this be done for other foreign conventions
1782             --  as well ???)
1783
1784             elsif Convention (Subp) = Convention_Java then
1785                null;
1786
1787             else
1788                Install_Null_Excluding_Check (Prev);
1789             end if;
1790          end if;
1791
1792          --  Perform appropriate validity checks on parameters that
1793          --  are entities.
1794
1795          if Validity_Checks_On then
1796             if  (Ekind (Formal) = E_In_Parameter
1797                    and then Validity_Check_In_Params)
1798               or else
1799                 (Ekind (Formal) = E_In_Out_Parameter
1800                    and then Validity_Check_In_Out_Params)
1801             then
1802                --  If the actual is an indexed component of a packed
1803                --  type, it has not been expanded yet. It will be
1804                --  copied in the validity code that follows, and has
1805                --  to be expanded appropriately, so reanalyze it.
1806
1807                if Nkind (Actual) = N_Indexed_Component then
1808                   Set_Analyzed (Actual, False);
1809                end if;
1810
1811                Ensure_Valid (Actual);
1812             end if;
1813          end if;
1814
1815          --  For IN OUT and OUT parameters, ensure that subscripts are valid
1816          --  since this is a left side reference. We only do this for calls
1817          --  from the source program since we assume that compiler generated
1818          --  calls explicitly generate any required checks. We also need it
1819          --  only if we are doing standard validity checks, since clearly it
1820          --  is not needed if validity checks are off, and in subscript
1821          --  validity checking mode, all indexed components are checked with
1822          --  a call directly from Expand_N_Indexed_Component.
1823
1824          if Comes_From_Source (N)
1825            and then Ekind (Formal) /= E_In_Parameter
1826            and then Validity_Checks_On
1827            and then Validity_Check_Default
1828            and then not Validity_Check_Subscripts
1829          then
1830             Check_Valid_Lvalue_Subscripts (Actual);
1831          end if;
1832
1833          --  Mark any scalar OUT parameter that is a simple variable
1834          --  as no longer known to be valid (unless the type is always
1835          --  valid). This reflects the fact that if an OUT parameter
1836          --  is never set in a procedure, then it can become invalid
1837          --  on return from the procedure.
1838
1839          if Ekind (Formal) = E_Out_Parameter
1840            and then Is_Entity_Name (Actual)
1841            and then Ekind (Entity (Actual)) = E_Variable
1842            and then not Is_Known_Valid (Etype (Actual))
1843          then
1844             Set_Is_Known_Valid (Entity (Actual), False);
1845          end if;
1846
1847          --  For an OUT or IN OUT parameter of an access type, if the
1848          --  actual is an entity, then it is no longer known to be non-null.
1849
1850          if Ekind (Formal) /= E_In_Parameter
1851            and then Is_Entity_Name (Actual)
1852            and then Is_Access_Type (Etype (Actual))
1853          then
1854             Set_Is_Known_Non_Null (Entity (Actual), False);
1855          end if;
1856
1857          --  If the formal is class wide and the actual is an aggregate, force
1858          --  evaluation so that the back end who does not know about class-wide
1859          --  type, does not generate a temporary of the wrong size.
1860
1861          if not Is_Class_Wide_Type (Etype (Formal)) then
1862             null;
1863
1864          elsif Nkind (Actual) = N_Aggregate
1865            or else (Nkind (Actual) = N_Qualified_Expression
1866                      and then Nkind (Expression (Actual)) = N_Aggregate)
1867          then
1868             Force_Evaluation (Actual);
1869          end if;
1870
1871          --  In a remote call, if the formal is of a class-wide type, check
1872          --  that the actual meets the requirements described in E.4(18).
1873
1874          if Remote
1875            and then Is_Class_Wide_Type (Etype (Formal))
1876          then
1877             Insert_Action (Actual,
1878               Make_Implicit_If_Statement (N,
1879                 Condition       =>
1880                   Make_Op_Not (Loc,
1881                     Get_Remotely_Callable
1882                       (Duplicate_Subexpr_Move_Checks (Actual))),
1883                 Then_Statements => New_List (
1884                   Make_Raise_Program_Error (Loc,
1885                     Reason => PE_Illegal_RACW_E_4_18))));
1886          end if;
1887
1888          --  This label is required when skipping extra actual generation for
1889          --  Unchecked_Union parameters.
1890
1891          <<Skip_Extra_Actual_Generation>>
1892
1893          Next_Actual (Actual);
1894          Next_Formal (Formal);
1895       end loop;
1896
1897       --  If we are expanding a rhs of an assignement we need to check if
1898       --  tag propagation is needed. This code belongs theorically in Analyze
1899       --  Assignment but has to be done earlier (bottom-up) because the
1900       --  assignment might be transformed into a declaration for an uncons-
1901       --  trained value, if the expression is classwide.
1902
1903       if Nkind (N) = N_Function_Call
1904         and then Is_Tag_Indeterminate (N)
1905         and then Is_Entity_Name (Name (N))
1906       then
1907          declare
1908             Ass : Node_Id := Empty;
1909
1910          begin
1911             if Nkind (Parent (N)) = N_Assignment_Statement then
1912                Ass := Parent (N);
1913
1914             elsif Nkind (Parent (N)) = N_Qualified_Expression
1915               and then Nkind (Parent (Parent (N))) = N_Assignment_Statement
1916             then
1917                Ass := Parent (Parent (N));
1918             end if;
1919
1920             if Present (Ass)
1921               and then Is_Class_Wide_Type (Etype (Name (Ass)))
1922             then
1923                if Etype (N) /= Root_Type (Etype (Name (Ass))) then
1924                   Error_Msg_NE
1925                     ("tag-indeterminate expression must have type&"
1926                       & "('R'M 5.2 (6))", N, Root_Type (Etype (Name (Ass))));
1927                else
1928                   Propagate_Tag (Name (Ass), N);
1929                end if;
1930
1931                --  The call will be rewritten as a dispatching call, and
1932                --  expanded as such.
1933
1934                return;
1935             end if;
1936          end;
1937       end if;
1938
1939       --  Ada 2005 (AI-251): If some formal is a class-wide interface, expand
1940       --  it to point to the correct secondary virtual table
1941
1942       if (Nkind (N) = N_Function_Call
1943            or else Nkind (N) = N_Procedure_Call_Statement)
1944         and then CW_Interface_Formals_Present
1945       then
1946          Expand_Interface_Actuals (N);
1947       end if;
1948
1949       --  Deals with Dispatch_Call if we still have a call, before expanding
1950       --  extra actuals since this will be done on the re-analysis of the
1951       --  dispatching call. Note that we do not try to shorten the actual
1952       --  list for a dispatching call, it would not make sense to do so.
1953       --  Expansion of dispatching calls is suppressed when Java_VM, because
1954       --  the JVM back end directly handles the generation of dispatching
1955       --  calls and would have to undo any expansion to an indirect call.
1956
1957       if (Nkind (N) = N_Function_Call
1958            or else Nkind (N) =  N_Procedure_Call_Statement)
1959         and then Present (Controlling_Argument (N))
1960         and then not Java_VM
1961       then
1962          Expand_Dispatching_Call (N);
1963
1964          --  The following return is worrisome. Is it really OK to
1965          --  skip all remaining processing in this procedure ???
1966
1967          return;
1968
1969       --  Similarly, expand calls to RCI subprograms on which pragma
1970       --  All_Calls_Remote applies. The rewriting will be reanalyzed
1971       --  later. Do this only when the call comes from source since we do
1972       --  not want such a rewritting to occur in expanded code.
1973
1974       elsif Is_All_Remote_Call (N) then
1975          Expand_All_Calls_Remote_Subprogram_Call (N);
1976
1977       --  Similarly, do not add extra actuals for an entry call whose entity
1978       --  is a protected procedure, or for an internal protected subprogram
1979       --  call, because it will be rewritten as a protected subprogram call
1980       --  and reanalyzed (see Expand_Protected_Subprogram_Call).
1981
1982       elsif Is_Protected_Type (Scope (Subp))
1983          and then (Ekind (Subp) = E_Procedure
1984                     or else Ekind (Subp) = E_Function)
1985       then
1986          null;
1987
1988       --  During that loop we gathered the extra actuals (the ones that
1989       --  correspond to Extra_Formals), so now they can be appended.
1990
1991       else
1992          while Is_Non_Empty_List (Extra_Actuals) loop
1993             Add_Actual_Parameter (Remove_Head (Extra_Actuals));
1994          end loop;
1995       end if;
1996
1997       --  At this point we have all the actuals, so this is the point at
1998       --  which the various expansion activities for actuals is carried out.
1999
2000       Expand_Actuals (N, Subp);
2001
2002       --  If the subprogram is a renaming, or if it is inherited, replace it
2003       --  in the call with the name of the actual subprogram being called.
2004       --  If this is a dispatching call, the run-time decides what to call.
2005       --  The Alias attribute does not apply to entries.
2006
2007       if Nkind (N) /= N_Entry_Call_Statement
2008         and then No (Controlling_Argument (N))
2009         and then Present (Parent_Subp)
2010       then
2011          if Present (Inherited_From_Formal (Subp)) then
2012             Parent_Subp := Inherited_From_Formal (Subp);
2013          else
2014             while Present (Alias (Parent_Subp)) loop
2015                Parent_Subp := Alias (Parent_Subp);
2016             end loop;
2017          end if;
2018
2019          Set_Entity (Name (N), Parent_Subp);
2020
2021          if Is_Abstract (Parent_Subp)
2022            and then not In_Instance
2023          then
2024             Error_Msg_NE
2025               ("cannot call abstract subprogram &!", Name (N), Parent_Subp);
2026          end if;
2027
2028          --  Add an explicit conversion for parameter of the derived type.
2029          --  This is only done for scalar and access in-parameters. Others
2030          --  have been expanded in expand_actuals.
2031
2032          Formal := First_Formal (Subp);
2033          Parent_Formal := First_Formal (Parent_Subp);
2034          Actual := First_Actual (N);
2035
2036          --  It is not clear that conversion is needed for intrinsic
2037          --  subprograms, but it certainly is for those that are user-
2038          --  defined, and that can be inherited on derivation, namely
2039          --  unchecked conversion and deallocation.
2040          --  General case needs study ???
2041
2042          if not Is_Intrinsic_Subprogram (Parent_Subp)
2043            or else Is_Generic_Instance (Parent_Subp)
2044          then
2045             while Present (Formal) loop
2046                if Etype (Formal) /= Etype (Parent_Formal)
2047                  and then Is_Scalar_Type (Etype (Formal))
2048                  and then Ekind (Formal) = E_In_Parameter
2049                  and then not Raises_Constraint_Error (Actual)
2050                then
2051                   Rewrite (Actual,
2052                     OK_Convert_To (Etype (Parent_Formal),
2053                       Relocate_Node (Actual)));
2054
2055                   Analyze (Actual);
2056                   Resolve (Actual, Etype (Parent_Formal));
2057                   Enable_Range_Check (Actual);
2058
2059                elsif Is_Access_Type (Etype (Formal))
2060                  and then Base_Type (Etype (Parent_Formal)) /=
2061                           Base_Type (Etype (Actual))
2062                then
2063                   if Ekind (Formal) /= E_In_Parameter then
2064                      Rewrite (Actual,
2065                        Convert_To (Etype (Parent_Formal),
2066                          Relocate_Node (Actual)));
2067
2068                      Analyze (Actual);
2069                      Resolve (Actual, Etype (Parent_Formal));
2070
2071                   elsif
2072                     Ekind (Etype (Parent_Formal)) = E_Anonymous_Access_Type
2073                       and then Designated_Type (Etype (Parent_Formal))
2074                                  /=
2075                                Designated_Type (Etype (Actual))
2076                       and then not Is_Controlling_Formal (Formal)
2077                   then
2078                      --  This unchecked conversion is not necessary unless
2079                      --  inlining is enabled, because in that case the type
2080                      --  mismatch may become visible in the body about to be
2081                      --  inlined.
2082
2083                      Rewrite (Actual,
2084                        Unchecked_Convert_To (Etype (Parent_Formal),
2085                          Relocate_Node (Actual)));
2086
2087                      Analyze (Actual);
2088                      Resolve (Actual, Etype (Parent_Formal));
2089                   end if;
2090                end if;
2091
2092                Next_Formal (Formal);
2093                Next_Formal (Parent_Formal);
2094                Next_Actual (Actual);
2095             end loop;
2096          end if;
2097
2098          Orig_Subp := Subp;
2099          Subp := Parent_Subp;
2100       end if;
2101
2102       --  Check for violation of No_Abort_Statements
2103
2104       if Is_RTE (Subp, RE_Abort_Task) then
2105          Check_Restriction (No_Abort_Statements, N);
2106
2107       --  Check for violation of No_Dynamic_Attachment
2108
2109       elsif RTU_Loaded (Ada_Interrupts)
2110         and then (Is_RTE (Subp, RE_Is_Reserved)      or else
2111                   Is_RTE (Subp, RE_Is_Attached)      or else
2112                   Is_RTE (Subp, RE_Current_Handler)  or else
2113                   Is_RTE (Subp, RE_Attach_Handler)   or else
2114                   Is_RTE (Subp, RE_Exchange_Handler) or else
2115                   Is_RTE (Subp, RE_Detach_Handler)   or else
2116                   Is_RTE (Subp, RE_Reference))
2117       then
2118          Check_Restriction (No_Dynamic_Attachment, N);
2119       end if;
2120
2121       --  Deal with case where call is an explicit dereference
2122
2123       if Nkind (Name (N)) = N_Explicit_Dereference then
2124
2125       --  Handle case of access to protected subprogram type
2126
2127          if Ekind (Base_Type (Etype (Prefix (Name (N))))) =
2128                                E_Access_Protected_Subprogram_Type
2129          then
2130             --  If this is a call through an access to protected operation,
2131             --  the prefix has the form (object'address, operation'access).
2132             --  Rewrite as a for other protected calls: the object is the
2133             --  first parameter of the list of actuals.
2134
2135             declare
2136                Call : Node_Id;
2137                Parm : List_Id;
2138                Nam  : Node_Id;
2139                Obj  : Node_Id;
2140                Ptr  : constant Node_Id := Prefix (Name (N));
2141
2142                T : constant Entity_Id :=
2143                      Equivalent_Type (Base_Type (Etype (Ptr)));
2144
2145                D_T : constant Entity_Id :=
2146                        Designated_Type (Base_Type (Etype (Ptr)));
2147
2148             begin
2149                Obj :=
2150                  Make_Selected_Component (Loc,
2151                    Prefix        => Unchecked_Convert_To (T, Ptr),
2152                    Selector_Name =>
2153                      New_Occurrence_Of (First_Entity (T), Loc));
2154
2155                Nam :=
2156                  Make_Selected_Component (Loc,
2157                    Prefix        => Unchecked_Convert_To (T, Ptr),
2158                    Selector_Name =>
2159                      New_Occurrence_Of (Next_Entity (First_Entity (T)), Loc));
2160
2161                Nam := Make_Explicit_Dereference (Loc, Nam);
2162
2163                if Present (Parameter_Associations (N))  then
2164                   Parm := Parameter_Associations (N);
2165                else
2166                   Parm := New_List;
2167                end if;
2168
2169                Prepend (Obj, Parm);
2170
2171                if Etype (D_T) = Standard_Void_Type then
2172                   Call := Make_Procedure_Call_Statement (Loc,
2173                     Name => Nam,
2174                     Parameter_Associations => Parm);
2175                else
2176                   Call := Make_Function_Call (Loc,
2177                     Name => Nam,
2178                     Parameter_Associations => Parm);
2179                end if;
2180
2181                Set_First_Named_Actual (Call, First_Named_Actual (N));
2182                Set_Etype (Call, Etype (D_T));
2183
2184                --  We do not re-analyze the call to avoid infinite recursion.
2185                --  We analyze separately the prefix and the object, and set
2186                --  the checks on the prefix that would otherwise be emitted
2187                --  when resolving a call.
2188
2189                Rewrite (N, Call);
2190                Analyze (Nam);
2191                Apply_Access_Check (Nam);
2192                Analyze (Obj);
2193                return;
2194             end;
2195          end if;
2196       end if;
2197
2198       --  If this is a call to an intrinsic subprogram, then perform the
2199       --  appropriate expansion to the corresponding tree node and we
2200       --  are all done (since after that the call is gone!)
2201
2202       --  In the case where the intrinsic is to be processed by the back end,
2203       --  the call to Expand_Intrinsic_Call will do nothing, which is fine,
2204       --  since the idea in this case is to pass the call unchanged.
2205
2206       if Is_Intrinsic_Subprogram (Subp) then
2207          Expand_Intrinsic_Call (N, Subp);
2208          return;
2209       end if;
2210
2211       if Ekind (Subp) = E_Function
2212         or else Ekind (Subp) = E_Procedure
2213       then
2214          if Is_Inlined (Subp) then
2215
2216             Inlined_Subprogram : declare
2217                Bod         : Node_Id;
2218                Must_Inline : Boolean := False;
2219                Spec        : constant Node_Id := Unit_Declaration_Node (Subp);
2220                Scop        : constant Entity_Id := Scope (Subp);
2221
2222                function In_Unfrozen_Instance return Boolean;
2223                --  If the subprogram comes from an instance in the same
2224                --  unit, and the instance is not yet frozen, inlining might
2225                --  trigger order-of-elaboration problems in gigi.
2226
2227                --------------------------
2228                -- In_Unfrozen_Instance --
2229                --------------------------
2230
2231                function In_Unfrozen_Instance return Boolean is
2232                   S : Entity_Id;
2233
2234                begin
2235                   S := Scop;
2236                   while Present (S)
2237                     and then S /= Standard_Standard
2238                   loop
2239                      if Is_Generic_Instance (S)
2240                        and then Present (Freeze_Node (S))
2241                        and then not Analyzed (Freeze_Node (S))
2242                      then
2243                         return True;
2244                      end if;
2245
2246                      S := Scope (S);
2247                   end loop;
2248
2249                   return False;
2250                end In_Unfrozen_Instance;
2251
2252             --  Start of processing for Inlined_Subprogram
2253
2254             begin
2255                --  Verify that the body to inline has already been seen, and
2256                --  that if the body is in the current unit the inlining does
2257                --  not occur earlier. This avoids order-of-elaboration problems
2258                --  in the back end.
2259
2260                --  This should be documented in sinfo/einfo ???
2261
2262                if No (Spec)
2263                  or else Nkind (Spec) /= N_Subprogram_Declaration
2264                  or else No (Body_To_Inline (Spec))
2265                then
2266                   Must_Inline := False;
2267
2268                --  If this an inherited function that returns a private
2269                --  type, do not inline if the full view is an unconstrained
2270                --  array, because such calls cannot be inlined.
2271
2272                elsif Present (Orig_Subp)
2273                  and then Is_Array_Type (Etype (Orig_Subp))
2274                  and then not Is_Constrained (Etype (Orig_Subp))
2275                then
2276                   Must_Inline := False;
2277
2278                elsif In_Unfrozen_Instance then
2279                   Must_Inline := False;
2280
2281                else
2282                   Bod := Body_To_Inline (Spec);
2283
2284                   if (In_Extended_Main_Code_Unit (N)
2285                         or else In_Extended_Main_Code_Unit (Parent (N))
2286                         or else Is_Always_Inlined (Subp))
2287                     and then (not In_Same_Extended_Unit (Sloc (Bod), Loc)
2288                                or else
2289                                  Earlier_In_Extended_Unit (Sloc (Bod), Loc))
2290                   then
2291                      Must_Inline := True;
2292
2293                   --  If we are compiling a package body that is not the main
2294                   --  unit, it must be for inlining/instantiation purposes,
2295                   --  in which case we inline the call to insure that the same
2296                   --  temporaries are generated when compiling the body by
2297                   --  itself. Otherwise link errors can occur.
2298
2299                   --  If the function being called is itself in the main unit,
2300                   --  we cannot inline, because there is a risk of double
2301                   --  elaboration and/or circularity: the inlining can make
2302                   --  visible a private entity in the body of the main unit,
2303                   --  that gigi will see before its sees its proper definition.
2304
2305                   elsif not (In_Extended_Main_Code_Unit (N))
2306                     and then In_Package_Body
2307                   then
2308                      Must_Inline := not In_Extended_Main_Source_Unit (Subp);
2309                   end if;
2310                end if;
2311
2312                if Must_Inline then
2313                   Expand_Inlined_Call (N, Subp, Orig_Subp);
2314
2315                else
2316                   --  Let the back end handle it
2317
2318                   Add_Inlined_Body (Subp);
2319
2320                   if Front_End_Inlining
2321                     and then Nkind (Spec) = N_Subprogram_Declaration
2322                     and then (In_Extended_Main_Code_Unit (N))
2323                     and then No (Body_To_Inline (Spec))
2324                     and then not Has_Completion (Subp)
2325                     and then In_Same_Extended_Unit (Sloc (Spec), Loc)
2326                   then
2327                      Cannot_Inline
2328                       ("cannot inline& (body not seen yet)?",
2329                        N, Subp);
2330                   end if;
2331                end if;
2332             end Inlined_Subprogram;
2333          end if;
2334       end if;
2335
2336       --  Check for a protected subprogram. This is either an intra-object
2337       --  call, or a protected function call. Protected procedure calls are
2338       --  rewritten as entry calls and handled accordingly.
2339
2340       Scop := Scope (Subp);
2341
2342       if Nkind (N) /= N_Entry_Call_Statement
2343         and then Is_Protected_Type (Scop)
2344       then
2345          --  If the call is an internal one, it is rewritten as a call to
2346          --  to the corresponding unprotected subprogram.
2347
2348          Expand_Protected_Subprogram_Call (N, Subp, Scop);
2349       end if;
2350
2351       --  Functions returning controlled objects need special attention
2352
2353       if Controlled_Type (Etype (Subp))
2354         and then not Is_Return_By_Reference_Type (Etype (Subp))
2355       then
2356          Expand_Ctrl_Function_Call (N);
2357       end if;
2358
2359       --  Test for First_Optional_Parameter, and if so, truncate parameter
2360       --  list if there are optional parameters at the trailing end.
2361       --  Note we never delete procedures for call via a pointer.
2362
2363       if (Ekind (Subp) = E_Procedure or else Ekind (Subp) = E_Function)
2364         and then Present (First_Optional_Parameter (Subp))
2365       then
2366          declare
2367             Last_Keep_Arg : Node_Id;
2368
2369          begin
2370             --  Last_Keep_Arg will hold the last actual that should be
2371             --  retained. If it remains empty at the end, it means that
2372             --  all parameters are optional.
2373
2374             Last_Keep_Arg := Empty;
2375
2376             --  Find first optional parameter, must be present since we
2377             --  checked the validity of the parameter before setting it.
2378
2379             Formal := First_Formal (Subp);
2380             Actual := First_Actual (N);
2381             while Formal /= First_Optional_Parameter (Subp) loop
2382                Last_Keep_Arg := Actual;
2383                Next_Formal (Formal);
2384                Next_Actual (Actual);
2385             end loop;
2386
2387             --  We have Formal and Actual pointing to the first potentially
2388             --  droppable argument. We can drop all the trailing arguments
2389             --  whose actual matches the default. Note that we know that all
2390             --  remaining formals have defaults, because we checked that this
2391             --  requirement was met before setting First_Optional_Parameter.
2392
2393             --  We use Fully_Conformant_Expressions to check for identity
2394             --  between formals and actuals, which may miss some cases, but
2395             --  on the other hand, this is only an optimization (if we fail
2396             --  to truncate a parameter it does not affect functionality).
2397             --  So if the default is 3 and the actual is 1+2, we consider
2398             --  them unequal, which hardly seems worrisome.
2399
2400             while Present (Formal) loop
2401                if not Fully_Conformant_Expressions
2402                     (Actual, Default_Value (Formal))
2403                then
2404                   Last_Keep_Arg := Actual;
2405                end if;
2406
2407                Next_Formal (Formal);
2408                Next_Actual (Actual);
2409             end loop;
2410
2411             --  If no arguments, delete entire list, this is the easy case
2412
2413             if No (Last_Keep_Arg) then
2414                while Is_Non_Empty_List (Parameter_Associations (N)) loop
2415                   Delete_Tree (Remove_Head (Parameter_Associations (N)));
2416                end loop;
2417
2418                Set_Parameter_Associations (N, No_List);
2419                Set_First_Named_Actual (N, Empty);
2420
2421             --  Case where at the last retained argument is positional. This
2422             --  is also an easy case, since the retained arguments are already
2423             --  in the right form, and we don't need to worry about the order
2424             --  of arguments that get eliminated.
2425
2426             elsif Is_List_Member (Last_Keep_Arg) then
2427                while Present (Next (Last_Keep_Arg)) loop
2428                   Delete_Tree (Remove_Next (Last_Keep_Arg));
2429                end loop;
2430
2431                Set_First_Named_Actual (N, Empty);
2432
2433             --  This is the annoying case where the last retained argument
2434             --  is a named parameter. Since the original arguments are not
2435             --  in declaration order, we may have to delete some fairly
2436             --  random collection of arguments.
2437
2438             else
2439                declare
2440                   Temp   : Node_Id;
2441                   Passoc : Node_Id;
2442
2443                   Discard : Node_Id;
2444                   pragma Warnings (Off, Discard);
2445
2446                begin
2447                   --  First step, remove all the named parameters from the
2448                   --  list (they are still chained using First_Named_Actual
2449                   --  and Next_Named_Actual, so we have not lost them!)
2450
2451                   Temp := First (Parameter_Associations (N));
2452
2453                   --  Case of all parameters named, remove them all
2454
2455                   if Nkind (Temp) = N_Parameter_Association then
2456                      while Is_Non_Empty_List (Parameter_Associations (N)) loop
2457                         Temp := Remove_Head (Parameter_Associations (N));
2458                      end loop;
2459
2460                   --  Case of mixed positional/named, remove named parameters
2461
2462                   else
2463                      while Nkind (Next (Temp)) /= N_Parameter_Association loop
2464                         Next (Temp);
2465                      end loop;
2466
2467                      while Present (Next (Temp)) loop
2468                         Discard := Remove_Next (Temp);
2469                      end loop;
2470                   end if;
2471
2472                   --  Now we loop through the named parameters, till we get
2473                   --  to the last one to be retained, adding them to the list.
2474                   --  Note that the Next_Named_Actual list does not need to be
2475                   --  touched since we are only reordering them on the actual
2476                   --  parameter association list.
2477
2478                   Passoc := Parent (First_Named_Actual (N));
2479                   loop
2480                      Temp := Relocate_Node (Passoc);
2481                      Append_To
2482                        (Parameter_Associations (N), Temp);
2483                      exit when
2484                        Last_Keep_Arg = Explicit_Actual_Parameter (Passoc);
2485                      Passoc := Parent (Next_Named_Actual (Passoc));
2486                   end loop;
2487
2488                   Set_Next_Named_Actual (Temp, Empty);
2489
2490                   loop
2491                      Temp := Next_Named_Actual (Passoc);
2492                      exit when No (Temp);
2493                      Set_Next_Named_Actual
2494                        (Passoc, Next_Named_Actual (Parent (Temp)));
2495                      Delete_Tree (Temp);
2496                   end loop;
2497                end;
2498             end if;
2499          end;
2500       end if;
2501    end Expand_Call;
2502
2503    --------------------------
2504    -- Expand_Inlined_Call --
2505    --------------------------
2506
2507    procedure Expand_Inlined_Call
2508     (N         : Node_Id;
2509      Subp      : Entity_Id;
2510      Orig_Subp : Entity_Id)
2511    is
2512       Loc       : constant Source_Ptr := Sloc (N);
2513       Is_Predef : constant Boolean :=
2514                    Is_Predefined_File_Name
2515                      (Unit_File_Name (Get_Source_Unit (Subp)));
2516       Orig_Bod  : constant Node_Id :=
2517                     Body_To_Inline (Unit_Declaration_Node (Subp));
2518
2519       Blk      : Node_Id;
2520       Bod      : Node_Id;
2521       Decl     : Node_Id;
2522       Exit_Lab : Entity_Id := Empty;
2523       F        : Entity_Id;
2524       A        : Node_Id;
2525       Lab_Decl : Node_Id;
2526       Lab_Id   : Node_Id;
2527       New_A    : Node_Id;
2528       Num_Ret  : Int := 0;
2529       Ret_Type : Entity_Id;
2530       Targ     : Node_Id;
2531       Temp     : Entity_Id;
2532       Temp_Typ : Entity_Id;
2533
2534       procedure Make_Exit_Label;
2535       --  Build declaration for exit label to be used in Return statements
2536
2537       function Process_Formals (N : Node_Id) return Traverse_Result;
2538       --  Replace occurrence of a formal with the corresponding actual, or
2539       --  the thunk generated for it.
2540
2541       function Process_Sloc (Nod : Node_Id) return Traverse_Result;
2542       --  If the call being expanded is that of an internal subprogram,
2543       --  set the sloc of the generated block to that of the call itself,
2544       --  so that the expansion is skipped by the -next- command in gdb.
2545       --  Same processing for a subprogram in a predefined file, e.g.
2546       --  Ada.Tags. If Debug_Generated_Code is true, suppress this change
2547       --  to simplify our own development.
2548
2549       procedure Rewrite_Function_Call (N : Node_Id; Blk : Node_Id);
2550       --  If the function body is a single expression, replace call with
2551       --  expression, else insert block appropriately.
2552
2553       procedure Rewrite_Procedure_Call (N : Node_Id; Blk : Node_Id);
2554       --  If procedure body has no local variables, inline body without
2555       --  creating block,  otherwise rewrite call with block.
2556
2557       function Formal_Is_Used_Once (Formal : Entity_Id) return Boolean;
2558       --  Determine whether a formal parameter is used only once in Orig_Bod
2559
2560       ---------------------
2561       -- Make_Exit_Label --
2562       ---------------------
2563
2564       procedure Make_Exit_Label is
2565       begin
2566          --  Create exit label for subprogram if one does not exist yet
2567
2568          if No (Exit_Lab) then
2569             Lab_Id := Make_Identifier (Loc, New_Internal_Name ('L'));
2570             Set_Entity (Lab_Id,
2571               Make_Defining_Identifier (Loc, Chars (Lab_Id)));
2572             Exit_Lab := Make_Label (Loc, Lab_Id);
2573
2574             Lab_Decl :=
2575               Make_Implicit_Label_Declaration (Loc,
2576                 Defining_Identifier  => Entity (Lab_Id),
2577                 Label_Construct      => Exit_Lab);
2578          end if;
2579       end Make_Exit_Label;
2580
2581       ---------------------
2582       -- Process_Formals --
2583       ---------------------
2584
2585       function Process_Formals (N : Node_Id) return Traverse_Result is
2586          A   : Entity_Id;
2587          E   : Entity_Id;
2588          Ret : Node_Id;
2589
2590       begin
2591          if Is_Entity_Name (N)
2592            and then Present (Entity (N))
2593          then
2594             E := Entity (N);
2595
2596             if Is_Formal (E)
2597               and then Scope (E) = Subp
2598             then
2599                A := Renamed_Object (E);
2600
2601                if Is_Entity_Name (A) then
2602                   Rewrite (N, New_Occurrence_Of (Entity (A), Loc));
2603
2604                elsif Nkind (A) = N_Defining_Identifier then
2605                   Rewrite (N, New_Occurrence_Of (A, Loc));
2606
2607                else   --  numeric literal
2608                   Rewrite (N, New_Copy (A));
2609                end if;
2610             end if;
2611
2612             return Skip;
2613
2614          elsif Nkind (N) = N_Return_Statement then
2615
2616             if No (Expression (N)) then
2617                Make_Exit_Label;
2618                Rewrite (N, Make_Goto_Statement (Loc,
2619                  Name => New_Copy (Lab_Id)));
2620
2621             else
2622                if Nkind (Parent (N)) = N_Handled_Sequence_Of_Statements
2623                  and then Nkind (Parent (Parent (N))) = N_Subprogram_Body
2624                then
2625                   --  Function body is a single expression. No need for
2626                   --  exit label.
2627
2628                   null;
2629
2630                else
2631                   Num_Ret := Num_Ret + 1;
2632                   Make_Exit_Label;
2633                end if;
2634
2635                --  Because of the presence of private types, the views of the
2636                --  expression and the context may be different, so place an
2637                --  unchecked conversion to the context type to avoid spurious
2638                --  errors, eg. when the expression is a numeric literal and
2639                --  the context is private. If the expression is an aggregate,
2640                --  use a qualified expression, because an aggregate is not a
2641                --  legal argument of a conversion.
2642
2643                if Nkind (Expression (N)) = N_Aggregate
2644                  or else Nkind (Expression (N)) = N_Null
2645                then
2646                   Ret :=
2647                     Make_Qualified_Expression (Sloc (N),
2648                        Subtype_Mark => New_Occurrence_Of (Ret_Type, Sloc (N)),
2649                        Expression => Relocate_Node (Expression (N)));
2650                else
2651                   Ret :=
2652                     Unchecked_Convert_To
2653                       (Ret_Type, Relocate_Node (Expression (N)));
2654                end if;
2655
2656                if Nkind (Targ) = N_Defining_Identifier then
2657                   Rewrite (N,
2658                     Make_Assignment_Statement (Loc,
2659                       Name => New_Occurrence_Of (Targ, Loc),
2660                       Expression => Ret));
2661                else
2662                   Rewrite (N,
2663                     Make_Assignment_Statement (Loc,
2664                       Name => New_Copy (Targ),
2665                       Expression => Ret));
2666                end if;
2667
2668                Set_Assignment_OK (Name (N));
2669
2670                if Present (Exit_Lab) then
2671                   Insert_After (N,
2672                     Make_Goto_Statement (Loc,
2673                       Name => New_Copy (Lab_Id)));
2674                end if;
2675             end if;
2676
2677             return OK;
2678
2679          --  Remove pragma Unreferenced since it may refer to formals that
2680          --  are not visible in the inlined body, and in any case we will
2681          --  not be posting warnings on the inlined body so it is unneeded.
2682
2683          elsif Nkind (N) = N_Pragma
2684            and then Chars (N) = Name_Unreferenced
2685          then
2686             Rewrite (N, Make_Null_Statement (Sloc (N)));
2687             return OK;
2688
2689          else
2690             return OK;
2691          end if;
2692       end Process_Formals;
2693
2694       procedure Replace_Formals is new Traverse_Proc (Process_Formals);
2695
2696       ------------------
2697       -- Process_Sloc --
2698       ------------------
2699
2700       function Process_Sloc (Nod : Node_Id) return Traverse_Result is
2701       begin
2702          if not Debug_Generated_Code then
2703             Set_Sloc (Nod, Sloc (N));
2704             Set_Comes_From_Source (Nod, False);
2705          end if;
2706
2707          return OK;
2708       end Process_Sloc;
2709
2710       procedure Reset_Slocs is new Traverse_Proc (Process_Sloc);
2711
2712       ---------------------------
2713       -- Rewrite_Function_Call --
2714       ---------------------------
2715
2716       procedure Rewrite_Function_Call (N : Node_Id; Blk : Node_Id) is
2717          HSS : constant Node_Id := Handled_Statement_Sequence (Blk);
2718          Fst : constant Node_Id := First (Statements (HSS));
2719
2720       begin
2721          --  Optimize simple case: function body is a single return statement,
2722          --  which has been expanded into an assignment.
2723
2724          if Is_Empty_List (Declarations (Blk))
2725            and then Nkind (Fst) = N_Assignment_Statement
2726            and then No (Next (Fst))
2727          then
2728
2729             --  The function call may have been rewritten as the temporary
2730             --  that holds the result of the call, in which case remove the
2731             --  now useless declaration.
2732
2733             if Nkind (N) = N_Identifier
2734               and then Nkind (Parent (Entity (N))) = N_Object_Declaration
2735             then
2736                Rewrite (Parent (Entity (N)), Make_Null_Statement (Loc));
2737             end if;
2738
2739             Rewrite (N, Expression (Fst));
2740
2741          elsif Nkind (N) = N_Identifier
2742            and then Nkind (Parent (Entity (N))) = N_Object_Declaration
2743          then
2744             --  The block assigns the result of the call to the temporary
2745
2746             Insert_After (Parent (Entity (N)), Blk);
2747
2748          elsif Nkind (Parent (N)) = N_Assignment_Statement
2749            and then Is_Entity_Name (Name (Parent (N)))
2750          then
2751             --  Replace assignment with the block
2752
2753             declare
2754                Original_Assignment : constant Node_Id := Parent (N);
2755
2756             begin
2757                --  Preserve the original assignment node to keep the complete
2758                --  assignment subtree consistent enough for Analyze_Assignment
2759                --  to proceed (specifically, the original Lhs node must still
2760                --  have an assignment statement as its parent).
2761
2762                --  We cannot rely on Original_Node to go back from the block
2763                --  node to the assignment node, because the assignment might
2764                --  already be a rewrite substitution.
2765
2766                Discard_Node (Relocate_Node (Original_Assignment));
2767                Rewrite (Original_Assignment, Blk);
2768             end;
2769
2770          elsif Nkind (Parent (N)) = N_Object_Declaration then
2771             Set_Expression (Parent (N), Empty);
2772             Insert_After (Parent (N), Blk);
2773          end if;
2774       end Rewrite_Function_Call;
2775
2776       ----------------------------
2777       -- Rewrite_Procedure_Call --
2778       ----------------------------
2779
2780       procedure Rewrite_Procedure_Call (N : Node_Id; Blk : Node_Id) is
2781          HSS  : constant Node_Id := Handled_Statement_Sequence (Blk);
2782       begin
2783          if Is_Empty_List (Declarations (Blk)) then
2784             Insert_List_After (N, Statements (HSS));
2785             Rewrite (N, Make_Null_Statement (Loc));
2786          else
2787             Rewrite (N, Blk);
2788          end if;
2789       end Rewrite_Procedure_Call;
2790
2791       -------------------------
2792       -- Formal_Is_Used_Once --
2793       ------------------------
2794
2795       function Formal_Is_Used_Once (Formal : Entity_Id) return Boolean is
2796          Use_Counter : Int := 0;
2797
2798          function Count_Uses (N : Node_Id) return Traverse_Result;
2799          --  Traverse the tree and count the uses of the formal parameter.
2800          --  In this case, for optimization purposes, we do not need to
2801          --  continue the traversal once more than one use is encountered.
2802
2803          ----------------
2804          -- Count_Uses --
2805          ----------------
2806
2807          function Count_Uses (N : Node_Id) return Traverse_Result is
2808          begin
2809             --  The original node is an identifier
2810
2811             if Nkind (N) = N_Identifier
2812               and then Present (Entity (N))
2813
2814                --  Original node's entity points to the one in the copied body
2815
2816               and then Nkind (Entity (N)) = N_Identifier
2817               and then Present (Entity (Entity (N)))
2818
2819                --  The entity of the copied node is the formal parameter
2820
2821               and then Entity (Entity (N)) = Formal
2822             then
2823                Use_Counter := Use_Counter + 1;
2824
2825                if Use_Counter > 1 then
2826
2827                   --  Denote more than one use and abandon the traversal
2828
2829                   Use_Counter := 2;
2830                   return Abandon;
2831
2832                end if;
2833             end if;
2834
2835             return OK;
2836          end Count_Uses;
2837
2838          procedure Count_Formal_Uses is new Traverse_Proc (Count_Uses);
2839
2840       --  Start of processing for Formal_Is_Used_Once
2841
2842       begin
2843          Count_Formal_Uses (Orig_Bod);
2844          return Use_Counter = 1;
2845       end Formal_Is_Used_Once;
2846
2847    --  Start of processing for Expand_Inlined_Call
2848
2849    begin
2850       --  Check for special case of To_Address call, and if so, just do an
2851       --  unchecked conversion instead of expanding the call. Not only is this
2852       --  more efficient, but it also avoids problem with order of elaboration
2853       --  when address clauses are inlined (address expression elaborated at
2854       --  wrong point).
2855
2856       if Subp = RTE (RE_To_Address) then
2857          Rewrite (N,
2858            Unchecked_Convert_To
2859             (RTE (RE_Address),
2860              Relocate_Node (First_Actual (N))));
2861          return;
2862       end if;
2863
2864       --  Check for an illegal attempt to inline a recursive procedure. If the
2865       --  subprogram has parameters this is detected when trying to supply a
2866       --  binding for parameters that already have one. For parameterless
2867       --  subprograms this must be done explicitly.
2868
2869       if In_Open_Scopes (Subp) then
2870          Error_Msg_N ("call to recursive subprogram cannot be inlined?", N);
2871          Set_Is_Inlined (Subp, False);
2872          return;
2873       end if;
2874
2875       if Nkind (Orig_Bod) = N_Defining_Identifier
2876         or else Nkind (Orig_Bod) = N_Defining_Operator_Symbol
2877       then
2878          --  Subprogram is a renaming_as_body. Calls appearing after the
2879          --  renaming can be replaced with calls to the renamed entity
2880          --  directly, because the subprograms are subtype conformant. If
2881          --  the renamed subprogram is an inherited operation, we must redo
2882          --  the expansion because implicit conversions may be needed.
2883
2884          Set_Name (N, New_Occurrence_Of (Orig_Bod, Loc));
2885
2886          if Present (Alias (Orig_Bod)) then
2887             Expand_Call (N);
2888          end if;
2889
2890          return;
2891       end if;
2892
2893       --  Use generic machinery to copy body of inlined subprogram, as if it
2894       --  were an instantiation, resetting source locations appropriately, so
2895       --  that nested inlined calls appear in the main unit.
2896
2897       Save_Env (Subp, Empty);
2898       Set_Copied_Sloc_For_Inlined_Body (N, Defining_Entity (Orig_Bod));
2899
2900       Bod := Copy_Generic_Node (Orig_Bod, Empty, Instantiating => True);
2901       Blk :=
2902         Make_Block_Statement (Loc,
2903           Declarations => Declarations (Bod),
2904           Handled_Statement_Sequence => Handled_Statement_Sequence (Bod));
2905
2906       if No (Declarations (Bod)) then
2907          Set_Declarations (Blk, New_List);
2908       end if;
2909
2910       --  If this is a derived function, establish the proper return type
2911
2912       if Present (Orig_Subp)
2913         and then Orig_Subp /= Subp
2914       then
2915          Ret_Type := Etype (Orig_Subp);
2916       else
2917          Ret_Type := Etype (Subp);
2918       end if;
2919
2920       --  Create temporaries for the actuals that are expressions, or that
2921       --  are scalars and require copying to preserve semantics.
2922
2923       F := First_Formal (Subp);
2924       A := First_Actual (N);
2925       while Present (F) loop
2926          if Present (Renamed_Object (F)) then
2927             Error_Msg_N ("cannot inline call to recursive subprogram", N);
2928             return;
2929          end if;
2930
2931          --  If the argument may be a controlling argument in a call within
2932          --  the inlined body, we must preserve its classwide nature to insure
2933          --  that dynamic dispatching take place subsequently. If the formal
2934          --  has a constraint it must be preserved to retain the semantics of
2935          --  the body.
2936
2937          if Is_Class_Wide_Type (Etype (F))
2938            or else (Is_Access_Type (Etype (F))
2939                       and then
2940                     Is_Class_Wide_Type (Designated_Type (Etype (F))))
2941          then
2942             Temp_Typ := Etype (F);
2943
2944          elsif Base_Type (Etype (F)) = Base_Type (Etype (A))
2945            and then Etype (F) /= Base_Type (Etype (F))
2946          then
2947             Temp_Typ := Etype (F);
2948
2949          else
2950             Temp_Typ := Etype (A);
2951          end if;
2952
2953          --  If the actual is a simple name or a literal, no need to
2954          --  create a temporary, object can be used directly.
2955
2956          if (Is_Entity_Name (A)
2957               and then
2958                (not Is_Scalar_Type (Etype (A))
2959                  or else Ekind (Entity (A)) = E_Enumeration_Literal))
2960
2961          --  When the actual is an identifier and the corresponding formal
2962          --  is used only once in the original body, the formal can be
2963          --  substituted directly with the actual parameter.
2964
2965            or else (Nkind (A) = N_Identifier
2966              and then Formal_Is_Used_Once (F))
2967
2968            or else Nkind (A) = N_Real_Literal
2969            or else Nkind (A) = N_Integer_Literal
2970            or else Nkind (A) = N_Character_Literal
2971          then
2972             if Etype (F) /= Etype (A) then
2973                Set_Renamed_Object
2974                 (F, Unchecked_Convert_To (Etype (F), Relocate_Node (A)));
2975             else
2976                Set_Renamed_Object (F, A);
2977             end if;
2978
2979          else
2980             Temp :=
2981               Make_Defining_Identifier (Loc,
2982                 Chars => New_Internal_Name ('C'));
2983
2984             --  If the actual for an in/in-out parameter is a view conversion,
2985             --  make it into an unchecked conversion, given that an untagged
2986             --  type conversion is not a proper object for a renaming.
2987
2988             --  In-out conversions that involve real conversions have already
2989             --  been transformed in Expand_Actuals.
2990
2991             if Nkind (A) = N_Type_Conversion
2992               and then Ekind (F) /= E_In_Parameter
2993             then
2994                New_A := Make_Unchecked_Type_Conversion (Loc,
2995                  Subtype_Mark => New_Occurrence_Of (Etype (F), Loc),
2996                  Expression   => Relocate_Node (Expression (A)));
2997
2998             elsif Etype (F) /= Etype (A) then
2999                New_A := Unchecked_Convert_To (Etype (F), Relocate_Node (A));
3000                Temp_Typ := Etype (F);
3001
3002             else
3003                New_A := Relocate_Node (A);
3004             end if;
3005
3006             Set_Sloc (New_A, Sloc (N));
3007
3008             if Ekind (F) = E_In_Parameter
3009               and then not Is_Limited_Type (Etype (A))
3010             then
3011                Decl :=
3012                  Make_Object_Declaration (Loc,
3013                    Defining_Identifier => Temp,
3014                    Constant_Present => True,
3015                    Object_Definition => New_Occurrence_Of (Temp_Typ, Loc),
3016                    Expression => New_A);
3017             else
3018                Decl :=
3019                  Make_Object_Renaming_Declaration (Loc,
3020                    Defining_Identifier => Temp,
3021                    Subtype_Mark        => New_Occurrence_Of (Temp_Typ, Loc),
3022                    Name                => New_A);
3023             end if;
3024
3025             Prepend (Decl, Declarations (Blk));
3026             Set_Renamed_Object (F, Temp);
3027          end if;
3028
3029          Next_Formal (F);
3030          Next_Actual (A);
3031       end loop;
3032
3033       --  Establish target of function call. If context is not assignment or
3034       --  declaration, create a temporary as a target. The declaration for
3035       --  the temporary may be subsequently optimized away if the body is a
3036       --  single expression, or if the left-hand side of the assignment is
3037       --  simple enough.
3038
3039       if Ekind (Subp) = E_Function then
3040          if Nkind (Parent (N)) = N_Assignment_Statement
3041            and then Is_Entity_Name (Name (Parent (N)))
3042          then
3043             Targ := Name (Parent (N));
3044
3045          else
3046             --  Replace call with temporary and create its declaration
3047
3048             Temp :=
3049               Make_Defining_Identifier (Loc, New_Internal_Name ('C'));
3050             Set_Is_Internal (Temp);
3051
3052             Decl :=
3053               Make_Object_Declaration (Loc,
3054                 Defining_Identifier => Temp,
3055                 Object_Definition =>
3056                   New_Occurrence_Of (Ret_Type, Loc));
3057
3058             Set_No_Initialization (Decl);
3059             Insert_Action (N, Decl);
3060             Rewrite (N, New_Occurrence_Of (Temp, Loc));
3061             Targ := Temp;
3062          end if;
3063       end if;
3064
3065       --  Traverse the tree and replace formals with actuals or their thunks.
3066       --  Attach block to tree before analysis and rewriting.
3067
3068       Replace_Formals (Blk);
3069       Set_Parent (Blk, N);
3070
3071       if not Comes_From_Source (Subp)
3072         or else Is_Predef
3073       then
3074          Reset_Slocs (Blk);
3075       end if;
3076
3077       if Present (Exit_Lab) then
3078
3079          --  If the body was a single expression, the single return statement
3080          --  and the corresponding label are useless.
3081
3082          if Num_Ret = 1
3083            and then
3084              Nkind (Last (Statements (Handled_Statement_Sequence (Blk)))) =
3085                N_Goto_Statement
3086          then
3087             Remove (Last (Statements (Handled_Statement_Sequence (Blk))));
3088          else
3089             Append (Lab_Decl, (Declarations (Blk)));
3090             Append (Exit_Lab, Statements (Handled_Statement_Sequence (Blk)));
3091          end if;
3092       end if;
3093
3094       --  Analyze Blk with In_Inlined_Body set, to avoid spurious errors on
3095       --  conflicting private views that Gigi would ignore. If this is
3096       --  predefined unit, analyze with checks off, as is done in the non-
3097       --  inlined run-time units.
3098
3099       declare
3100          I_Flag : constant Boolean := In_Inlined_Body;
3101
3102       begin
3103          In_Inlined_Body := True;
3104
3105          if Is_Predef then
3106             declare
3107                Style : constant Boolean := Style_Check;
3108             begin
3109                Style_Check := False;
3110                Analyze (Blk, Suppress => All_Checks);
3111                Style_Check := Style;
3112             end;
3113
3114          else
3115             Analyze (Blk);
3116          end if;
3117
3118          In_Inlined_Body := I_Flag;
3119       end;
3120
3121       if Ekind (Subp) = E_Procedure then
3122          Rewrite_Procedure_Call (N, Blk);
3123       else
3124          Rewrite_Function_Call (N, Blk);
3125       end if;
3126
3127       Restore_Env;
3128
3129       --  Cleanup mapping between formals and actuals for other expansions
3130
3131       F := First_Formal (Subp);
3132       while Present (F) loop
3133          Set_Renamed_Object (F, Empty);
3134          Next_Formal (F);
3135       end loop;
3136    end Expand_Inlined_Call;
3137
3138    ----------------------------
3139    -- Expand_N_Function_Call --
3140    ----------------------------
3141
3142    procedure Expand_N_Function_Call (N : Node_Id) is
3143       Typ   : constant Entity_Id := Etype (N);
3144
3145       function Returned_By_Reference return Boolean;
3146       --  If the return type is returned through the secondary stack. that is
3147       --  by reference, we don't want to create a temp to force stack checking.
3148       --  Shouldn't this function be moved to exp_util???
3149
3150       function Rhs_Of_Assign_Or_Decl (N : Node_Id) return Boolean;
3151       --  If the call is the right side of an assignment or the expression in
3152       --  an object declaration, we don't need to create a temp as the left
3153       --  side will already trigger stack checking if necessary.
3154       --
3155       --  If the call is a component in an extension aggregate, it will be
3156       --  expanded into assignments as well, so no temporary is needed. This
3157       --  also solves the problem of functions returning types with unknown
3158       --  discriminants, where it is not possible to declare an object of the
3159       --  type altogether.
3160
3161       ---------------------------
3162       -- Returned_By_Reference --
3163       ---------------------------
3164
3165       function Returned_By_Reference return Boolean is
3166          S : Entity_Id;
3167
3168       begin
3169          if Is_Return_By_Reference_Type (Typ) then
3170             return True;
3171
3172          elsif Nkind (Parent (N)) /= N_Return_Statement then
3173             return False;
3174
3175          elsif Requires_Transient_Scope (Typ) then
3176
3177             --  Verify that the return type of the enclosing function has the
3178             --  same constrained status as that of the expression.
3179
3180             S := Current_Scope;
3181             while Ekind (S) /= E_Function loop
3182                S := Scope (S);
3183             end loop;
3184
3185             return Is_Constrained (Typ) = Is_Constrained (Etype (S));
3186          else
3187             return False;
3188          end if;
3189       end Returned_By_Reference;
3190
3191       ---------------------------
3192       -- Rhs_Of_Assign_Or_Decl --
3193       ---------------------------
3194
3195       function Rhs_Of_Assign_Or_Decl (N : Node_Id) return Boolean is
3196       begin
3197          if (Nkind (Parent (N)) = N_Assignment_Statement
3198                and then Expression (Parent (N)) = N)
3199            or else
3200              (Nkind (Parent (N)) = N_Qualified_Expression
3201                 and then Nkind (Parent (Parent (N))) = N_Assignment_Statement
3202                   and then Expression (Parent (Parent (N))) = Parent (N))
3203            or else
3204              (Nkind (Parent (N)) = N_Object_Declaration
3205                 and then Expression (Parent (N)) = N)
3206            or else
3207              (Nkind (Parent (N)) = N_Component_Association
3208                 and then Expression (Parent (N)) = N
3209                   and then Nkind (Parent (Parent (N))) = N_Aggregate
3210                     and then Rhs_Of_Assign_Or_Decl (Parent (Parent (N))))
3211            or else
3212              (Nkind (Parent (N)) = N_Extension_Aggregate
3213                and then Is_Private_Type (Etype (Typ)))
3214          then
3215             return True;
3216          else
3217             return False;
3218          end if;
3219       end Rhs_Of_Assign_Or_Decl;
3220
3221    --  Start of processing for Expand_N_Function_Call
3222
3223    begin
3224       --  A special check. If stack checking is enabled, and the return type
3225       --  might generate a large temporary, and the call is not the right side
3226       --  of an assignment, then generate an explicit temporary. We do this
3227       --  because otherwise gigi may generate a large temporary on the fly and
3228       --  this can cause trouble with stack checking.
3229
3230       --  This is unecessary if the call is the expression in an object
3231       --  declaration, or if it appears outside of any library unit. This can
3232       --  only happen if it appears as an actual in a library-level instance,
3233       --  in which case a temporary will be generated for it once the instance
3234       --  itself is installed.
3235
3236       if May_Generate_Large_Temp (Typ)
3237         and then not Rhs_Of_Assign_Or_Decl (N)
3238         and then not Returned_By_Reference
3239         and then Current_Scope /= Standard_Standard
3240       then
3241          if Stack_Checking_Enabled then
3242
3243             --  Note: it might be thought that it would be OK to use a call to
3244             --  Force_Evaluation here, but that's not good enough, because
3245             --  that can results in a 'Reference construct that may still need
3246             --  a temporary.
3247
3248             declare
3249                Loc      : constant Source_Ptr := Sloc (N);
3250                Temp_Obj : constant Entity_Id :=
3251                             Make_Defining_Identifier (Loc,
3252                               Chars => New_Internal_Name ('F'));
3253                Temp_Typ : Entity_Id := Typ;
3254                Decl     : Node_Id;
3255                A        : Node_Id;
3256                F        : Entity_Id;
3257                Proc     : Entity_Id;
3258
3259             begin
3260                if Is_Tagged_Type (Typ)
3261                  and then Present (Controlling_Argument (N))
3262                then
3263                   if Nkind (Parent (N)) /= N_Procedure_Call_Statement
3264                     and then Nkind (Parent (N)) /= N_Function_Call
3265                   then
3266                      --  If this is a tag-indeterminate call, the object must
3267                      --  be classwide.
3268
3269                      if Is_Tag_Indeterminate (N) then
3270                         Temp_Typ := Class_Wide_Type (Typ);
3271                      end if;
3272
3273                   else
3274                      --  If this is a dispatching call that is itself the
3275                      --  controlling argument of an enclosing call, the
3276                      --  nominal subtype of the object that replaces it must
3277                      --  be classwide, so that dispatching will take place
3278                      --  properly. If it is not a controlling argument, the
3279                      --  object is not classwide.
3280
3281                      Proc := Entity (Name (Parent (N)));
3282
3283                      F    := First_Formal (Proc);
3284                      A    := First_Actual (Parent (N));
3285                      while A /= N loop
3286                         Next_Formal (F);
3287                         Next_Actual (A);
3288                      end loop;
3289
3290                      if Is_Controlling_Formal (F) then
3291                         Temp_Typ := Class_Wide_Type (Typ);
3292                      end if;
3293                   end if;
3294                end if;
3295
3296                Decl :=
3297                  Make_Object_Declaration (Loc,
3298                    Defining_Identifier => Temp_Obj,
3299                    Object_Definition   => New_Occurrence_Of (Temp_Typ, Loc),
3300                    Constant_Present    => True,
3301                    Expression          => Relocate_Node (N));
3302                Set_Assignment_OK (Decl);
3303
3304                Insert_Actions (N, New_List (Decl));
3305                Rewrite (N, New_Occurrence_Of (Temp_Obj, Loc));
3306             end;
3307
3308          else
3309             --  If stack-checking is not enabled, increment serial number
3310             --  for internal names, so that subsequent symbols are consistent
3311             --  with and without stack-checking.
3312
3313             Synchronize_Serial_Number;
3314
3315             --  Now we can expand the call with consistent symbol names
3316
3317             Expand_Call (N);
3318          end if;
3319
3320       --  Normal case, expand the call
3321
3322       else
3323          Expand_Call (N);
3324       end if;
3325    end Expand_N_Function_Call;
3326
3327    ---------------------------------------
3328    -- Expand_N_Procedure_Call_Statement --
3329    ---------------------------------------
3330
3331    procedure Expand_N_Procedure_Call_Statement (N : Node_Id) is
3332    begin
3333       Expand_Call (N);
3334    end Expand_N_Procedure_Call_Statement;
3335
3336    ------------------------------
3337    -- Expand_N_Subprogram_Body --
3338    ------------------------------
3339
3340    --  Add poll call if ATC polling is enabled, unless the body will be
3341    --  inlined by the back-end.
3342
3343    --  Add return statement if last statement in body is not a return statement
3344    --  (this makes things easier on Gigi which does not want to have to handle
3345    --  a missing return).
3346
3347    --  Add call to Activate_Tasks if body is a task activator
3348
3349    --  Deal with possible detection of infinite recursion
3350
3351    --  Eliminate body completely if convention stubbed
3352
3353    --  Encode entity names within body, since we will not need to reference
3354    --  these entities any longer in the front end.
3355
3356    --  Initialize scalar out parameters if Initialize/Normalize_Scalars
3357
3358    --  Reset Pure indication if any parameter has root type System.Address
3359
3360    --  Wrap thread body
3361
3362    procedure Expand_N_Subprogram_Body (N : Node_Id) is
3363       Loc      : constant Source_Ptr := Sloc (N);
3364       H        : constant Node_Id    := Handled_Statement_Sequence (N);
3365       Body_Id  : Entity_Id;
3366       Spec_Id  : Entity_Id;
3367       Except_H : Node_Id;
3368       Scop     : Entity_Id;
3369       Dec      : Node_Id;
3370       Next_Op  : Node_Id;
3371       L        : List_Id;
3372
3373       procedure Add_Return (S : List_Id);
3374       --  Append a return statement to the statement sequence S if the last
3375       --  statement is not already a return or a goto statement. Note that
3376       --  the latter test is not critical, it does not matter if we add a
3377       --  few extra returns, since they get eliminated anyway later on.
3378
3379       procedure Expand_Thread_Body;
3380       --  Perform required expansion of a thread body
3381
3382       ----------------
3383       -- Add_Return --
3384       ----------------
3385
3386       procedure Add_Return (S : List_Id) is
3387       begin
3388          if not Is_Transfer (Last (S)) then
3389
3390             --  The source location for the return is the end label
3391             --  of the procedure in all cases. This is a bit odd when
3392             --  there are exception handlers, but not much else we can do.
3393
3394             Append_To (S, Make_Return_Statement (Sloc (End_Label (H))));
3395          end if;
3396       end Add_Return;
3397
3398       ------------------------
3399       -- Expand_Thread_Body --
3400       ------------------------
3401
3402       --  The required expansion of a thread body is as follows
3403
3404       --  procedure <thread body procedure name> is
3405
3406       --    _Secondary_Stack : aliased
3407       --       Storage_Elements.Storage_Array
3408       --         (1 .. Storage_Offset (Sec_Stack_Size));
3409       --    for _Secondary_Stack'Alignment use Standard'Maximum_Alignment;
3410
3411       --    _Process_ATSD : aliased System.Threads.ATSD;
3412
3413       --  begin
3414       --     System.Threads.Thread_Body_Enter;
3415       --       (_Secondary_Stack'Address,
3416       --        _Secondary_Stack'Length,
3417       --        _Process_ATSD'Address);
3418
3419       --     declare
3420       --        <user declarations>
3421       --     begin
3422       --        <user statements>
3423       --     <user exception handlers>
3424       --     end;
3425
3426       --    System.Threads.Thread_Body_Leave;
3427
3428       --  exception
3429       --     when E : others =>
3430       --       System.Threads.Thread_Body_Exceptional_Exit (E);
3431       --  end;
3432
3433       --  Note the exception handler is omitted if pragma Restriction
3434       --  No_Exception_Handlers is currently active.
3435
3436       procedure Expand_Thread_Body is
3437          User_Decls    : constant List_Id := Declarations (N);
3438          Sec_Stack_Len : Node_Id;
3439
3440          TB_Pragma  : constant Node_Id :=
3441                         Get_Rep_Pragma (Spec_Id, Name_Thread_Body);
3442
3443          Ent_SS   : Entity_Id;
3444          Ent_ATSD : Entity_Id;
3445          Ent_EO   : Entity_Id;
3446
3447          Decl_SS   : Node_Id;
3448          Decl_ATSD : Node_Id;
3449
3450          Excep_Handlers : List_Id;
3451
3452       begin
3453          New_Scope (Spec_Id);
3454
3455          --  Get proper setting for secondary stack size
3456
3457          if List_Length (Pragma_Argument_Associations (TB_Pragma)) = 2 then
3458             Sec_Stack_Len :=
3459               Expression (Last (Pragma_Argument_Associations (TB_Pragma)));
3460          else
3461             Sec_Stack_Len :=
3462               New_Occurrence_Of (RTE (RE_Default_Secondary_Stack_Size), Loc);
3463          end if;
3464
3465          Sec_Stack_Len := Convert_To (RTE (RE_Storage_Offset), Sec_Stack_Len);
3466
3467          --  Build and set declarations for the wrapped thread body
3468
3469          Ent_SS   := Make_Defining_Identifier (Loc, Name_uSecondary_Stack);
3470          Ent_ATSD := Make_Defining_Identifier (Loc, Name_uProcess_ATSD);
3471
3472          Decl_SS :=
3473            Make_Object_Declaration (Loc,
3474              Defining_Identifier => Ent_SS,
3475              Aliased_Present     => True,
3476              Object_Definition   =>
3477                Make_Subtype_Indication (Loc,
3478                  Subtype_Mark =>
3479                    New_Occurrence_Of (RTE (RE_Storage_Array), Loc),
3480                  Constraint   =>
3481                    Make_Index_Or_Discriminant_Constraint (Loc,
3482                      Constraints => New_List (
3483                        Make_Range (Loc,
3484                          Low_Bound  => Make_Integer_Literal (Loc, 1),
3485                          High_Bound => Sec_Stack_Len)))));
3486
3487          Decl_ATSD :=
3488            Make_Object_Declaration (Loc,
3489              Defining_Identifier => Ent_ATSD,
3490              Aliased_Present     => True,
3491              Object_Definition   => New_Occurrence_Of (RTE (RE_ATSD), Loc));
3492
3493          Set_Declarations (N, New_List (Decl_SS, Decl_ATSD));
3494          Analyze (Decl_SS);
3495          Analyze (Decl_ATSD);
3496          Set_Alignment (Ent_SS, UI_From_Int (Maximum_Alignment));
3497
3498          --  Create new exception handler
3499
3500          if Restriction_Active (No_Exception_Handlers) then
3501             Excep_Handlers := No_List;
3502
3503          else
3504             Check_Restriction (No_Exception_Handlers, N);
3505
3506             Ent_EO := Make_Defining_Identifier (Loc, Name_uE);
3507
3508             Excep_Handlers := New_List (
3509               Make_Exception_Handler (Loc,
3510                 Choice_Parameter => Ent_EO,
3511                 Exception_Choices => New_List (
3512                   Make_Others_Choice (Loc)),
3513                 Statements => New_List (
3514                   Make_Procedure_Call_Statement (Loc,
3515                     Name =>
3516                       New_Occurrence_Of
3517                         (RTE (RE_Thread_Body_Exceptional_Exit), Loc),
3518                     Parameter_Associations => New_List (
3519                       New_Occurrence_Of (Ent_EO, Loc))))));
3520          end if;
3521
3522          --  Now build new handled statement sequence and analyze it
3523
3524          Set_Handled_Statement_Sequence (N,
3525            Make_Handled_Sequence_Of_Statements (Loc,
3526              Statements => New_List (
3527
3528                Make_Procedure_Call_Statement (Loc,
3529                  Name => New_Occurrence_Of (RTE (RE_Thread_Body_Enter), Loc),
3530                  Parameter_Associations => New_List (
3531
3532                    Make_Attribute_Reference (Loc,
3533                      Prefix => New_Occurrence_Of (Ent_SS, Loc),
3534                      Attribute_Name => Name_Address),
3535
3536                    Make_Attribute_Reference (Loc,
3537                      Prefix => New_Occurrence_Of (Ent_SS, Loc),
3538                      Attribute_Name => Name_Length),
3539
3540                    Make_Attribute_Reference (Loc,
3541                      Prefix => New_Occurrence_Of (Ent_ATSD, Loc),
3542                      Attribute_Name => Name_Address))),
3543
3544                Make_Block_Statement (Loc,
3545                  Declarations => User_Decls,
3546                  Handled_Statement_Sequence => H),
3547
3548                Make_Procedure_Call_Statement (Loc,
3549                  Name => New_Occurrence_Of (RTE (RE_Thread_Body_Leave), Loc))),
3550
3551              Exception_Handlers => Excep_Handlers));
3552
3553          Analyze (Handled_Statement_Sequence (N));
3554          End_Scope;
3555       end Expand_Thread_Body;
3556
3557    --  Start of processing for Expand_N_Subprogram_Body
3558
3559    begin
3560       --  Set L to either the list of declarations if present, or
3561       --  to the list of statements if no declarations are present.
3562       --  This is used to insert new stuff at the start.
3563
3564       if Is_Non_Empty_List (Declarations (N)) then
3565          L := Declarations (N);
3566       else
3567          L := Statements (Handled_Statement_Sequence (N));
3568       end if;
3569
3570       --  Find entity for subprogram
3571
3572       Body_Id := Defining_Entity (N);
3573
3574       if Present (Corresponding_Spec (N)) then
3575          Spec_Id := Corresponding_Spec (N);
3576       else
3577          Spec_Id := Body_Id;
3578       end if;
3579
3580       --  Need poll on entry to subprogram if polling enabled. We only
3581       --  do this for non-empty subprograms, since it does not seem
3582       --  necessary to poll for a dummy null subprogram. Do not add polling
3583       --  point if calls to this subprogram will be inlined by the back-end,
3584       --  to avoid repeated polling points in nested inlinings.
3585
3586       if Is_Non_Empty_List (L) then
3587          if Is_Inlined (Spec_Id)
3588            and then Front_End_Inlining
3589            and then Optimization_Level > 1
3590          then
3591             null;
3592          else
3593             Generate_Poll_Call (First (L));
3594          end if;
3595       end if;
3596
3597       --  If this is a Pure function which has any parameters whose root
3598       --  type is System.Address, reset the Pure indication, since it will
3599       --  likely cause incorrect code to be generated as the parameter is
3600       --  probably a pointer, and the fact that the same pointer is passed
3601       --  does not mean that the same value is being referenced.
3602
3603       --  Note that if the programmer gave an explicit Pure_Function pragma,
3604       --  then we believe the programmer, and leave the subprogram Pure.
3605
3606       --  This code should probably be at the freeze point, so that it
3607       --  happens even on a -gnatc (or more importantly -gnatt) compile
3608       --  so that the semantic tree has Is_Pure set properly ???
3609
3610       if Is_Pure (Spec_Id)
3611         and then Is_Subprogram (Spec_Id)
3612         and then not Has_Pragma_Pure_Function (Spec_Id)
3613       then
3614          declare
3615             F : Entity_Id;
3616
3617          begin
3618             F := First_Formal (Spec_Id);
3619             while Present (F) loop
3620                if Is_Descendent_Of_Address (Etype (F)) then
3621                   Set_Is_Pure (Spec_Id, False);
3622
3623                   if Spec_Id /= Body_Id then
3624                      Set_Is_Pure (Body_Id, False);
3625                   end if;
3626
3627                   exit;
3628                end if;
3629
3630                Next_Formal (F);
3631             end loop;
3632          end;
3633       end if;
3634
3635       --  Initialize any scalar OUT args if Initialize/Normalize_Scalars
3636
3637       if Init_Or_Norm_Scalars and then Is_Subprogram (Spec_Id) then
3638          declare
3639             F : Entity_Id;
3640             V : constant Boolean := Validity_Checks_On;
3641
3642          begin
3643             --  We turn off validity checking, since we do not want any
3644             --  check on the initializing value itself (which we know
3645             --  may well be invalid!)
3646
3647             Validity_Checks_On := False;
3648
3649             --  Loop through formals
3650
3651             F := First_Formal (Spec_Id);
3652             while Present (F) loop
3653                if Is_Scalar_Type (Etype (F))
3654                  and then Ekind (F) = E_Out_Parameter
3655                then
3656                   Insert_Before_And_Analyze (First (L),
3657                     Make_Assignment_Statement (Loc,
3658                       Name => New_Occurrence_Of (F, Loc),
3659                       Expression => Get_Simple_Init_Val (Etype (F), Loc)));
3660                end if;
3661
3662                Next_Formal (F);
3663             end loop;
3664
3665             Validity_Checks_On := V;
3666          end;
3667       end if;
3668
3669       Scop := Scope (Spec_Id);
3670
3671       --  Add discriminal renamings to protected subprograms. Install new
3672       --  discriminals for expansion of the next subprogram of this protected
3673       --  type, if any.
3674
3675       if Is_List_Member (N)
3676         and then Present (Parent (List_Containing (N)))
3677         and then Nkind (Parent (List_Containing (N))) = N_Protected_Body
3678       then
3679          Add_Discriminal_Declarations
3680            (Declarations (N), Scop, Name_uObject, Loc);
3681          Add_Private_Declarations (Declarations (N), Scop, Name_uObject, Loc);
3682
3683          --  Associate privals and discriminals with the next protected
3684          --  operation body to be expanded. These are used to expand references
3685          --  to private data objects and discriminants, respectively.
3686
3687          Next_Op := Next_Protected_Operation (N);
3688
3689          if Present (Next_Op) then
3690             Dec := Parent (Base_Type (Scop));
3691             Set_Privals (Dec, Next_Op, Loc);
3692             Set_Discriminals (Dec);
3693          end if;
3694       end if;
3695
3696       --  Clear out statement list for stubbed procedure
3697
3698       if Present (Corresponding_Spec (N)) then
3699          Set_Elaboration_Flag (N, Spec_Id);
3700
3701          if Convention (Spec_Id) = Convention_Stubbed
3702            or else Is_Eliminated (Spec_Id)
3703          then
3704             Set_Declarations (N, Empty_List);
3705             Set_Handled_Statement_Sequence (N,
3706               Make_Handled_Sequence_Of_Statements (Loc,
3707                 Statements => New_List (
3708                   Make_Null_Statement (Loc))));
3709             return;
3710          end if;
3711       end if;
3712
3713       --  Returns_By_Ref flag is normally set when the subprogram is frozen
3714       --  but subprograms with no specs are not frozen.
3715
3716       declare
3717          Typ  : constant Entity_Id := Etype (Spec_Id);
3718          Utyp : constant Entity_Id := Underlying_Type (Typ);
3719
3720       begin
3721          if not Acts_As_Spec (N)
3722            and then Nkind (Parent (Parent (Spec_Id))) /=
3723              N_Subprogram_Body_Stub
3724          then
3725             null;
3726
3727          elsif Is_Return_By_Reference_Type (Typ) then
3728             Set_Returns_By_Ref (Spec_Id);
3729
3730          elsif Present (Utyp) and then Controlled_Type (Utyp) then
3731             Set_Returns_By_Ref (Spec_Id);
3732          end if;
3733       end;
3734
3735       --  For a procedure, we add a return for all possible syntactic ends
3736       --  of the subprogram. Note that reanalysis is not necessary in this
3737       --  case since it would require a lot of work and accomplish nothing.
3738
3739       if Ekind (Spec_Id) = E_Procedure
3740         or else Ekind (Spec_Id) = E_Generic_Procedure
3741       then
3742          Add_Return (Statements (H));
3743
3744          if Present (Exception_Handlers (H)) then
3745             Except_H := First_Non_Pragma (Exception_Handlers (H));
3746             while Present (Except_H) loop
3747                Add_Return (Statements (Except_H));
3748                Next_Non_Pragma (Except_H);
3749             end loop;
3750          end if;
3751
3752       --  For a function, we must deal with the case where there is at least
3753       --  one missing return. What we do is to wrap the entire body of the
3754       --  function in a block:
3755
3756       --    begin
3757       --      ...
3758       --    end;
3759
3760       --  becomes
3761
3762       --    begin
3763       --       begin
3764       --          ...
3765       --       end;
3766
3767       --       raise Program_Error;
3768       --    end;
3769
3770       --  This approach is necessary because the raise must be signalled
3771       --  to the caller, not handled by any local handler (RM 6.4(11)).
3772
3773       --  Note: we do not need to analyze the constructed sequence here,
3774       --  since it has no handler, and an attempt to analyze the handled
3775       --  statement sequence twice is risky in various ways (e.g. the
3776       --  issue of expanding cleanup actions twice).
3777
3778       elsif Has_Missing_Return (Spec_Id) then
3779          declare
3780             Hloc : constant Source_Ptr := Sloc (H);
3781             Blok : constant Node_Id    :=
3782                      Make_Block_Statement (Hloc,
3783                        Handled_Statement_Sequence => H);
3784             Rais : constant Node_Id    :=
3785                      Make_Raise_Program_Error (Hloc,
3786                        Reason => PE_Missing_Return);
3787
3788          begin
3789             Set_Handled_Statement_Sequence (N,
3790               Make_Handled_Sequence_Of_Statements (Hloc,
3791                 Statements => New_List (Blok, Rais)));
3792
3793             New_Scope (Spec_Id);
3794             Analyze (Blok);
3795             Analyze (Rais);
3796             Pop_Scope;
3797          end;
3798       end if;
3799
3800       --  If subprogram contains a parameterless recursive call, then we may
3801       --  have an infinite recursion, so see if we can generate code to check
3802       --  for this possibility if storage checks are not suppressed.
3803
3804       if Ekind (Spec_Id) = E_Procedure
3805         and then Has_Recursive_Call (Spec_Id)
3806         and then not Storage_Checks_Suppressed (Spec_Id)
3807       then
3808          Detect_Infinite_Recursion (N, Spec_Id);
3809       end if;
3810
3811       --  Finally, if we are in Normalize_Scalars mode, then any scalar out
3812       --  parameters must be initialized to the appropriate default value.
3813
3814       if Ekind (Spec_Id) = E_Procedure and then Normalize_Scalars then
3815          declare
3816             Floc   : Source_Ptr;
3817             Formal : Entity_Id;
3818             Stm    : Node_Id;
3819
3820          begin
3821             Formal := First_Formal (Spec_Id);
3822             while Present (Formal) loop
3823                Floc := Sloc (Formal);
3824
3825                if Ekind (Formal) = E_Out_Parameter
3826                  and then Is_Scalar_Type (Etype (Formal))
3827                then
3828                   Stm :=
3829                     Make_Assignment_Statement (Floc,
3830                       Name => New_Occurrence_Of (Formal, Floc),
3831                       Expression =>
3832                         Get_Simple_Init_Val (Etype (Formal), Floc));
3833                   Prepend (Stm, Declarations (N));
3834                   Analyze (Stm);
3835                end if;
3836
3837                Next_Formal (Formal);
3838             end loop;
3839          end;
3840       end if;
3841
3842       --  Deal with thread body
3843
3844       if Is_Thread_Body (Spec_Id) then
3845          Expand_Thread_Body;
3846       end if;
3847
3848       --  Set to encode entity names in package body before gigi is called
3849
3850       Qualify_Entity_Names (N);
3851    end Expand_N_Subprogram_Body;
3852
3853    -----------------------------------
3854    -- Expand_N_Subprogram_Body_Stub --
3855    -----------------------------------
3856
3857    procedure Expand_N_Subprogram_Body_Stub (N : Node_Id) is
3858    begin
3859       if Present (Corresponding_Body (N)) then
3860          Expand_N_Subprogram_Body (
3861            Unit_Declaration_Node (Corresponding_Body (N)));
3862       end if;
3863    end Expand_N_Subprogram_Body_Stub;
3864
3865    -------------------------------------
3866    -- Expand_N_Subprogram_Declaration --
3867    -------------------------------------
3868
3869    --  If the declaration appears within a protected body, it is a private
3870    --  operation of the protected type. We must create the corresponding
3871    --  protected subprogram an associated formals. For a normal protected
3872    --  operation, this is done when expanding the protected type declaration.
3873
3874    --  If the declaration is for a null procedure, emit null body
3875
3876    procedure Expand_N_Subprogram_Declaration (N : Node_Id) is
3877       Loc       : constant Source_Ptr := Sloc (N);
3878       Subp      : constant Entity_Id  := Defining_Entity (N);
3879       Scop      : constant Entity_Id  := Scope (Subp);
3880       Prot_Decl : Node_Id;
3881       Prot_Bod  : Node_Id;
3882       Prot_Id   : Entity_Id;
3883
3884    begin
3885       --  Deal with case of protected subprogram. Do not generate protected
3886       --  operation if operation is flagged as eliminated.
3887
3888       if Is_List_Member (N)
3889         and then Present (Parent (List_Containing (N)))
3890         and then Nkind (Parent (List_Containing (N))) = N_Protected_Body
3891         and then Is_Protected_Type (Scop)
3892       then
3893          if No (Protected_Body_Subprogram (Subp))
3894            and then not Is_Eliminated (Subp)
3895          then
3896             Prot_Decl :=
3897               Make_Subprogram_Declaration (Loc,
3898                 Specification =>
3899                   Build_Protected_Sub_Specification
3900                     (N, Scop, Unprotected_Mode));
3901
3902             --  The protected subprogram is declared outside of the protected
3903             --  body. Given that the body has frozen all entities so far, we
3904             --  analyze the subprogram and perform freezing actions explicitly.
3905             --  If the body is a subunit, the insertion point is before the
3906             --  stub in the parent.
3907
3908             Prot_Bod := Parent (List_Containing (N));
3909
3910             if Nkind (Parent (Prot_Bod)) = N_Subunit then
3911                Prot_Bod := Corresponding_Stub (Parent (Prot_Bod));
3912             end if;
3913
3914             Insert_Before (Prot_Bod, Prot_Decl);
3915             Prot_Id := Defining_Unit_Name (Specification (Prot_Decl));
3916
3917             New_Scope (Scope (Scop));
3918             Analyze (Prot_Decl);
3919             Create_Extra_Formals (Prot_Id);
3920             Set_Protected_Body_Subprogram (Subp, Prot_Id);
3921             Pop_Scope;
3922          end if;
3923
3924       elsif Nkind (Specification (N)) = N_Procedure_Specification
3925         and then Null_Present (Specification (N))
3926       then
3927          declare
3928             Bod : constant Node_Id :=
3929                     Make_Subprogram_Body (Loc,
3930                       Specification =>
3931                         New_Copy_Tree (Specification (N)),
3932                       Declarations => New_List,
3933                      Handled_Statement_Sequence =>
3934                         Make_Handled_Sequence_Of_Statements (Loc,
3935                           Statements => New_List (Make_Null_Statement (Loc))));
3936          begin
3937             Set_Body_To_Inline (N, Bod);
3938             Insert_After (N, Bod);
3939             Analyze (Bod);
3940
3941             --  Corresponding_Spec isn't being set by Analyze_Subprogram_Body,
3942             --  evidently because Set_Has_Completion is called earlier for null
3943             --  procedures in Analyze_Subprogram_Declaration, so we force its
3944             --  setting here. If the setting of Has_Completion is not set
3945             --  earlier, then it can result in missing body errors if other
3946             --  errors were already reported (since expansion is turned off).
3947
3948             --  Should creation of the empty body be moved to the analyzer???
3949
3950             Set_Corresponding_Spec (Bod, Defining_Entity (Specification (N)));
3951          end;
3952       end if;
3953    end Expand_N_Subprogram_Declaration;
3954
3955    ---------------------------------------
3956    -- Expand_Protected_Object_Reference --
3957    ---------------------------------------
3958
3959    function Expand_Protected_Object_Reference
3960      (N    : Node_Id;
3961       Scop : Entity_Id)
3962      return Node_Id
3963    is
3964       Loc   : constant Source_Ptr := Sloc (N);
3965       Corr  : Entity_Id;
3966       Rec   : Node_Id;
3967       Param : Entity_Id;
3968       Proc  : Entity_Id;
3969
3970    begin
3971       Rec := Make_Identifier (Loc, Name_uObject);
3972       Set_Etype (Rec, Corresponding_Record_Type (Scop));
3973
3974       --  Find enclosing protected operation, and retrieve its first parameter,
3975       --  which denotes the enclosing protected object. If the enclosing
3976       --  operation is an entry, we are immediately within the protected body,
3977       --  and we can retrieve the object from the service entries procedure. A
3978       --  barrier function has has the same signature as an entry. A barrier
3979       --  function is compiled within the protected object, but unlike
3980       --  protected operations its never needs locks, so that its protected
3981       --  body subprogram points to itself.
3982
3983       Proc := Current_Scope;
3984       while Present (Proc)
3985         and then Scope (Proc) /= Scop
3986       loop
3987          Proc := Scope (Proc);
3988       end loop;
3989
3990       Corr := Protected_Body_Subprogram (Proc);
3991
3992       if No (Corr) then
3993
3994          --  Previous error left expansion incomplete.
3995          --  Nothing to do on this call.
3996
3997          return Empty;
3998       end if;
3999
4000       Param :=
4001         Defining_Identifier
4002           (First (Parameter_Specifications (Parent (Corr))));
4003
4004       if Is_Subprogram (Proc)
4005         and then Proc /= Corr
4006       then
4007          --  Protected function or procedure
4008
4009          Set_Entity (Rec, Param);
4010
4011          --  Rec is a reference to an entity which will not be in scope when
4012          --  the call is reanalyzed, and needs no further analysis.
4013
4014          Set_Analyzed (Rec);
4015
4016       else
4017          --  Entry or barrier function for entry body. The first parameter of
4018          --  the entry body procedure is pointer to the object. We create a
4019          --  local variable of the proper type, duplicating what is done to
4020          --  define _object later on.
4021
4022          declare
4023             Decls : List_Id;
4024             Obj_Ptr : constant Entity_Id :=  Make_Defining_Identifier (Loc,
4025                                                Chars =>
4026                                                  New_Internal_Name ('T'));
4027
4028          begin
4029             Decls := New_List (
4030               Make_Full_Type_Declaration (Loc,
4031                 Defining_Identifier => Obj_Ptr,
4032                   Type_Definition =>
4033                      Make_Access_To_Object_Definition (Loc,
4034                        Subtype_Indication =>
4035                          New_Reference_To
4036                       (Corresponding_Record_Type (Scop), Loc))));
4037
4038             Insert_Actions (N, Decls);
4039             Insert_Actions (N, Freeze_Entity (Obj_Ptr, Sloc (N)));
4040
4041             Rec :=
4042               Make_Explicit_Dereference (Loc,
4043                 Unchecked_Convert_To (Obj_Ptr,
4044                   New_Occurrence_Of (Param, Loc)));
4045
4046             --  Analyze new actual. Other actuals in calls are already analyzed
4047             --  and the list of actuals is not renalyzed after rewriting.
4048
4049             Set_Parent (Rec, N);
4050             Analyze (Rec);
4051          end;
4052       end if;
4053
4054       return Rec;
4055    end Expand_Protected_Object_Reference;
4056
4057    --------------------------------------
4058    -- Expand_Protected_Subprogram_Call --
4059    --------------------------------------
4060
4061    procedure Expand_Protected_Subprogram_Call
4062      (N    : Node_Id;
4063       Subp : Entity_Id;
4064       Scop : Entity_Id)
4065    is
4066       Rec   : Node_Id;
4067
4068    begin
4069       --  If the protected object is not an enclosing scope, this is
4070       --  an inter-object function call. Inter-object procedure
4071       --  calls are expanded by Exp_Ch9.Build_Simple_Entry_Call.
4072       --  The call is intra-object only if the subprogram being
4073       --  called is in the protected body being compiled, and if the
4074       --  protected object in the call is statically the enclosing type.
4075       --  The object may be an component of some other data structure,
4076       --  in which case this must be handled as an inter-object call.
4077
4078       if not In_Open_Scopes (Scop)
4079         or else not Is_Entity_Name (Name (N))
4080       then
4081          if Nkind (Name (N)) = N_Selected_Component then
4082             Rec := Prefix (Name (N));
4083
4084          else
4085             pragma Assert (Nkind (Name (N)) = N_Indexed_Component);
4086             Rec := Prefix (Prefix (Name (N)));
4087          end if;
4088
4089          Build_Protected_Subprogram_Call (N,
4090            Name => New_Occurrence_Of (Subp, Sloc (N)),
4091            Rec =>  Convert_Concurrent (Rec, Etype (Rec)),
4092            External => True);
4093
4094       else
4095          Rec := Expand_Protected_Object_Reference (N, Scop);
4096
4097          if No (Rec) then
4098             return;
4099          end if;
4100
4101          Build_Protected_Subprogram_Call (N,
4102            Name     => Name (N),
4103            Rec      => Rec,
4104            External => False);
4105
4106       end if;
4107
4108       Analyze (N);
4109
4110       --  If it is a function call it can appear in elaboration code and
4111       --  the called entity must be frozen here.
4112
4113       if Ekind (Subp) = E_Function then
4114          Freeze_Expression (Name (N));
4115       end if;
4116    end Expand_Protected_Subprogram_Call;
4117
4118    -----------------------
4119    -- Freeze_Subprogram --
4120    -----------------------
4121
4122    procedure Freeze_Subprogram (N : Node_Id) is
4123       Loc : constant Source_Ptr := Sloc (N);
4124       E   : constant Entity_Id  := Entity (N);
4125
4126       procedure Check_Overriding_Inherited_Interfaces (E : Entity_Id);
4127       --  (Ada 2005): Check if the primitive E covers some interface already
4128       --  implemented by some ancestor of the tagged-type associated with E.
4129
4130       procedure Register_Interface_DT_Entry
4131         (Prim                : Entity_Id;
4132          Ancestor_Iface_Prim : Entity_Id := Empty);
4133       --  (Ada 2005): Register an interface primitive in a secondary dispatch
4134       --  table. If Prim overrides an ancestor primitive of its associated
4135       --  tagged-type then Ancestor_Iface_Prim indicates the entity of that
4136       --  immediate ancestor associated with the interface; otherwise Prim and
4137       --  Ancestor_Iface_Prim have the same info.
4138
4139       procedure Register_Predefined_DT_Entry (Prim : Entity_Id);
4140       --  (Ada 2005): Register a predefined primitive in all the secondary
4141       --  dispatch tables of its primitive type.
4142
4143       -------------------------------------------
4144       -- Check_Overriding_Inherited_Interfaces --
4145       -------------------------------------------
4146
4147       procedure Check_Overriding_Inherited_Interfaces (E : Entity_Id) is
4148          Typ          : Entity_Id;
4149          Elmt         : Elmt_Id;
4150          Prim_Op      : Entity_Id;
4151          Overriden_Op : Entity_Id := Empty;
4152
4153       begin
4154          if Ada_Version < Ada_05
4155            or else not Is_Overriding_Operation (E)
4156            or else Is_Predefined_Dispatching_Operation (E)
4157            or else Present (Alias (E))
4158          then
4159             return;
4160          end if;
4161
4162          --  Get the entity associated with this primitive operation
4163
4164          Typ := Scope (DTC_Entity (E));
4165          loop
4166             exit when Etype (Typ) = Typ
4167               or else (Present (Full_View (Etype (Typ)))
4168                          and then Full_View (Etype (Typ)) = Typ);
4169
4170             --  Climb to the immediate ancestor handling private types
4171
4172             if Present (Full_View (Etype (Typ))) then
4173                Typ := Full_View (Etype (Typ));
4174             else
4175                Typ := Etype (Typ);
4176             end if;
4177
4178             if Present (Abstract_Interfaces (Typ)) then
4179
4180                --  Look for the overriden subprogram in the primary dispatch
4181                --  table of the ancestor.
4182
4183                Overriden_Op := Empty;
4184                Elmt         := First_Elmt (Primitive_Operations (Typ));
4185                while Present (Elmt) loop
4186                   Prim_Op := Node (Elmt);
4187
4188                   if Chars (Prim_Op) = Chars (E)
4189                     and then Type_Conformant
4190                                (New_Id => Prim_Op,
4191                                 Old_Id => E,
4192                                 Skip_Controlling_Formals => True)
4193                     and then DT_Position (Prim_Op) = DT_Position (E)
4194                     and then Etype (DTC_Entity (Prim_Op)) = RTE (RE_Tag)
4195                     and then not Present (Abstract_Interface_Alias (Prim_Op))
4196                   then
4197                      if Overriden_Op = Empty then
4198                         Overriden_Op := Prim_Op;
4199
4200                      --  Additional check to ensure that if two candidates have
4201                      --  been found then they refer to the same subprogram.
4202
4203                      else
4204                         declare
4205                            A1 : Entity_Id;
4206                            A2 : Entity_Id;
4207
4208                         begin
4209                            A1 := Overriden_Op;
4210                            while Present (Alias (A1)) loop
4211                               A1 := Alias (A1);
4212                            end loop;
4213
4214                            A2 := Prim_Op;
4215                            while Present (Alias (A2)) loop
4216                               A2 := Alias (A2);
4217                            end loop;
4218
4219                            if A1 /= A2 then
4220                               raise Program_Error;
4221                            end if;
4222                         end;
4223                      end if;
4224                   end if;
4225
4226                   Next_Elmt (Elmt);
4227                end loop;
4228
4229                --  If not found this is the first overriding of some abstract
4230                --  interface.
4231
4232                if Overriden_Op /= Empty then
4233
4234                   --  Find the entries associated with interfaces that are
4235                   --  alias of this primitive operation in the ancestor.
4236
4237                   Elmt := First_Elmt (Primitive_Operations (Typ));
4238                   while Present (Elmt) loop
4239                      Prim_Op := Node (Elmt);
4240
4241                      if Present (Abstract_Interface_Alias (Prim_Op))
4242                        and then Alias (Prim_Op) = Overriden_Op
4243                      then
4244                         Register_Interface_DT_Entry (E, Prim_Op);
4245                      end if;
4246
4247                      Next_Elmt (Elmt);
4248                   end loop;
4249                end if;
4250             end if;
4251          end loop;
4252       end Check_Overriding_Inherited_Interfaces;
4253
4254       ---------------------------------
4255       -- Register_Interface_DT_Entry --
4256       ---------------------------------
4257
4258       procedure Register_Interface_DT_Entry
4259         (Prim                : Entity_Id;
4260          Ancestor_Iface_Prim : Entity_Id := Empty)
4261       is
4262          Prim_Typ     : Entity_Id;
4263          Prim_Op      : Entity_Id;
4264          Iface_Typ    : Entity_Id;
4265          Iface_DT_Ptr : Entity_Id;
4266          Iface_Tag    : Entity_Id;
4267          New_Thunk    : Node_Id;
4268          Thunk_Id     : Entity_Id;
4269
4270       begin
4271          if not Present (Ancestor_Iface_Prim) then
4272             Prim_Typ  := Scope (DTC_Entity (Alias (Prim)));
4273             Iface_Typ := Scope (DTC_Entity (Abstract_Interface_Alias (Prim)));
4274
4275             --  Generate the code of the thunk only when this primitive
4276             --  operation is associated with a secondary dispatch table.
4277
4278             if Is_Interface (Iface_Typ) then
4279                Iface_Tag := Find_Interface_Tag
4280                               (T     => Prim_Typ,
4281                                Iface => Iface_Typ);
4282
4283                if Etype (Iface_Tag) = RTE (RE_Interface_Tag) then
4284                   Thunk_Id  :=
4285                     Make_Defining_Identifier (Loc,
4286                       Chars => New_Internal_Name ('T'));
4287
4288                   New_Thunk :=
4289                     Expand_Interface_Thunk
4290                       (N           => Prim,
4291                        Thunk_Alias => Alias (Prim),
4292                        Thunk_Id    => Thunk_Id,
4293                        Thunk_Tag   => Iface_Tag);
4294
4295                   Insert_After (N, New_Thunk);
4296
4297                   Iface_DT_Ptr :=
4298                     Find_Interface_ADT
4299                       (T     => Prim_Typ,
4300                        Iface => Iface_Typ);
4301
4302                   Insert_After (New_Thunk,
4303                     Fill_Secondary_DT_Entry (Sloc (Prim),
4304                       Prim         => Prim,
4305                       Iface_DT_Ptr => Iface_DT_Ptr,
4306                       Thunk_Id     => Thunk_Id));
4307                end if;
4308             end if;
4309
4310          else
4311             Iface_Typ :=
4312               Scope (DTC_Entity (Abstract_Interface_Alias
4313                                   (Ancestor_Iface_Prim)));
4314
4315             Iface_Tag :=
4316               Find_Interface_Tag
4317                 (T     => Scope (DTC_Entity (Alias (Ancestor_Iface_Prim))),
4318                  Iface => Iface_Typ);
4319
4320             --  Generate the thunk only if the associated tag is an interface
4321             --  tag. The case in which the associated tag is the primary tag
4322             --  occurs when a tagged type is a direct derivation of an
4323             --  interface. For example:
4324
4325             --    type I is interface;
4326             --    ...
4327             --    type T is new I with ...
4328
4329             if Etype (Iface_Tag) = RTE (RE_Interface_Tag) then
4330                Thunk_Id :=
4331                  Make_Defining_Identifier (Loc,
4332                    Chars => New_Internal_Name ('T'));
4333
4334                if Present (Alias (Prim)) then
4335                   Prim_Op := Alias (Prim);
4336                else
4337                   Prim_Op := Prim;
4338                end if;
4339
4340                New_Thunk :=
4341                  Expand_Interface_Thunk
4342                    (N           => Ancestor_Iface_Prim,
4343                     Thunk_Alias => Prim_Op,
4344                     Thunk_Id    => Thunk_Id,
4345                     Thunk_Tag   => Iface_Tag);
4346
4347                Insert_After (N, New_Thunk);
4348
4349                Iface_DT_Ptr :=
4350                  Find_Interface_ADT
4351                    (T     => Scope (DTC_Entity (Prim_Op)),
4352                     Iface => Iface_Typ);
4353
4354                Insert_After (New_Thunk,
4355                  Fill_Secondary_DT_Entry (Sloc (Prim),
4356                    Prim         => Ancestor_Iface_Prim,
4357                    Iface_DT_Ptr => Iface_DT_Ptr,
4358                    Thunk_Id     => Thunk_Id));
4359             end if;
4360          end if;
4361       end Register_Interface_DT_Entry;
4362
4363       ----------------------------------
4364       -- Register_Predefined_DT_Entry --
4365       ----------------------------------
4366
4367       procedure Register_Predefined_DT_Entry (Prim : Entity_Id) is
4368          Iface_DT_Ptr : Elmt_Id;
4369          Iface_Tag    : Entity_Id;
4370          Iface_Typ    : Elmt_Id;
4371          New_Thunk    : Entity_Id;
4372          Prim_Typ     : Entity_Id;
4373          Thunk_Id     : Entity_Id;
4374
4375       begin
4376          Prim_Typ := Scope (DTC_Entity (Prim));
4377
4378          if not Present (Access_Disp_Table (Prim_Typ))
4379            or else not Present (Abstract_Interfaces (Prim_Typ))
4380          then
4381             return;
4382          end if;
4383
4384          --  Skip the first acces-to-dispatch-table pointer since it leads
4385          --  to the primary dispatch table. We are only concerned with the
4386          --  secondary dispatch table pointers. Note that the access-to-
4387          --  dispatch-table pointer corresponds to the first implemented
4388          --  interface retrieved below.
4389
4390          Iface_DT_Ptr := Next_Elmt (First_Elmt (Access_Disp_Table (Prim_Typ)));
4391          Iface_Typ := First_Elmt (Abstract_Interfaces (Prim_Typ));
4392          while Present (Iface_DT_Ptr) and then Present (Iface_Typ) loop
4393             Iface_Tag := Find_Interface_Tag (Prim_Typ, Node (Iface_Typ));
4394             pragma Assert (Present (Iface_Tag));
4395
4396             if Etype (Iface_Tag) = RTE (RE_Interface_Tag) then
4397                Thunk_Id := Make_Defining_Identifier (Loc,
4398                              New_Internal_Name ('T'));
4399
4400                New_Thunk :=
4401                  Expand_Interface_Thunk
4402                   (N           => Prim,
4403                    Thunk_Alias => Prim,
4404                    Thunk_Id    => Thunk_Id,
4405                    Thunk_Tag   => Iface_Tag);
4406
4407                Insert_After (N, New_Thunk);
4408                Insert_After (New_Thunk,
4409                  Make_DT_Access_Action (Node (Iface_Typ),
4410                    Action => Set_Prim_Op_Address,
4411                    Args   => New_List (
4412                      Unchecked_Convert_To (RTE (RE_Tag),
4413                        New_Reference_To (Node (Iface_DT_Ptr), Loc)),
4414
4415                      Make_Integer_Literal (Loc, DT_Position (Prim)),
4416
4417                      Make_Attribute_Reference (Loc,
4418                        Prefix         => New_Reference_To (Thunk_Id, Loc),
4419                        Attribute_Name => Name_Address))));
4420             end if;
4421
4422             Next_Elmt (Iface_DT_Ptr);
4423             Next_Elmt (Iface_Typ);
4424          end loop;
4425       end Register_Predefined_DT_Entry;
4426
4427    --  Start of processing for Freeze_Subprogram
4428
4429    begin
4430       --  When a primitive is frozen, enter its name in the corresponding
4431       --  dispatch table. If the DTC_Entity field is not set this is an
4432       --  overridden primitive that can be ignored. We suppress the
4433       --  initialization of the dispatch table entry when Java_VM because
4434       --  the dispatching mechanism is handled internally by the JVM.
4435
4436       if Is_Dispatching_Operation (E)
4437         and then not Is_Abstract (E)
4438         and then Present (DTC_Entity (E))
4439         and then not Java_VM
4440         and then not Is_CPP_Class (Scope (DTC_Entity (E)))
4441       then
4442          Check_Overriding_Operation (E);
4443
4444          if Ada_Version < Ada_05 then
4445             Insert_After (N,
4446               Fill_DT_Entry (Sloc (N), Prim => E));
4447
4448          else
4449             declare
4450                Typ : constant Entity_Id := Scope (DTC_Entity (E));
4451
4452             begin
4453                --  There is no dispatch table associated with abstract
4454                --  interface types; each type implementing interfaces
4455                --  will fill the associated secondary DT entries.
4456
4457                if not Is_Interface (Typ)
4458                  or else Present (Alias (E))
4459                then
4460                   --  Ada 2005 (AI-251): Check if this entry corresponds with
4461                   --  a subprogram that covers an abstract interface type.
4462
4463                   if Present (Abstract_Interface_Alias (E)) then
4464                      Register_Interface_DT_Entry (E);
4465
4466                   --  Common case: Primitive subprogram
4467
4468                   else
4469                      --  Generate thunks for all the predefined operations
4470
4471                      if Is_Predefined_Dispatching_Operation (E) then
4472                         Register_Predefined_DT_Entry (E);
4473                      end if;
4474
4475                      Insert_After (N,
4476                        Fill_DT_Entry (Sloc (N), Prim => E));
4477                      Check_Overriding_Inherited_Interfaces (E);
4478                   end if;
4479                end if;
4480             end;
4481          end if;
4482       end if;
4483
4484       --  Mark functions that return by reference. Note that it cannot be
4485       --  part of the normal semantic analysis of the spec since the
4486       --  underlying returned type may not be known yet (for private types).
4487
4488       declare
4489          Typ  : constant Entity_Id := Etype (E);
4490          Utyp : constant Entity_Id := Underlying_Type (Typ);
4491
4492       begin
4493          if Is_Return_By_Reference_Type (Typ) then
4494             Set_Returns_By_Ref (E);
4495
4496          elsif Present (Utyp) and then Controlled_Type (Utyp) then
4497             Set_Returns_By_Ref (E);
4498          end if;
4499       end;
4500    end Freeze_Subprogram;
4501
4502 end Exp_Ch6;