OSDN Git Service

2003-10-21 Arnaud Charlet <charlet@act-europe.fr>
[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-2003, 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,  59 Temple Place - Suite 330,  Boston, --
20 -- MA 02111-1307, 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_Ch11; use Exp_Ch11;
38 with Exp_Dbug; use Exp_Dbug;
39 with Exp_Disp; use Exp_Disp;
40 with Exp_Dist; use Exp_Dist;
41 with Exp_Intr; use Exp_Intr;
42 with Exp_Pakd; use Exp_Pakd;
43 with Exp_Tss;  use Exp_Tss;
44 with Exp_Util; use Exp_Util;
45 with Fname;    use Fname;
46 with Freeze;   use Freeze;
47 with Hostparm; use Hostparm;
48 with Inline;   use Inline;
49 with Lib;      use Lib;
50 with Nlists;   use Nlists;
51 with Nmake;    use Nmake;
52 with Opt;      use Opt;
53 with Restrict; use Restrict;
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_Res;  use Sem_Res;
63 with Sem_Util; use Sem_Util;
64 with Sinfo;    use Sinfo;
65 with Snames;   use Snames;
66 with Stand;    use Stand;
67 with Tbuild;   use Tbuild;
68 with Uintp;    use Uintp;
69 with Validsw;  use Validsw;
70
71 package body Exp_Ch6 is
72
73    -----------------------
74    -- Local Subprograms --
75    -----------------------
76
77    procedure Check_Overriding_Operation (Subp : Entity_Id);
78    --  Subp is a dispatching operation. Check whether it may override an
79    --  inherited private operation, in which case its DT entry is that of
80    --  the hidden operation, not the one it may have received earlier.
81    --  This must be done before emitting the code to set the corresponding
82    --  DT to the address of the subprogram. The actual placement of Subp in
83    --  the proper place in the list of primitive operations is done in
84    --  Declare_Inherited_Private_Subprograms, which also has to deal with
85    --  implicit operations. This duplication is unavoidable for now???
86
87    procedure Detect_Infinite_Recursion (N : Node_Id; Spec : Entity_Id);
88    --  This procedure is called only if the subprogram body N, whose spec
89    --  has the given entity Spec, contains a parameterless recursive call.
90    --  It attempts to generate runtime code to detect if this a case of
91    --  infinite recursion.
92    --
93    --  The body is scanned to determine dependencies. If the only external
94    --  dependencies are on a small set of scalar variables, then the values
95    --  of these variables are captured on entry to the subprogram, and if
96    --  the values are not changed for the call, we know immediately that
97    --  we have an infinite recursion.
98
99    procedure Expand_Actuals (N : Node_Id; Subp : Entity_Id);
100    --  For each actual of an in-out parameter which is a numeric conversion
101    --  of the form T(A), where A denotes a variable, we insert the declaration:
102    --
103    --    Temp : T := T (A);
104    --
105    --  prior to the call. Then we replace the actual with a reference to Temp,
106    --  and append the assignment:
107    --
108    --    A := TypeA (Temp);
109    --
110    --  after the call. Here TypeA is the actual type of variable A.
111    --  For out parameters, the initial declaration has no expression.
112    --  If A is not an entity name, we generate instead:
113    --
114    --    Var  : TypeA renames A;
115    --    Temp : T := Var;       --  omitting expression for out parameter.
116    --    ...
117    --    Var := TypeA (Temp);
118    --
119    --  For other in-out parameters, we emit the required constraint checks
120    --  before and/or after the call.
121    --
122    --  For all parameter modes, actuals that denote components and slices
123    --  of packed arrays are expanded into suitable temporaries.
124
125    procedure Expand_Inlined_Call
126     (N         : Node_Id;
127      Subp      : Entity_Id;
128      Orig_Subp : Entity_Id);
129    --  If called subprogram can be inlined by the front-end, retrieve the
130    --  analyzed body, replace formals with actuals and expand call in place.
131    --  Generate thunks for actuals that are expressions, and insert the
132    --  corresponding constant declarations before the call. If the original
133    --  call is to a derived operation, the return type is the one of the
134    --  derived operation, but the body is that of the original, so return
135    --  expressions in the body must be converted to the desired type (which
136    --  is simply not noted in the tree without inline expansion).
137
138    function Expand_Protected_Object_Reference
139      (N    : Node_Id;
140       Scop : Entity_Id)
141       return Node_Id;
142
143    procedure Expand_Protected_Subprogram_Call
144      (N    : Node_Id;
145       Subp : Entity_Id;
146       Scop : Entity_Id);
147    --  A call to a protected subprogram within the protected object may appear
148    --  as a regular call. The list of actuals must be expanded to contain a
149    --  reference to the object itself, and the call becomes a call to the
150    --  corresponding protected subprogram.
151
152    --------------------------------
153    -- Check_Overriding_Operation --
154    --------------------------------
155
156    procedure Check_Overriding_Operation (Subp : Entity_Id) is
157       Typ     : constant Entity_Id := Find_Dispatching_Type (Subp);
158       Op_List : constant Elist_Id  := Primitive_Operations (Typ);
159       Op_Elmt : Elmt_Id;
160       Prim_Op : Entity_Id;
161       Par_Op  : Entity_Id;
162
163    begin
164       if Is_Derived_Type (Typ)
165         and then not Is_Private_Type (Typ)
166         and then In_Open_Scopes (Scope (Etype (Typ)))
167         and then Typ = Base_Type (Typ)
168       then
169          --  Subp overrides an inherited private operation if there is
170          --  an inherited operation with a different name than Subp (see
171          --  Derive_Subprogram) whose Alias is a hidden  subprogram with
172          --  the same name as Subp.
173
174          Op_Elmt := First_Elmt (Op_List);
175          while Present (Op_Elmt) loop
176             Prim_Op := Node (Op_Elmt);
177             Par_Op  := Alias (Prim_Op);
178
179             if Present (Par_Op)
180               and then not Comes_From_Source (Prim_Op)
181               and then Chars (Prim_Op) /= Chars (Par_Op)
182               and then Chars (Par_Op) = Chars (Subp)
183               and then Is_Hidden (Par_Op)
184               and then Type_Conformant (Prim_Op, Subp)
185             then
186                Set_DT_Position (Subp, DT_Position (Prim_Op));
187             end if;
188
189             Next_Elmt (Op_Elmt);
190          end loop;
191       end if;
192    end Check_Overriding_Operation;
193
194    -------------------------------
195    -- Detect_Infinite_Recursion --
196    -------------------------------
197
198    procedure Detect_Infinite_Recursion (N : Node_Id; Spec : Entity_Id) is
199       Loc : constant Source_Ptr := Sloc (N);
200
201       Var_List : constant Elist_Id := New_Elmt_List;
202       --  List of globals referenced by body of procedure
203
204       Call_List : constant Elist_Id := New_Elmt_List;
205       --  List of recursive calls in body of procedure
206
207       Shad_List : constant Elist_Id := New_Elmt_List;
208       --  List of entity id's for entities created to capture the
209       --  value of referenced globals on entry to the procedure.
210
211       Scop : constant Uint := Scope_Depth (Spec);
212       --  This is used to record the scope depth of the current
213       --  procedure, so that we can identify global references.
214
215       Max_Vars : constant := 4;
216       --  Do not test more than four global variables
217
218       Count_Vars : Natural := 0;
219       --  Count variables found so far
220
221       Var  : Entity_Id;
222       Elm  : Elmt_Id;
223       Ent  : Entity_Id;
224       Call : Elmt_Id;
225       Decl : Node_Id;
226       Test : Node_Id;
227       Elm1 : Elmt_Id;
228       Elm2 : Elmt_Id;
229       Last : Node_Id;
230
231       function Process (Nod : Node_Id) return Traverse_Result;
232       --  Function to traverse the subprogram body (using Traverse_Func)
233
234       -------------
235       -- Process --
236       -------------
237
238       function Process (Nod : Node_Id) return Traverse_Result is
239       begin
240          --  Procedure call
241
242          if Nkind (Nod) = N_Procedure_Call_Statement then
243
244             --  Case of one of the detected recursive calls
245
246             if Is_Entity_Name (Name (Nod))
247               and then Has_Recursive_Call (Entity (Name (Nod)))
248               and then Entity (Name (Nod)) = Spec
249             then
250                Append_Elmt (Nod, Call_List);
251                return Skip;
252
253             --  Any other procedure call may have side effects
254
255             else
256                return Abandon;
257             end if;
258
259          --  A call to a pure function can always be ignored
260
261          elsif Nkind (Nod) = N_Function_Call
262            and then Is_Entity_Name (Name (Nod))
263            and then Is_Pure (Entity (Name (Nod)))
264          then
265             return Skip;
266
267          --  Case of an identifier reference
268
269          elsif Nkind (Nod) = N_Identifier then
270             Ent := Entity (Nod);
271
272             --  If no entity, then ignore the reference
273
274             --  Not clear why this can happen. To investigate, remove this
275             --  test and look at the crash that occurs here in 3401-004 ???
276
277             if No (Ent) then
278                return Skip;
279
280             --  Ignore entities with no Scope, again not clear how this
281             --  can happen, to investigate, look at 4108-008 ???
282
283             elsif No (Scope (Ent)) then
284                return Skip;
285
286             --  Ignore the reference if not to a more global object
287
288             elsif Scope_Depth (Scope (Ent)) >= Scop then
289                return Skip;
290
291             --  References to types, exceptions and constants are always OK
292
293             elsif Is_Type (Ent)
294               or else Ekind (Ent) = E_Exception
295               or else Ekind (Ent) = E_Constant
296             then
297                return Skip;
298
299             --  If other than a non-volatile scalar variable, we have some
300             --  kind of global reference (e.g. to a function) that we cannot
301             --  deal with so we forget the attempt.
302
303             elsif Ekind (Ent) /= E_Variable
304               or else not Is_Scalar_Type (Etype (Ent))
305               or else Treat_As_Volatile (Ent)
306             then
307                return Abandon;
308
309             --  Otherwise we have a reference to a global scalar
310
311             else
312                --  Loop through global entities already detected
313
314                Elm := First_Elmt (Var_List);
315                loop
316                   --  If not detected before, record this new global reference
317
318                   if No (Elm) then
319                      Count_Vars := Count_Vars + 1;
320
321                      if Count_Vars <= Max_Vars then
322                         Append_Elmt (Entity (Nod), Var_List);
323                      else
324                         return Abandon;
325                      end if;
326
327                      exit;
328
329                   --  If recorded before, ignore
330
331                   elsif Node (Elm) = Entity (Nod) then
332                      return Skip;
333
334                   --  Otherwise keep looking
335
336                   else
337                      Next_Elmt (Elm);
338                   end if;
339                end loop;
340
341                return Skip;
342             end if;
343
344          --  For all other node kinds, recursively visit syntactic children
345
346          else
347             return OK;
348          end if;
349       end Process;
350
351       function Traverse_Body is new Traverse_Func;
352
353    --  Start of processing for Detect_Infinite_Recursion
354
355    begin
356       --  Do not attempt detection in No_Implicit_Conditional mode,
357       --  since we won't be able to generate the code to handle the
358       --  recursion in any case.
359
360       if Restrictions (No_Implicit_Conditionals) then
361          return;
362       end if;
363
364       --  Otherwise do traversal and quit if we get abandon signal
365
366       if Traverse_Body (N) = Abandon then
367          return;
368
369       --  We must have a call, since Has_Recursive_Call was set. If not
370       --  just ignore (this is only an error check, so if we have a funny
371       --  situation, due to bugs or errors, we do not want to bomb!)
372
373       elsif Is_Empty_Elmt_List (Call_List) then
374          return;
375       end if;
376
377       --  Here is the case where we detect recursion at compile time
378
379       --  Push our current scope for analyzing the declarations and
380       --  code that we will insert for the checking.
381
382       New_Scope (Spec);
383
384       --  This loop builds temporary variables for each of the
385       --  referenced globals, so that at the end of the loop the
386       --  list Shad_List contains these temporaries in one-to-one
387       --  correspondence with the elements in Var_List.
388
389       Last := Empty;
390       Elm := First_Elmt (Var_List);
391       while Present (Elm) loop
392          Var := Node (Elm);
393          Ent :=
394            Make_Defining_Identifier (Loc,
395              Chars => New_Internal_Name ('S'));
396          Append_Elmt (Ent, Shad_List);
397
398          --  Insert a declaration for this temporary at the start of
399          --  the declarations for the procedure. The temporaries are
400          --  declared as constant objects initialized to the current
401          --  values of the corresponding temporaries.
402
403          Decl :=
404            Make_Object_Declaration (Loc,
405              Defining_Identifier => Ent,
406              Object_Definition   => New_Occurrence_Of (Etype (Var), Loc),
407              Constant_Present    => True,
408              Expression          => New_Occurrence_Of (Var, Loc));
409
410          if No (Last) then
411             Prepend (Decl, Declarations (N));
412          else
413             Insert_After (Last, Decl);
414          end if;
415
416          Last := Decl;
417          Analyze (Decl);
418          Next_Elmt (Elm);
419       end loop;
420
421       --  Loop through calls
422
423       Call := First_Elmt (Call_List);
424       while Present (Call) loop
425
426          --  Build a predicate expression of the form
427
428          --    True
429          --      and then global1 = temp1
430          --      and then global2 = temp2
431          --      ...
432
433          --  This predicate determines if any of the global values
434          --  referenced by the procedure have changed since the
435          --  current call, if not an infinite recursion is assured.
436
437          Test := New_Occurrence_Of (Standard_True, Loc);
438
439          Elm1 := First_Elmt (Var_List);
440          Elm2 := First_Elmt (Shad_List);
441          while Present (Elm1) loop
442             Test :=
443               Make_And_Then (Loc,
444                 Left_Opnd  => Test,
445                 Right_Opnd =>
446                   Make_Op_Eq (Loc,
447                     Left_Opnd  => New_Occurrence_Of (Node (Elm1), Loc),
448                     Right_Opnd => New_Occurrence_Of (Node (Elm2), Loc)));
449
450             Next_Elmt (Elm1);
451             Next_Elmt (Elm2);
452          end loop;
453
454          --  Now we replace the call with the sequence
455
456          --    if no-changes (see above) then
457          --       raise Storage_Error;
458          --    else
459          --       original-call
460          --    end if;
461
462          Rewrite (Node (Call),
463            Make_If_Statement (Loc,
464              Condition       => Test,
465              Then_Statements => New_List (
466                Make_Raise_Storage_Error (Loc,
467                  Reason => SE_Infinite_Recursion)),
468
469              Else_Statements => New_List (
470                Relocate_Node (Node (Call)))));
471
472          Analyze (Node (Call));
473
474          Next_Elmt (Call);
475       end loop;
476
477       --  Remove temporary scope stack entry used for analysis
478
479       Pop_Scope;
480    end Detect_Infinite_Recursion;
481
482    --------------------
483    -- Expand_Actuals --
484    --------------------
485
486    procedure Expand_Actuals (N : Node_Id; Subp : Entity_Id) is
487       Loc       : constant Source_Ptr := Sloc (N);
488       Actual    : Node_Id;
489       Formal    : Entity_Id;
490       N_Node    : Node_Id;
491       Post_Call : List_Id;
492       E_Formal  : Entity_Id;
493
494       procedure Add_Call_By_Copy_Code;
495       --  For cases where the parameter must be passed by copy, this routine
496       --  generates a temporary variable into which the actual is copied and
497       --  then passes this as the parameter. For an OUT or IN OUT parameter,
498       --  an assignment is also generated to copy the result back. The call
499       --  also takes care of any constraint checks required for the type
500       --  conversion case (on both the way in and the way out).
501
502       procedure Add_Packed_Call_By_Copy_Code;
503       --  This is used when the actual involves a reference to an element
504       --  of a packed array, where we can appropriately use a simpler
505       --  approach than the full call by copy code. We just copy the value
506       --  in and out of an appropriate temporary.
507
508       procedure Check_Fortran_Logical;
509       --  A value of type Logical that is passed through a formal parameter
510       --  must be normalized because .TRUE. usually does not have the same
511       --  representation as True. We assume that .FALSE. = False = 0.
512       --  What about functions that return a logical type ???
513
514       function Make_Var (Actual : Node_Id) return Entity_Id;
515       --  Returns an entity that refers to the given actual parameter,
516       --  Actual (not including any type conversion). If Actual is an
517       --  entity name, then this entity is returned unchanged, otherwise
518       --  a renaming is created to provide an entity for the actual.
519
520       procedure Reset_Packed_Prefix;
521       --  The expansion of a packed array component reference is delayed in
522       --  the context of a call. Now we need to complete the expansion, so we
523       --  unmark the analyzed bits in all prefixes.
524
525       ---------------------------
526       -- Add_Call_By_Copy_Code --
527       ---------------------------
528
529       procedure Add_Call_By_Copy_Code is
530          Expr    : Node_Id;
531          Init    : Node_Id;
532          Temp    : Entity_Id;
533          Var     : Entity_Id;
534          V_Typ   : Entity_Id;
535          Crep    : Boolean;
536
537       begin
538          Temp := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
539
540          if Nkind (Actual) = N_Type_Conversion then
541             V_Typ := Etype (Expression (Actual));
542             Var   := Make_Var (Expression (Actual));
543             Crep  := not Same_Representation
544                        (Etype (Formal), Etype (Expression (Actual)));
545          else
546             V_Typ := Etype (Actual);
547             Var   := Make_Var (Actual);
548             Crep  := False;
549          end if;
550
551          --  Setup initialization for case of in out parameter, or an out
552          --  parameter where the formal is an unconstrained array (in the
553          --  latter case, we have to pass in an object with bounds).
554
555          if Ekind (Formal) = E_In_Out_Parameter
556            or else (Is_Array_Type (Etype (Formal))
557                      and then
558                     not Is_Constrained (Etype (Formal)))
559          then
560             if Nkind (Actual) = N_Type_Conversion then
561                if Conversion_OK (Actual) then
562                   Init := OK_Convert_To
563                             (Etype (Formal), New_Occurrence_Of (Var, Loc));
564                else
565                   Init := Convert_To
566                             (Etype (Formal), New_Occurrence_Of (Var, Loc));
567                end if;
568             else
569                Init := New_Occurrence_Of (Var, Loc);
570             end if;
571
572          --  An initialization is created for packed conversions as
573          --  actuals for out parameters to enable Make_Object_Declaration
574          --  to determine the proper subtype for N_Node. Note that this
575          --  is wasteful because the extra copying on the call side is
576          --  not required for such out parameters. ???
577
578          elsif Ekind (Formal) = E_Out_Parameter
579            and then Nkind (Actual) = N_Type_Conversion
580            and then (Is_Bit_Packed_Array (Etype (Formal))
581                        or else
582                      Is_Bit_Packed_Array (Etype (Expression (Actual))))
583          then
584             if Conversion_OK (Actual) then
585                Init :=
586                  OK_Convert_To (Etype (Formal), New_Occurrence_Of (Var, Loc));
587             else
588                Init :=
589                  Convert_To (Etype (Formal), New_Occurrence_Of (Var, Loc));
590             end if;
591          else
592             Init := Empty;
593          end if;
594
595          N_Node :=
596            Make_Object_Declaration (Loc,
597              Defining_Identifier => Temp,
598              Object_Definition   =>
599                New_Occurrence_Of (Etype (Formal), Loc),
600              Expression => Init);
601          Set_Assignment_OK (N_Node);
602          Insert_Action (N, N_Node);
603
604          --  Now, normally the deal here is that we use the defining
605          --  identifier created by that object declaration. There is
606          --  one exception to this. In the change of representation case
607          --  the above declaration will end up looking like:
608
609          --    temp : type := identifier;
610
611          --  And in this case we might as well use the identifier directly
612          --  and eliminate the temporary. Note that the analysis of the
613          --  declaration was not a waste of time in that case, since it is
614          --  what generated the necessary change of representation code. If
615          --  the change of representation introduced additional code, as in
616          --  a fixed-integer conversion, the expression is not an identifier
617          --  and must be kept.
618
619          if Crep
620            and then Present (Expression (N_Node))
621            and then Is_Entity_Name (Expression (N_Node))
622          then
623             Temp := Entity (Expression (N_Node));
624             Rewrite (N_Node, Make_Null_Statement (Loc));
625          end if;
626
627          --  For IN parameter, all we do is to replace the actual
628
629          if Ekind (Formal) = E_In_Parameter then
630             Rewrite (Actual, New_Reference_To (Temp, Loc));
631             Analyze (Actual);
632
633          --  Processing for OUT or IN OUT parameter
634
635          else
636             --  If type conversion, use reverse conversion on exit
637
638             if Nkind (Actual) = N_Type_Conversion then
639                if Conversion_OK (Actual) then
640                   Expr := OK_Convert_To (V_Typ, New_Occurrence_Of (Temp, Loc));
641                else
642                   Expr := Convert_To (V_Typ, New_Occurrence_Of (Temp, Loc));
643                end if;
644             else
645                Expr := New_Occurrence_Of (Temp, Loc);
646             end if;
647
648             Rewrite (Actual, New_Reference_To (Temp, Loc));
649             Analyze (Actual);
650
651             Append_To (Post_Call,
652               Make_Assignment_Statement (Loc,
653                 Name       => New_Occurrence_Of (Var, Loc),
654                 Expression => Expr));
655
656             Set_Assignment_OK (Name (Last (Post_Call)));
657          end if;
658       end Add_Call_By_Copy_Code;
659
660       ----------------------------------
661       -- Add_Packed_Call_By_Copy_Code --
662       ----------------------------------
663
664       procedure Add_Packed_Call_By_Copy_Code is
665          Temp   : Entity_Id;
666          Incod  : Node_Id;
667          Outcod : Node_Id;
668          Lhs    : Node_Id;
669          Rhs    : Node_Id;
670
671       begin
672          Reset_Packed_Prefix;
673
674          --  Prepare to generate code
675
676          Temp := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
677          Incod  := Relocate_Node (Actual);
678          Outcod := New_Copy_Tree (Incod);
679
680          --  Generate declaration of temporary variable, initializing it
681          --  with the input parameter unless we have an OUT variable.
682
683          if Ekind (Formal) = E_Out_Parameter then
684             Incod := Empty;
685          end if;
686
687          Insert_Action (N,
688            Make_Object_Declaration (Loc,
689              Defining_Identifier => Temp,
690              Object_Definition   =>
691                New_Occurrence_Of (Etype (Formal), Loc),
692              Expression => Incod));
693
694          --  The actual is simply a reference to the temporary
695
696          Rewrite (Actual, New_Occurrence_Of (Temp, Loc));
697
698          --  Generate copy out if OUT or IN OUT parameter
699
700          if Ekind (Formal) /= E_In_Parameter then
701             Lhs := Outcod;
702             Rhs := New_Occurrence_Of (Temp, Loc);
703
704             --  Deal with conversion
705
706             if Nkind (Lhs) = N_Type_Conversion then
707                Lhs := Expression (Lhs);
708                Rhs := Convert_To (Etype (Actual), Rhs);
709             end if;
710
711             Append_To (Post_Call,
712               Make_Assignment_Statement (Loc,
713                 Name       => Lhs,
714                 Expression => Rhs));
715          end if;
716       end Add_Packed_Call_By_Copy_Code;
717
718       ---------------------------
719       -- Check_Fortran_Logical --
720       ---------------------------
721
722       procedure Check_Fortran_Logical is
723          Logical : constant Entity_Id := Etype (Formal);
724          Var     : Entity_Id;
725
726       --  Note: this is very incomplete, e.g. it does not handle arrays
727       --  of logical values. This is really not the right approach at all???)
728
729       begin
730          if Convention (Subp) = Convention_Fortran
731            and then Root_Type (Etype (Formal)) = Standard_Boolean
732            and then Ekind (Formal) /= E_In_Parameter
733          then
734             Var := Make_Var (Actual);
735             Append_To (Post_Call,
736               Make_Assignment_Statement (Loc,
737                 Name => New_Occurrence_Of (Var, Loc),
738                 Expression =>
739                   Unchecked_Convert_To (
740                     Logical,
741                     Make_Op_Ne (Loc,
742                       Left_Opnd  => New_Occurrence_Of (Var, Loc),
743                       Right_Opnd =>
744                         Unchecked_Convert_To (
745                           Logical,
746                           New_Occurrence_Of (Standard_False, Loc))))));
747          end if;
748       end Check_Fortran_Logical;
749
750       --------------
751       -- Make_Var --
752       --------------
753
754       function Make_Var (Actual : Node_Id) return Entity_Id is
755          Var : Entity_Id;
756
757       begin
758          if Is_Entity_Name (Actual) then
759             return Entity (Actual);
760
761          else
762             Var := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
763
764             N_Node :=
765               Make_Object_Renaming_Declaration (Loc,
766                 Defining_Identifier => Var,
767                 Subtype_Mark        =>
768                   New_Occurrence_Of (Etype (Actual), Loc),
769                 Name                => Relocate_Node (Actual));
770
771             Insert_Action (N, N_Node);
772             return Var;
773          end if;
774       end Make_Var;
775
776       -------------------------
777       -- Reset_Packed_Prefix --
778       -------------------------
779
780       procedure Reset_Packed_Prefix is
781          Pfx : Node_Id := Actual;
782
783       begin
784          loop
785             Set_Analyzed (Pfx, False);
786             exit when Nkind (Pfx) /= N_Selected_Component
787               and then Nkind (Pfx) /= N_Indexed_Component;
788             Pfx := Prefix (Pfx);
789          end loop;
790       end Reset_Packed_Prefix;
791
792    --  Start of processing for Expand_Actuals
793
794    begin
795       Formal := First_Formal (Subp);
796       Actual := First_Actual (N);
797
798       Post_Call := New_List;
799
800       while Present (Formal) loop
801          E_Formal := Etype (Formal);
802
803          if Is_Scalar_Type (E_Formal)
804            or else Nkind (Actual) = N_Slice
805          then
806             Check_Fortran_Logical;
807
808          --  RM 6.4.1 (11)
809
810          elsif Ekind (Formal) /= E_Out_Parameter then
811
812             --  The unusual case of the current instance of a protected type
813             --  requires special handling. This can only occur in the context
814             --  of a call within the body of a protected operation.
815
816             if Is_Entity_Name (Actual)
817               and then Ekind (Entity (Actual)) = E_Protected_Type
818               and then In_Open_Scopes (Entity (Actual))
819             then
820                if Scope (Subp) /= Entity (Actual) then
821                   Error_Msg_N ("operation outside protected type may not "
822                     & "call back its protected operations?", Actual);
823                end if;
824
825                Rewrite (Actual,
826                  Expand_Protected_Object_Reference (N, Entity (Actual)));
827             end if;
828
829             Apply_Constraint_Check (Actual, E_Formal);
830
831          --  Out parameter case. No constraint checks on access type
832          --  RM 6.4.1 (13)
833
834          elsif Is_Access_Type (E_Formal) then
835             null;
836
837          --  RM 6.4.1 (14)
838
839          elsif Has_Discriminants (Base_Type (E_Formal))
840            or else Has_Non_Null_Base_Init_Proc (E_Formal)
841          then
842             Apply_Constraint_Check (Actual, E_Formal);
843
844          --  RM 6.4.1 (15)
845
846          else
847             Apply_Constraint_Check (Actual, Base_Type (E_Formal));
848          end if;
849
850          --  Processing for IN-OUT and OUT parameters
851
852          if Ekind (Formal) /= E_In_Parameter then
853
854             --  For type conversions of arrays, apply length/range checks
855
856             if Is_Array_Type (E_Formal)
857               and then Nkind (Actual) = N_Type_Conversion
858             then
859                if Is_Constrained (E_Formal) then
860                   Apply_Length_Check (Expression (Actual), E_Formal);
861                else
862                   Apply_Range_Check (Expression (Actual), E_Formal);
863                end if;
864             end if;
865
866             --  If argument is a type conversion for a type that is passed
867             --  by copy, then we must pass the parameter by copy.
868
869             if Nkind (Actual) = N_Type_Conversion
870               and then
871                 (Is_Numeric_Type (E_Formal)
872                   or else Is_Access_Type (E_Formal)
873                   or else Is_Enumeration_Type (E_Formal)
874                   or else Is_Bit_Packed_Array (Etype (Formal))
875                   or else Is_Bit_Packed_Array (Etype (Expression (Actual)))
876
877                   --  Also pass by copy if change of representation
878
879                   or else not Same_Representation
880                                (Etype (Formal),
881                                 Etype (Expression (Actual))))
882             then
883                Add_Call_By_Copy_Code;
884
885             --  References to components of bit packed arrays are expanded
886             --  at this point, rather than at the point of analysis of the
887             --  actuals, to handle the expansion of the assignment to
888             --  [in] out parameters.
889
890             elsif Is_Ref_To_Bit_Packed_Array (Actual) then
891                Add_Packed_Call_By_Copy_Code;
892
893             --  References to slices of bit packed arrays are expanded
894
895             elsif Is_Ref_To_Bit_Packed_Slice (Actual) then
896                Add_Call_By_Copy_Code;
897
898             --  References to possibly unaligned slices of arrays are expanded
899
900             elsif Is_Possibly_Unaligned_Slice (Actual) then
901                Add_Call_By_Copy_Code;
902
903             --  Deal with access types where the actual subtpe and the
904             --  formal subtype are not the same, requiring a check.
905
906             --  It is necessary to exclude tagged types because of "downward
907             --  conversion" errors and a strange assertion error in namet
908             --  from gnatf in bug 1215-001 ???
909
910             elsif Is_Access_Type (E_Formal)
911               and then not Same_Type (E_Formal, Etype (Actual))
912               and then not Is_Tagged_Type (Designated_Type (E_Formal))
913             then
914                Add_Call_By_Copy_Code;
915
916             elsif Is_Entity_Name (Actual)
917               and then Treat_As_Volatile (Entity (Actual))
918               and then not Is_Scalar_Type (Etype (Entity (Actual)))
919               and then not Treat_As_Volatile (E_Formal)
920             then
921                Add_Call_By_Copy_Code;
922
923             elsif Nkind (Actual) = N_Indexed_Component
924               and then Is_Entity_Name (Prefix (Actual))
925               and then Has_Volatile_Components (Entity (Prefix (Actual)))
926             then
927                Add_Call_By_Copy_Code;
928             end if;
929
930          --  Processing for IN parameters
931
932          else
933             --  For IN parameters is in the packed array case, we expand an
934             --  indexed component (the circuit in Exp_Ch4 deliberately left
935             --  indexed components appearing as actuals untouched, so that
936             --  the special processing above for the OUT and IN OUT cases
937             --  could be performed. We could make the test in Exp_Ch4 more
938             --  complex and have it detect the parameter mode, but it is
939             --  easier simply to handle all cases here.
940
941             if Nkind (Actual) = N_Indexed_Component
942               and then Is_Packed (Etype (Prefix (Actual)))
943             then
944                Reset_Packed_Prefix;
945                Expand_Packed_Element_Reference (Actual);
946
947             --  If we have a reference to a bit packed array, we copy it,
948             --  since the actual must be byte aligned.
949
950             --  Is this really necessary in all cases???
951
952             elsif Is_Ref_To_Bit_Packed_Array (Actual) then
953                Add_Packed_Call_By_Copy_Code;
954
955             --  Similarly, we have to expand slices of packed arrays here
956             --  because the result must be byte aligned.
957
958             elsif Is_Ref_To_Bit_Packed_Slice (Actual) then
959                Add_Call_By_Copy_Code;
960
961             --  Only processing remaining is to pass by copy if this is a
962             --  reference to a possibly unaligned slice, since the caller
963             --  expects an appropriately aligned argument.
964
965             elsif Is_Possibly_Unaligned_Slice (Actual) then
966                Add_Call_By_Copy_Code;
967             end if;
968          end if;
969
970          Next_Formal (Formal);
971          Next_Actual (Actual);
972       end loop;
973
974       --  Find right place to put post call stuff if it is present
975
976       if not Is_Empty_List (Post_Call) then
977
978          --  If call is not a list member, it must be the triggering
979          --  statement of a triggering alternative or an entry call
980          --  alternative, and we can add the post call stuff to the
981          --  corresponding statement list.
982
983          if not Is_List_Member (N) then
984             declare
985                P : constant Node_Id := Parent (N);
986
987             begin
988                pragma Assert (Nkind (P) = N_Triggering_Alternative
989                  or else Nkind (P) = N_Entry_Call_Alternative);
990
991                if Is_Non_Empty_List (Statements (P)) then
992                   Insert_List_Before_And_Analyze
993                     (First (Statements (P)), Post_Call);
994                else
995                   Set_Statements (P, Post_Call);
996                end if;
997             end;
998
999          --  Otherwise, normal case where N is in a statement sequence,
1000          --  just put the post-call stuff after the call statement.
1001
1002          else
1003             Insert_Actions_After (N, Post_Call);
1004          end if;
1005       end if;
1006
1007       --  The call node itself is re-analyzed in Expand_Call.
1008
1009    end Expand_Actuals;
1010
1011    -----------------
1012    -- Expand_Call --
1013    -----------------
1014
1015    --  This procedure handles expansion of function calls and procedure call
1016    --  statements (i.e. it serves as the body for Expand_N_Function_Call and
1017    --  Expand_N_Procedure_Call_Statement. Processing for calls includes:
1018
1019    --    Replace call to Raise_Exception by Raise_Exception always if possible
1020    --    Provide values of actuals for all formals in Extra_Formals list
1021    --    Replace "call" to enumeration literal function by literal itself
1022    --    Rewrite call to predefined operator as operator
1023    --    Replace actuals to in-out parameters that are numeric conversions,
1024    --     with explicit assignment to temporaries before and after the call.
1025    --    Remove optional actuals if First_Optional_Parameter specified.
1026
1027    --   Note that the list of actuals has been filled with default expressions
1028    --   during semantic analysis of the call. Only the extra actuals required
1029    --   for the 'Constrained attribute and for accessibility checks are added
1030    --   at this point.
1031
1032    procedure Expand_Call (N : Node_Id) is
1033       Loc           : constant Source_Ptr := Sloc (N);
1034       Remote        : constant Boolean    := Is_Remote_Call (N);
1035       Subp          : Entity_Id;
1036       Orig_Subp     : Entity_Id := Empty;
1037       Parent_Subp   : Entity_Id;
1038       Parent_Formal : Entity_Id;
1039       Actual        : Node_Id;
1040       Formal        : Entity_Id;
1041       Prev          : Node_Id := Empty;
1042       Prev_Orig     : Node_Id;
1043       Scop          : Entity_Id;
1044       Extra_Actuals : List_Id := No_List;
1045       Cond          : Node_Id;
1046
1047       procedure Add_Actual_Parameter (Insert_Param : Node_Id);
1048       --  Adds one entry to the end of the actual parameter list. Used for
1049       --  default parameters and for extra actuals (for Extra_Formals).
1050       --  The argument is an N_Parameter_Association node.
1051
1052       procedure Add_Extra_Actual (Expr : Node_Id; EF : Entity_Id);
1053       --  Adds an extra actual to the list of extra actuals. Expr
1054       --  is the expression for the value of the actual, EF is the
1055       --  entity for the extra formal.
1056
1057       function Inherited_From_Formal (S : Entity_Id) return Entity_Id;
1058       --  Within an instance, a type derived from a non-tagged formal derived
1059       --  type inherits from the original parent, not from the actual. This is
1060       --  tested in 4723-003. The current derivation mechanism has the derived
1061       --  type inherit from the actual, which is only correct outside of the
1062       --  instance. If the subprogram is inherited, we test for this particular
1063       --  case through a convoluted tree traversal before setting the proper
1064       --  subprogram to be called.
1065
1066       --------------------------
1067       -- Add_Actual_Parameter --
1068       --------------------------
1069
1070       procedure Add_Actual_Parameter (Insert_Param : Node_Id) is
1071          Actual_Expr : constant Node_Id :=
1072                          Explicit_Actual_Parameter (Insert_Param);
1073
1074       begin
1075          --  Case of insertion is first named actual
1076
1077          if No (Prev) or else
1078             Nkind (Parent (Prev)) /= N_Parameter_Association
1079          then
1080             Set_Next_Named_Actual (Insert_Param, First_Named_Actual (N));
1081             Set_First_Named_Actual (N, Actual_Expr);
1082
1083             if No (Prev) then
1084                if not Present (Parameter_Associations (N)) then
1085                   Set_Parameter_Associations (N, New_List);
1086                   Append (Insert_Param, Parameter_Associations (N));
1087                end if;
1088             else
1089                Insert_After (Prev, Insert_Param);
1090             end if;
1091
1092          --  Case of insertion is not first named actual
1093
1094          else
1095             Set_Next_Named_Actual
1096               (Insert_Param, Next_Named_Actual (Parent (Prev)));
1097             Set_Next_Named_Actual (Parent (Prev), Actual_Expr);
1098             Append (Insert_Param, Parameter_Associations (N));
1099          end if;
1100
1101          Prev := Actual_Expr;
1102       end Add_Actual_Parameter;
1103
1104       ----------------------
1105       -- Add_Extra_Actual --
1106       ----------------------
1107
1108       procedure Add_Extra_Actual (Expr : Node_Id; EF : Entity_Id) is
1109          Loc : constant Source_Ptr := Sloc (Expr);
1110
1111       begin
1112          if Extra_Actuals = No_List then
1113             Extra_Actuals := New_List;
1114             Set_Parent (Extra_Actuals, N);
1115          end if;
1116
1117          Append_To (Extra_Actuals,
1118            Make_Parameter_Association (Loc,
1119              Explicit_Actual_Parameter => Expr,
1120              Selector_Name =>
1121                Make_Identifier (Loc, Chars (EF))));
1122
1123          Analyze_And_Resolve (Expr, Etype (EF));
1124       end Add_Extra_Actual;
1125
1126       ---------------------------
1127       -- Inherited_From_Formal --
1128       ---------------------------
1129
1130       function Inherited_From_Formal (S : Entity_Id) return Entity_Id is
1131          Par      : Entity_Id;
1132          Gen_Par  : Entity_Id;
1133          Gen_Prim : Elist_Id;
1134          Elmt     : Elmt_Id;
1135          Indic    : Node_Id;
1136
1137       begin
1138          --  If the operation is inherited, it is attached to the corresponding
1139          --  type derivation. If the parent in the derivation is a generic
1140          --  actual, it is a subtype of the actual, and we have to recover the
1141          --  original derived type declaration to find the proper parent.
1142
1143          if Nkind (Parent (S)) /= N_Full_Type_Declaration
1144            or else not Is_Derived_Type (Defining_Identifier (Parent (S)))
1145            or else Nkind (Type_Definition (Original_Node (Parent (S))))
1146              /= N_Derived_Type_Definition
1147            or else not In_Instance
1148          then
1149             return Empty;
1150
1151          else
1152             Indic :=
1153               (Subtype_Indication
1154                 (Type_Definition (Original_Node (Parent (S)))));
1155
1156             if Nkind (Indic) = N_Subtype_Indication then
1157                Par := Entity (Subtype_Mark (Indic));
1158             else
1159                Par := Entity (Indic);
1160             end if;
1161          end if;
1162
1163          if not Is_Generic_Actual_Type (Par)
1164            or else Is_Tagged_Type (Par)
1165            or else Nkind (Parent (Par)) /= N_Subtype_Declaration
1166            or else not In_Open_Scopes (Scope (Par))
1167          then
1168             return Empty;
1169
1170          else
1171             Gen_Par := Generic_Parent_Type (Parent (Par));
1172          end if;
1173
1174          --  If the generic parent type is still the generic type, this
1175          --  is a private formal, not a derived formal, and there are no
1176          --  operations inherited from the formal.
1177
1178          if Nkind (Parent (Gen_Par)) = N_Formal_Type_Declaration then
1179             return Empty;
1180          end if;
1181
1182          Gen_Prim := Collect_Primitive_Operations (Gen_Par);
1183          Elmt := First_Elmt (Gen_Prim);
1184
1185          while Present (Elmt) loop
1186             if Chars (Node (Elmt)) = Chars (S) then
1187                declare
1188                   F1 : Entity_Id;
1189                   F2 : Entity_Id;
1190                begin
1191
1192                   F1 := First_Formal (S);
1193                   F2 := First_Formal (Node (Elmt));
1194
1195                   while Present (F1)
1196                     and then Present (F2)
1197                   loop
1198
1199                      if Etype (F1) = Etype (F2)
1200                        or else Etype (F2) = Gen_Par
1201                      then
1202                         Next_Formal (F1);
1203                         Next_Formal (F2);
1204                      else
1205                         Next_Elmt (Elmt);
1206                         exit;   --  not the right subprogram
1207                      end if;
1208
1209                      return Node (Elmt);
1210                   end loop;
1211                end;
1212
1213             else
1214                Next_Elmt (Elmt);
1215             end if;
1216          end loop;
1217
1218          raise Program_Error;
1219       end Inherited_From_Formal;
1220
1221    --  Start of processing for Expand_Call
1222
1223    begin
1224       --  Ignore if previous error
1225
1226       if Nkind (N) in N_Has_Etype and then Etype (N) = Any_Type then
1227          return;
1228       end if;
1229
1230       --  Call using access to subprogram with explicit dereference
1231
1232       if Nkind (Name (N)) = N_Explicit_Dereference then
1233          Subp        := Etype (Name (N));
1234          Parent_Subp := Empty;
1235
1236       --  Case of call to simple entry, where the Name is a selected component
1237       --  whose prefix is the task, and whose selector name is the entry name
1238
1239       elsif Nkind (Name (N)) = N_Selected_Component then
1240          Subp        := Entity (Selector_Name (Name (N)));
1241          Parent_Subp := Empty;
1242
1243       --  Case of call to member of entry family, where Name is an indexed
1244       --  component, with the prefix being a selected component giving the
1245       --  task and entry family name, and the index being the entry index.
1246
1247       elsif Nkind (Name (N)) = N_Indexed_Component then
1248          Subp        := Entity (Selector_Name (Prefix (Name (N))));
1249          Parent_Subp := Empty;
1250
1251       --  Normal case
1252
1253       else
1254          Subp        := Entity (Name (N));
1255          Parent_Subp := Alias (Subp);
1256
1257          --  Replace call to Raise_Exception by call to Raise_Exception_Always
1258          --  if we can tell that the first parameter cannot possibly be null.
1259          --  This helps optimization and also generation of warnings.
1260
1261          if not Restrictions (No_Exception_Handlers)
1262            and then Is_RTE (Subp, RE_Raise_Exception)
1263          then
1264             declare
1265                FA : constant Node_Id := Original_Node (First_Actual (N));
1266
1267             begin
1268                --  The case we catch is where the first argument is obtained
1269                --  using the Identity attribute (which must always be non-null)
1270
1271                if Nkind (FA) = N_Attribute_Reference
1272                  and then Attribute_Name (FA) = Name_Identity
1273                then
1274                   Subp := RTE (RE_Raise_Exception_Always);
1275                   Set_Entity (Name (N), Subp);
1276                end if;
1277             end;
1278          end if;
1279
1280          if Ekind (Subp) = E_Entry then
1281             Parent_Subp := Empty;
1282          end if;
1283       end if;
1284
1285       --  First step, compute extra actuals, corresponding to any
1286       --  Extra_Formals present. Note that we do not access Extra_Formals
1287       --  directly, instead we simply note the presence of the extra
1288       --  formals as we process the regular formals and collect the
1289       --  corresponding actuals in Extra_Actuals.
1290
1291       --  We also generate any required range checks for actuals as we go
1292       --  through the loop, since this is a convenient place to do this.
1293
1294       Formal := First_Formal (Subp);
1295       Actual := First_Actual (N);
1296       while Present (Formal) loop
1297
1298          --  Generate range check if required (not activated yet ???)
1299
1300 --         if Do_Range_Check (Actual) then
1301 --            Set_Do_Range_Check (Actual, False);
1302 --            Generate_Range_Check
1303 --              (Actual, Etype (Formal), CE_Range_Check_Failed);
1304 --         end if;
1305
1306          --  Prepare to examine current entry
1307
1308          Prev := Actual;
1309          Prev_Orig := Original_Node (Prev);
1310
1311          --  Create possible extra actual for constrained case. Usually,
1312          --  the extra actual is of the form actual'constrained, but since
1313          --  this attribute is only available for unconstrained records,
1314          --  TRUE is expanded if the type of the formal happens to be
1315          --  constrained (for instance when this procedure is inherited
1316          --  from an unconstrained record to a constrained one) or if the
1317          --  actual has no discriminant (its type is constrained). An
1318          --  exception to this is the case of a private type without
1319          --  discriminants. In this case we pass FALSE because the
1320          --  object has underlying discriminants with defaults.
1321
1322          if Present (Extra_Constrained (Formal)) then
1323             if Ekind (Etype (Prev)) in Private_Kind
1324               and then not Has_Discriminants (Base_Type (Etype (Prev)))
1325             then
1326                Add_Extra_Actual (
1327                  New_Occurrence_Of (Standard_False, Loc),
1328                  Extra_Constrained (Formal));
1329
1330             elsif Is_Constrained (Etype (Formal))
1331               or else not Has_Discriminants (Etype (Prev))
1332             then
1333                Add_Extra_Actual (
1334                  New_Occurrence_Of (Standard_True, Loc),
1335                  Extra_Constrained (Formal));
1336
1337             else
1338                --  If the actual is a type conversion, then the constrained
1339                --  test applies to the actual, not the target type.
1340
1341                declare
1342                   Act_Prev : Node_Id := Prev;
1343
1344                begin
1345                   --  Test for unchecked conversions as well, which can
1346                   --  occur as out parameter actuals on calls to stream
1347                   --  procedures.
1348
1349                   while Nkind (Act_Prev) = N_Type_Conversion
1350                     or else Nkind (Act_Prev) = N_Unchecked_Type_Conversion
1351                   loop
1352                      Act_Prev := Expression (Act_Prev);
1353                   end loop;
1354
1355                   Add_Extra_Actual (
1356                     Make_Attribute_Reference (Sloc (Prev),
1357                       Prefix =>
1358                         Duplicate_Subexpr_No_Checks
1359                           (Act_Prev, Name_Req => True),
1360                       Attribute_Name => Name_Constrained),
1361                     Extra_Constrained (Formal));
1362                end;
1363             end if;
1364          end if;
1365
1366          --  Create possible extra actual for accessibility level
1367
1368          if Present (Extra_Accessibility (Formal)) then
1369             if Is_Entity_Name (Prev_Orig) then
1370
1371                --  When passing an access parameter as the actual to another
1372                --  access parameter we need to pass along the actual's own
1373                --  associated access level parameter. This is done is we are
1374                --  in the scope of the formal access parameter (if this is an
1375                --  inlined body the extra formal is irrelevant).
1376
1377                if Ekind (Entity (Prev_Orig)) in Formal_Kind
1378                  and then Ekind (Etype (Prev_Orig)) = E_Anonymous_Access_Type
1379                  and then In_Open_Scopes (Scope (Entity (Prev_Orig)))
1380                then
1381                   declare
1382                      Parm_Ent : constant Entity_Id := Param_Entity (Prev_Orig);
1383
1384                   begin
1385                      pragma Assert (Present (Parm_Ent));
1386
1387                      if Present (Extra_Accessibility (Parm_Ent)) then
1388                         Add_Extra_Actual (
1389                           New_Occurrence_Of
1390                             (Extra_Accessibility (Parm_Ent), Loc),
1391                           Extra_Accessibility (Formal));
1392
1393                      --  If the actual access parameter does not have an
1394                      --  associated extra formal providing its scope level,
1395                      --  then treat the actual as having library-level
1396                      --  accessibility.
1397
1398                      else
1399                         Add_Extra_Actual (
1400                           Make_Integer_Literal (Loc,
1401                             Intval => Scope_Depth (Standard_Standard)),
1402                           Extra_Accessibility (Formal));
1403                      end if;
1404                   end;
1405
1406                --  The actual is a normal access value, so just pass the
1407                --  level of the actual's access type.
1408
1409                else
1410                   Add_Extra_Actual (
1411                     Make_Integer_Literal (Loc,
1412                       Intval => Type_Access_Level (Etype (Prev_Orig))),
1413                     Extra_Accessibility (Formal));
1414                end if;
1415
1416             else
1417                case Nkind (Prev_Orig) is
1418
1419                   when N_Attribute_Reference =>
1420
1421                      case Get_Attribute_Id (Attribute_Name (Prev_Orig)) is
1422
1423                         --  For X'Access, pass on the level of the prefix X
1424
1425                         when Attribute_Access =>
1426                            Add_Extra_Actual (
1427                              Make_Integer_Literal (Loc,
1428                                Intval =>
1429                                  Object_Access_Level (Prefix (Prev_Orig))),
1430                              Extra_Accessibility (Formal));
1431
1432                         --  Treat the unchecked attributes as library-level
1433
1434                         when Attribute_Unchecked_Access |
1435                            Attribute_Unrestricted_Access =>
1436                            Add_Extra_Actual (
1437                              Make_Integer_Literal (Loc,
1438                                Intval => Scope_Depth (Standard_Standard)),
1439                              Extra_Accessibility (Formal));
1440
1441                         --  No other cases of attributes returning access
1442                         --  values that can be passed to access parameters
1443
1444                         when others =>
1445                            raise Program_Error;
1446
1447                      end case;
1448
1449                   --  For allocators we pass the level of the execution of
1450                   --  the called subprogram, which is one greater than the
1451                   --  current scope level.
1452
1453                   when N_Allocator =>
1454                      Add_Extra_Actual (
1455                        Make_Integer_Literal (Loc,
1456                         Scope_Depth (Current_Scope) + 1),
1457                        Extra_Accessibility (Formal));
1458
1459                   --  For other cases we simply pass the level of the
1460                   --  actual's access type.
1461
1462                   when others =>
1463                      Add_Extra_Actual (
1464                        Make_Integer_Literal (Loc,
1465                          Intval => Type_Access_Level (Etype (Prev_Orig))),
1466                        Extra_Accessibility (Formal));
1467
1468                end case;
1469             end if;
1470          end if;
1471
1472          --  Perform the check of 4.6(49) that prevents a null value
1473          --  from being passed as an actual to an access parameter.
1474          --  Note that the check is elided in the common cases of
1475          --  passing an access attribute or access parameter as an
1476          --  actual. Also, we currently don't enforce this check for
1477          --  expander-generated actuals and when -gnatdj is set.
1478
1479          if Ekind (Etype (Formal)) /= E_Anonymous_Access_Type
1480            or else Access_Checks_Suppressed (Subp)
1481          then
1482             null;
1483
1484          elsif Debug_Flag_J then
1485             null;
1486
1487          elsif not Comes_From_Source (Prev) then
1488             null;
1489
1490          elsif Is_Entity_Name (Prev)
1491            and then Ekind (Etype (Prev)) = E_Anonymous_Access_Type
1492          then
1493             null;
1494
1495          elsif Nkind (Prev) = N_Allocator
1496            or else Nkind (Prev) = N_Attribute_Reference
1497          then
1498             null;
1499
1500          --  Suppress null checks when passing to access parameters
1501          --  of Java subprograms. (Should this be done for other
1502          --  foreign conventions as well ???)
1503
1504          elsif Convention (Subp) = Convention_Java then
1505             null;
1506
1507          else
1508             Cond :=
1509               Make_Op_Eq (Loc,
1510                 Left_Opnd => Duplicate_Subexpr_No_Checks (Prev),
1511                 Right_Opnd => Make_Null (Loc));
1512             Insert_Action (Prev,
1513               Make_Raise_Constraint_Error (Loc,
1514                 Condition => Cond,
1515                 Reason    => CE_Access_Parameter_Is_Null));
1516          end if;
1517
1518          --  Perform appropriate validity checks on parameters that
1519          --  are entities.
1520
1521          if Validity_Checks_On then
1522             if Ekind (Formal) = E_In_Parameter
1523               and then Validity_Check_In_Params
1524               and then Is_Entity_Name (Actual)
1525             then
1526                Ensure_Valid (Actual);
1527
1528             elsif Ekind (Formal) = E_In_Out_Parameter
1529               and then Validity_Check_In_Out_Params
1530             then
1531                Ensure_Valid (Actual);
1532             end if;
1533          end if;
1534
1535          --  For IN OUT and OUT parameters, ensure that subscripts are valid
1536          --  since this is a left side reference. We only do this for calls
1537          --  from the source program since we assume that compiler generated
1538          --  calls explicitly generate any required checks. We also need it
1539          --  only if we are doing standard validity checks, since clearly it
1540          --  is not needed if validity checks are off, and in subscript
1541          --  validity checking mode, all indexed components are checked with
1542          --  a call directly from Expand_N_Indexed_Component.
1543
1544          if Comes_From_Source (N)
1545            and then Ekind (Formal) /= E_In_Parameter
1546            and then Validity_Checks_On
1547            and then Validity_Check_Default
1548            and then not Validity_Check_Subscripts
1549          then
1550             Check_Valid_Lvalue_Subscripts (Actual);
1551          end if;
1552
1553          --  Mark any scalar OUT parameter that is a simple variable
1554          --  as no longer known to be valid (unless the type is always
1555          --  valid). This reflects the fact that if an OUT parameter
1556          --  is never set in a procedure, then it can become invalid
1557          --  on return from the procedure.
1558
1559          if Ekind (Formal) = E_Out_Parameter
1560            and then Is_Entity_Name (Actual)
1561            and then Ekind (Entity (Actual)) = E_Variable
1562            and then not Is_Known_Valid (Etype (Actual))
1563          then
1564             Set_Is_Known_Valid (Entity (Actual), False);
1565          end if;
1566
1567          --  For an OUT or IN OUT parameter of an access type, if the
1568          --  actual is an entity, then it is no longer known to be non-null.
1569
1570          if Ekind (Formal) /= E_In_Parameter
1571            and then Is_Entity_Name (Actual)
1572            and then Is_Access_Type (Etype (Actual))
1573          then
1574             Set_Is_Known_Non_Null (Entity (Actual), False);
1575          end if;
1576
1577          --  If the formal is class wide and the actual is an aggregate, force
1578          --  evaluation so that the back end who does not know about class-wide
1579          --  type, does not generate a temporary of the wrong size.
1580
1581          if not Is_Class_Wide_Type (Etype (Formal)) then
1582             null;
1583
1584          elsif Nkind (Actual) = N_Aggregate
1585            or else (Nkind (Actual) = N_Qualified_Expression
1586                      and then Nkind (Expression (Actual)) = N_Aggregate)
1587          then
1588             Force_Evaluation (Actual);
1589          end if;
1590
1591          --  In a remote call, if the formal is of a class-wide type, check
1592          --  that the actual meets the requirements described in E.4(18).
1593
1594          if Remote
1595            and then Is_Class_Wide_Type (Etype (Formal))
1596          then
1597             Insert_Action (Actual,
1598               Make_Implicit_If_Statement (N,
1599                 Condition       =>
1600                   Make_Op_Not (Loc,
1601                     Get_Remotely_Callable
1602                       (Duplicate_Subexpr_Move_Checks (Actual))),
1603                 Then_Statements => New_List (
1604                   Make_Procedure_Call_Statement (Loc,
1605                     New_Occurrence_Of (RTE
1606                       (RE_Raise_Program_Error_For_E_4_18), Loc)))));
1607          end if;
1608
1609          Next_Actual (Actual);
1610          Next_Formal (Formal);
1611       end loop;
1612
1613       --  If we are expanding a rhs of an assignement we need to check if
1614       --  tag propagation is needed. This code belongs theorically in Analyze
1615       --  Assignment but has to be done earlier (bottom-up) because the
1616       --  assignment might be transformed into a declaration for an uncons-
1617       --  trained value, if the expression is classwide.
1618
1619       if Nkind (N) = N_Function_Call
1620         and then Is_Tag_Indeterminate (N)
1621         and then Is_Entity_Name (Name (N))
1622       then
1623          declare
1624             Ass : Node_Id := Empty;
1625
1626          begin
1627             if Nkind (Parent (N)) = N_Assignment_Statement then
1628                Ass := Parent (N);
1629
1630             elsif Nkind (Parent (N)) = N_Qualified_Expression
1631               and then Nkind (Parent (Parent (N))) = N_Assignment_Statement
1632             then
1633                Ass := Parent (Parent (N));
1634             end if;
1635
1636             if Present (Ass)
1637               and then Is_Class_Wide_Type (Etype (Name (Ass)))
1638             then
1639                if Etype (N) /= Root_Type (Etype (Name (Ass))) then
1640                   Error_Msg_NE
1641                     ("tag-indeterminate expression must have type&"
1642                       & "('R'M 5.2 (6))", N, Root_Type (Etype (Name (Ass))));
1643                else
1644                   Propagate_Tag (Name (Ass), N);
1645                end if;
1646
1647                --  The call will be rewritten as a dispatching call, and
1648                --  expanded as such.
1649
1650                return;
1651             end if;
1652          end;
1653       end if;
1654
1655       --  Deals with Dispatch_Call if we still have a call, before expanding
1656       --  extra actuals since this will be done on the re-analysis of the
1657       --  dispatching call. Note that we do not try to shorten the actual
1658       --  list for a dispatching call, it would not make sense to do so.
1659       --  Expansion of dispatching calls is suppressed when Java_VM, because
1660       --  the JVM back end directly handles the generation of dispatching
1661       --  calls and would have to undo any expansion to an indirect call.
1662
1663       if (Nkind (N) = N_Function_Call
1664            or else Nkind (N) =  N_Procedure_Call_Statement)
1665         and then Present (Controlling_Argument (N))
1666         and then not Java_VM
1667       then
1668          Expand_Dispatch_Call (N);
1669
1670          --  The following return is worrisome. Is it really OK to
1671          --  skip all remaining processing in this procedure ???
1672
1673          return;
1674
1675       --  Similarly, expand calls to RCI subprograms on which pragma
1676       --  All_Calls_Remote applies. The rewriting will be reanalyzed
1677       --  later. Do this only when the call comes from source since we do
1678       --  not want such a rewritting to occur in expanded code.
1679
1680       elsif Is_All_Remote_Call (N) then
1681          Expand_All_Calls_Remote_Subprogram_Call (N);
1682
1683       --  Similarly, do not add extra actuals for an entry call whose entity
1684       --  is a protected procedure, or for an internal protected subprogram
1685       --  call, because it will be rewritten as a protected subprogram call
1686       --  and reanalyzed (see Expand_Protected_Subprogram_Call).
1687
1688       elsif Is_Protected_Type (Scope (Subp))
1689          and then (Ekind (Subp) = E_Procedure
1690                     or else Ekind (Subp) = E_Function)
1691       then
1692          null;
1693
1694       --  During that loop we gathered the extra actuals (the ones that
1695       --  correspond to Extra_Formals), so now they can be appended.
1696
1697       else
1698          while Is_Non_Empty_List (Extra_Actuals) loop
1699             Add_Actual_Parameter (Remove_Head (Extra_Actuals));
1700          end loop;
1701       end if;
1702
1703       if Ekind (Subp) = E_Procedure
1704          or else (Ekind (Subp) = E_Subprogram_Type
1705                    and then Etype (Subp) = Standard_Void_Type)
1706          or else Is_Entry (Subp)
1707       then
1708          Expand_Actuals (N, Subp);
1709       end if;
1710
1711       --  If the subprogram is a renaming, or if it is inherited, replace it
1712       --  in the call with the name of the actual subprogram being called.
1713       --  If this is a dispatching call, the run-time decides what to call.
1714       --  The Alias attribute does not apply to entries.
1715
1716       if Nkind (N) /= N_Entry_Call_Statement
1717         and then No (Controlling_Argument (N))
1718         and then Present (Parent_Subp)
1719       then
1720          if Present (Inherited_From_Formal (Subp)) then
1721             Parent_Subp := Inherited_From_Formal (Subp);
1722          else
1723             while Present (Alias (Parent_Subp)) loop
1724                Parent_Subp := Alias (Parent_Subp);
1725             end loop;
1726          end if;
1727
1728          Set_Entity (Name (N), Parent_Subp);
1729
1730          if Is_Abstract (Parent_Subp)
1731            and then not In_Instance
1732          then
1733             Error_Msg_NE
1734               ("cannot call abstract subprogram &!", Name (N), Parent_Subp);
1735          end if;
1736
1737          --  Add an explicit conversion for parameter of the derived type.
1738          --  This is only done for scalar and access in-parameters. Others
1739          --  have been expanded in expand_actuals.
1740
1741          Formal := First_Formal (Subp);
1742          Parent_Formal := First_Formal (Parent_Subp);
1743          Actual := First_Actual (N);
1744
1745          --  It is not clear that conversion is needed for intrinsic
1746          --  subprograms, but it certainly is for those that are user-
1747          --  defined, and that can be inherited on derivation, namely
1748          --  unchecked conversion and deallocation.
1749          --  General case needs study ???
1750
1751          if not Is_Intrinsic_Subprogram (Parent_Subp)
1752            or else Is_Generic_Instance (Parent_Subp)
1753          then
1754             while Present (Formal) loop
1755
1756                if Etype (Formal) /= Etype (Parent_Formal)
1757                  and then Is_Scalar_Type (Etype (Formal))
1758                  and then Ekind (Formal) = E_In_Parameter
1759                  and then not Raises_Constraint_Error (Actual)
1760                then
1761                   Rewrite (Actual,
1762                     OK_Convert_To (Etype (Parent_Formal),
1763                       Relocate_Node (Actual)));
1764
1765                   Analyze (Actual);
1766                   Resolve (Actual, Etype (Parent_Formal));
1767                   Enable_Range_Check (Actual);
1768
1769                elsif Is_Access_Type (Etype (Formal))
1770                  and then Base_Type (Etype (Parent_Formal))
1771                    /= Base_Type (Etype (Actual))
1772                then
1773                   if Ekind (Formal) /= E_In_Parameter then
1774                      Rewrite (Actual,
1775                        Convert_To (Etype (Parent_Formal),
1776                          Relocate_Node (Actual)));
1777
1778                      Analyze (Actual);
1779                      Resolve (Actual, Etype (Parent_Formal));
1780
1781                   elsif
1782                     Ekind (Etype (Parent_Formal)) = E_Anonymous_Access_Type
1783                       and then Designated_Type (Etype (Parent_Formal))
1784                                  /=
1785                                Designated_Type (Etype (Actual))
1786                       and then not Is_Controlling_Formal (Formal)
1787                   then
1788                      --  This unchecked conversion is not necessary unless
1789                      --  inlining is enabled, because in that case the type
1790                      --  mismatch may become visible in the body about to be
1791                      --  inlined.
1792
1793                      Rewrite (Actual,
1794                        Unchecked_Convert_To (Etype (Parent_Formal),
1795                          Relocate_Node (Actual)));
1796
1797                      Analyze (Actual);
1798                      Resolve (Actual, Etype (Parent_Formal));
1799                   end if;
1800                end if;
1801
1802                Next_Formal (Formal);
1803                Next_Formal (Parent_Formal);
1804                Next_Actual (Actual);
1805             end loop;
1806          end if;
1807
1808          Orig_Subp := Subp;
1809          Subp := Parent_Subp;
1810       end if;
1811
1812       if Is_RTE (Subp, RE_Abort_Task) then
1813          Check_Restriction (No_Abort_Statements, N);
1814       end if;
1815
1816       --  Some more special cases for cases other than explicit dereference
1817
1818       if Nkind (Name (N)) /= N_Explicit_Dereference then
1819
1820          --  Calls to an enumeration literal are replaced by the literal
1821          --  This case occurs only when we have a call to a function that
1822          --  is a renaming of an enumeration literal. The normal case of
1823          --  a direct reference to an enumeration literal has already been
1824          --  been dealt with by Resolve_Call. If the function is itself
1825          --  inherited (see 7423-001) the literal of the parent type must
1826          --  be explicitly converted to the return type of the function.
1827
1828          if Ekind (Subp) = E_Enumeration_Literal then
1829             if Base_Type (Etype (Subp)) /= Base_Type (Etype (N)) then
1830                Rewrite
1831                  (N, Convert_To (Etype (N), New_Occurrence_Of (Subp, Loc)));
1832             else
1833                Rewrite (N, New_Occurrence_Of (Subp, Loc));
1834             end if;
1835
1836             Resolve (N);
1837          end if;
1838
1839       --  Handle case of access to protected subprogram type
1840
1841       else
1842          if Ekind (Base_Type (Etype (Prefix (Name (N))))) =
1843                                E_Access_Protected_Subprogram_Type
1844          then
1845             --  If this is a call through an access to protected operation,
1846             --  the prefix has the form (object'address, operation'access).
1847             --  Rewrite as a for other protected calls: the object is the
1848             --  first parameter of the list of actuals.
1849
1850             declare
1851                Call : Node_Id;
1852                Parm : List_Id;
1853                Nam  : Node_Id;
1854                Obj  : Node_Id;
1855                Ptr  : constant Node_Id := Prefix (Name (N));
1856
1857                T : constant Entity_Id :=
1858                      Equivalent_Type (Base_Type (Etype (Ptr)));
1859
1860                D_T : constant Entity_Id :=
1861                        Designated_Type (Base_Type (Etype (Ptr)));
1862
1863             begin
1864                Obj := Make_Selected_Component (Loc,
1865                  Prefix => Unchecked_Convert_To (T, Ptr),
1866                  Selector_Name => New_Occurrence_Of (First_Entity (T), Loc));
1867
1868                Nam := Make_Selected_Component (Loc,
1869                  Prefix => Unchecked_Convert_To (T, Ptr),
1870                  Selector_Name => New_Occurrence_Of (
1871                    Next_Entity (First_Entity (T)), Loc));
1872
1873                Nam := Make_Explicit_Dereference (Loc, Nam);
1874
1875                if Present (Parameter_Associations (N))  then
1876                   Parm := Parameter_Associations (N);
1877                else
1878                   Parm := New_List;
1879                end if;
1880
1881                Prepend (Obj, Parm);
1882
1883                if Etype (D_T) = Standard_Void_Type then
1884                   Call := Make_Procedure_Call_Statement (Loc,
1885                     Name => Nam,
1886                     Parameter_Associations => Parm);
1887                else
1888                   Call := Make_Function_Call (Loc,
1889                     Name => Nam,
1890                     Parameter_Associations => Parm);
1891                end if;
1892
1893                Set_First_Named_Actual (Call, First_Named_Actual (N));
1894                Set_Etype (Call, Etype (D_T));
1895
1896                --  We do not re-analyze the call to avoid infinite recursion.
1897                --  We analyze separately the prefix and the object, and set
1898                --  the checks on the prefix that would otherwise be emitted
1899                --  when resolving a call.
1900
1901                Rewrite (N, Call);
1902                Analyze (Nam);
1903                Apply_Access_Check (Nam);
1904                Analyze (Obj);
1905                return;
1906             end;
1907          end if;
1908       end if;
1909
1910       --  If this is a call to an intrinsic subprogram, then perform the
1911       --  appropriate expansion to the corresponding tree node and we
1912       --  are all done (since after that the call is gone!)
1913
1914       if Is_Intrinsic_Subprogram (Subp) then
1915          Expand_Intrinsic_Call (N, Subp);
1916          return;
1917       end if;
1918
1919       if Ekind (Subp) = E_Function
1920         or else Ekind (Subp) = E_Procedure
1921       then
1922          if Is_Inlined (Subp) then
1923
1924             declare
1925                Bod         : Node_Id;
1926                Must_Inline : Boolean := False;
1927                Spec        : constant Node_Id := Unit_Declaration_Node (Subp);
1928
1929             begin
1930                --  Verify that the body to inline has already been seen,
1931                --  and that if the body is in the current unit the inlining
1932                --  does not occur earlier. This avoids order-of-elaboration
1933                --  problems in gigi.
1934
1935                if No (Spec)
1936                  or else Nkind (Spec) /= N_Subprogram_Declaration
1937                  or else No (Body_To_Inline (Spec))
1938                then
1939                   Must_Inline := False;
1940
1941                else
1942                   Bod := Body_To_Inline (Spec);
1943
1944                   if (In_Extended_Main_Code_Unit (N)
1945                         or else In_Extended_Main_Code_Unit (Parent (N))
1946                         or else Is_Always_Inlined (Subp))
1947                     and then (not In_Same_Extended_Unit (Sloc (Bod), Loc)
1948                                or else
1949                                  Earlier_In_Extended_Unit (Sloc (Bod), Loc))
1950                   then
1951                      Must_Inline := True;
1952
1953                   --  If we are compiling a package body that is not the main
1954                   --  unit, it must be for inlining/instantiation purposes,
1955                   --  in which case we inline the call to insure that the same
1956                   --  temporaries are generated when compiling the body by
1957                   --  itself. Otherwise link errors can occur.
1958
1959                   elsif not (In_Extended_Main_Code_Unit (N))
1960                     and then In_Package_Body
1961                   then
1962                      Must_Inline := True;
1963                   end if;
1964                end if;
1965
1966                if Must_Inline then
1967                   Expand_Inlined_Call (N, Subp, Orig_Subp);
1968
1969                else
1970                   --  Let the back end handle it
1971
1972                   Add_Inlined_Body (Subp);
1973
1974                   if Front_End_Inlining
1975                     and then Nkind (Spec) = N_Subprogram_Declaration
1976                     and then (In_Extended_Main_Code_Unit (N))
1977                     and then No (Body_To_Inline (Spec))
1978                     and then not Has_Completion (Subp)
1979                     and then In_Same_Extended_Unit (Sloc (Spec), Loc)
1980                   then
1981                      Cannot_Inline
1982                       ("cannot inline& (body not seen yet)?",
1983                        N, Subp);
1984                   end if;
1985                end if;
1986             end;
1987          end if;
1988       end if;
1989
1990       --  Check for a protected subprogram. This is either an intra-object
1991       --  call, or a protected function call. Protected procedure calls are
1992       --  rewritten as entry calls and handled accordingly.
1993
1994       Scop := Scope (Subp);
1995
1996       if Nkind (N) /= N_Entry_Call_Statement
1997         and then Is_Protected_Type (Scop)
1998       then
1999          --  If the call is an internal one, it is rewritten as a call to
2000          --  to the corresponding unprotected subprogram.
2001
2002          Expand_Protected_Subprogram_Call (N, Subp, Scop);
2003       end if;
2004
2005       --  Functions returning controlled objects need special attention
2006
2007       if Controlled_Type (Etype (Subp))
2008         and then not Is_Return_By_Reference_Type (Etype (Subp))
2009       then
2010          Expand_Ctrl_Function_Call (N);
2011       end if;
2012
2013       --  Test for First_Optional_Parameter, and if so, truncate parameter
2014       --  list if there are optional parameters at the trailing end.
2015       --  Note we never delete procedures for call via a pointer.
2016
2017       if (Ekind (Subp) = E_Procedure or else Ekind (Subp) = E_Function)
2018         and then Present (First_Optional_Parameter (Subp))
2019       then
2020          declare
2021             Last_Keep_Arg : Node_Id;
2022
2023          begin
2024             --  Last_Keep_Arg will hold the last actual that should be
2025             --  retained. If it remains empty at the end, it means that
2026             --  all parameters are optional.
2027
2028             Last_Keep_Arg := Empty;
2029
2030             --  Find first optional parameter, must be present since we
2031             --  checked the validity of the parameter before setting it.
2032
2033             Formal := First_Formal (Subp);
2034             Actual := First_Actual (N);
2035             while Formal /= First_Optional_Parameter (Subp) loop
2036                Last_Keep_Arg := Actual;
2037                Next_Formal (Formal);
2038                Next_Actual (Actual);
2039             end loop;
2040
2041             --  We have Formal and Actual pointing to the first potentially
2042             --  droppable argument. We can drop all the trailing arguments
2043             --  whose actual matches the default. Note that we know that all
2044             --  remaining formals have defaults, because we checked that this
2045             --  requirement was met before setting First_Optional_Parameter.
2046
2047             --  We use Fully_Conformant_Expressions to check for identity
2048             --  between formals and actuals, which may miss some cases, but
2049             --  on the other hand, this is only an optimization (if we fail
2050             --  to truncate a parameter it does not affect functionality).
2051             --  So if the default is 3 and the actual is 1+2, we consider
2052             --  them unequal, which hardly seems worrisome.
2053
2054             while Present (Formal) loop
2055                if not Fully_Conformant_Expressions
2056                     (Actual, Default_Value (Formal))
2057                then
2058                   Last_Keep_Arg := Actual;
2059                end if;
2060
2061                Next_Formal (Formal);
2062                Next_Actual (Actual);
2063             end loop;
2064
2065             --  If no arguments, delete entire list, this is the easy case
2066
2067             if No (Last_Keep_Arg) then
2068                while Is_Non_Empty_List (Parameter_Associations (N)) loop
2069                   Delete_Tree (Remove_Head (Parameter_Associations (N)));
2070                end loop;
2071
2072                Set_Parameter_Associations (N, No_List);
2073                Set_First_Named_Actual (N, Empty);
2074
2075             --  Case where at the last retained argument is positional. This
2076             --  is also an easy case, since the retained arguments are already
2077             --  in the right form, and we don't need to worry about the order
2078             --  of arguments that get eliminated.
2079
2080             elsif Is_List_Member (Last_Keep_Arg) then
2081                while Present (Next (Last_Keep_Arg)) loop
2082                   Delete_Tree (Remove_Next (Last_Keep_Arg));
2083                end loop;
2084
2085                Set_First_Named_Actual (N, Empty);
2086
2087             --  This is the annoying case where the last retained argument
2088             --  is a named parameter. Since the original arguments are not
2089             --  in declaration order, we may have to delete some fairly
2090             --  random collection of arguments.
2091
2092             else
2093                declare
2094                   Temp   : Node_Id;
2095                   Passoc : Node_Id;
2096
2097                   Discard : Node_Id;
2098                   pragma Warnings (Off, Discard);
2099
2100                begin
2101                   --  First step, remove all the named parameters from the
2102                   --  list (they are still chained using First_Named_Actual
2103                   --  and Next_Named_Actual, so we have not lost them!)
2104
2105                   Temp := First (Parameter_Associations (N));
2106
2107                   --  Case of all parameters named, remove them all
2108
2109                   if Nkind (Temp) = N_Parameter_Association then
2110                      while Is_Non_Empty_List (Parameter_Associations (N)) loop
2111                         Temp := Remove_Head (Parameter_Associations (N));
2112                      end loop;
2113
2114                   --  Case of mixed positional/named, remove named parameters
2115
2116                   else
2117                      while Nkind (Next (Temp)) /= N_Parameter_Association loop
2118                         Next (Temp);
2119                      end loop;
2120
2121                      while Present (Next (Temp)) loop
2122                         Discard := Remove_Next (Temp);
2123                      end loop;
2124                   end if;
2125
2126                   --  Now we loop through the named parameters, till we get
2127                   --  to the last one to be retained, adding them to the list.
2128                   --  Note that the Next_Named_Actual list does not need to be
2129                   --  touched since we are only reordering them on the actual
2130                   --  parameter association list.
2131
2132                   Passoc := Parent (First_Named_Actual (N));
2133                   loop
2134                      Temp := Relocate_Node (Passoc);
2135                      Append_To
2136                        (Parameter_Associations (N), Temp);
2137                      exit when
2138                        Last_Keep_Arg = Explicit_Actual_Parameter (Passoc);
2139                      Passoc := Parent (Next_Named_Actual (Passoc));
2140                   end loop;
2141
2142                   Set_Next_Named_Actual (Temp, Empty);
2143
2144                   loop
2145                      Temp := Next_Named_Actual (Passoc);
2146                      exit when No (Temp);
2147                      Set_Next_Named_Actual
2148                        (Passoc, Next_Named_Actual (Parent (Temp)));
2149                      Delete_Tree (Temp);
2150                   end loop;
2151                end;
2152             end if;
2153          end;
2154       end if;
2155    end Expand_Call;
2156
2157    --------------------------
2158    -- Expand_Inlined_Call --
2159    --------------------------
2160
2161    procedure Expand_Inlined_Call
2162     (N         : Node_Id;
2163      Subp      : Entity_Id;
2164      Orig_Subp : Entity_Id)
2165    is
2166       Loc       : constant Source_Ptr := Sloc (N);
2167       Is_Predef : constant Boolean :=
2168                    Is_Predefined_File_Name
2169                      (Unit_File_Name (Get_Source_Unit (Subp)));
2170       Orig_Bod  : constant Node_Id :=
2171                     Body_To_Inline (Unit_Declaration_Node (Subp));
2172
2173       Blk      : Node_Id;
2174       Bod      : Node_Id;
2175       Decl     : Node_Id;
2176       Exit_Lab : Entity_Id := Empty;
2177       F        : Entity_Id;
2178       A        : Node_Id;
2179       Lab_Decl : Node_Id;
2180       Lab_Id   : Node_Id;
2181       New_A    : Node_Id;
2182       Num_Ret  : Int := 0;
2183       Ret_Type : Entity_Id;
2184       Targ     : Node_Id;
2185       Temp     : Entity_Id;
2186       Temp_Typ : Entity_Id;
2187
2188       procedure Make_Exit_Label;
2189       --  Build declaration for exit label to be used in Return statements.
2190
2191       function Process_Formals (N : Node_Id) return Traverse_Result;
2192       --  Replace occurrence of a formal with the corresponding actual, or
2193       --  the thunk generated for it.
2194
2195       function Process_Sloc (Nod : Node_Id) return Traverse_Result;
2196       --  If the call being expanded is that of an internal subprogram,
2197       --  set the sloc of the generated block to that of the call itself,
2198       --  so that the expansion is skipped by the -next- command in gdb.
2199       --  Same processing for a subprogram in a predefined file, e.g.
2200       --  Ada.Tags. If Debug_Generated_Code is true, suppress this change
2201       --  to simplify our own development.
2202
2203       procedure Rewrite_Function_Call (N : Node_Id; Blk : Node_Id);
2204       --  If the function body is a single expression, replace call with
2205       --  expression, else insert block appropriately.
2206
2207       procedure Rewrite_Procedure_Call (N : Node_Id; Blk : Node_Id);
2208       --  If procedure body has no local variables, inline body without
2209       --  creating block,  otherwise rewrite call with block.
2210
2211       ---------------------
2212       -- Make_Exit_Label --
2213       ---------------------
2214
2215       procedure Make_Exit_Label is
2216       begin
2217          --  Create exit label for subprogram, if one doesn't exist yet.
2218
2219          if No (Exit_Lab) then
2220             Lab_Id := Make_Identifier (Loc, New_Internal_Name ('L'));
2221             Set_Entity (Lab_Id,
2222               Make_Defining_Identifier (Loc, Chars (Lab_Id)));
2223             Exit_Lab := Make_Label (Loc, Lab_Id);
2224
2225             Lab_Decl :=
2226               Make_Implicit_Label_Declaration (Loc,
2227                 Defining_Identifier  => Entity (Lab_Id),
2228                 Label_Construct      => Exit_Lab);
2229          end if;
2230       end Make_Exit_Label;
2231
2232       ---------------------
2233       -- Process_Formals --
2234       ---------------------
2235
2236       function Process_Formals (N : Node_Id) return Traverse_Result is
2237          A   : Entity_Id;
2238          E   : Entity_Id;
2239          Ret : Node_Id;
2240
2241       begin
2242          if Is_Entity_Name (N)
2243            and then Present (Entity (N))
2244          then
2245             E := Entity (N);
2246
2247             if Is_Formal (E)
2248               and then Scope (E) = Subp
2249             then
2250                A := Renamed_Object (E);
2251
2252                if Is_Entity_Name (A) then
2253                   Rewrite (N, New_Occurrence_Of (Entity (A), Loc));
2254
2255                elsif Nkind (A) = N_Defining_Identifier then
2256                   Rewrite (N, New_Occurrence_Of (A, Loc));
2257
2258                else   --  numeric literal
2259                   Rewrite (N, New_Copy (A));
2260                end if;
2261             end if;
2262
2263             return Skip;
2264
2265          elsif Nkind (N) = N_Return_Statement then
2266
2267             if No (Expression (N)) then
2268                Make_Exit_Label;
2269                Rewrite (N, Make_Goto_Statement (Loc,
2270                  Name => New_Copy (Lab_Id)));
2271
2272             else
2273                if Nkind (Parent (N)) = N_Handled_Sequence_Of_Statements
2274                  and then Nkind (Parent (Parent (N))) = N_Subprogram_Body
2275                then
2276                   --  Function body is a single expression. No need for
2277                   --  exit label.
2278
2279                   null;
2280
2281                else
2282                   Num_Ret := Num_Ret + 1;
2283                   Make_Exit_Label;
2284                end if;
2285
2286                --  Because of the presence of private types, the views of the
2287                --  expression and the context may be different, so place an
2288                --  unchecked conversion to the context type to avoid spurious
2289                --  errors, eg. when the expression is a numeric literal and
2290                --  the context is private. If the expression is an aggregate,
2291                --  use a qualified expression, because an aggregate is not a
2292                --  legal argument of a conversion.
2293
2294                if Nkind (Expression (N)) = N_Aggregate
2295                  or else Nkind (Expression (N)) = N_Null
2296                then
2297                   Ret :=
2298                     Make_Qualified_Expression (Sloc (N),
2299                        Subtype_Mark => New_Occurrence_Of (Ret_Type, Sloc (N)),
2300                        Expression => Relocate_Node (Expression (N)));
2301                else
2302                   Ret :=
2303                     Unchecked_Convert_To
2304                       (Ret_Type, Relocate_Node (Expression (N)));
2305                end if;
2306
2307                if Nkind (Targ) = N_Defining_Identifier then
2308                   Rewrite (N,
2309                     Make_Assignment_Statement (Loc,
2310                       Name => New_Occurrence_Of (Targ, Loc),
2311                       Expression => Ret));
2312                else
2313                   Rewrite (N,
2314                     Make_Assignment_Statement (Loc,
2315                       Name => New_Copy (Targ),
2316                       Expression => Ret));
2317                end if;
2318
2319                Set_Assignment_OK (Name (N));
2320
2321                if Present (Exit_Lab) then
2322                   Insert_After (N,
2323                     Make_Goto_Statement (Loc,
2324                       Name => New_Copy (Lab_Id)));
2325                end if;
2326             end if;
2327
2328             return OK;
2329
2330          --  Remove pragma Unreferenced since it may refer to formals that
2331          --  are not visible in the inlined body, and in any case we will
2332          --  not be posting warnings on the inlined body so it is unneeded.
2333
2334          elsif Nkind (N) = N_Pragma
2335            and then Chars (N) = Name_Unreferenced
2336          then
2337             Rewrite (N, Make_Null_Statement (Sloc (N)));
2338             return OK;
2339
2340          else
2341             return OK;
2342          end if;
2343       end Process_Formals;
2344
2345       procedure Replace_Formals is new Traverse_Proc (Process_Formals);
2346
2347       ------------------
2348       -- Process_Sloc --
2349       ------------------
2350
2351       function Process_Sloc (Nod : Node_Id) return Traverse_Result is
2352       begin
2353          if not Debug_Generated_Code then
2354             Set_Sloc (Nod, Sloc (N));
2355             Set_Comes_From_Source (Nod, False);
2356          end if;
2357
2358          return OK;
2359       end Process_Sloc;
2360
2361       procedure Reset_Slocs is new Traverse_Proc (Process_Sloc);
2362
2363       ---------------------------
2364       -- Rewrite_Function_Call --
2365       ---------------------------
2366
2367       procedure Rewrite_Function_Call (N : Node_Id; Blk : Node_Id) is
2368          HSS : constant Node_Id := Handled_Statement_Sequence (Blk);
2369          Fst : constant Node_Id := First (Statements (HSS));
2370
2371       begin
2372          --  Optimize simple case: function body is a single return statement,
2373          --  which has been expanded into an assignment.
2374
2375          if Is_Empty_List (Declarations (Blk))
2376            and then Nkind (Fst) = N_Assignment_Statement
2377            and then No (Next (Fst))
2378          then
2379
2380             --  The function call may have been rewritten as the temporary
2381             --  that holds the result of the call, in which case remove the
2382             --  now useless declaration.
2383
2384             if Nkind (N) = N_Identifier
2385               and then Nkind (Parent (Entity (N))) = N_Object_Declaration
2386             then
2387                Rewrite (Parent (Entity (N)), Make_Null_Statement (Loc));
2388             end if;
2389
2390             Rewrite (N, Expression (Fst));
2391
2392          elsif Nkind (N) = N_Identifier
2393            and then Nkind (Parent (Entity (N))) = N_Object_Declaration
2394          then
2395
2396             --  The block assigns the result of the call to the temporary.
2397
2398             Insert_After (Parent (Entity (N)), Blk);
2399
2400          elsif Nkind (Parent (N)) = N_Assignment_Statement
2401            and then Is_Entity_Name (Name (Parent (N)))
2402          then
2403
2404             --  Replace assignment with the block
2405
2406             Rewrite (Parent (N), Blk);
2407
2408          elsif Nkind (Parent (N)) = N_Object_Declaration then
2409             Set_Expression (Parent (N), Empty);
2410             Insert_After (Parent (N), Blk);
2411          end if;
2412       end Rewrite_Function_Call;
2413
2414       ----------------------------
2415       -- Rewrite_Procedure_Call --
2416       ----------------------------
2417
2418       procedure Rewrite_Procedure_Call (N : Node_Id; Blk : Node_Id) is
2419          HSS  : constant Node_Id := Handled_Statement_Sequence (Blk);
2420
2421       begin
2422          if Is_Empty_List (Declarations (Blk)) then
2423             Insert_List_After (N, Statements (HSS));
2424             Rewrite (N, Make_Null_Statement (Loc));
2425          else
2426             Rewrite (N, Blk);
2427          end if;
2428       end Rewrite_Procedure_Call;
2429
2430    --  Start of processing for Expand_Inlined_Call
2431
2432    begin
2433       --  Check for special case of To_Address call, and if so, just
2434       --  do an unchecked conversion instead of expanding the call.
2435       --  Not only is this more efficient, but it also avoids a
2436       --  problem with order of elaboration when address clauses
2437       --  are inlined (address expr elaborated at wrong point).
2438
2439       if Subp = RTE (RE_To_Address) then
2440          Rewrite (N,
2441            Unchecked_Convert_To
2442             (RTE (RE_Address),
2443              Relocate_Node (First_Actual (N))));
2444          return;
2445       end if;
2446
2447       if Nkind (Orig_Bod) = N_Defining_Identifier then
2448
2449          --  Subprogram is a renaming_as_body. Calls appearing after the
2450          --  renaming can be replaced with calls to the renamed entity
2451          --  directly, because the subprograms are subtype conformant.
2452
2453          Set_Name (N, New_Occurrence_Of (Orig_Bod, Loc));
2454          return;
2455       end if;
2456
2457       --  Use generic machinery to copy body of inlined subprogram, as if it
2458       --  were an instantiation, resetting source locations appropriately, so
2459       --  that nested inlined calls appear in the main unit.
2460
2461       Save_Env (Subp, Empty);
2462       Set_Copied_Sloc_For_Inlined_Body (N, Defining_Entity (Orig_Bod));
2463
2464       Bod := Copy_Generic_Node (Orig_Bod, Empty, Instantiating => True);
2465       Blk :=
2466         Make_Block_Statement (Loc,
2467           Declarations => Declarations (Bod),
2468           Handled_Statement_Sequence => Handled_Statement_Sequence (Bod));
2469
2470       if No (Declarations (Bod)) then
2471          Set_Declarations (Blk, New_List);
2472       end if;
2473
2474       --  If this is a derived function, establish the proper return type.
2475
2476       if Present (Orig_Subp)
2477         and then Orig_Subp /= Subp
2478       then
2479          Ret_Type := Etype (Orig_Subp);
2480       else
2481          Ret_Type := Etype (Subp);
2482       end if;
2483
2484       F := First_Formal (Subp);
2485       A := First_Actual (N);
2486
2487       --  Create temporaries for the actuals that are expressions, or that
2488       --  are scalars and require copying to preserve semantics.
2489
2490       while Present (F) loop
2491          if Present (Renamed_Object (F)) then
2492             Error_Msg_N (" cannot inline call to recursive subprogram", N);
2493             return;
2494          end if;
2495
2496          --  If the argument may be a controlling argument in a call within
2497          --  the inlined body, we must preserve its classwide nature to
2498          --  insure that dynamic dispatching take place subsequently.
2499          --  If the formal has a constraint it must be preserved to retain
2500          --  the semantics of the body.
2501
2502          if Is_Class_Wide_Type (Etype (F))
2503            or else (Is_Access_Type (Etype (F))
2504                       and then
2505                     Is_Class_Wide_Type (Designated_Type (Etype (F))))
2506          then
2507             Temp_Typ := Etype (F);
2508
2509          elsif Base_Type (Etype (F)) = Base_Type (Etype (A))
2510            and then Etype (F) /= Base_Type (Etype (F))
2511          then
2512             Temp_Typ := Etype (F);
2513
2514          else
2515             Temp_Typ := Etype (A);
2516          end if;
2517
2518          --  Comments needed here ???
2519
2520          if (Is_Entity_Name (A)
2521               and then
2522                (not Is_Scalar_Type (Etype (A))
2523                  or else Ekind (Entity (A)) = E_Enumeration_Literal))
2524
2525            or else Nkind (A) = N_Real_Literal
2526            or else Nkind (A) = N_Integer_Literal
2527            or else Nkind (A) = N_Character_Literal
2528          then
2529             if Etype (F) /= Etype (A) then
2530                Set_Renamed_Object
2531                 (F, Unchecked_Convert_To (Etype (F), Relocate_Node (A)));
2532             else
2533                Set_Renamed_Object (F, A);
2534             end if;
2535
2536          else
2537             Temp :=
2538               Make_Defining_Identifier (Loc,
2539                 Chars => New_Internal_Name ('C'));
2540
2541             --  If the actual for an in/in-out parameter is a view conversion,
2542             --  make it into an unchecked conversion, given that an untagged
2543             --  type conversion is not a proper object for a renaming.
2544
2545             --  In-out conversions that involve real conversions have already
2546             --  been transformed in Expand_Actuals.
2547
2548             if Nkind (A) = N_Type_Conversion
2549               and then Ekind (F) /= E_In_Parameter
2550             then
2551                New_A := Make_Unchecked_Type_Conversion (Loc,
2552                  Subtype_Mark => New_Occurrence_Of (Etype (F), Loc),
2553                  Expression   => Relocate_Node (Expression (A)));
2554
2555             elsif Etype (F) /= Etype (A) then
2556                New_A := Unchecked_Convert_To (Etype (F), Relocate_Node (A));
2557                Temp_Typ := Etype (F);
2558
2559             else
2560                New_A := Relocate_Node (A);
2561             end if;
2562
2563             Set_Sloc (New_A, Sloc (N));
2564
2565             if Ekind (F) = E_In_Parameter
2566               and then not Is_Limited_Type (Etype (A))
2567             then
2568                Decl :=
2569                  Make_Object_Declaration (Loc,
2570                    Defining_Identifier => Temp,
2571                    Constant_Present => True,
2572                    Object_Definition => New_Occurrence_Of (Temp_Typ, Loc),
2573                    Expression => New_A);
2574             else
2575                Decl :=
2576                  Make_Object_Renaming_Declaration (Loc,
2577                    Defining_Identifier => Temp,
2578                    Subtype_Mark        => New_Occurrence_Of (Temp_Typ, Loc),
2579                    Name                => New_A);
2580             end if;
2581
2582             Prepend (Decl, Declarations (Blk));
2583             Set_Renamed_Object (F, Temp);
2584          end if;
2585
2586          Next_Formal (F);
2587          Next_Actual (A);
2588       end loop;
2589
2590       --  Establish target of function call. If context is not assignment or
2591       --  declaration, create a temporary as a target. The declaration for
2592       --  the temporary may be subsequently optimized away if the body is a
2593       --  single expression, or if the left-hand side of the assignment is
2594       --  simple enough.
2595
2596       if Ekind (Subp) = E_Function then
2597          if Nkind (Parent (N)) = N_Assignment_Statement
2598            and then Is_Entity_Name (Name (Parent (N)))
2599          then
2600             Targ := Name (Parent (N));
2601
2602          else
2603             --  Replace call with temporary, and create its declaration.
2604
2605             Temp :=
2606               Make_Defining_Identifier (Loc, New_Internal_Name ('C'));
2607
2608             Decl :=
2609               Make_Object_Declaration (Loc,
2610                 Defining_Identifier => Temp,
2611                 Object_Definition =>
2612                   New_Occurrence_Of (Ret_Type, Loc));
2613
2614             Set_No_Initialization (Decl);
2615             Insert_Action (N, Decl);
2616             Rewrite (N, New_Occurrence_Of (Temp, Loc));
2617             Targ := Temp;
2618          end if;
2619       end if;
2620
2621       --  Traverse the tree and replace  formals with actuals or their thunks.
2622       --  Attach block to tree before analysis and rewriting.
2623
2624       Replace_Formals (Blk);
2625       Set_Parent (Blk, N);
2626
2627       if not Comes_From_Source (Subp)
2628         or else Is_Predef
2629       then
2630          Reset_Slocs (Blk);
2631       end if;
2632
2633       if Present (Exit_Lab) then
2634
2635          --  If the body was a single expression, the single return statement
2636          --  and the corresponding label are useless.
2637
2638          if Num_Ret = 1
2639            and then
2640              Nkind (Last (Statements (Handled_Statement_Sequence (Blk)))) =
2641                N_Goto_Statement
2642          then
2643             Remove (Last (Statements (Handled_Statement_Sequence (Blk))));
2644          else
2645             Append (Lab_Decl, (Declarations (Blk)));
2646             Append (Exit_Lab, Statements (Handled_Statement_Sequence (Blk)));
2647          end if;
2648       end if;
2649
2650       --  Analyze Blk with In_Inlined_Body set, to avoid spurious errors on
2651       --  conflicting private views that Gigi would ignore. If this is a
2652       --  predefined unit, analyze with checks off, as is done in the non-
2653       --  inlined run-time units.
2654
2655       declare
2656          I_Flag : constant Boolean := In_Inlined_Body;
2657
2658       begin
2659          In_Inlined_Body := True;
2660
2661          if Is_Predef then
2662             declare
2663                Style : constant Boolean := Style_Check;
2664             begin
2665                Style_Check := False;
2666                Analyze (Blk, Suppress => All_Checks);
2667                Style_Check := Style;
2668             end;
2669
2670          else
2671             Analyze (Blk);
2672          end if;
2673
2674          In_Inlined_Body := I_Flag;
2675       end;
2676
2677       if Ekind (Subp) = E_Procedure then
2678          Rewrite_Procedure_Call (N, Blk);
2679       else
2680          Rewrite_Function_Call (N, Blk);
2681       end if;
2682
2683       Restore_Env;
2684
2685       --  Cleanup mapping between formals and actuals, for other expansions.
2686
2687       F := First_Formal (Subp);
2688
2689       while Present (F) loop
2690          Set_Renamed_Object (F, Empty);
2691          Next_Formal (F);
2692       end loop;
2693    end Expand_Inlined_Call;
2694
2695    ----------------------------
2696    -- Expand_N_Function_Call --
2697    ----------------------------
2698
2699    procedure Expand_N_Function_Call (N : Node_Id) is
2700       Typ : constant Entity_Id := Etype (N);
2701
2702       function Returned_By_Reference return Boolean;
2703       --  If the return type is returned through the secondary stack. that is
2704       --  by reference, we don't want to create a temp to force stack checking.
2705
2706       function Returned_By_Reference return Boolean is
2707          S : Entity_Id := Current_Scope;
2708
2709       begin
2710          if Is_Return_By_Reference_Type (Typ) then
2711             return True;
2712
2713          elsif Nkind (Parent (N)) /= N_Return_Statement then
2714             return False;
2715
2716          elsif Requires_Transient_Scope (Typ) then
2717
2718             --  Verify that the return type of the enclosing function has
2719             --  the same constrained status as that of the expression.
2720
2721             while Ekind (S) /= E_Function loop
2722                S := Scope (S);
2723             end loop;
2724
2725             return Is_Constrained (Typ) = Is_Constrained (Etype (S));
2726          else
2727             return False;
2728          end if;
2729       end Returned_By_Reference;
2730
2731    --  Start of processing for Expand_N_Function_Call
2732
2733    begin
2734       --  A special check. If stack checking is enabled, and the return type
2735       --  might generate a large temporary, and the call is not the right
2736       --  side of an assignment, then generate an explicit temporary. We do
2737       --  this because otherwise gigi may generate a large temporary on the
2738       --  fly and this can cause trouble with stack checking.
2739
2740       if May_Generate_Large_Temp (Typ)
2741         and then Nkind (Parent (N)) /= N_Assignment_Statement
2742         and then
2743           (Nkind (Parent (N)) /= N_Qualified_Expression
2744              or else Nkind (Parent (Parent (N))) /= N_Assignment_Statement)
2745         and then
2746           (Nkind (Parent (N)) /= N_Object_Declaration
2747              or else Expression (Parent (N)) /= N)
2748         and then not Returned_By_Reference
2749       then
2750          --  Note: it might be thought that it would be OK to use a call to
2751          --  Force_Evaluation here, but that's not good enough, because that
2752          --  results in a 'Reference construct that may still need a temporary.
2753
2754          declare
2755             Loc      : constant Source_Ptr := Sloc (N);
2756             Temp_Obj : constant Entity_Id :=
2757                          Make_Defining_Identifier (Loc,
2758                            Chars => New_Internal_Name ('F'));
2759             Temp_Typ : Entity_Id := Typ;
2760             Decl     : Node_Id;
2761             A        : Node_Id;
2762             F        : Entity_Id;
2763             Proc     : Entity_Id;
2764
2765          begin
2766             if Is_Tagged_Type (Typ)
2767               and then Present (Controlling_Argument (N))
2768             then
2769                if Nkind (Parent (N)) /= N_Procedure_Call_Statement
2770                  and then Nkind (Parent (N)) /= N_Function_Call
2771                then
2772                   --  If this is a tag-indeterminate call, the object must
2773                   --  be classwide.
2774
2775                   if Is_Tag_Indeterminate (N) then
2776                      Temp_Typ := Class_Wide_Type (Typ);
2777                   end if;
2778
2779                else
2780                   --  If this is a dispatching call that is itself the
2781                   --  controlling argument of an enclosing call, the nominal
2782                   --  subtype of the object that replaces it must be classwide,
2783                   --  so that dispatching will take place properly. If it is
2784                   --  not a controlling argument, the object is not classwide.
2785
2786                   Proc := Entity (Name (Parent (N)));
2787                   F    := First_Formal (Proc);
2788                   A    := First_Actual (Parent (N));
2789
2790                   while A /= N loop
2791                      Next_Formal (F);
2792                      Next_Actual (A);
2793                   end loop;
2794
2795                   if Is_Controlling_Formal (F) then
2796                      Temp_Typ := Class_Wide_Type (Typ);
2797                   end if;
2798                end if;
2799             end if;
2800
2801             Decl :=
2802               Make_Object_Declaration (Loc,
2803                 Defining_Identifier => Temp_Obj,
2804                 Object_Definition   => New_Occurrence_Of (Temp_Typ, Loc),
2805                 Constant_Present    => True,
2806                 Expression          => Relocate_Node (N));
2807             Set_Assignment_OK (Decl);
2808
2809             Insert_Actions (N, New_List (Decl));
2810             Rewrite (N, New_Occurrence_Of (Temp_Obj, Loc));
2811          end;
2812
2813       --  Normal case, expand the call
2814
2815       else
2816          Expand_Call (N);
2817       end if;
2818    end Expand_N_Function_Call;
2819
2820    ---------------------------------------
2821    -- Expand_N_Procedure_Call_Statement --
2822    ---------------------------------------
2823
2824    procedure Expand_N_Procedure_Call_Statement (N : Node_Id) is
2825    begin
2826       Expand_Call (N);
2827    end Expand_N_Procedure_Call_Statement;
2828
2829    ------------------------------
2830    -- Expand_N_Subprogram_Body --
2831    ------------------------------
2832
2833    --  Add poll call if ATC polling is enabled
2834
2835    --  Add return statement if last statement in body is not a return
2836    --  statement (this makes things easier on Gigi which does not want
2837    --  to have to handle a missing return).
2838
2839    --  Add call to Activate_Tasks if body is a task activator
2840
2841    --  Deal with possible detection of infinite recursion
2842
2843    --  Eliminate body completely if convention stubbed
2844
2845    --  Encode entity names within body, since we will not need to reference
2846    --  these entities any longer in the front end.
2847
2848    --  Initialize scalar out parameters if Initialize/Normalize_Scalars
2849
2850    --  Reset Pure indication if any parameter has root type System.Address
2851
2852    procedure Expand_N_Subprogram_Body (N : Node_Id) is
2853       Loc      : constant Source_Ptr := Sloc (N);
2854       H        : constant Node_Id    := Handled_Statement_Sequence (N);
2855       Body_Id  : Entity_Id;
2856       Spec_Id  : Entity_Id;
2857       Except_H : Node_Id;
2858       Scop     : Entity_Id;
2859       Dec      : Node_Id;
2860       Next_Op  : Node_Id;
2861       L        : List_Id;
2862
2863       procedure Add_Return (S : List_Id);
2864       --  Append a return statement to the statement sequence S if the last
2865       --  statement is not already a return or a goto statement. Note that
2866       --  the latter test is not critical, it does not matter if we add a
2867       --  few extra returns, since they get eliminated anyway later on.
2868
2869       ----------------
2870       -- Add_Return --
2871       ----------------
2872
2873       procedure Add_Return (S : List_Id) is
2874       begin
2875          if not Is_Transfer (Last (S)) then
2876
2877             --  The source location for the return is the end label
2878             --  of the procedure in all cases. This is a bit odd when
2879             --  there are exception handlers, but not much else we can do.
2880
2881             Append_To (S, Make_Return_Statement (Sloc (End_Label (H))));
2882          end if;
2883       end Add_Return;
2884
2885    --  Start of processing for Expand_N_Subprogram_Body
2886
2887    begin
2888       --  Set L to either the list of declarations if present, or
2889       --  to the list of statements if no declarations are present.
2890       --  This is used to insert new stuff at the start.
2891
2892       if Is_Non_Empty_List (Declarations (N)) then
2893          L := Declarations (N);
2894       else
2895          L := Statements (Handled_Statement_Sequence (N));
2896       end if;
2897
2898       --  Need poll on entry to subprogram if polling enabled. We only
2899       --  do this for non-empty subprograms, since it does not seem
2900       --  necessary to poll for a dummy null subprogram.
2901
2902       if Is_Non_Empty_List (L) then
2903          Generate_Poll_Call (First (L));
2904       end if;
2905
2906       --  Find entity for subprogram
2907
2908       Body_Id := Defining_Entity (N);
2909
2910       if Present (Corresponding_Spec (N)) then
2911          Spec_Id := Corresponding_Spec (N);
2912       else
2913          Spec_Id := Body_Id;
2914       end if;
2915
2916       --  If this is a Pure function which has any parameters whose root
2917       --  type is System.Address, reset the Pure indication, since it will
2918       --  likely cause incorrect code to be generated.
2919
2920       if Is_Pure (Spec_Id)
2921         and then Is_Subprogram (Spec_Id)
2922         and then not Has_Pragma_Pure_Function (Spec_Id)
2923       then
2924          declare
2925             F : Entity_Id := First_Formal (Spec_Id);
2926
2927          begin
2928             while Present (F) loop
2929                if Is_RTE (Root_Type (Etype (F)), RE_Address) then
2930                   Set_Is_Pure (Spec_Id, False);
2931
2932                   if Spec_Id /= Body_Id then
2933                      Set_Is_Pure (Body_Id, False);
2934                   end if;
2935
2936                   exit;
2937                end if;
2938
2939                Next_Formal (F);
2940             end loop;
2941          end;
2942       end if;
2943
2944       --  Initialize any scalar OUT args if Initialize/Normalize_Scalars
2945
2946       if Init_Or_Norm_Scalars and then Is_Subprogram (Spec_Id) then
2947          declare
2948             F : Entity_Id        := First_Formal (Spec_Id);
2949             V : constant Boolean := Validity_Checks_On;
2950
2951          begin
2952             --  We turn off validity checking, since we do not want any
2953             --  check on the initializing value itself (which we know
2954             --  may well be invalid!)
2955
2956             Validity_Checks_On := False;
2957
2958             --  Loop through formals
2959
2960             while Present (F) loop
2961                if Is_Scalar_Type (Etype (F))
2962                  and then Ekind (F) = E_Out_Parameter
2963                then
2964                   Insert_Before_And_Analyze (First (L),
2965                     Make_Assignment_Statement (Loc,
2966                       Name => New_Occurrence_Of (F, Loc),
2967                       Expression => Get_Simple_Init_Val (Etype (F), Loc)));
2968                end if;
2969
2970                Next_Formal (F);
2971             end loop;
2972
2973             Validity_Checks_On := V;
2974          end;
2975       end if;
2976
2977       --  Clear out statement list for stubbed procedure
2978
2979       if Present (Corresponding_Spec (N)) then
2980          Set_Elaboration_Flag (N, Spec_Id);
2981
2982          if Convention (Spec_Id) = Convention_Stubbed
2983            or else Is_Eliminated (Spec_Id)
2984          then
2985             Set_Declarations (N, Empty_List);
2986             Set_Handled_Statement_Sequence (N,
2987               Make_Handled_Sequence_Of_Statements (Loc,
2988                 Statements => New_List (
2989                   Make_Null_Statement (Loc))));
2990             return;
2991          end if;
2992       end if;
2993
2994       Scop := Scope (Spec_Id);
2995
2996       --  Returns_By_Ref flag is normally set when the subprogram is frozen
2997       --  but subprograms with no specs are not frozen
2998
2999       declare
3000          Typ  : constant Entity_Id := Etype (Spec_Id);
3001          Utyp : constant Entity_Id := Underlying_Type (Typ);
3002
3003       begin
3004          if not Acts_As_Spec (N)
3005            and then Nkind (Parent (Parent (Spec_Id))) /=
3006              N_Subprogram_Body_Stub
3007          then
3008             null;
3009
3010          elsif Is_Return_By_Reference_Type (Typ) then
3011             Set_Returns_By_Ref (Spec_Id);
3012
3013          elsif Present (Utyp) and then Controlled_Type (Utyp) then
3014             Set_Returns_By_Ref (Spec_Id);
3015          end if;
3016       end;
3017
3018       --  For a procedure, we add a return for all possible syntactic ends
3019       --  of the subprogram. Note that reanalysis is not necessary in this
3020       --  case since it would require a lot of work and accomplish nothing.
3021
3022       if Ekind (Spec_Id) = E_Procedure
3023         or else Ekind (Spec_Id) = E_Generic_Procedure
3024       then
3025          Add_Return (Statements (H));
3026
3027          if Present (Exception_Handlers (H)) then
3028             Except_H := First_Non_Pragma (Exception_Handlers (H));
3029
3030             while Present (Except_H) loop
3031                Add_Return (Statements (Except_H));
3032                Next_Non_Pragma (Except_H);
3033             end loop;
3034          end if;
3035
3036       --  For a function, we must deal with the case where there is at
3037       --  least one missing return. What we do is to wrap the entire body
3038       --  of the function in a block:
3039
3040       --    begin
3041       --      ...
3042       --    end;
3043
3044       --  becomes
3045
3046       --    begin
3047       --       begin
3048       --          ...
3049       --       end;
3050
3051       --       raise Program_Error;
3052       --    end;
3053
3054       --  This approach is necessary because the raise must be signalled
3055       --  to the caller, not handled by any local handler (RM 6.4(11)).
3056
3057       --  Note: we do not need to analyze the constructed sequence here,
3058       --  since it has no handler, and an attempt to analyze the handled
3059       --  statement sequence twice is risky in various ways (e.g. the
3060       --  issue of expanding cleanup actions twice).
3061
3062       elsif Has_Missing_Return (Spec_Id) then
3063          declare
3064             Hloc : constant Source_Ptr := Sloc (H);
3065             Blok : constant Node_Id    :=
3066                      Make_Block_Statement (Hloc,
3067                        Handled_Statement_Sequence => H);
3068             Rais : constant Node_Id    :=
3069                      Make_Raise_Program_Error (Hloc,
3070                        Reason => PE_Missing_Return);
3071
3072          begin
3073             Set_Handled_Statement_Sequence (N,
3074               Make_Handled_Sequence_Of_Statements (Hloc,
3075                 Statements => New_List (Blok, Rais)));
3076
3077             New_Scope (Spec_Id);
3078             Analyze (Blok);
3079             Analyze (Rais);
3080             Pop_Scope;
3081          end;
3082       end if;
3083
3084       --  Add discriminal renamings to protected subprograms.
3085       --  Install new discriminals for expansion of the next
3086       --  subprogram of this protected type, if any.
3087
3088       if Is_List_Member (N)
3089         and then Present (Parent (List_Containing (N)))
3090         and then Nkind (Parent (List_Containing (N))) = N_Protected_Body
3091       then
3092          Add_Discriminal_Declarations
3093            (Declarations (N), Scop, Name_uObject, Loc);
3094          Add_Private_Declarations (Declarations (N), Scop, Name_uObject, Loc);
3095
3096          --  Associate privals and discriminals with the next protected
3097          --  operation body to be expanded. These are used to expand
3098          --  references to private data objects and discriminants,
3099          --  respectively.
3100
3101          Next_Op := Next_Protected_Operation (N);
3102
3103          if Present (Next_Op) then
3104             Dec := Parent (Base_Type (Scop));
3105             Set_Privals (Dec, Next_Op, Loc);
3106             Set_Discriminals (Dec);
3107          end if;
3108       end if;
3109
3110       --  If subprogram contains a parameterless recursive call, then we may
3111       --  have an infinite recursion, so see if we can generate code to check
3112       --  for this possibility if storage checks are not suppressed.
3113
3114       if Ekind (Spec_Id) = E_Procedure
3115         and then Has_Recursive_Call (Spec_Id)
3116         and then not Storage_Checks_Suppressed (Spec_Id)
3117       then
3118          Detect_Infinite_Recursion (N, Spec_Id);
3119       end if;
3120
3121       --  Finally, if we are in Normalize_Scalars mode, then any scalar out
3122       --  parameters must be initialized to the appropriate default value.
3123
3124       if Ekind (Spec_Id) = E_Procedure and then Normalize_Scalars then
3125          declare
3126             Floc   : Source_Ptr;
3127             Formal : Entity_Id;
3128             Stm    : Node_Id;
3129
3130          begin
3131             Formal := First_Formal (Spec_Id);
3132
3133             while Present (Formal) loop
3134                Floc := Sloc (Formal);
3135
3136                if Ekind (Formal) = E_Out_Parameter
3137                  and then Is_Scalar_Type (Etype (Formal))
3138                then
3139                   Stm :=
3140                     Make_Assignment_Statement (Floc,
3141                       Name => New_Occurrence_Of (Formal, Floc),
3142                       Expression =>
3143                         Get_Simple_Init_Val (Etype (Formal), Floc));
3144                   Prepend (Stm, Declarations (N));
3145                   Analyze (Stm);
3146                end if;
3147
3148                Next_Formal (Formal);
3149             end loop;
3150          end;
3151       end if;
3152
3153       --  If the subprogram does not have pending instantiations, then we
3154       --  must generate the subprogram descriptor now, since the code for
3155       --  the subprogram is complete, and this is our last chance. However
3156       --  if there are pending instantiations, then the code is not
3157       --  complete, and we will delay the generation.
3158
3159       if Is_Subprogram (Spec_Id)
3160         and then not Delay_Subprogram_Descriptors (Spec_Id)
3161       then
3162          Generate_Subprogram_Descriptor_For_Subprogram (N, Spec_Id);
3163       end if;
3164
3165       --  Set to encode entity names in package body before gigi is called
3166
3167       Qualify_Entity_Names (N);
3168    end Expand_N_Subprogram_Body;
3169
3170    -----------------------------------
3171    -- Expand_N_Subprogram_Body_Stub --
3172    -----------------------------------
3173
3174    procedure Expand_N_Subprogram_Body_Stub (N : Node_Id) is
3175    begin
3176       if Present (Corresponding_Body (N)) then
3177          Expand_N_Subprogram_Body (
3178            Unit_Declaration_Node (Corresponding_Body (N)));
3179       end if;
3180    end Expand_N_Subprogram_Body_Stub;
3181
3182    -------------------------------------
3183    -- Expand_N_Subprogram_Declaration --
3184    -------------------------------------
3185
3186    --  If the declaration appears within a protected body, it is a private
3187    --  operation of the protected type. We must create the corresponding
3188    --  protected subprogram an associated formals. For a normal protected
3189    --  operation, this is done when expanding the protected type declaration.
3190
3191    procedure Expand_N_Subprogram_Declaration (N : Node_Id) is
3192       Loc       : constant Source_Ptr := Sloc (N);
3193       Subp      : constant Entity_Id  := Defining_Entity (N);
3194       Scop      : constant Entity_Id  := Scope (Subp);
3195       Prot_Decl : Node_Id;
3196       Prot_Bod  : Node_Id;
3197       Prot_Id   : Entity_Id;
3198
3199    begin
3200       --  Deal with case of protected subprogram
3201
3202       if Is_List_Member (N)
3203         and then Present (Parent (List_Containing (N)))
3204         and then Nkind (Parent (List_Containing (N))) = N_Protected_Body
3205         and then Is_Protected_Type (Scop)
3206       then
3207          if No (Protected_Body_Subprogram (Subp)) then
3208             Prot_Decl :=
3209               Make_Subprogram_Declaration (Loc,
3210                 Specification =>
3211                   Build_Protected_Sub_Specification
3212                     (N, Scop, Unprotected => True));
3213
3214             --  The protected subprogram is declared outside of the protected
3215             --  body. Given that the body has frozen all entities so far, we
3216             --  analyze the subprogram and perform freezing actions explicitly.
3217             --  If the body is a subunit, the insertion point is before the
3218             --  stub in the parent.
3219
3220             Prot_Bod := Parent (List_Containing (N));
3221
3222             if Nkind (Parent (Prot_Bod)) = N_Subunit then
3223                Prot_Bod := Corresponding_Stub (Parent (Prot_Bod));
3224             end if;
3225
3226             Insert_Before (Prot_Bod, Prot_Decl);
3227             Prot_Id := Defining_Unit_Name (Specification (Prot_Decl));
3228
3229             New_Scope (Scope (Scop));
3230             Analyze (Prot_Decl);
3231             Create_Extra_Formals (Prot_Id);
3232             Set_Protected_Body_Subprogram (Subp, Prot_Id);
3233             Pop_Scope;
3234          end if;
3235       end if;
3236    end Expand_N_Subprogram_Declaration;
3237
3238    ---------------------------------------
3239    -- Expand_Protected_Object_Reference --
3240    ---------------------------------------
3241
3242    function Expand_Protected_Object_Reference
3243      (N    : Node_Id;
3244       Scop : Entity_Id)
3245      return Node_Id
3246    is
3247       Loc   : constant Source_Ptr := Sloc (N);
3248       Corr  : Entity_Id;
3249       Rec   : Node_Id;
3250       Param : Entity_Id;
3251       Proc  : Entity_Id;
3252
3253    begin
3254       Rec := Make_Identifier (Loc, Name_uObject);
3255       Set_Etype (Rec, Corresponding_Record_Type (Scop));
3256
3257       --  Find enclosing protected operation, and retrieve its first
3258       --  parameter, which denotes the enclosing protected object.
3259       --  If the enclosing operation is an entry, we are immediately
3260       --  within the protected body, and we can retrieve the object
3261       --  from the service entries procedure. A barrier function has
3262       --  has the same signature as an entry. A barrier function is
3263       --  compiled within the protected object, but unlike protected
3264       --  operations its never needs locks, so that its protected body
3265       --  subprogram points to itself.
3266
3267       Proc := Current_Scope;
3268
3269       while Present (Proc)
3270         and then Scope (Proc) /= Scop
3271       loop
3272          Proc := Scope (Proc);
3273       end loop;
3274
3275       Corr := Protected_Body_Subprogram (Proc);
3276
3277       if No (Corr) then
3278
3279          --  Previous error left expansion incomplete.
3280          --  Nothing to do on this call.
3281
3282          return Empty;
3283       end if;
3284
3285       Param :=
3286         Defining_Identifier
3287           (First (Parameter_Specifications (Parent (Corr))));
3288
3289       if Is_Subprogram (Proc)
3290         and then Proc /= Corr
3291       then
3292          --  Protected function or procedure.
3293
3294          Set_Entity (Rec, Param);
3295
3296          --  Rec is a reference to an entity which will not be in scope
3297          --  when the call is reanalyzed, and needs no further analysis.
3298
3299          Set_Analyzed (Rec);
3300
3301       else
3302          --  Entry or barrier function for entry body.
3303          --  The first parameter of the entry body procedure is a
3304          --  pointer to the object. We create a local variable
3305          --  of the proper type, duplicating what is done to define
3306          --  _object later on.
3307
3308          declare
3309             Decls : List_Id;
3310             Obj_Ptr : constant Entity_Id :=  Make_Defining_Identifier (Loc,
3311                                                Chars =>
3312                                                  New_Internal_Name ('T'));
3313
3314          begin
3315             Decls := New_List (
3316               Make_Full_Type_Declaration (Loc,
3317                 Defining_Identifier => Obj_Ptr,
3318                   Type_Definition =>
3319                      Make_Access_To_Object_Definition (Loc,
3320                        Subtype_Indication =>
3321                          New_Reference_To
3322                       (Corresponding_Record_Type (Scop), Loc))));
3323
3324             Insert_Actions (N, Decls);
3325             Insert_Actions (N, Freeze_Entity (Obj_Ptr, Sloc (N)));
3326
3327             Rec :=
3328               Make_Explicit_Dereference (Loc,
3329                 Unchecked_Convert_To (Obj_Ptr,
3330                   New_Occurrence_Of (Param, Loc)));
3331
3332             --  Analyze new actual. Other actuals in calls are already
3333             --  analyzed and the list of actuals is not renalyzed after
3334             --  rewriting.
3335
3336             Set_Parent (Rec, N);
3337             Analyze (Rec);
3338          end;
3339       end if;
3340
3341       return Rec;
3342    end Expand_Protected_Object_Reference;
3343
3344    --------------------------------------
3345    -- Expand_Protected_Subprogram_Call --
3346    --------------------------------------
3347
3348    procedure Expand_Protected_Subprogram_Call
3349      (N    : Node_Id;
3350       Subp : Entity_Id;
3351       Scop : Entity_Id)
3352    is
3353       Rec   : Node_Id;
3354
3355    begin
3356       --  If the protected object is not an enclosing scope, this is
3357       --  an inter-object function call. Inter-object procedure
3358       --  calls are expanded by Exp_Ch9.Build_Simple_Entry_Call.
3359       --  The call is intra-object only if the subprogram being
3360       --  called is in the protected body being compiled, and if the
3361       --  protected object in the call is statically the enclosing type.
3362       --  The object may be an component of some other data structure,
3363       --  in which case this must be handled as an inter-object call.
3364
3365       if not In_Open_Scopes (Scop)
3366         or else not Is_Entity_Name (Name (N))
3367       then
3368          if Nkind (Name (N)) = N_Selected_Component then
3369             Rec := Prefix (Name (N));
3370
3371          else
3372             pragma Assert (Nkind (Name (N)) = N_Indexed_Component);
3373             Rec := Prefix (Prefix (Name (N)));
3374          end if;
3375
3376          Build_Protected_Subprogram_Call (N,
3377            Name => New_Occurrence_Of (Subp, Sloc (N)),
3378            Rec =>  Convert_Concurrent (Rec, Etype (Rec)),
3379            External => True);
3380
3381       else
3382          Rec := Expand_Protected_Object_Reference (N, Scop);
3383
3384          if No (Rec) then
3385             return;
3386          end if;
3387
3388          Build_Protected_Subprogram_Call (N,
3389            Name     => Name (N),
3390            Rec      => Rec,
3391            External => False);
3392
3393       end if;
3394
3395       Analyze (N);
3396
3397       --  If it is a function call it can appear in elaboration code and
3398       --  the called entity must be frozen here.
3399
3400       if Ekind (Subp) = E_Function then
3401          Freeze_Expression (Name (N));
3402       end if;
3403    end Expand_Protected_Subprogram_Call;
3404
3405    -----------------------
3406    -- Freeze_Subprogram --
3407    -----------------------
3408
3409    procedure Freeze_Subprogram (N : Node_Id) is
3410       E : constant Entity_Id := Entity (N);
3411
3412    begin
3413       --  When a primitive is frozen, enter its name in the corresponding
3414       --  dispatch table. If the DTC_Entity field is not set this is an
3415       --  overridden primitive that can be ignored. We suppress the
3416       --  initialization of the dispatch table entry when Java_VM because
3417       --  the dispatching mechanism is handled internally by the JVM.
3418
3419       if Is_Dispatching_Operation (E)
3420         and then not Is_Abstract (E)
3421         and then Present (DTC_Entity (E))
3422         and then not Is_CPP_Class (Scope (DTC_Entity (E)))
3423         and then not Java_VM
3424       then
3425          Check_Overriding_Operation (E);
3426          Insert_After (N, Fill_DT_Entry (Sloc (N), E));
3427       end if;
3428
3429       --  Mark functions that return by reference. Note that it cannot be
3430       --  part of the normal semantic analysis of the spec since the
3431       --  underlying returned type may not be known yet (for private types)
3432
3433       declare
3434          Typ  : constant Entity_Id := Etype (E);
3435          Utyp : constant Entity_Id := Underlying_Type (Typ);
3436
3437       begin
3438          if Is_Return_By_Reference_Type (Typ) then
3439             Set_Returns_By_Ref (E);
3440
3441          elsif Present (Utyp) and then Controlled_Type (Utyp) then
3442             Set_Returns_By_Ref (E);
3443          end if;
3444       end;
3445    end Freeze_Subprogram;
3446
3447 end Exp_Ch6;