OSDN Git Service

More improvements to sparc VIS vec_init code generation.
[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-2011, Free Software Foundation, Inc.         --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17 -- for  more details.  You should have  received  a copy of the GNU General --
18 -- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license.          --
20 --                                                                          --
21 -- GNAT was originally developed  by the GNAT team at  New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
23 --                                                                          --
24 ------------------------------------------------------------------------------
25
26 with Atree;    use Atree;
27 with Checks;   use Checks;
28 with Debug;    use Debug;
29 with Einfo;    use Einfo;
30 with Errout;   use Errout;
31 with Elists;   use Elists;
32 with Exp_Aggr; use Exp_Aggr;
33 with Exp_Atag; use Exp_Atag;
34 with Exp_Ch2;  use Exp_Ch2;
35 with Exp_Ch3;  use Exp_Ch3;
36 with Exp_Ch7;  use Exp_Ch7;
37 with Exp_Ch9;  use Exp_Ch9;
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 Exp_VFpt; use Exp_VFpt;
46 with Fname;    use Fname;
47 with Freeze;   use Freeze;
48 with Inline;   use Inline;
49 with Lib;      use Lib;
50 with Namet;    use Namet;
51 with Nlists;   use Nlists;
52 with Nmake;    use Nmake;
53 with Opt;      use Opt;
54 with Restrict; use Restrict;
55 with Rident;   use Rident;
56 with Rtsfind;  use Rtsfind;
57 with Sem;      use Sem;
58 with Sem_Aux;  use Sem_Aux;
59 with Sem_Ch6;  use Sem_Ch6;
60 with Sem_Ch8;  use Sem_Ch8;
61 with Sem_Ch12; use Sem_Ch12;
62 with Sem_Ch13; use Sem_Ch13;
63 with Sem_Eval; use Sem_Eval;
64 with Sem_Disp; use Sem_Disp;
65 with Sem_Dist; use Sem_Dist;
66 with Sem_Mech; use Sem_Mech;
67 with Sem_Res;  use Sem_Res;
68 with Sem_SCIL; use Sem_SCIL;
69 with Sem_Util; use Sem_Util;
70 with Sinfo;    use Sinfo;
71 with Snames;   use Snames;
72 with Stand;    use Stand;
73 with Targparm; use Targparm;
74 with Tbuild;   use Tbuild;
75 with Uintp;    use Uintp;
76 with Validsw;  use Validsw;
77
78 package body Exp_Ch6 is
79
80    -----------------------
81    -- Local Subprograms --
82    -----------------------
83
84    procedure Add_Access_Actual_To_Build_In_Place_Call
85      (Function_Call : Node_Id;
86       Function_Id   : Entity_Id;
87       Return_Object : Node_Id;
88       Is_Access     : Boolean := False);
89    --  Ada 2005 (AI-318-02): Apply the Unrestricted_Access attribute to the
90    --  object name given by Return_Object and add the attribute to the end of
91    --  the actual parameter list associated with the build-in-place function
92    --  call denoted by Function_Call. However, if Is_Access is True, then
93    --  Return_Object is already an access expression, in which case it's passed
94    --  along directly to the build-in-place function. Finally, if Return_Object
95    --  is empty, then pass a null literal as the actual.
96
97    procedure Add_Unconstrained_Actuals_To_Build_In_Place_Call
98      (Function_Call  : Node_Id;
99       Function_Id    : Entity_Id;
100       Alloc_Form     : BIP_Allocation_Form := Unspecified;
101       Alloc_Form_Exp : Node_Id             := Empty;
102       Pool_Actual    : Node_Id             := Make_Null (No_Location));
103    --  Ada 2005 (AI-318-02): Add the actuals needed for a build-in-place
104    --  function call that returns a caller-unknown-size result (BIP_Alloc_Form
105    --  and BIP_Storage_Pool). If Alloc_Form_Exp is present, then use it,
106    --  otherwise pass a literal corresponding to the Alloc_Form parameter
107    --  (which must not be Unspecified in that case). Pool_Actual is the
108    --  parameter to pass to BIP_Storage_Pool.
109
110    procedure Add_Finalization_Master_Actual_To_Build_In_Place_Call
111      (Func_Call  : Node_Id;
112       Func_Id    : Entity_Id;
113       Ptr_Typ    : Entity_Id := Empty;
114       Master_Exp : Node_Id   := Empty);
115    --  Ada 2005 (AI-318-02): If the result type of a build-in-place call needs
116    --  finalization actions, add an actual parameter which is a pointer to the
117    --  finalization master of the caller. If Master_Exp is not Empty, then that
118    --  will be passed as the actual. Otherwise, if Ptr_Typ is left Empty, this
119    --  will result in an automatic "null" value for the actual.
120
121    procedure Add_Task_Actuals_To_Build_In_Place_Call
122      (Function_Call : Node_Id;
123       Function_Id   : Entity_Id;
124       Master_Actual : Node_Id);
125    --  Ada 2005 (AI-318-02): For a build-in-place call, if the result type
126    --  contains tasks, add two actual parameters: the master, and a pointer to
127    --  the caller's activation chain. Master_Actual is the actual parameter
128    --  expression to pass for the master. In most cases, this is the current
129    --  master (_master). The two exceptions are: If the function call is the
130    --  initialization expression for an allocator, we pass the master of the
131    --  access type. If the function call is the initialization expression for a
132    --  return object, we pass along the master passed in by the caller. The
133    --  activation chain to pass is always the local one. Note: Master_Actual
134    --  can be Empty, but only if there are no tasks.
135
136    procedure Check_Overriding_Operation (Subp : Entity_Id);
137    --  Subp is a dispatching operation. Check whether it may override an
138    --  inherited private operation, in which case its DT entry is that of
139    --  the hidden operation, not the one it may have received earlier.
140    --  This must be done before emitting the code to set the corresponding
141    --  DT to the address of the subprogram. The actual placement of Subp in
142    --  the proper place in the list of primitive operations is done in
143    --  Declare_Inherited_Private_Subprograms, which also has to deal with
144    --  implicit operations. This duplication is unavoidable for now???
145
146    procedure Detect_Infinite_Recursion (N : Node_Id; Spec : Entity_Id);
147    --  This procedure is called only if the subprogram body N, whose spec
148    --  has the given entity Spec, contains a parameterless recursive call.
149    --  It attempts to generate runtime code to detect if this a case of
150    --  infinite recursion.
151    --
152    --  The body is scanned to determine dependencies. If the only external
153    --  dependencies are on a small set of scalar variables, then the values
154    --  of these variables are captured on entry to the subprogram, and if
155    --  the values are not changed for the call, we know immediately that
156    --  we have an infinite recursion.
157
158    procedure Expand_Ctrl_Function_Call (N : Node_Id);
159    --  N is a function call which returns a controlled object. Transform the
160    --  call into a temporary which retrieves the returned object from the
161    --  secondary stack using 'reference.
162
163    procedure Expand_Inlined_Call
164     (N         : Node_Id;
165      Subp      : Entity_Id;
166      Orig_Subp : Entity_Id);
167    --  If called subprogram can be inlined by the front-end, retrieve the
168    --  analyzed body, replace formals with actuals and expand call in place.
169    --  Generate thunks for actuals that are expressions, and insert the
170    --  corresponding constant declarations before the call. If the original
171    --  call is to a derived operation, the return type is the one of the
172    --  derived operation, but the body is that of the original, so return
173    --  expressions in the body must be converted to the desired type (which
174    --  is simply not noted in the tree without inline expansion).
175
176    procedure Expand_Non_Function_Return (N : Node_Id);
177    --  Called by Expand_N_Simple_Return_Statement in case we're returning from
178    --  a procedure body, entry body, accept statement, or extended return
179    --  statement. Note that all non-function returns are simple return
180    --  statements.
181
182    function Expand_Protected_Object_Reference
183      (N    : Node_Id;
184       Scop : Entity_Id) return Node_Id;
185
186    procedure Expand_Protected_Subprogram_Call
187      (N    : Node_Id;
188       Subp : Entity_Id;
189       Scop : Entity_Id);
190    --  A call to a protected subprogram within the protected object may appear
191    --  as a regular call. The list of actuals must be expanded to contain a
192    --  reference to the object itself, and the call becomes a call to the
193    --  corresponding protected subprogram.
194
195    function Has_Unconstrained_Access_Discriminants
196      (Subtyp : Entity_Id) return Boolean;
197    --  Returns True if the given subtype is unconstrained and has one
198    --  or more access discriminants.
199
200    procedure Expand_Simple_Function_Return (N : Node_Id);
201    --  Expand simple return from function. In the case where we are returning
202    --  from a function body this is called by Expand_N_Simple_Return_Statement.
203
204    ----------------------------------------------
205    -- Add_Access_Actual_To_Build_In_Place_Call --
206    ----------------------------------------------
207
208    procedure Add_Access_Actual_To_Build_In_Place_Call
209      (Function_Call : Node_Id;
210       Function_Id   : Entity_Id;
211       Return_Object : Node_Id;
212       Is_Access     : Boolean := False)
213    is
214       Loc            : constant Source_Ptr := Sloc (Function_Call);
215       Obj_Address    : Node_Id;
216       Obj_Acc_Formal : Entity_Id;
217
218    begin
219       --  Locate the implicit access parameter in the called function
220
221       Obj_Acc_Formal := Build_In_Place_Formal (Function_Id, BIP_Object_Access);
222
223       --  If no return object is provided, then pass null
224
225       if not Present (Return_Object) then
226          Obj_Address := Make_Null (Loc);
227          Set_Parent (Obj_Address, Function_Call);
228
229       --  If Return_Object is already an expression of an access type, then use
230       --  it directly, since it must be an access value denoting the return
231       --  object, and couldn't possibly be the return object itself.
232
233       elsif Is_Access then
234          Obj_Address := Return_Object;
235          Set_Parent (Obj_Address, Function_Call);
236
237       --  Apply Unrestricted_Access to caller's return object
238
239       else
240          Obj_Address :=
241             Make_Attribute_Reference (Loc,
242               Prefix         => Return_Object,
243               Attribute_Name => Name_Unrestricted_Access);
244
245          Set_Parent (Return_Object, Obj_Address);
246          Set_Parent (Obj_Address, Function_Call);
247       end if;
248
249       Analyze_And_Resolve (Obj_Address, Etype (Obj_Acc_Formal));
250
251       --  Build the parameter association for the new actual and add it to the
252       --  end of the function's actuals.
253
254       Add_Extra_Actual_To_Call (Function_Call, Obj_Acc_Formal, Obj_Address);
255    end Add_Access_Actual_To_Build_In_Place_Call;
256
257    ------------------------------------------------------
258    -- Add_Unconstrained_Actuals_To_Build_In_Place_Call --
259    ------------------------------------------------------
260
261    procedure Add_Unconstrained_Actuals_To_Build_In_Place_Call
262      (Function_Call  : Node_Id;
263       Function_Id    : Entity_Id;
264       Alloc_Form     : BIP_Allocation_Form := Unspecified;
265       Alloc_Form_Exp : Node_Id             := Empty;
266       Pool_Actual    : Node_Id             := Make_Null (No_Location))
267    is
268       Loc               : constant Source_Ptr := Sloc (Function_Call);
269       Alloc_Form_Actual : Node_Id;
270       Alloc_Form_Formal : Node_Id;
271       Pool_Formal       : Node_Id;
272
273    begin
274       --  The allocation form generally doesn't need to be passed in the case
275       --  of a constrained result subtype, since normally the caller performs
276       --  the allocation in that case. However this formal is still needed in
277       --  the case where the function has a tagged result, because generally
278       --  such functions can be called in a dispatching context and such calls
279       --  must be handled like calls to class-wide functions.
280
281       if Is_Constrained (Underlying_Type (Etype (Function_Id)))
282         and then not Is_Tagged_Type (Underlying_Type (Etype (Function_Id)))
283       then
284          return;
285       end if;
286
287       --  Locate the implicit allocation form parameter in the called function.
288       --  Maybe it would be better for each implicit formal of a build-in-place
289       --  function to have a flag or a Uint attribute to identify it. ???
290
291       Alloc_Form_Formal := Build_In_Place_Formal (Function_Id, BIP_Alloc_Form);
292
293       if Present (Alloc_Form_Exp) then
294          pragma Assert (Alloc_Form = Unspecified);
295
296          Alloc_Form_Actual := Alloc_Form_Exp;
297
298       else
299          pragma Assert (Alloc_Form /= Unspecified);
300
301          Alloc_Form_Actual :=
302            Make_Integer_Literal (Loc,
303              Intval => UI_From_Int (BIP_Allocation_Form'Pos (Alloc_Form)));
304       end if;
305
306       Analyze_And_Resolve (Alloc_Form_Actual, Etype (Alloc_Form_Formal));
307
308       --  Build the parameter association for the new actual and add it to the
309       --  end of the function's actuals.
310
311       Add_Extra_Actual_To_Call
312         (Function_Call, Alloc_Form_Formal, Alloc_Form_Actual);
313
314       --  Pass the Storage_Pool parameter. This parameter is omitted on
315       --  .NET/JVM/ZFP as those targets do not support pools.
316
317       if VM_Target = No_VM
318         and then RTE_Available (RE_Root_Storage_Pool_Ptr)
319       then
320          Pool_Formal := Build_In_Place_Formal (Function_Id, BIP_Storage_Pool);
321          Analyze_And_Resolve (Pool_Actual, Etype (Pool_Formal));
322          Add_Extra_Actual_To_Call
323            (Function_Call, Pool_Formal, Pool_Actual);
324       end if;
325    end Add_Unconstrained_Actuals_To_Build_In_Place_Call;
326
327    -----------------------------------------------------------
328    -- Add_Finalization_Master_Actual_To_Build_In_Place_Call --
329    -----------------------------------------------------------
330
331    procedure Add_Finalization_Master_Actual_To_Build_In_Place_Call
332      (Func_Call  : Node_Id;
333       Func_Id    : Entity_Id;
334       Ptr_Typ    : Entity_Id := Empty;
335       Master_Exp : Node_Id   := Empty)
336    is
337    begin
338       if not Needs_BIP_Finalization_Master (Func_Id) then
339          return;
340       end if;
341
342       declare
343          Formal : constant Entity_Id :=
344                     Build_In_Place_Formal (Func_Id, BIP_Finalization_Master);
345          Loc    : constant Source_Ptr := Sloc (Func_Call);
346
347          Actual    : Node_Id;
348          Desig_Typ : Entity_Id;
349
350       begin
351          --  If there is a finalization master actual, such as the implicit
352          --  finalization master of an enclosing build-in-place function,
353          --  then this must be added as an extra actual of the call.
354
355          if Present (Master_Exp) then
356             Actual := Master_Exp;
357
358          --  Case where the context does not require an actual master
359
360          elsif No (Ptr_Typ) then
361             Actual := Make_Null (Loc);
362
363          else
364             Desig_Typ := Directly_Designated_Type (Ptr_Typ);
365
366             --  Check for a library-level access type whose designated type has
367             --  supressed finalization. Such an access types lack a master.
368             --  Pass a null actual to the callee in order to signal a missing
369             --  master.
370
371             if Is_Library_Level_Entity (Ptr_Typ)
372               and then Finalize_Storage_Only (Desig_Typ)
373             then
374                Actual := Make_Null (Loc);
375
376             --  Types in need of finalization actions
377
378             elsif Needs_Finalization (Desig_Typ) then
379
380                --  The general mechanism of creating finalization masters for
381                --  anonymous access types is disabled by default, otherwise
382                --  finalization masters will pop all over the place. Such types
383                --  use context-specific masters.
384
385                if Ekind (Ptr_Typ) = E_Anonymous_Access_Type
386                  and then No (Finalization_Master (Ptr_Typ))
387                then
388                   Build_Finalization_Master
389                     (Typ        => Ptr_Typ,
390                      Ins_Node   => Associated_Node_For_Itype (Ptr_Typ),
391                      Encl_Scope => Scope (Ptr_Typ));
392                end if;
393
394                --  Access-to-controlled types should always have a master
395
396                pragma Assert (Present (Finalization_Master (Ptr_Typ)));
397
398                Actual :=
399                  Make_Attribute_Reference (Loc,
400                    Prefix =>
401                      New_Reference_To (Finalization_Master (Ptr_Typ), Loc),
402                    Attribute_Name => Name_Unrestricted_Access);
403
404             --  Tagged types
405
406             else
407                Actual := Make_Null (Loc);
408             end if;
409          end if;
410
411          Analyze_And_Resolve (Actual, Etype (Formal));
412
413          --  Build the parameter association for the new actual and add it to
414          --  the end of the function's actuals.
415
416          Add_Extra_Actual_To_Call (Func_Call, Formal, Actual);
417       end;
418    end Add_Finalization_Master_Actual_To_Build_In_Place_Call;
419
420    ------------------------------
421    -- Add_Extra_Actual_To_Call --
422    ------------------------------
423
424    procedure Add_Extra_Actual_To_Call
425      (Subprogram_Call : Node_Id;
426       Extra_Formal    : Entity_Id;
427       Extra_Actual    : Node_Id)
428    is
429       Loc         : constant Source_Ptr := Sloc (Subprogram_Call);
430       Param_Assoc : Node_Id;
431
432    begin
433       Param_Assoc :=
434         Make_Parameter_Association (Loc,
435           Selector_Name             => New_Occurrence_Of (Extra_Formal, Loc),
436           Explicit_Actual_Parameter => Extra_Actual);
437
438       Set_Parent (Param_Assoc, Subprogram_Call);
439       Set_Parent (Extra_Actual, Param_Assoc);
440
441       if Present (Parameter_Associations (Subprogram_Call)) then
442          if Nkind (Last (Parameter_Associations (Subprogram_Call))) =
443               N_Parameter_Association
444          then
445
446             --  Find last named actual, and append
447
448             declare
449                L : Node_Id;
450             begin
451                L := First_Actual (Subprogram_Call);
452                while Present (L) loop
453                   if No (Next_Actual (L)) then
454                      Set_Next_Named_Actual (Parent (L), Extra_Actual);
455                      exit;
456                   end if;
457                   Next_Actual (L);
458                end loop;
459             end;
460
461          else
462             Set_First_Named_Actual (Subprogram_Call, Extra_Actual);
463          end if;
464
465          Append (Param_Assoc, To => Parameter_Associations (Subprogram_Call));
466
467       else
468          Set_Parameter_Associations (Subprogram_Call, New_List (Param_Assoc));
469          Set_First_Named_Actual (Subprogram_Call, Extra_Actual);
470       end if;
471    end Add_Extra_Actual_To_Call;
472
473    ---------------------------------------------
474    -- Add_Task_Actuals_To_Build_In_Place_Call --
475    ---------------------------------------------
476
477    procedure Add_Task_Actuals_To_Build_In_Place_Call
478      (Function_Call : Node_Id;
479       Function_Id   : Entity_Id;
480       Master_Actual : Node_Id)
481    is
482       Loc           : constant Source_Ptr := Sloc (Function_Call);
483       Result_Subt   : constant Entity_Id :=
484                         Available_View (Etype (Function_Id));
485       Actual        : Node_Id;
486       Chain_Actual  : Node_Id;
487       Chain_Formal  : Node_Id;
488       Master_Formal : Node_Id;
489
490    begin
491       --  No such extra parameters are needed if there are no tasks
492
493       if not Has_Task (Result_Subt) then
494          return;
495       end if;
496
497       Actual := Master_Actual;
498
499       --  Use a dummy _master actual in case of No_Task_Hierarchy
500
501       if Restriction_Active (No_Task_Hierarchy) then
502          Actual := New_Occurrence_Of (RTE (RE_Library_Task_Level), Loc);
503
504       --  In the case where we use the master associated with an access type,
505       --  the actual is an entity and requires an explicit reference.
506
507       elsif Nkind (Actual) = N_Defining_Identifier then
508          Actual := New_Reference_To (Actual, Loc);
509       end if;
510
511       --  Locate the implicit master parameter in the called function
512
513       Master_Formal := Build_In_Place_Formal (Function_Id, BIP_Task_Master);
514       Analyze_And_Resolve (Actual, Etype (Master_Formal));
515
516       --  Build the parameter association for the new actual and add it to the
517       --  end of the function's actuals.
518
519       Add_Extra_Actual_To_Call (Function_Call, Master_Formal, Actual);
520
521       --  Locate the implicit activation chain parameter in the called function
522
523       Chain_Formal :=
524         Build_In_Place_Formal (Function_Id, BIP_Activation_Chain);
525
526       --  Create the actual which is a pointer to the current activation chain
527
528       Chain_Actual :=
529         Make_Attribute_Reference (Loc,
530           Prefix         => Make_Identifier (Loc, Name_uChain),
531           Attribute_Name => Name_Unrestricted_Access);
532
533       Analyze_And_Resolve (Chain_Actual, Etype (Chain_Formal));
534
535       --  Build the parameter association for the new actual and add it to the
536       --  end of the function's actuals.
537
538       Add_Extra_Actual_To_Call (Function_Call, Chain_Formal, Chain_Actual);
539    end Add_Task_Actuals_To_Build_In_Place_Call;
540
541    -----------------------
542    -- BIP_Formal_Suffix --
543    -----------------------
544
545    function BIP_Formal_Suffix (Kind : BIP_Formal_Kind) return String is
546    begin
547       case Kind is
548          when BIP_Alloc_Form          =>
549             return "BIPalloc";
550          when BIP_Storage_Pool        =>
551             return "BIPstoragepool";
552          when BIP_Finalization_Master =>
553             return "BIPfinalizationmaster";
554          when BIP_Task_Master         =>
555             return "BIPtaskmaster";
556          when BIP_Activation_Chain    =>
557             return "BIPactivationchain";
558          when BIP_Object_Access       =>
559             return "BIPaccess";
560       end case;
561    end BIP_Formal_Suffix;
562
563    ---------------------------
564    -- Build_In_Place_Formal --
565    ---------------------------
566
567    function Build_In_Place_Formal
568      (Func : Entity_Id;
569       Kind : BIP_Formal_Kind) return Entity_Id
570    is
571       Formal_Name  : constant Name_Id :=
572                        New_External_Name
573                          (Chars (Func), BIP_Formal_Suffix (Kind));
574       Extra_Formal : Entity_Id := Extra_Formals (Func);
575
576    begin
577       --  Maybe it would be better for each implicit formal of a build-in-place
578       --  function to have a flag or a Uint attribute to identify it. ???
579
580       --  The return type in the function declaration may have been a limited
581       --  view, and the extra formals for the function were not generated at
582       --  that point. At the point of call the full view must be available and
583       --  the extra formals can be created.
584
585       if No (Extra_Formal) then
586          Create_Extra_Formals (Func);
587          Extra_Formal := Extra_Formals (Func);
588       end if;
589
590       loop
591          pragma Assert (Present (Extra_Formal));
592          exit when Chars (Extra_Formal) = Formal_Name;
593
594          Next_Formal_With_Extras (Extra_Formal);
595       end loop;
596
597       return Extra_Formal;
598    end Build_In_Place_Formal;
599
600    --------------------------------
601    -- Check_Overriding_Operation --
602    --------------------------------
603
604    procedure Check_Overriding_Operation (Subp : Entity_Id) is
605       Typ     : constant Entity_Id := Find_Dispatching_Type (Subp);
606       Op_List : constant Elist_Id  := Primitive_Operations (Typ);
607       Op_Elmt : Elmt_Id;
608       Prim_Op : Entity_Id;
609       Par_Op  : Entity_Id;
610
611    begin
612       if Is_Derived_Type (Typ)
613         and then not Is_Private_Type (Typ)
614         and then In_Open_Scopes (Scope (Etype (Typ)))
615         and then Is_Base_Type (Typ)
616       then
617          --  Subp overrides an inherited private operation if there is an
618          --  inherited operation with a different name than Subp (see
619          --  Derive_Subprogram) whose Alias is a hidden subprogram with the
620          --  same name as Subp.
621
622          Op_Elmt := First_Elmt (Op_List);
623          while Present (Op_Elmt) loop
624             Prim_Op := Node (Op_Elmt);
625             Par_Op  := Alias (Prim_Op);
626
627             if Present (Par_Op)
628               and then not Comes_From_Source (Prim_Op)
629               and then Chars (Prim_Op) /= Chars (Par_Op)
630               and then Chars (Par_Op) = Chars (Subp)
631               and then Is_Hidden (Par_Op)
632               and then Type_Conformant (Prim_Op, Subp)
633             then
634                Set_DT_Position (Subp, DT_Position (Prim_Op));
635             end if;
636
637             Next_Elmt (Op_Elmt);
638          end loop;
639       end if;
640    end Check_Overriding_Operation;
641
642    -------------------------------
643    -- Detect_Infinite_Recursion --
644    -------------------------------
645
646    procedure Detect_Infinite_Recursion (N : Node_Id; Spec : Entity_Id) is
647       Loc : constant Source_Ptr := Sloc (N);
648
649       Var_List : constant Elist_Id := New_Elmt_List;
650       --  List of globals referenced by body of procedure
651
652       Call_List : constant Elist_Id := New_Elmt_List;
653       --  List of recursive calls in body of procedure
654
655       Shad_List : constant Elist_Id := New_Elmt_List;
656       --  List of entity id's for entities created to capture the value of
657       --  referenced globals on entry to the procedure.
658
659       Scop : constant Uint := Scope_Depth (Spec);
660       --  This is used to record the scope depth of the current procedure, so
661       --  that we can identify global references.
662
663       Max_Vars : constant := 4;
664       --  Do not test more than four global variables
665
666       Count_Vars : Natural := 0;
667       --  Count variables found so far
668
669       Var  : Entity_Id;
670       Elm  : Elmt_Id;
671       Ent  : Entity_Id;
672       Call : Elmt_Id;
673       Decl : Node_Id;
674       Test : Node_Id;
675       Elm1 : Elmt_Id;
676       Elm2 : Elmt_Id;
677       Last : Node_Id;
678
679       function Process (Nod : Node_Id) return Traverse_Result;
680       --  Function to traverse the subprogram body (using Traverse_Func)
681
682       -------------
683       -- Process --
684       -------------
685
686       function Process (Nod : Node_Id) return Traverse_Result is
687       begin
688          --  Procedure call
689
690          if Nkind (Nod) = N_Procedure_Call_Statement then
691
692             --  Case of one of the detected recursive calls
693
694             if Is_Entity_Name (Name (Nod))
695               and then Has_Recursive_Call (Entity (Name (Nod)))
696               and then Entity (Name (Nod)) = Spec
697             then
698                Append_Elmt (Nod, Call_List);
699                return Skip;
700
701             --  Any other procedure call may have side effects
702
703             else
704                return Abandon;
705             end if;
706
707          --  A call to a pure function can always be ignored
708
709          elsif Nkind (Nod) = N_Function_Call
710            and then Is_Entity_Name (Name (Nod))
711            and then Is_Pure (Entity (Name (Nod)))
712          then
713             return Skip;
714
715          --  Case of an identifier reference
716
717          elsif Nkind (Nod) = N_Identifier then
718             Ent := Entity (Nod);
719
720             --  If no entity, then ignore the reference
721
722             --  Not clear why this can happen. To investigate, remove this
723             --  test and look at the crash that occurs here in 3401-004 ???
724
725             if No (Ent) then
726                return Skip;
727
728             --  Ignore entities with no Scope, again not clear how this
729             --  can happen, to investigate, look at 4108-008 ???
730
731             elsif No (Scope (Ent)) then
732                return Skip;
733
734             --  Ignore the reference if not to a more global object
735
736             elsif Scope_Depth (Scope (Ent)) >= Scop then
737                return Skip;
738
739             --  References to types, exceptions and constants are always OK
740
741             elsif Is_Type (Ent)
742               or else Ekind (Ent) = E_Exception
743               or else Ekind (Ent) = E_Constant
744             then
745                return Skip;
746
747             --  If other than a non-volatile scalar variable, we have some
748             --  kind of global reference (e.g. to a function) that we cannot
749             --  deal with so we forget the attempt.
750
751             elsif Ekind (Ent) /= E_Variable
752               or else not Is_Scalar_Type (Etype (Ent))
753               or else Treat_As_Volatile (Ent)
754             then
755                return Abandon;
756
757             --  Otherwise we have a reference to a global scalar
758
759             else
760                --  Loop through global entities already detected
761
762                Elm := First_Elmt (Var_List);
763                loop
764                   --  If not detected before, record this new global reference
765
766                   if No (Elm) then
767                      Count_Vars := Count_Vars + 1;
768
769                      if Count_Vars <= Max_Vars then
770                         Append_Elmt (Entity (Nod), Var_List);
771                      else
772                         return Abandon;
773                      end if;
774
775                      exit;
776
777                   --  If recorded before, ignore
778
779                   elsif Node (Elm) = Entity (Nod) then
780                      return Skip;
781
782                   --  Otherwise keep looking
783
784                   else
785                      Next_Elmt (Elm);
786                   end if;
787                end loop;
788
789                return Skip;
790             end if;
791
792          --  For all other node kinds, recursively visit syntactic children
793
794          else
795             return OK;
796          end if;
797       end Process;
798
799       function Traverse_Body is new Traverse_Func (Process);
800
801    --  Start of processing for Detect_Infinite_Recursion
802
803    begin
804       --  Do not attempt detection in No_Implicit_Conditional mode, since we
805       --  won't be able to generate the code to handle the recursion in any
806       --  case.
807
808       if Restriction_Active (No_Implicit_Conditionals) then
809          return;
810       end if;
811
812       --  Otherwise do traversal and quit if we get abandon signal
813
814       if Traverse_Body (N) = Abandon then
815          return;
816
817       --  We must have a call, since Has_Recursive_Call was set. If not just
818       --  ignore (this is only an error check, so if we have a funny situation,
819       --  due to bugs or errors, we do not want to bomb!)
820
821       elsif Is_Empty_Elmt_List (Call_List) then
822          return;
823       end if;
824
825       --  Here is the case where we detect recursion at compile time
826
827       --  Push our current scope for analyzing the declarations and code that
828       --  we will insert for the checking.
829
830       Push_Scope (Spec);
831
832       --  This loop builds temporary variables for each of the referenced
833       --  globals, so that at the end of the loop the list Shad_List contains
834       --  these temporaries in one-to-one correspondence with the elements in
835       --  Var_List.
836
837       Last := Empty;
838       Elm := First_Elmt (Var_List);
839       while Present (Elm) loop
840          Var := Node (Elm);
841          Ent := Make_Temporary (Loc, 'S');
842          Append_Elmt (Ent, Shad_List);
843
844          --  Insert a declaration for this temporary at the start of the
845          --  declarations for the procedure. The temporaries are declared as
846          --  constant objects initialized to the current values of the
847          --  corresponding temporaries.
848
849          Decl :=
850            Make_Object_Declaration (Loc,
851              Defining_Identifier => Ent,
852              Object_Definition   => New_Occurrence_Of (Etype (Var), Loc),
853              Constant_Present    => True,
854              Expression          => New_Occurrence_Of (Var, Loc));
855
856          if No (Last) then
857             Prepend (Decl, Declarations (N));
858          else
859             Insert_After (Last, Decl);
860          end if;
861
862          Last := Decl;
863          Analyze (Decl);
864          Next_Elmt (Elm);
865       end loop;
866
867       --  Loop through calls
868
869       Call := First_Elmt (Call_List);
870       while Present (Call) loop
871
872          --  Build a predicate expression of the form
873
874          --    True
875          --      and then global1 = temp1
876          --      and then global2 = temp2
877          --      ...
878
879          --  This predicate determines if any of the global values
880          --  referenced by the procedure have changed since the
881          --  current call, if not an infinite recursion is assured.
882
883          Test := New_Occurrence_Of (Standard_True, Loc);
884
885          Elm1 := First_Elmt (Var_List);
886          Elm2 := First_Elmt (Shad_List);
887          while Present (Elm1) loop
888             Test :=
889               Make_And_Then (Loc,
890                 Left_Opnd  => Test,
891                 Right_Opnd =>
892                   Make_Op_Eq (Loc,
893                     Left_Opnd  => New_Occurrence_Of (Node (Elm1), Loc),
894                     Right_Opnd => New_Occurrence_Of (Node (Elm2), Loc)));
895
896             Next_Elmt (Elm1);
897             Next_Elmt (Elm2);
898          end loop;
899
900          --  Now we replace the call with the sequence
901
902          --    if no-changes (see above) then
903          --       raise Storage_Error;
904          --    else
905          --       original-call
906          --    end if;
907
908          Rewrite (Node (Call),
909            Make_If_Statement (Loc,
910              Condition       => Test,
911              Then_Statements => New_List (
912                Make_Raise_Storage_Error (Loc,
913                  Reason => SE_Infinite_Recursion)),
914
915              Else_Statements => New_List (
916                Relocate_Node (Node (Call)))));
917
918          Analyze (Node (Call));
919
920          Next_Elmt (Call);
921       end loop;
922
923       --  Remove temporary scope stack entry used for analysis
924
925       Pop_Scope;
926    end Detect_Infinite_Recursion;
927
928    --------------------
929    -- Expand_Actuals --
930    --------------------
931
932    procedure Expand_Actuals (N : Node_Id; Subp : Entity_Id) is
933       Loc       : constant Source_Ptr := Sloc (N);
934       Actual    : Node_Id;
935       Formal    : Entity_Id;
936       N_Node    : Node_Id;
937       Post_Call : List_Id;
938       E_Formal  : Entity_Id;
939
940       procedure Add_Call_By_Copy_Code;
941       --  For cases where the parameter must be passed by copy, this routine
942       --  generates a temporary variable into which the actual is copied and
943       --  then passes this as the parameter. For an OUT or IN OUT parameter,
944       --  an assignment is also generated to copy the result back. The call
945       --  also takes care of any constraint checks required for the type
946       --  conversion case (on both the way in and the way out).
947
948       procedure Add_Simple_Call_By_Copy_Code;
949       --  This is similar to the above, but is used in cases where we know
950       --  that all that is needed is to simply create a temporary and copy
951       --  the value in and out of the temporary.
952
953       procedure Check_Fortran_Logical;
954       --  A value of type Logical that is passed through a formal parameter
955       --  must be normalized because .TRUE. usually does not have the same
956       --  representation as True. We assume that .FALSE. = False = 0.
957       --  What about functions that return a logical type ???
958
959       function Is_Legal_Copy return Boolean;
960       --  Check that an actual can be copied before generating the temporary
961       --  to be used in the call. If the actual is of a by_reference type then
962       --  the program is illegal (this can only happen in the presence of
963       --  rep. clauses that force an incorrect alignment). If the formal is
964       --  a by_reference parameter imposed by a DEC pragma, emit a warning to
965       --  the effect that this might lead to unaligned arguments.
966
967       function Make_Var (Actual : Node_Id) return Entity_Id;
968       --  Returns an entity that refers to the given actual parameter,
969       --  Actual (not including any type conversion). If Actual is an
970       --  entity name, then this entity is returned unchanged, otherwise
971       --  a renaming is created to provide an entity for the actual.
972
973       procedure Reset_Packed_Prefix;
974       --  The expansion of a packed array component reference is delayed in
975       --  the context of a call. Now we need to complete the expansion, so we
976       --  unmark the analyzed bits in all prefixes.
977
978       ---------------------------
979       -- Add_Call_By_Copy_Code --
980       ---------------------------
981
982       procedure Add_Call_By_Copy_Code is
983          Expr  : Node_Id;
984          Init  : Node_Id;
985          Temp  : Entity_Id;
986          Indic : Node_Id;
987          Var   : Entity_Id;
988          F_Typ : constant Entity_Id := Etype (Formal);
989          V_Typ : Entity_Id;
990          Crep  : Boolean;
991
992       begin
993          if not Is_Legal_Copy then
994             return;
995          end if;
996
997          Temp := Make_Temporary (Loc, 'T', Actual);
998
999          --  Use formal type for temp, unless formal type is an unconstrained
1000          --  array, in which case we don't have to worry about bounds checks,
1001          --  and we use the actual type, since that has appropriate bounds.
1002
1003          if Is_Array_Type (F_Typ) and then not Is_Constrained (F_Typ) then
1004             Indic := New_Occurrence_Of (Etype (Actual), Loc);
1005          else
1006             Indic := New_Occurrence_Of (Etype (Formal), Loc);
1007          end if;
1008
1009          if Nkind (Actual) = N_Type_Conversion then
1010             V_Typ := Etype (Expression (Actual));
1011
1012             --  If the formal is an (in-)out parameter, capture the name
1013             --  of the variable in order to build the post-call assignment.
1014
1015             Var := Make_Var (Expression (Actual));
1016
1017             Crep := not Same_Representation
1018                           (F_Typ, Etype (Expression (Actual)));
1019
1020          else
1021             V_Typ := Etype (Actual);
1022             Var   := Make_Var (Actual);
1023             Crep  := False;
1024          end if;
1025
1026          --  Setup initialization for case of in out parameter, or an out
1027          --  parameter where the formal is an unconstrained array (in the
1028          --  latter case, we have to pass in an object with bounds).
1029
1030          --  If this is an out parameter, the initial copy is wasteful, so as
1031          --  an optimization for the one-dimensional case we extract the
1032          --  bounds of the actual and build an uninitialized temporary of the
1033          --  right size.
1034
1035          if Ekind (Formal) = E_In_Out_Parameter
1036            or else (Is_Array_Type (F_Typ) and then not Is_Constrained (F_Typ))
1037          then
1038             if Nkind (Actual) = N_Type_Conversion then
1039                if Conversion_OK (Actual) then
1040                   Init := OK_Convert_To (F_Typ, New_Occurrence_Of (Var, Loc));
1041                else
1042                   Init := Convert_To (F_Typ, New_Occurrence_Of (Var, Loc));
1043                end if;
1044
1045             elsif Ekind (Formal) = E_Out_Parameter
1046               and then Is_Array_Type (F_Typ)
1047               and then Number_Dimensions (F_Typ) = 1
1048               and then not Has_Non_Null_Base_Init_Proc (F_Typ)
1049             then
1050                --  Actual is a one-dimensional array or slice, and the type
1051                --  requires no initialization. Create a temporary of the
1052                --  right size, but do not copy actual into it (optimization).
1053
1054                Init := Empty;
1055                Indic :=
1056                  Make_Subtype_Indication (Loc,
1057                    Subtype_Mark =>
1058                      New_Occurrence_Of (F_Typ, Loc),
1059                    Constraint   =>
1060                      Make_Index_Or_Discriminant_Constraint (Loc,
1061                        Constraints => New_List (
1062                          Make_Range (Loc,
1063                            Low_Bound  =>
1064                              Make_Attribute_Reference (Loc,
1065                                Prefix => New_Occurrence_Of (Var, Loc),
1066                                Attribute_Name => Name_First),
1067                            High_Bound =>
1068                              Make_Attribute_Reference (Loc,
1069                                Prefix => New_Occurrence_Of (Var, Loc),
1070                                Attribute_Name => Name_Last)))));
1071
1072             else
1073                Init := New_Occurrence_Of (Var, Loc);
1074             end if;
1075
1076          --  An initialization is created for packed conversions as
1077          --  actuals for out parameters to enable Make_Object_Declaration
1078          --  to determine the proper subtype for N_Node. Note that this
1079          --  is wasteful because the extra copying on the call side is
1080          --  not required for such out parameters. ???
1081
1082          elsif Ekind (Formal) = E_Out_Parameter
1083            and then Nkind (Actual) = N_Type_Conversion
1084            and then (Is_Bit_Packed_Array (F_Typ)
1085                        or else
1086                      Is_Bit_Packed_Array (Etype (Expression (Actual))))
1087          then
1088             if Conversion_OK (Actual) then
1089                Init := OK_Convert_To (F_Typ, New_Occurrence_Of (Var, Loc));
1090             else
1091                Init := Convert_To (F_Typ, New_Occurrence_Of (Var, Loc));
1092             end if;
1093
1094          elsif Ekind (Formal) = E_In_Parameter then
1095
1096             --  Handle the case in which the actual is a type conversion
1097
1098             if Nkind (Actual) = N_Type_Conversion then
1099                if Conversion_OK (Actual) then
1100                   Init := OK_Convert_To (F_Typ, New_Occurrence_Of (Var, Loc));
1101                else
1102                   Init := Convert_To (F_Typ, New_Occurrence_Of (Var, Loc));
1103                end if;
1104             else
1105                Init := New_Occurrence_Of (Var, Loc);
1106             end if;
1107
1108          else
1109             Init := Empty;
1110          end if;
1111
1112          N_Node :=
1113            Make_Object_Declaration (Loc,
1114              Defining_Identifier => Temp,
1115              Object_Definition   => Indic,
1116              Expression          => Init);
1117          Set_Assignment_OK (N_Node);
1118          Insert_Action (N, N_Node);
1119
1120          --  Now, normally the deal here is that we use the defining
1121          --  identifier created by that object declaration. There is
1122          --  one exception to this. In the change of representation case
1123          --  the above declaration will end up looking like:
1124
1125          --    temp : type := identifier;
1126
1127          --  And in this case we might as well use the identifier directly
1128          --  and eliminate the temporary. Note that the analysis of the
1129          --  declaration was not a waste of time in that case, since it is
1130          --  what generated the necessary change of representation code. If
1131          --  the change of representation introduced additional code, as in
1132          --  a fixed-integer conversion, the expression is not an identifier
1133          --  and must be kept.
1134
1135          if Crep
1136            and then Present (Expression (N_Node))
1137            and then Is_Entity_Name (Expression (N_Node))
1138          then
1139             Temp := Entity (Expression (N_Node));
1140             Rewrite (N_Node, Make_Null_Statement (Loc));
1141          end if;
1142
1143          --  For IN parameter, all we do is to replace the actual
1144
1145          if Ekind (Formal) = E_In_Parameter then
1146             Rewrite (Actual, New_Reference_To (Temp, Loc));
1147             Analyze (Actual);
1148
1149          --  Processing for OUT or IN OUT parameter
1150
1151          else
1152             --  Kill current value indications for the temporary variable we
1153             --  created, since we just passed it as an OUT parameter.
1154
1155             Kill_Current_Values (Temp);
1156             Set_Is_Known_Valid (Temp, False);
1157
1158             --  If type conversion, use reverse conversion on exit
1159
1160             if Nkind (Actual) = N_Type_Conversion then
1161                if Conversion_OK (Actual) then
1162                   Expr := OK_Convert_To (V_Typ, New_Occurrence_Of (Temp, Loc));
1163                else
1164                   Expr := Convert_To (V_Typ, New_Occurrence_Of (Temp, Loc));
1165                end if;
1166             else
1167                Expr := New_Occurrence_Of (Temp, Loc);
1168             end if;
1169
1170             Rewrite (Actual, New_Reference_To (Temp, Loc));
1171             Analyze (Actual);
1172
1173             --  If the actual is a conversion of a packed reference, it may
1174             --  already have been expanded by Remove_Side_Effects, and the
1175             --  resulting variable is a temporary which does not designate
1176             --  the proper out-parameter, which may not be addressable. In
1177             --  that case, generate an assignment to the original expression
1178             --  (before expansion of the packed reference) so that the proper
1179             --  expansion of assignment to a packed component can take place.
1180
1181             declare
1182                Obj : Node_Id;
1183                Lhs : Node_Id;
1184
1185             begin
1186                if Is_Renaming_Of_Object (Var)
1187                  and then Nkind (Renamed_Object (Var)) = N_Selected_Component
1188                  and then Is_Entity_Name (Prefix (Renamed_Object (Var)))
1189                  and then Nkind (Original_Node (Prefix (Renamed_Object (Var))))
1190                    = N_Indexed_Component
1191                  and then
1192                    Has_Non_Standard_Rep (Etype (Prefix (Renamed_Object (Var))))
1193                then
1194                   Obj := Renamed_Object (Var);
1195                   Lhs :=
1196                     Make_Selected_Component (Loc,
1197                       Prefix        =>
1198                         New_Copy_Tree (Original_Node (Prefix (Obj))),
1199                       Selector_Name => New_Copy (Selector_Name (Obj)));
1200                   Reset_Analyzed_Flags (Lhs);
1201
1202                else
1203                   Lhs :=  New_Occurrence_Of (Var, Loc);
1204                end if;
1205
1206                Set_Assignment_OK (Lhs);
1207
1208                if Is_Access_Type (E_Formal)
1209                  and then Is_Entity_Name (Lhs)
1210                  and then
1211                    Present (Effective_Extra_Accessibility (Entity (Lhs)))
1212                then
1213                   --  Copyback target is an Ada 2012 stand-alone object
1214                   --  of an anonymous access type
1215
1216                   pragma Assert (Ada_Version >= Ada_2012);
1217
1218                   if Type_Access_Level (E_Formal) >
1219                      Object_Access_Level (Lhs)
1220                   then
1221                      Append_To (Post_Call,
1222                        Make_Raise_Program_Error (Loc,
1223                          Reason => PE_Accessibility_Check_Failed));
1224                   end if;
1225
1226                   Append_To (Post_Call,
1227                     Make_Assignment_Statement (Loc,
1228                       Name       => Lhs,
1229                       Expression => Expr));
1230
1231                   --  We would like to somehow suppress generation of the
1232                   --  extra_accessibility assignment generated by the expansion
1233                   --  of the above assignment statement. It's not a correctness
1234                   --  issue because the following assignment renders it dead,
1235                   --  but generating back-to-back assignments to the same
1236                   --  target is undesirable. ???
1237
1238                   Append_To (Post_Call,
1239                     Make_Assignment_Statement (Loc,
1240                       Name       => New_Occurrence_Of (
1241                         Effective_Extra_Accessibility (Entity (Lhs)), Loc),
1242                       Expression => Make_Integer_Literal (Loc,
1243                         Type_Access_Level (E_Formal))));
1244
1245                else
1246                   Append_To (Post_Call,
1247                     Make_Assignment_Statement (Loc,
1248                       Name       => Lhs,
1249                       Expression => Expr));
1250                end if;
1251             end;
1252          end if;
1253       end Add_Call_By_Copy_Code;
1254
1255       ----------------------------------
1256       -- Add_Simple_Call_By_Copy_Code --
1257       ----------------------------------
1258
1259       procedure Add_Simple_Call_By_Copy_Code is
1260          Temp   : Entity_Id;
1261          Decl   : Node_Id;
1262          Incod  : Node_Id;
1263          Outcod : Node_Id;
1264          Lhs    : Node_Id;
1265          Rhs    : Node_Id;
1266          Indic  : Node_Id;
1267          F_Typ  : constant Entity_Id := Etype (Formal);
1268
1269       begin
1270          if not Is_Legal_Copy then
1271             return;
1272          end if;
1273
1274          --  Use formal type for temp, unless formal type is an unconstrained
1275          --  array, in which case we don't have to worry about bounds checks,
1276          --  and we use the actual type, since that has appropriate bounds.
1277
1278          if Is_Array_Type (F_Typ) and then not Is_Constrained (F_Typ) then
1279             Indic := New_Occurrence_Of (Etype (Actual), Loc);
1280          else
1281             Indic := New_Occurrence_Of (Etype (Formal), Loc);
1282          end if;
1283
1284          --  Prepare to generate code
1285
1286          Reset_Packed_Prefix;
1287
1288          Temp := Make_Temporary (Loc, 'T', Actual);
1289          Incod  := Relocate_Node (Actual);
1290          Outcod := New_Copy_Tree (Incod);
1291
1292          --  Generate declaration of temporary variable, initializing it
1293          --  with the input parameter unless we have an OUT formal or
1294          --  this is an initialization call.
1295
1296          --  If the formal is an out parameter with discriminants, the
1297          --  discriminants must be captured even if the rest of the object
1298          --  is in principle uninitialized, because the discriminants may
1299          --  be read by the called subprogram.
1300
1301          if Ekind (Formal) = E_Out_Parameter then
1302             Incod := Empty;
1303
1304             if Has_Discriminants (Etype (Formal)) then
1305                Indic := New_Occurrence_Of (Etype (Actual), Loc);
1306             end if;
1307
1308          elsif Inside_Init_Proc then
1309
1310             --  Could use a comment here to match comment below ???
1311
1312             if Nkind (Actual) /= N_Selected_Component
1313               or else
1314                 not Has_Discriminant_Dependent_Constraint
1315                   (Entity (Selector_Name (Actual)))
1316             then
1317                Incod := Empty;
1318
1319             --  Otherwise, keep the component in order to generate the proper
1320             --  actual subtype, that depends on enclosing discriminants.
1321
1322             else
1323                null;
1324             end if;
1325          end if;
1326
1327          Decl :=
1328            Make_Object_Declaration (Loc,
1329              Defining_Identifier => Temp,
1330              Object_Definition   => Indic,
1331              Expression          => Incod);
1332
1333          if Inside_Init_Proc
1334            and then No (Incod)
1335          then
1336             --  If the call is to initialize a component of a composite type,
1337             --  and the component does not depend on discriminants, use the
1338             --  actual type of the component. This is required in case the
1339             --  component is constrained, because in general the formal of the
1340             --  initialization procedure will be unconstrained. Note that if
1341             --  the component being initialized is constrained by an enclosing
1342             --  discriminant, the presence of the initialization in the
1343             --  declaration will generate an expression for the actual subtype.
1344
1345             Set_No_Initialization (Decl);
1346             Set_Object_Definition (Decl,
1347               New_Occurrence_Of (Etype (Actual), Loc));
1348          end if;
1349
1350          Insert_Action (N, Decl);
1351
1352          --  The actual is simply a reference to the temporary
1353
1354          Rewrite (Actual, New_Occurrence_Of (Temp, Loc));
1355
1356          --  Generate copy out if OUT or IN OUT parameter
1357
1358          if Ekind (Formal) /= E_In_Parameter then
1359             Lhs := Outcod;
1360             Rhs := New_Occurrence_Of (Temp, Loc);
1361
1362             --  Deal with conversion
1363
1364             if Nkind (Lhs) = N_Type_Conversion then
1365                Lhs := Expression (Lhs);
1366                Rhs := Convert_To (Etype (Actual), Rhs);
1367             end if;
1368
1369             Append_To (Post_Call,
1370               Make_Assignment_Statement (Loc,
1371                 Name       => Lhs,
1372                 Expression => Rhs));
1373             Set_Assignment_OK (Name (Last (Post_Call)));
1374          end if;
1375       end Add_Simple_Call_By_Copy_Code;
1376
1377       ---------------------------
1378       -- Check_Fortran_Logical --
1379       ---------------------------
1380
1381       procedure Check_Fortran_Logical is
1382          Logical : constant Entity_Id := Etype (Formal);
1383          Var     : Entity_Id;
1384
1385       --  Note: this is very incomplete, e.g. it does not handle arrays
1386       --  of logical values. This is really not the right approach at all???)
1387
1388       begin
1389          if Convention (Subp) = Convention_Fortran
1390            and then Root_Type (Etype (Formal)) = Standard_Boolean
1391            and then Ekind (Formal) /= E_In_Parameter
1392          then
1393             Var := Make_Var (Actual);
1394             Append_To (Post_Call,
1395               Make_Assignment_Statement (Loc,
1396                 Name => New_Occurrence_Of (Var, Loc),
1397                 Expression =>
1398                   Unchecked_Convert_To (
1399                     Logical,
1400                     Make_Op_Ne (Loc,
1401                       Left_Opnd  => New_Occurrence_Of (Var, Loc),
1402                       Right_Opnd =>
1403                         Unchecked_Convert_To (
1404                           Logical,
1405                           New_Occurrence_Of (Standard_False, Loc))))));
1406          end if;
1407       end Check_Fortran_Logical;
1408
1409       -------------------
1410       -- Is_Legal_Copy --
1411       -------------------
1412
1413       function Is_Legal_Copy return Boolean is
1414       begin
1415          --  An attempt to copy a value of such a type can only occur if
1416          --  representation clauses give the actual a misaligned address.
1417
1418          if Is_By_Reference_Type (Etype (Formal)) then
1419             Error_Msg_N
1420               ("misaligned actual cannot be passed by reference", Actual);
1421             return False;
1422
1423          --  For users of Starlet, we assume that the specification of by-
1424          --  reference mechanism is mandatory. This may lead to unaligned
1425          --  objects but at least for DEC legacy code it is known to work.
1426          --  The warning will alert users of this code that a problem may
1427          --  be lurking.
1428
1429          elsif Mechanism (Formal) = By_Reference
1430            and then Is_Valued_Procedure (Scope (Formal))
1431          then
1432             Error_Msg_N
1433               ("by_reference actual may be misaligned?", Actual);
1434             return False;
1435
1436          else
1437             return True;
1438          end if;
1439       end Is_Legal_Copy;
1440
1441       --------------
1442       -- Make_Var --
1443       --------------
1444
1445       function Make_Var (Actual : Node_Id) return Entity_Id is
1446          Var : Entity_Id;
1447
1448       begin
1449          if Is_Entity_Name (Actual) then
1450             return Entity (Actual);
1451
1452          else
1453             Var := Make_Temporary (Loc, 'T', Actual);
1454
1455             N_Node :=
1456               Make_Object_Renaming_Declaration (Loc,
1457                 Defining_Identifier => Var,
1458                 Subtype_Mark        =>
1459                   New_Occurrence_Of (Etype (Actual), Loc),
1460                 Name                => Relocate_Node (Actual));
1461
1462             Insert_Action (N, N_Node);
1463             return Var;
1464          end if;
1465       end Make_Var;
1466
1467       -------------------------
1468       -- Reset_Packed_Prefix --
1469       -------------------------
1470
1471       procedure Reset_Packed_Prefix is
1472          Pfx : Node_Id := Actual;
1473       begin
1474          loop
1475             Set_Analyzed (Pfx, False);
1476             exit when
1477               not Nkind_In (Pfx, N_Selected_Component, N_Indexed_Component);
1478             Pfx := Prefix (Pfx);
1479          end loop;
1480       end Reset_Packed_Prefix;
1481
1482    --  Start of processing for Expand_Actuals
1483
1484    begin
1485       Post_Call := New_List;
1486
1487       Formal := First_Formal (Subp);
1488       Actual := First_Actual (N);
1489       while Present (Formal) loop
1490          E_Formal := Etype (Formal);
1491
1492          if Is_Scalar_Type (E_Formal)
1493            or else Nkind (Actual) = N_Slice
1494          then
1495             Check_Fortran_Logical;
1496
1497          --  RM 6.4.1 (11)
1498
1499          elsif Ekind (Formal) /= E_Out_Parameter then
1500
1501             --  The unusual case of the current instance of a protected type
1502             --  requires special handling. This can only occur in the context
1503             --  of a call within the body of a protected operation.
1504
1505             if Is_Entity_Name (Actual)
1506               and then Ekind (Entity (Actual)) = E_Protected_Type
1507               and then In_Open_Scopes (Entity (Actual))
1508             then
1509                if Scope (Subp) /= Entity (Actual) then
1510                   Error_Msg_N ("operation outside protected type may not "
1511                     & "call back its protected operations?", Actual);
1512                end if;
1513
1514                Rewrite (Actual,
1515                  Expand_Protected_Object_Reference (N, Entity (Actual)));
1516             end if;
1517
1518             --  Ada 2005 (AI-318-02): If the actual parameter is a call to a
1519             --  build-in-place function, then a temporary return object needs
1520             --  to be created and access to it must be passed to the function.
1521             --  Currently we limit such functions to those with inherently
1522             --  limited result subtypes, but eventually we plan to expand the
1523             --  functions that are treated as build-in-place to include other
1524             --  composite result types.
1525
1526             if Is_Build_In_Place_Function_Call (Actual) then
1527                Make_Build_In_Place_Call_In_Anonymous_Context (Actual);
1528             end if;
1529
1530             Apply_Constraint_Check (Actual, E_Formal);
1531
1532          --  Out parameter case. No constraint checks on access type
1533          --  RM 6.4.1 (13)
1534
1535          elsif Is_Access_Type (E_Formal) then
1536             null;
1537
1538          --  RM 6.4.1 (14)
1539
1540          elsif Has_Discriminants (Base_Type (E_Formal))
1541            or else Has_Non_Null_Base_Init_Proc (E_Formal)
1542          then
1543             Apply_Constraint_Check (Actual, E_Formal);
1544
1545          --  RM 6.4.1 (15)
1546
1547          else
1548             Apply_Constraint_Check (Actual, Base_Type (E_Formal));
1549          end if;
1550
1551          --  Processing for IN-OUT and OUT parameters
1552
1553          if Ekind (Formal) /= E_In_Parameter then
1554
1555             --  For type conversions of arrays, apply length/range checks
1556
1557             if Is_Array_Type (E_Formal)
1558               and then Nkind (Actual) = N_Type_Conversion
1559             then
1560                if Is_Constrained (E_Formal) then
1561                   Apply_Length_Check (Expression (Actual), E_Formal);
1562                else
1563                   Apply_Range_Check (Expression (Actual), E_Formal);
1564                end if;
1565             end if;
1566
1567             --  If argument is a type conversion for a type that is passed
1568             --  by copy, then we must pass the parameter by copy.
1569
1570             if Nkind (Actual) = N_Type_Conversion
1571               and then
1572                 (Is_Numeric_Type (E_Formal)
1573                   or else Is_Access_Type (E_Formal)
1574                   or else Is_Enumeration_Type (E_Formal)
1575                   or else Is_Bit_Packed_Array (Etype (Formal))
1576                   or else Is_Bit_Packed_Array (Etype (Expression (Actual)))
1577
1578                   --  Also pass by copy if change of representation
1579
1580                   or else not Same_Representation
1581                                (Etype (Formal),
1582                                 Etype (Expression (Actual))))
1583             then
1584                Add_Call_By_Copy_Code;
1585
1586             --  References to components of bit packed arrays are expanded
1587             --  at this point, rather than at the point of analysis of the
1588             --  actuals, to handle the expansion of the assignment to
1589             --  [in] out parameters.
1590
1591             elsif Is_Ref_To_Bit_Packed_Array (Actual) then
1592                Add_Simple_Call_By_Copy_Code;
1593
1594             --  If a non-scalar actual is possibly bit-aligned, we need a copy
1595             --  because the back-end cannot cope with such objects. In other
1596             --  cases where alignment forces a copy, the back-end generates
1597             --  it properly. It should not be generated unconditionally in the
1598             --  front-end because it does not know precisely the alignment
1599             --  requirements of the target, and makes too conservative an
1600             --  estimate, leading to superfluous copies or spurious errors
1601             --  on by-reference parameters.
1602
1603             elsif Nkind (Actual) = N_Selected_Component
1604               and then
1605                 Component_May_Be_Bit_Aligned (Entity (Selector_Name (Actual)))
1606               and then not Represented_As_Scalar (Etype (Formal))
1607             then
1608                Add_Simple_Call_By_Copy_Code;
1609
1610             --  References to slices of bit packed arrays are expanded
1611
1612             elsif Is_Ref_To_Bit_Packed_Slice (Actual) then
1613                Add_Call_By_Copy_Code;
1614
1615             --  References to possibly unaligned slices of arrays are expanded
1616
1617             elsif Is_Possibly_Unaligned_Slice (Actual) then
1618                Add_Call_By_Copy_Code;
1619
1620             --  Deal with access types where the actual subtype and the
1621             --  formal subtype are not the same, requiring a check.
1622
1623             --  It is necessary to exclude tagged types because of "downward
1624             --  conversion" errors.
1625
1626             elsif Is_Access_Type (E_Formal)
1627               and then not Same_Type (E_Formal, Etype (Actual))
1628               and then not Is_Tagged_Type (Designated_Type (E_Formal))
1629             then
1630                Add_Call_By_Copy_Code;
1631
1632             --  If the actual is not a scalar and is marked for volatile
1633             --  treatment, whereas the formal is not volatile, then pass
1634             --  by copy unless it is a by-reference type.
1635
1636             --  Note: we use Is_Volatile here rather than Treat_As_Volatile,
1637             --  because this is the enforcement of a language rule that applies
1638             --  only to "real" volatile variables, not e.g. to the address
1639             --  clause overlay case.
1640
1641             elsif Is_Entity_Name (Actual)
1642               and then Is_Volatile (Entity (Actual))
1643               and then not Is_By_Reference_Type (Etype (Actual))
1644               and then not Is_Scalar_Type (Etype (Entity (Actual)))
1645               and then not Is_Volatile (E_Formal)
1646             then
1647                Add_Call_By_Copy_Code;
1648
1649             elsif Nkind (Actual) = N_Indexed_Component
1650               and then Is_Entity_Name (Prefix (Actual))
1651               and then Has_Volatile_Components (Entity (Prefix (Actual)))
1652             then
1653                Add_Call_By_Copy_Code;
1654
1655             --  Add call-by-copy code for the case of scalar out parameters
1656             --  when it is not known at compile time that the subtype of the
1657             --  formal is a subrange of the subtype of the actual (or vice
1658             --  versa for in out parameters), in order to get range checks
1659             --  on such actuals. (Maybe this case should be handled earlier
1660             --  in the if statement???)
1661
1662             elsif Is_Scalar_Type (E_Formal)
1663               and then
1664                 (not In_Subrange_Of (E_Formal, Etype (Actual))
1665                   or else
1666                     (Ekind (Formal) = E_In_Out_Parameter
1667                       and then not In_Subrange_Of (Etype (Actual), E_Formal)))
1668             then
1669                --  Perhaps the setting back to False should be done within
1670                --  Add_Call_By_Copy_Code, since it could get set on other
1671                --  cases occurring above???
1672
1673                if Do_Range_Check (Actual) then
1674                   Set_Do_Range_Check (Actual, False);
1675                end if;
1676
1677                Add_Call_By_Copy_Code;
1678             end if;
1679
1680          --  Processing for IN parameters
1681
1682          else
1683             --  For IN parameters is in the packed array case, we expand an
1684             --  indexed component (the circuit in Exp_Ch4 deliberately left
1685             --  indexed components appearing as actuals untouched, so that
1686             --  the special processing above for the OUT and IN OUT cases
1687             --  could be performed. We could make the test in Exp_Ch4 more
1688             --  complex and have it detect the parameter mode, but it is
1689             --  easier simply to handle all cases here.)
1690
1691             if Nkind (Actual) = N_Indexed_Component
1692               and then Is_Packed (Etype (Prefix (Actual)))
1693             then
1694                Reset_Packed_Prefix;
1695                Expand_Packed_Element_Reference (Actual);
1696
1697             --  If we have a reference to a bit packed array, we copy it, since
1698             --  the actual must be byte aligned.
1699
1700             --  Is this really necessary in all cases???
1701
1702             elsif Is_Ref_To_Bit_Packed_Array (Actual) then
1703                Add_Simple_Call_By_Copy_Code;
1704
1705             --  If a non-scalar actual is possibly unaligned, we need a copy
1706
1707             elsif Is_Possibly_Unaligned_Object (Actual)
1708               and then not Represented_As_Scalar (Etype (Formal))
1709             then
1710                Add_Simple_Call_By_Copy_Code;
1711
1712             --  Similarly, we have to expand slices of packed arrays here
1713             --  because the result must be byte aligned.
1714
1715             elsif Is_Ref_To_Bit_Packed_Slice (Actual) then
1716                Add_Call_By_Copy_Code;
1717
1718             --  Only processing remaining is to pass by copy if this is a
1719             --  reference to a possibly unaligned slice, since the caller
1720             --  expects an appropriately aligned argument.
1721
1722             elsif Is_Possibly_Unaligned_Slice (Actual) then
1723                Add_Call_By_Copy_Code;
1724
1725             --  An unusual case: a current instance of an enclosing task can be
1726             --  an actual, and must be replaced by a reference to self.
1727
1728             elsif Is_Entity_Name (Actual)
1729               and then Is_Task_Type (Entity (Actual))
1730             then
1731                if In_Open_Scopes (Entity (Actual)) then
1732                   Rewrite (Actual,
1733                     (Make_Function_Call (Loc,
1734                      Name => New_Reference_To (RTE (RE_Self), Loc))));
1735                   Analyze (Actual);
1736
1737                --  A task type cannot otherwise appear as an actual
1738
1739                else
1740                   raise Program_Error;
1741                end if;
1742             end if;
1743          end if;
1744
1745          Next_Formal (Formal);
1746          Next_Actual (Actual);
1747       end loop;
1748
1749       --  Find right place to put post call stuff if it is present
1750
1751       if not Is_Empty_List (Post_Call) then
1752
1753          --  If call is not a list member, it must be the triggering statement
1754          --  of a triggering alternative or an entry call alternative, and we
1755          --  can add the post call stuff to the corresponding statement list.
1756
1757          if not Is_List_Member (N) then
1758             declare
1759                P : constant Node_Id := Parent (N);
1760
1761             begin
1762                pragma Assert (Nkind_In (P, N_Triggering_Alternative,
1763                                            N_Entry_Call_Alternative));
1764
1765                if Is_Non_Empty_List (Statements (P)) then
1766                   Insert_List_Before_And_Analyze
1767                     (First (Statements (P)), Post_Call);
1768                else
1769                   Set_Statements (P, Post_Call);
1770                end if;
1771             end;
1772
1773          --  Otherwise, normal case where N is in a statement sequence,
1774          --  just put the post-call stuff after the call statement.
1775
1776          else
1777             Insert_Actions_After (N, Post_Call);
1778          end if;
1779       end if;
1780
1781       --  The call node itself is re-analyzed in Expand_Call
1782
1783    end Expand_Actuals;
1784
1785    -----------------
1786    -- Expand_Call --
1787    -----------------
1788
1789    --  This procedure handles expansion of function calls and procedure call
1790    --  statements (i.e. it serves as the body for Expand_N_Function_Call and
1791    --  Expand_N_Procedure_Call_Statement). Processing for calls includes:
1792
1793    --    Replace call to Raise_Exception by Raise_Exception_Always if possible
1794    --    Provide values of actuals for all formals in Extra_Formals list
1795    --    Replace "call" to enumeration literal function by literal itself
1796    --    Rewrite call to predefined operator as operator
1797    --    Replace actuals to in-out parameters that are numeric conversions,
1798    --     with explicit assignment to temporaries before and after the call.
1799    --    Remove optional actuals if First_Optional_Parameter specified.
1800
1801    --   Note that the list of actuals has been filled with default expressions
1802    --   during semantic analysis of the call. Only the extra actuals required
1803    --   for the 'Constrained attribute and for accessibility checks are added
1804    --   at this point.
1805
1806    procedure Expand_Call (N : Node_Id) is
1807       Loc           : constant Source_Ptr := Sloc (N);
1808       Call_Node     : Node_Id := N;
1809       Extra_Actuals : List_Id := No_List;
1810       Prev          : Node_Id := Empty;
1811
1812       procedure Add_Actual_Parameter (Insert_Param : Node_Id);
1813       --  Adds one entry to the end of the actual parameter list. Used for
1814       --  default parameters and for extra actuals (for Extra_Formals). The
1815       --  argument is an N_Parameter_Association node.
1816
1817       procedure Add_Extra_Actual (Expr : Node_Id; EF : Entity_Id);
1818       --  Adds an extra actual to the list of extra actuals. Expr is the
1819       --  expression for the value of the actual, EF is the entity for the
1820       --  extra formal.
1821
1822       function Inherited_From_Formal (S : Entity_Id) return Entity_Id;
1823       --  Within an instance, a type derived from a non-tagged formal derived
1824       --  type inherits from the original parent, not from the actual. The
1825       --  current derivation mechanism has the derived type inherit from the
1826       --  actual, which is only correct outside of the instance. If the
1827       --  subprogram is inherited, we test for this particular case through a
1828       --  convoluted tree traversal before setting the proper subprogram to be
1829       --  called.
1830
1831       function Is_Direct_Deep_Call (Subp : Entity_Id) return Boolean;
1832       --  Determine if Subp denotes a non-dispatching call to a Deep routine
1833
1834       function New_Value (From : Node_Id) return Node_Id;
1835       --  From is the original Expression. New_Value is equivalent to a call
1836       --  to Duplicate_Subexpr with an explicit dereference when From is an
1837       --  access parameter.
1838
1839       --------------------------
1840       -- Add_Actual_Parameter --
1841       --------------------------
1842
1843       procedure Add_Actual_Parameter (Insert_Param : Node_Id) is
1844          Actual_Expr : constant Node_Id :=
1845                          Explicit_Actual_Parameter (Insert_Param);
1846
1847       begin
1848          --  Case of insertion is first named actual
1849
1850          if No (Prev) or else
1851             Nkind (Parent (Prev)) /= N_Parameter_Association
1852          then
1853             Set_Next_Named_Actual
1854               (Insert_Param, First_Named_Actual (Call_Node));
1855             Set_First_Named_Actual (Call_Node, Actual_Expr);
1856
1857             if No (Prev) then
1858                if No (Parameter_Associations (Call_Node)) then
1859                   Set_Parameter_Associations (Call_Node, New_List);
1860                end if;
1861
1862                Append (Insert_Param, Parameter_Associations (Call_Node));
1863
1864             else
1865                Insert_After (Prev, Insert_Param);
1866             end if;
1867
1868          --  Case of insertion is not first named actual
1869
1870          else
1871             Set_Next_Named_Actual
1872               (Insert_Param, Next_Named_Actual (Parent (Prev)));
1873             Set_Next_Named_Actual (Parent (Prev), Actual_Expr);
1874             Append (Insert_Param, Parameter_Associations (Call_Node));
1875          end if;
1876
1877          Prev := Actual_Expr;
1878       end Add_Actual_Parameter;
1879
1880       ----------------------
1881       -- Add_Extra_Actual --
1882       ----------------------
1883
1884       procedure Add_Extra_Actual (Expr : Node_Id; EF : Entity_Id) is
1885          Loc : constant Source_Ptr := Sloc (Expr);
1886
1887       begin
1888          if Extra_Actuals = No_List then
1889             Extra_Actuals := New_List;
1890             Set_Parent (Extra_Actuals, Call_Node);
1891          end if;
1892
1893          Append_To (Extra_Actuals,
1894            Make_Parameter_Association (Loc,
1895              Selector_Name             => Make_Identifier (Loc, Chars (EF)),
1896              Explicit_Actual_Parameter => Expr));
1897
1898          Analyze_And_Resolve (Expr, Etype (EF));
1899
1900          if Nkind (Call_Node) = N_Function_Call then
1901             Set_Is_Accessibility_Actual (Parent (Expr));
1902          end if;
1903       end Add_Extra_Actual;
1904
1905       ---------------------------
1906       -- Inherited_From_Formal --
1907       ---------------------------
1908
1909       function Inherited_From_Formal (S : Entity_Id) return Entity_Id is
1910          Par      : Entity_Id;
1911          Gen_Par  : Entity_Id;
1912          Gen_Prim : Elist_Id;
1913          Elmt     : Elmt_Id;
1914          Indic    : Node_Id;
1915
1916       begin
1917          --  If the operation is inherited, it is attached to the corresponding
1918          --  type derivation. If the parent in the derivation is a generic
1919          --  actual, it is a subtype of the actual, and we have to recover the
1920          --  original derived type declaration to find the proper parent.
1921
1922          if Nkind (Parent (S)) /= N_Full_Type_Declaration
1923            or else not Is_Derived_Type (Defining_Identifier (Parent (S)))
1924            or else Nkind (Type_Definition (Original_Node (Parent (S)))) /=
1925                                                    N_Derived_Type_Definition
1926            or else not In_Instance
1927          then
1928             return Empty;
1929
1930          else
1931             Indic :=
1932               Subtype_Indication
1933                 (Type_Definition (Original_Node (Parent (S))));
1934
1935             if Nkind (Indic) = N_Subtype_Indication then
1936                Par := Entity (Subtype_Mark (Indic));
1937             else
1938                Par := Entity (Indic);
1939             end if;
1940          end if;
1941
1942          if not Is_Generic_Actual_Type (Par)
1943            or else Is_Tagged_Type (Par)
1944            or else Nkind (Parent (Par)) /= N_Subtype_Declaration
1945            or else not In_Open_Scopes (Scope (Par))
1946          then
1947             return Empty;
1948          else
1949             Gen_Par := Generic_Parent_Type (Parent (Par));
1950          end if;
1951
1952          --  If the actual has no generic parent type, the formal is not
1953          --  a formal derived type, so nothing to inherit.
1954
1955          if No (Gen_Par) then
1956             return Empty;
1957          end if;
1958
1959          --  If the generic parent type is still the generic type, this is a
1960          --  private formal, not a derived formal, and there are no operations
1961          --  inherited from the formal.
1962
1963          if Nkind (Parent (Gen_Par)) = N_Formal_Type_Declaration then
1964             return Empty;
1965          end if;
1966
1967          Gen_Prim := Collect_Primitive_Operations (Gen_Par);
1968
1969          Elmt := First_Elmt (Gen_Prim);
1970          while Present (Elmt) loop
1971             if Chars (Node (Elmt)) = Chars (S) then
1972                declare
1973                   F1 : Entity_Id;
1974                   F2 : Entity_Id;
1975
1976                begin
1977                   F1 := First_Formal (S);
1978                   F2 := First_Formal (Node (Elmt));
1979                   while Present (F1)
1980                     and then Present (F2)
1981                   loop
1982                      if Etype (F1) = Etype (F2)
1983                        or else Etype (F2) = Gen_Par
1984                      then
1985                         Next_Formal (F1);
1986                         Next_Formal (F2);
1987                      else
1988                         Next_Elmt (Elmt);
1989                         exit;   --  not the right subprogram
1990                      end if;
1991
1992                      return Node (Elmt);
1993                   end loop;
1994                end;
1995
1996             else
1997                Next_Elmt (Elmt);
1998             end if;
1999          end loop;
2000
2001          raise Program_Error;
2002       end Inherited_From_Formal;
2003
2004       -------------------------
2005       -- Is_Direct_Deep_Call --
2006       -------------------------
2007
2008       function Is_Direct_Deep_Call (Subp : Entity_Id) return Boolean is
2009       begin
2010          if Is_TSS (Subp, TSS_Deep_Adjust)
2011            or else Is_TSS (Subp, TSS_Deep_Finalize)
2012            or else Is_TSS (Subp, TSS_Deep_Initialize)
2013          then
2014             declare
2015                Actual : Node_Id;
2016                Formal : Node_Id;
2017
2018             begin
2019                Actual := First (Parameter_Associations (N));
2020                Formal := First_Formal (Subp);
2021                while Present (Actual)
2022                  and then Present (Formal)
2023                loop
2024                   if Nkind (Actual) = N_Identifier
2025                     and then Is_Controlling_Actual (Actual)
2026                     and then Etype (Actual) = Etype (Formal)
2027                   then
2028                      return True;
2029                   end if;
2030
2031                   Next (Actual);
2032                   Next_Formal (Formal);
2033                end loop;
2034             end;
2035          end if;
2036
2037          return False;
2038       end Is_Direct_Deep_Call;
2039
2040       ---------------
2041       -- New_Value --
2042       ---------------
2043
2044       function New_Value (From : Node_Id) return Node_Id is
2045          Res : constant Node_Id := Duplicate_Subexpr (From);
2046       begin
2047          if Is_Access_Type (Etype (From)) then
2048             return
2049               Make_Explicit_Dereference (Sloc (From),
2050                 Prefix => Res);
2051          else
2052             return Res;
2053          end if;
2054       end New_Value;
2055
2056       --  Local variables
2057
2058       Curr_S        : constant Entity_Id := Current_Scope;
2059       Remote        : constant Boolean   := Is_Remote_Call (Call_Node);
2060       Actual        : Node_Id;
2061       Formal        : Entity_Id;
2062       Orig_Subp     : Entity_Id := Empty;
2063       Param_Count   : Natural := 0;
2064       Parent_Formal : Entity_Id;
2065       Parent_Subp   : Entity_Id;
2066       Scop          : Entity_Id;
2067       Subp          : Entity_Id;
2068
2069       Prev_Orig : Node_Id;
2070       --  Original node for an actual, which may have been rewritten. If the
2071       --  actual is a function call that has been transformed from a selected
2072       --  component, the original node is unanalyzed. Otherwise, it carries
2073       --  semantic information used to generate additional actuals.
2074
2075       CW_Interface_Formals_Present : Boolean := False;
2076
2077    --  Start of processing for Expand_Call
2078
2079    begin
2080       --  Ignore if previous error
2081
2082       if Nkind (Call_Node) in N_Has_Etype
2083         and then Etype (Call_Node) = Any_Type
2084       then
2085          return;
2086       end if;
2087
2088       --  Call using access to subprogram with explicit dereference
2089
2090       if Nkind (Name (Call_Node)) = N_Explicit_Dereference then
2091          Subp        := Etype (Name (Call_Node));
2092          Parent_Subp := Empty;
2093
2094       --  Case of call to simple entry, where the Name is a selected component
2095       --  whose prefix is the task, and whose selector name is the entry name
2096
2097       elsif Nkind (Name (Call_Node)) = N_Selected_Component then
2098          Subp        := Entity (Selector_Name (Name (Call_Node)));
2099          Parent_Subp := Empty;
2100
2101       --  Case of call to member of entry family, where Name is an indexed
2102       --  component, with the prefix being a selected component giving the
2103       --  task and entry family name, and the index being the entry index.
2104
2105       elsif Nkind (Name (Call_Node)) = N_Indexed_Component then
2106          Subp        := Entity (Selector_Name (Prefix (Name (Call_Node))));
2107          Parent_Subp := Empty;
2108
2109       --  Normal case
2110
2111       else
2112          Subp        := Entity (Name (Call_Node));
2113          Parent_Subp := Alias (Subp);
2114
2115          --  Replace call to Raise_Exception by call to Raise_Exception_Always
2116          --  if we can tell that the first parameter cannot possibly be null.
2117          --  This improves efficiency by avoiding a run-time test.
2118
2119          --  We do not do this if Raise_Exception_Always does not exist, which
2120          --  can happen in configurable run time profiles which provide only a
2121          --  Raise_Exception.
2122
2123          if Is_RTE (Subp, RE_Raise_Exception)
2124            and then RTE_Available (RE_Raise_Exception_Always)
2125          then
2126             declare
2127                FA : constant Node_Id :=
2128                       Original_Node (First_Actual (Call_Node));
2129
2130             begin
2131                --  The case we catch is where the first argument is obtained
2132                --  using the Identity attribute (which must always be
2133                --  non-null).
2134
2135                if Nkind (FA) = N_Attribute_Reference
2136                  and then Attribute_Name (FA) = Name_Identity
2137                then
2138                   Subp := RTE (RE_Raise_Exception_Always);
2139                   Set_Name (Call_Node, New_Occurrence_Of (Subp, Loc));
2140                end if;
2141             end;
2142          end if;
2143
2144          if Ekind (Subp) = E_Entry then
2145             Parent_Subp := Empty;
2146          end if;
2147       end if;
2148
2149       --  Detect the following code in System.Finalization_Masters only on
2150       --  .NET/JVM targets:
2151       --
2152       --    procedure Finalize (Master : in out Finalization_Master) is
2153       --    begin
2154       --       . . .
2155       --       begin
2156       --          Finalize (Curr_Ptr.all);
2157       --
2158       --  Since .NET/JVM compilers lack address arithmetic and Deep_Finalize
2159       --  cannot be named in library or user code, the compiler has to install
2160       --  a kludge and transform the call to Finalize into Deep_Finalize.
2161
2162       if VM_Target /= No_VM
2163         and then Chars (Subp) = Name_Finalize
2164         and then Ekind (Curr_S) = E_Block
2165         and then Ekind (Scope (Curr_S)) = E_Procedure
2166         and then Chars (Scope (Curr_S)) = Name_Finalize
2167         and then Etype (First_Formal (Scope (Curr_S))) =
2168                    RTE (RE_Finalization_Master)
2169       then
2170          declare
2171             Deep_Fin : constant Entity_Id :=
2172                          Find_Prim_Op (RTE (RE_Root_Controlled),
2173                                        TSS_Deep_Finalize);
2174          begin
2175             --  Since Root_Controlled is a tagged type, the compiler should
2176             --  always generate Deep_Finalize for it.
2177
2178             pragma Assert (Present (Deep_Fin));
2179
2180             --  Generate:
2181             --    Deep_Finalize (Curr_Ptr.all);
2182
2183             Rewrite (N,
2184               Make_Procedure_Call_Statement (Loc,
2185                 Name =>
2186                   New_Reference_To (Deep_Fin, Loc),
2187                 Parameter_Associations =>
2188                   New_Copy_List_Tree (Parameter_Associations (N))));
2189
2190             Analyze (N);
2191             return;
2192          end;
2193       end if;
2194
2195       --  Ada 2005 (AI-345): We have a procedure call as a triggering
2196       --  alternative in an asynchronous select or as an entry call in
2197       --  a conditional or timed select. Check whether the procedure call
2198       --  is a renaming of an entry and rewrite it as an entry call.
2199
2200       if Ada_Version >= Ada_2005
2201         and then Nkind (Call_Node) = N_Procedure_Call_Statement
2202         and then
2203            ((Nkind (Parent (Call_Node)) = N_Triggering_Alternative
2204               and then Triggering_Statement (Parent (Call_Node)) = Call_Node)
2205           or else
2206             (Nkind (Parent (Call_Node)) = N_Entry_Call_Alternative
2207               and then Entry_Call_Statement (Parent (Call_Node)) = Call_Node))
2208       then
2209          declare
2210             Ren_Decl : Node_Id;
2211             Ren_Root : Entity_Id := Subp;
2212
2213          begin
2214             --  This may be a chain of renamings, find the root
2215
2216             if Present (Alias (Ren_Root)) then
2217                Ren_Root := Alias (Ren_Root);
2218             end if;
2219
2220             if Present (Original_Node (Parent (Parent (Ren_Root)))) then
2221                Ren_Decl := Original_Node (Parent (Parent (Ren_Root)));
2222
2223                if Nkind (Ren_Decl) = N_Subprogram_Renaming_Declaration then
2224                   Rewrite (Call_Node,
2225                     Make_Entry_Call_Statement (Loc,
2226                       Name =>
2227                         New_Copy_Tree (Name (Ren_Decl)),
2228                       Parameter_Associations =>
2229                         New_Copy_List_Tree
2230                           (Parameter_Associations (Call_Node))));
2231
2232                   return;
2233                end if;
2234             end if;
2235          end;
2236       end if;
2237
2238       --  First step, compute extra actuals, corresponding to any Extra_Formals
2239       --  present. Note that we do not access Extra_Formals directly, instead
2240       --  we simply note the presence of the extra formals as we process the
2241       --  regular formals collecting corresponding actuals in Extra_Actuals.
2242
2243       --  We also generate any required range checks for actuals for in formals
2244       --  as we go through the loop, since this is a convenient place to do it.
2245       --  (Though it seems that this would be better done in Expand_Actuals???)
2246
2247       Formal := First_Formal (Subp);
2248       Actual := First_Actual (Call_Node);
2249       Param_Count := 1;
2250       while Present (Formal) loop
2251
2252          --  Generate range check if required
2253
2254          if Do_Range_Check (Actual)
2255            and then Ekind (Formal) = E_In_Parameter
2256          then
2257             Set_Do_Range_Check (Actual, False);
2258             Generate_Range_Check
2259               (Actual, Etype (Formal), CE_Range_Check_Failed);
2260          end if;
2261
2262          --  Prepare to examine current entry
2263
2264          Prev := Actual;
2265          Prev_Orig := Original_Node (Prev);
2266
2267          --  Ada 2005 (AI-251): Check if any formal is a class-wide interface
2268          --  to expand it in a further round.
2269
2270          CW_Interface_Formals_Present :=
2271            CW_Interface_Formals_Present
2272              or else
2273                (Ekind (Etype (Formal)) = E_Class_Wide_Type
2274                  and then Is_Interface (Etype (Etype (Formal))))
2275              or else
2276                (Ekind (Etype (Formal)) = E_Anonymous_Access_Type
2277                  and then Is_Interface (Directly_Designated_Type
2278                                          (Etype (Etype (Formal)))));
2279
2280          --  Create possible extra actual for constrained case. Usually, the
2281          --  extra actual is of the form actual'constrained, but since this
2282          --  attribute is only available for unconstrained records, TRUE is
2283          --  expanded if the type of the formal happens to be constrained (for
2284          --  instance when this procedure is inherited from an unconstrained
2285          --  record to a constrained one) or if the actual has no discriminant
2286          --  (its type is constrained). An exception to this is the case of a
2287          --  private type without discriminants. In this case we pass FALSE
2288          --  because the object has underlying discriminants with defaults.
2289
2290          if Present (Extra_Constrained (Formal)) then
2291             if Ekind (Etype (Prev)) in Private_Kind
2292               and then not Has_Discriminants (Base_Type (Etype (Prev)))
2293             then
2294                Add_Extra_Actual
2295                  (New_Occurrence_Of (Standard_False, Loc),
2296                   Extra_Constrained (Formal));
2297
2298             elsif Is_Constrained (Etype (Formal))
2299               or else not Has_Discriminants (Etype (Prev))
2300             then
2301                Add_Extra_Actual
2302                  (New_Occurrence_Of (Standard_True, Loc),
2303                   Extra_Constrained (Formal));
2304
2305             --  Do not produce extra actuals for Unchecked_Union parameters.
2306             --  Jump directly to the end of the loop.
2307
2308             elsif Is_Unchecked_Union (Base_Type (Etype (Actual))) then
2309                goto Skip_Extra_Actual_Generation;
2310
2311             else
2312                --  If the actual is a type conversion, then the constrained
2313                --  test applies to the actual, not the target type.
2314
2315                declare
2316                   Act_Prev : Node_Id;
2317
2318                begin
2319                   --  Test for unchecked conversions as well, which can occur
2320                   --  as out parameter actuals on calls to stream procedures.
2321
2322                   Act_Prev := Prev;
2323                   while Nkind_In (Act_Prev, N_Type_Conversion,
2324                                             N_Unchecked_Type_Conversion)
2325                   loop
2326                      Act_Prev := Expression (Act_Prev);
2327                   end loop;
2328
2329                   --  If the expression is a conversion of a dereference, this
2330                   --  is internally generated code that manipulates addresses,
2331                   --  e.g. when building interface tables. No check should
2332                   --  occur in this case, and the discriminated object is not
2333                   --  directly a hand.
2334
2335                   if not Comes_From_Source (Actual)
2336                     and then Nkind (Actual) = N_Unchecked_Type_Conversion
2337                     and then Nkind (Act_Prev) = N_Explicit_Dereference
2338                   then
2339                      Add_Extra_Actual
2340                        (New_Occurrence_Of (Standard_False, Loc),
2341                         Extra_Constrained (Formal));
2342
2343                   else
2344                      Add_Extra_Actual
2345                        (Make_Attribute_Reference (Sloc (Prev),
2346                         Prefix =>
2347                           Duplicate_Subexpr_No_Checks
2348                             (Act_Prev, Name_Req => True),
2349                         Attribute_Name => Name_Constrained),
2350                         Extra_Constrained (Formal));
2351                   end if;
2352                end;
2353             end if;
2354          end if;
2355
2356          --  Create possible extra actual for accessibility level
2357
2358          if Present (Extra_Accessibility (Formal)) then
2359
2360             --  Ada 2005 (AI-252): If the actual was rewritten as an Access
2361             --  attribute, then the original actual may be an aliased object
2362             --  occurring as the prefix in a call using "Object.Operation"
2363             --  notation. In that case we must pass the level of the object,
2364             --  so Prev_Orig is reset to Prev and the attribute will be
2365             --  processed by the code for Access attributes further below.
2366
2367             if Prev_Orig /= Prev
2368               and then Nkind (Prev) = N_Attribute_Reference
2369               and then
2370                 Get_Attribute_Id (Attribute_Name (Prev)) = Attribute_Access
2371               and then Is_Aliased_View (Prev_Orig)
2372             then
2373                Prev_Orig := Prev;
2374             end if;
2375
2376             --  Ada 2005 (AI-251): Thunks must propagate the extra actuals of
2377             --  accessibility levels.
2378
2379             if Ekind (Current_Scope) in Subprogram_Kind
2380               and then Is_Thunk (Current_Scope)
2381             then
2382                declare
2383                   Parm_Ent : Entity_Id;
2384
2385                begin
2386                   if Is_Controlling_Actual (Actual) then
2387
2388                      --  Find the corresponding actual of the thunk
2389
2390                      Parm_Ent := First_Entity (Current_Scope);
2391                      for J in 2 .. Param_Count loop
2392                         Next_Entity (Parm_Ent);
2393                      end loop;
2394
2395                   else pragma Assert (Is_Entity_Name (Actual));
2396                      Parm_Ent := Entity (Actual);
2397                   end if;
2398
2399                   Add_Extra_Actual
2400                     (New_Occurrence_Of (Extra_Accessibility (Parm_Ent), Loc),
2401                      Extra_Accessibility (Formal));
2402                end;
2403
2404             elsif Is_Entity_Name (Prev_Orig) then
2405
2406                --  When passing an access parameter, or a renaming of an access
2407                --  parameter, as the actual to another access parameter we need
2408                --  to pass along the actual's own access level parameter. This
2409                --  is done if we are within the scope of the formal access
2410                --  parameter (if this is an inlined body the extra formal is
2411                --  irrelevant).
2412
2413                if (Is_Formal (Entity (Prev_Orig))
2414                     or else
2415                       (Present (Renamed_Object (Entity (Prev_Orig)))
2416                         and then
2417                           Is_Entity_Name (Renamed_Object (Entity (Prev_Orig)))
2418                         and then
2419                           Is_Formal
2420                             (Entity (Renamed_Object (Entity (Prev_Orig))))))
2421                  and then Ekind (Etype (Prev_Orig)) = E_Anonymous_Access_Type
2422                  and then In_Open_Scopes (Scope (Entity (Prev_Orig)))
2423                then
2424                   declare
2425                      Parm_Ent : constant Entity_Id := Param_Entity (Prev_Orig);
2426
2427                   begin
2428                      pragma Assert (Present (Parm_Ent));
2429
2430                      if Present (Extra_Accessibility (Parm_Ent)) then
2431                         Add_Extra_Actual
2432                           (New_Occurrence_Of
2433                              (Extra_Accessibility (Parm_Ent), Loc),
2434                            Extra_Accessibility (Formal));
2435
2436                      --  If the actual access parameter does not have an
2437                      --  associated extra formal providing its scope level,
2438                      --  then treat the actual as having library-level
2439                      --  accessibility.
2440
2441                      else
2442                         Add_Extra_Actual
2443                           (Make_Integer_Literal (Loc,
2444                              Intval => Scope_Depth (Standard_Standard)),
2445                            Extra_Accessibility (Formal));
2446                      end if;
2447                   end;
2448
2449                --  The actual is a normal access value, so just pass the level
2450                --  of the actual's access type.
2451
2452                else
2453                   Add_Extra_Actual
2454                     (Dynamic_Accessibility_Level (Prev_Orig),
2455                      Extra_Accessibility (Formal));
2456                end if;
2457
2458             --  If the actual is an access discriminant, then pass the level
2459             --  of the enclosing object (RM05-3.10.2(12.4/2)).
2460
2461             elsif Nkind (Prev_Orig) = N_Selected_Component
2462               and then Ekind (Entity (Selector_Name (Prev_Orig))) =
2463                                                        E_Discriminant
2464               and then Ekind (Etype (Entity (Selector_Name (Prev_Orig)))) =
2465                                                        E_Anonymous_Access_Type
2466             then
2467                Add_Extra_Actual
2468                  (Make_Integer_Literal (Loc,
2469                     Intval => Object_Access_Level (Prefix (Prev_Orig))),
2470                   Extra_Accessibility (Formal));
2471
2472             --  All other cases
2473
2474             else
2475                case Nkind (Prev_Orig) is
2476
2477                   when N_Attribute_Reference =>
2478                      case Get_Attribute_Id (Attribute_Name (Prev_Orig)) is
2479
2480                         --  For X'Access, pass on the level of the prefix X
2481
2482                         when Attribute_Access =>
2483
2484                            --  If this is an Access attribute applied to the
2485                            --  the current instance object passed to a type
2486                            --  initialization procedure, then use the level
2487                            --  of the type itself. This is not really correct,
2488                            --  as there should be an extra level parameter
2489                            --  passed in with _init formals (only in the case
2490                            --  where the type is immutably limited), but we
2491                            --  don't have an easy way currently to create such
2492                            --  an extra formal (init procs aren't ever frozen).
2493                            --  For now we just use the level of the type,
2494                            --  which may be too shallow, but that works better
2495                            --  than passing Object_Access_Level of the type,
2496                            --  which can be one level too deep in some cases.
2497                            --  ???
2498
2499                            if Is_Entity_Name (Prefix (Prev_Orig))
2500                              and then Is_Type (Entity (Prefix (Prev_Orig)))
2501                            then
2502                               Add_Extra_Actual
2503                                 (Make_Integer_Literal (Loc,
2504                                    Intval =>
2505                                      Type_Access_Level
2506                                        (Entity (Prefix (Prev_Orig)))),
2507                                  Extra_Accessibility (Formal));
2508
2509                            else
2510                               Add_Extra_Actual
2511                                 (Make_Integer_Literal (Loc,
2512                                    Intval =>
2513                                      Object_Access_Level
2514                                        (Prefix (Prev_Orig))),
2515                                  Extra_Accessibility (Formal));
2516                            end if;
2517
2518                         --  Treat the unchecked attributes as library-level
2519
2520                         when Attribute_Unchecked_Access |
2521                            Attribute_Unrestricted_Access =>
2522                            Add_Extra_Actual
2523                              (Make_Integer_Literal (Loc,
2524                                 Intval => Scope_Depth (Standard_Standard)),
2525                               Extra_Accessibility (Formal));
2526
2527                         --  No other cases of attributes returning access
2528                         --  values that can be passed to access parameters.
2529
2530                         when others =>
2531                            raise Program_Error;
2532
2533                      end case;
2534
2535                   --  For allocators we pass the level of the execution of the
2536                   --  called subprogram, which is one greater than the current
2537                   --  scope level.
2538
2539                   when N_Allocator =>
2540                      Add_Extra_Actual
2541                        (Make_Integer_Literal (Loc,
2542                           Intval => Scope_Depth (Current_Scope) + 1),
2543                         Extra_Accessibility (Formal));
2544
2545                   --  For most other cases we simply pass the level of the
2546                   --  actual's access type. The type is retrieved from
2547                   --  Prev rather than Prev_Orig, because in some cases
2548                   --  Prev_Orig denotes an original expression that has
2549                   --  not been analyzed.
2550
2551                   when others =>
2552                      Add_Extra_Actual
2553                        (Dynamic_Accessibility_Level (Prev),
2554                         Extra_Accessibility (Formal));
2555                end case;
2556             end if;
2557          end if;
2558
2559          --  Perform the check of 4.6(49) that prevents a null value from being
2560          --  passed as an actual to an access parameter. Note that the check
2561          --  is elided in the common cases of passing an access attribute or
2562          --  access parameter as an actual. Also, we currently don't enforce
2563          --  this check for expander-generated actuals and when -gnatdj is set.
2564
2565          if Ada_Version >= Ada_2005 then
2566
2567             --  Ada 2005 (AI-231): Check null-excluding access types. Note that
2568             --  the intent of 6.4.1(13) is that null-exclusion checks should
2569             --  not be done for 'out' parameters, even though it refers only
2570             --  to constraint checks, and a null_exclusion is not a constraint.
2571             --  Note that AI05-0196-1 corrects this mistake in the RM.
2572
2573             if Is_Access_Type (Etype (Formal))
2574               and then Can_Never_Be_Null (Etype (Formal))
2575               and then Ekind (Formal) /= E_Out_Parameter
2576               and then Nkind (Prev) /= N_Raise_Constraint_Error
2577               and then (Known_Null (Prev)
2578                          or else not Can_Never_Be_Null (Etype (Prev)))
2579             then
2580                Install_Null_Excluding_Check (Prev);
2581             end if;
2582
2583          --  Ada_Version < Ada_2005
2584
2585          else
2586             if Ekind (Etype (Formal)) /= E_Anonymous_Access_Type
2587               or else Access_Checks_Suppressed (Subp)
2588             then
2589                null;
2590
2591             elsif Debug_Flag_J then
2592                null;
2593
2594             elsif not Comes_From_Source (Prev) then
2595                null;
2596
2597             elsif Is_Entity_Name (Prev)
2598               and then Ekind (Etype (Prev)) = E_Anonymous_Access_Type
2599             then
2600                null;
2601
2602             elsif Nkind_In (Prev, N_Allocator, N_Attribute_Reference) then
2603                null;
2604
2605             --  Suppress null checks when passing to access parameters of Java
2606             --  and CIL subprograms. (Should this be done for other foreign
2607             --  conventions as well ???)
2608
2609             elsif Convention (Subp) = Convention_Java
2610               or else Convention (Subp) = Convention_CIL
2611             then
2612                null;
2613
2614             else
2615                Install_Null_Excluding_Check (Prev);
2616             end if;
2617          end if;
2618
2619          --  Perform appropriate validity checks on parameters that
2620          --  are entities.
2621
2622          if Validity_Checks_On then
2623             if  (Ekind (Formal) = E_In_Parameter
2624                   and then Validity_Check_In_Params)
2625               or else
2626                 (Ekind (Formal) = E_In_Out_Parameter
2627                   and then Validity_Check_In_Out_Params)
2628             then
2629                --  If the actual is an indexed component of a packed type (or
2630                --  is an indexed or selected component whose prefix recursively
2631                --  meets this condition), it has not been expanded yet. It will
2632                --  be copied in the validity code that follows, and has to be
2633                --  expanded appropriately, so reanalyze it.
2634
2635                --  What we do is just to unset analyzed bits on prefixes till
2636                --  we reach something that does not have a prefix.
2637
2638                declare
2639                   Nod : Node_Id;
2640
2641                begin
2642                   Nod := Actual;
2643                   while Nkind_In (Nod, N_Indexed_Component,
2644                                        N_Selected_Component)
2645                   loop
2646                      Set_Analyzed (Nod, False);
2647                      Nod := Prefix (Nod);
2648                   end loop;
2649                end;
2650
2651                Ensure_Valid (Actual);
2652             end if;
2653          end if;
2654
2655          --  For Ada 2012, if a parameter is aliased, the actual must be an
2656          --  aliased object.
2657
2658          if Is_Aliased (Formal) and then not Is_Aliased_View (Actual) then
2659             Error_Msg_NE
2660               ("actual for aliased formal& must be aliased object",
2661                Actual, Formal);
2662          end if;
2663
2664          --  For IN OUT and OUT parameters, ensure that subscripts are valid
2665          --  since this is a left side reference. We only do this for calls
2666          --  from the source program since we assume that compiler generated
2667          --  calls explicitly generate any required checks. We also need it
2668          --  only if we are doing standard validity checks, since clearly it is
2669          --  not needed if validity checks are off, and in subscript validity
2670          --  checking mode, all indexed components are checked with a call
2671          --  directly from Expand_N_Indexed_Component.
2672
2673          if Comes_From_Source (Call_Node)
2674            and then Ekind (Formal) /= E_In_Parameter
2675            and then Validity_Checks_On
2676            and then Validity_Check_Default
2677            and then not Validity_Check_Subscripts
2678          then
2679             Check_Valid_Lvalue_Subscripts (Actual);
2680          end if;
2681
2682          --  Mark any scalar OUT parameter that is a simple variable as no
2683          --  longer known to be valid (unless the type is always valid). This
2684          --  reflects the fact that if an OUT parameter is never set in a
2685          --  procedure, then it can become invalid on the procedure return.
2686
2687          if Ekind (Formal) = E_Out_Parameter
2688            and then Is_Entity_Name (Actual)
2689            and then Ekind (Entity (Actual)) = E_Variable
2690            and then not Is_Known_Valid (Etype (Actual))
2691          then
2692             Set_Is_Known_Valid (Entity (Actual), False);
2693          end if;
2694
2695          --  For an OUT or IN OUT parameter, if the actual is an entity, then
2696          --  clear current values, since they can be clobbered. We are probably
2697          --  doing this in more places than we need to, but better safe than
2698          --  sorry when it comes to retaining bad current values!
2699
2700          if Ekind (Formal) /= E_In_Parameter
2701            and then Is_Entity_Name (Actual)
2702            and then Present (Entity (Actual))
2703          then
2704             declare
2705                Ent : constant Entity_Id := Entity (Actual);
2706                Sav : Node_Id;
2707
2708             begin
2709                --  For an OUT or IN OUT parameter that is an assignable entity,
2710                --  we do not want to clobber the Last_Assignment field, since
2711                --  if it is set, it was precisely because it is indeed an OUT
2712                --  or IN OUT parameter! We do reset the Is_Known_Valid flag
2713                --  since the subprogram could have returned in invalid value.
2714
2715                if Ekind_In (Formal, E_Out_Parameter, E_In_Out_Parameter)
2716                  and then Is_Assignable (Ent)
2717                then
2718                   Sav := Last_Assignment (Ent);
2719                   Kill_Current_Values (Ent);
2720                   Set_Last_Assignment (Ent, Sav);
2721                   Set_Is_Known_Valid (Ent, False);
2722
2723                   --  For all other cases, just kill the current values
2724
2725                else
2726                   Kill_Current_Values (Ent);
2727                end if;
2728             end;
2729          end if;
2730
2731          --  If the formal is class wide and the actual is an aggregate, force
2732          --  evaluation so that the back end who does not know about class-wide
2733          --  type, does not generate a temporary of the wrong size.
2734
2735          if not Is_Class_Wide_Type (Etype (Formal)) then
2736             null;
2737
2738          elsif Nkind (Actual) = N_Aggregate
2739            or else (Nkind (Actual) = N_Qualified_Expression
2740                      and then Nkind (Expression (Actual)) = N_Aggregate)
2741          then
2742             Force_Evaluation (Actual);
2743          end if;
2744
2745          --  In a remote call, if the formal is of a class-wide type, check
2746          --  that the actual meets the requirements described in E.4(18).
2747
2748          if Remote and then Is_Class_Wide_Type (Etype (Formal)) then
2749             Insert_Action (Actual,
2750               Make_Transportable_Check (Loc,
2751                 Duplicate_Subexpr_Move_Checks (Actual)));
2752          end if;
2753
2754          --  This label is required when skipping extra actual generation for
2755          --  Unchecked_Union parameters.
2756
2757          <<Skip_Extra_Actual_Generation>>
2758
2759          Param_Count := Param_Count + 1;
2760          Next_Actual (Actual);
2761          Next_Formal (Formal);
2762       end loop;
2763
2764       --  If we are calling an Ada2012 function which needs to have the
2765       --  "accessibility level determined by the point of call" (AI05-0234)
2766       --  passed in to it, then pass it in.
2767
2768       if Ekind_In (Subp, E_Function, E_Operator, E_Subprogram_Type)
2769         and then
2770           Present (Extra_Accessibility_Of_Result (Ultimate_Alias (Subp)))
2771       then
2772          declare
2773             Ancestor : Node_Id := Parent (Call_Node);
2774             Level    : Node_Id := Empty;
2775             Defer    : Boolean := False;
2776
2777          begin
2778             --  Unimplemented: if Subp returns an anonymous access type, then
2779
2780             --    a) if the call is the operand of an explict conversion, then
2781             --       the target type of the conversion (a named access type)
2782             --       determines the accessibility level pass in;
2783
2784             --    b) if the call defines an access discriminant of an object
2785             --       (e.g., the discriminant of an object being created by an
2786             --       allocator, or the discriminant of a function result),
2787             --       then the accessibility level to pass in is that of the
2788             --       discriminated object being initialized).
2789
2790             --  ???
2791
2792             while Nkind (Ancestor) = N_Qualified_Expression
2793             loop
2794                Ancestor := Parent (Ancestor);
2795             end loop;
2796
2797             case Nkind (Ancestor) is
2798                when N_Allocator =>
2799
2800                   --  At this point, we'd like to assign
2801
2802                   --    Level := Dynamic_Accessibility_Level (Ancestor);
2803
2804                   --  but Etype of Ancestor may not have been set yet,
2805                   --  so that doesn't work.
2806
2807                   --  Handle this later in Expand_Allocator_Expression.
2808
2809                   Defer := True;
2810
2811                when N_Object_Declaration | N_Object_Renaming_Declaration =>
2812                   declare
2813                      Def_Id : constant Entity_Id :=
2814                                 Defining_Identifier (Ancestor);
2815
2816                   begin
2817                      if Is_Return_Object (Def_Id) then
2818                         if Present (Extra_Accessibility_Of_Result
2819                                      (Return_Applies_To (Scope (Def_Id))))
2820                         then
2821                            --  Pass along value that was passed in if the
2822                            --  routine we are returning from also has an
2823                            --  Accessibility_Of_Result formal.
2824
2825                            Level :=
2826                              New_Occurrence_Of
2827                               (Extra_Accessibility_Of_Result
2828                                 (Return_Applies_To (Scope (Def_Id))), Loc);
2829                         end if;
2830                      else
2831                         Level :=
2832                           Make_Integer_Literal (Loc,
2833                             Intval => Object_Access_Level (Def_Id));
2834                      end if;
2835                   end;
2836
2837                when N_Simple_Return_Statement =>
2838                   if Present (Extra_Accessibility_Of_Result
2839                                (Return_Applies_To
2840                                  (Return_Statement_Entity (Ancestor))))
2841                   then
2842                      --  Pass along value that was passed in if the routine
2843                      --  we are returning from also has an
2844                      --  Accessibility_Of_Result formal.
2845
2846                      Level :=
2847                        New_Occurrence_Of
2848                          (Extra_Accessibility_Of_Result
2849                             (Return_Applies_To
2850                                (Return_Statement_Entity (Ancestor))), Loc);
2851                   end if;
2852
2853                when others =>
2854                   null;
2855             end case;
2856
2857             if not Defer then
2858                if not Present (Level) then
2859
2860                   --  The "innermost master that evaluates the function call".
2861
2862                   --  ??? - Should we use Integer'Last here instead in order
2863                   --  to deal with (some of) the problems associated with
2864                   --  calls to subps whose enclosing scope is unknown (e.g.,
2865                   --  Anon_Access_To_Subp_Param.all)?
2866
2867                   Level := Make_Integer_Literal (Loc,
2868                              Scope_Depth (Current_Scope) + 1);
2869                end if;
2870
2871                Add_Extra_Actual
2872                  (Level,
2873                   Extra_Accessibility_Of_Result (Ultimate_Alias (Subp)));
2874             end if;
2875          end;
2876       end if;
2877
2878       --  If we are expanding a rhs of an assignment we need to check if tag
2879       --  propagation is needed. You might expect this processing to be in
2880       --  Analyze_Assignment but has to be done earlier (bottom-up) because the
2881       --  assignment might be transformed to a declaration for an unconstrained
2882       --  value if the expression is classwide.
2883
2884       if Nkind (Call_Node) = N_Function_Call
2885         and then Is_Tag_Indeterminate (Call_Node)
2886         and then Is_Entity_Name (Name (Call_Node))
2887       then
2888          declare
2889             Ass : Node_Id := Empty;
2890
2891          begin
2892             if Nkind (Parent (Call_Node)) = N_Assignment_Statement then
2893                Ass := Parent (Call_Node);
2894
2895             elsif Nkind (Parent (Call_Node)) = N_Qualified_Expression
2896               and then Nkind (Parent (Parent (Call_Node))) =
2897                                                   N_Assignment_Statement
2898             then
2899                Ass := Parent (Parent (Call_Node));
2900
2901             elsif Nkind (Parent (Call_Node)) = N_Explicit_Dereference
2902               and then Nkind (Parent (Parent (Call_Node))) =
2903                                                   N_Assignment_Statement
2904             then
2905                Ass := Parent (Parent (Call_Node));
2906             end if;
2907
2908             if Present (Ass)
2909               and then Is_Class_Wide_Type (Etype (Name (Ass)))
2910             then
2911                if Is_Access_Type (Etype (Call_Node)) then
2912                   if Designated_Type (Etype (Call_Node)) /=
2913                     Root_Type (Etype (Name (Ass)))
2914                   then
2915                      Error_Msg_NE
2916                        ("tag-indeterminate expression "
2917                          & " must have designated type& (RM 5.2 (6))",
2918                          Call_Node, Root_Type (Etype (Name (Ass))));
2919                   else
2920                      Propagate_Tag (Name (Ass), Call_Node);
2921                   end if;
2922
2923                elsif Etype (Call_Node) /= Root_Type (Etype (Name (Ass))) then
2924                   Error_Msg_NE
2925                     ("tag-indeterminate expression must have type&"
2926                      & "(RM 5.2 (6))",
2927                      Call_Node, Root_Type (Etype (Name (Ass))));
2928
2929                else
2930                   Propagate_Tag (Name (Ass), Call_Node);
2931                end if;
2932
2933                --  The call will be rewritten as a dispatching call, and
2934                --  expanded as such.
2935
2936                return;
2937             end if;
2938          end;
2939       end if;
2940
2941       --  Ada 2005 (AI-251): If some formal is a class-wide interface, expand
2942       --  it to point to the correct secondary virtual table
2943
2944       if Nkind_In (Call_Node, N_Function_Call, N_Procedure_Call_Statement)
2945         and then CW_Interface_Formals_Present
2946       then
2947          Expand_Interface_Actuals (Call_Node);
2948       end if;
2949
2950       --  Deals with Dispatch_Call if we still have a call, before expanding
2951       --  extra actuals since this will be done on the re-analysis of the
2952       --  dispatching call. Note that we do not try to shorten the actual list
2953       --  for a dispatching call, it would not make sense to do so. Expansion
2954       --  of dispatching calls is suppressed when VM_Target, because the VM
2955       --  back-ends directly handle the generation of dispatching calls and
2956       --  would have to undo any expansion to an indirect call.
2957
2958       if Nkind_In (Call_Node, N_Function_Call, N_Procedure_Call_Statement)
2959         and then Present (Controlling_Argument (Call_Node))
2960       then
2961          declare
2962             Call_Typ   : constant Entity_Id := Etype (Call_Node);
2963             Typ        : constant Entity_Id := Find_Dispatching_Type (Subp);
2964             Eq_Prim_Op : Entity_Id := Empty;
2965             New_Call   : Node_Id;
2966             Param      : Node_Id;
2967             Prev_Call  : Node_Id;
2968
2969          begin
2970             if not Is_Limited_Type (Typ) then
2971                Eq_Prim_Op := Find_Prim_Op (Typ, Name_Op_Eq);
2972             end if;
2973
2974             if Tagged_Type_Expansion then
2975                Expand_Dispatching_Call (Call_Node);
2976
2977                --  The following return is worrisome. Is it really OK to skip
2978                --  all remaining processing in this procedure ???
2979
2980                return;
2981
2982             --  VM targets
2983
2984             else
2985                Apply_Tag_Checks (Call_Node);
2986
2987                --  If this is a dispatching "=", we must first compare the
2988                --  tags so we generate: x.tag = y.tag and then x = y
2989
2990                if Subp = Eq_Prim_Op then
2991
2992                   --  Mark the node as analyzed to avoid reanalizing this
2993                   --  dispatching call (which would cause a never-ending loop)
2994
2995                   Prev_Call := Relocate_Node (Call_Node);
2996                   Set_Analyzed (Prev_Call);
2997
2998                   Param := First_Actual (Call_Node);
2999                   New_Call :=
3000                     Make_And_Then (Loc,
3001                       Left_Opnd =>
3002                            Make_Op_Eq (Loc,
3003                              Left_Opnd =>
3004                                Make_Selected_Component (Loc,
3005                                  Prefix        => New_Value (Param),
3006                                  Selector_Name =>
3007                                    New_Reference_To (First_Tag_Component (Typ),
3008                                                      Loc)),
3009
3010                              Right_Opnd =>
3011                                Make_Selected_Component (Loc,
3012                                  Prefix        =>
3013                                    Unchecked_Convert_To (Typ,
3014                                      New_Value (Next_Actual (Param))),
3015                                  Selector_Name =>
3016                                    New_Reference_To
3017                                      (First_Tag_Component (Typ), Loc))),
3018                       Right_Opnd => Prev_Call);
3019
3020                   Rewrite (Call_Node, New_Call);
3021
3022                   Analyze_And_Resolve
3023                     (Call_Node, Call_Typ, Suppress => All_Checks);
3024                end if;
3025
3026                --  Expansion of a dispatching call results in an indirect call,
3027                --  which in turn causes current values to be killed (see
3028                --  Resolve_Call), so on VM targets we do the call here to
3029                --  ensure consistent warnings between VM and non-VM targets.
3030
3031                Kill_Current_Values;
3032             end if;
3033
3034             --  If this is a dispatching "=" then we must update the reference
3035             --  to the call node because we generated:
3036             --     x.tag = y.tag and then x = y
3037
3038             if Subp = Eq_Prim_Op then
3039                Call_Node := Right_Opnd (Call_Node);
3040             end if;
3041          end;
3042       end if;
3043
3044       --  Similarly, expand calls to RCI subprograms on which pragma
3045       --  All_Calls_Remote applies. The rewriting will be reanalyzed
3046       --  later. Do this only when the call comes from source since we
3047       --  do not want such a rewriting to occur in expanded code.
3048
3049       if Is_All_Remote_Call (Call_Node) then
3050          Expand_All_Calls_Remote_Subprogram_Call (Call_Node);
3051
3052       --  Similarly, do not add extra actuals for an entry call whose entity
3053       --  is a protected procedure, or for an internal protected subprogram
3054       --  call, because it will be rewritten as a protected subprogram call
3055       --  and reanalyzed (see Expand_Protected_Subprogram_Call).
3056
3057       elsif Is_Protected_Type (Scope (Subp))
3058          and then (Ekind (Subp) = E_Procedure
3059                     or else Ekind (Subp) = E_Function)
3060       then
3061          null;
3062
3063       --  During that loop we gathered the extra actuals (the ones that
3064       --  correspond to Extra_Formals), so now they can be appended.
3065
3066       else
3067          while Is_Non_Empty_List (Extra_Actuals) loop
3068             Add_Actual_Parameter (Remove_Head (Extra_Actuals));
3069          end loop;
3070       end if;
3071
3072       --  At this point we have all the actuals, so this is the point at which
3073       --  the various expansion activities for actuals is carried out.
3074
3075       Expand_Actuals (Call_Node, Subp);
3076
3077       --  If the subprogram is a renaming, or if it is inherited, replace it in
3078       --  the call with the name of the actual subprogram being called. If this
3079       --  is a dispatching call, the run-time decides what to call. The Alias
3080       --  attribute does not apply to entries.
3081
3082       if Nkind (Call_Node) /= N_Entry_Call_Statement
3083         and then No (Controlling_Argument (Call_Node))
3084         and then Present (Parent_Subp)
3085         and then not Is_Direct_Deep_Call (Subp)
3086       then
3087          if Present (Inherited_From_Formal (Subp)) then
3088             Parent_Subp := Inherited_From_Formal (Subp);
3089          else
3090             Parent_Subp := Ultimate_Alias (Parent_Subp);
3091          end if;
3092
3093          --  The below setting of Entity is suspect, see F109-018 discussion???
3094
3095          Set_Entity (Name (Call_Node), Parent_Subp);
3096
3097          if Is_Abstract_Subprogram (Parent_Subp)
3098            and then not In_Instance
3099          then
3100             Error_Msg_NE
3101               ("cannot call abstract subprogram &!",
3102                Name (Call_Node), Parent_Subp);
3103          end if;
3104
3105          --  Inspect all formals of derived subprogram Subp. Compare parameter
3106          --  types with the parent subprogram and check whether an actual may
3107          --  need a type conversion to the corresponding formal of the parent
3108          --  subprogram.
3109
3110          --  Not clear whether intrinsic subprograms need such conversions. ???
3111
3112          if not Is_Intrinsic_Subprogram (Parent_Subp)
3113            or else Is_Generic_Instance (Parent_Subp)
3114          then
3115             declare
3116                procedure Convert (Act : Node_Id; Typ : Entity_Id);
3117                --  Rewrite node Act as a type conversion of Act to Typ. Analyze
3118                --  and resolve the newly generated construct.
3119
3120                -------------
3121                -- Convert --
3122                -------------
3123
3124                procedure Convert (Act : Node_Id; Typ : Entity_Id) is
3125                begin
3126                   Rewrite (Act, OK_Convert_To (Typ, Relocate_Node (Act)));
3127                   Analyze (Act);
3128                   Resolve (Act, Typ);
3129                end Convert;
3130
3131                --  Local variables
3132
3133                Actual_Typ : Entity_Id;
3134                Formal_Typ : Entity_Id;
3135                Parent_Typ : Entity_Id;
3136
3137             begin
3138                Actual := First_Actual (Call_Node);
3139                Formal := First_Formal (Subp);
3140                Parent_Formal := First_Formal (Parent_Subp);
3141                while Present (Formal) loop
3142                   Actual_Typ := Etype (Actual);
3143                   Formal_Typ := Etype (Formal);
3144                   Parent_Typ := Etype (Parent_Formal);
3145
3146                   --  For an IN parameter of a scalar type, the parent formal
3147                   --  type and derived formal type differ or the parent formal
3148                   --  type and actual type do not match statically.
3149
3150                   if Is_Scalar_Type (Formal_Typ)
3151                     and then Ekind (Formal) = E_In_Parameter
3152                     and then Formal_Typ /= Parent_Typ
3153                     and then
3154                       not Subtypes_Statically_Match (Parent_Typ, Actual_Typ)
3155                     and then not Raises_Constraint_Error (Actual)
3156                   then
3157                      Convert (Actual, Parent_Typ);
3158                      Enable_Range_Check (Actual);
3159
3160                      --  If the actual has been marked as requiring a range
3161                      --  check, then generate it here.
3162
3163                      if Do_Range_Check (Actual) then
3164                         Set_Do_Range_Check (Actual, False);
3165                         Generate_Range_Check
3166                           (Actual, Etype (Formal), CE_Range_Check_Failed);
3167                      end if;
3168
3169                   --  For access types, the parent formal type and actual type
3170                   --  differ.
3171
3172                   elsif Is_Access_Type (Formal_Typ)
3173                     and then Base_Type (Parent_Typ) /= Base_Type (Actual_Typ)
3174                   then
3175                      if Ekind (Formal) /= E_In_Parameter then
3176                         Convert (Actual, Parent_Typ);
3177
3178                      elsif Ekind (Parent_Typ) = E_Anonymous_Access_Type
3179                        and then Designated_Type (Parent_Typ) /=
3180                                 Designated_Type (Actual_Typ)
3181                        and then not Is_Controlling_Formal (Formal)
3182                      then
3183                         --  This unchecked conversion is not necessary unless
3184                         --  inlining is enabled, because in that case the type
3185                         --  mismatch may become visible in the body about to be
3186                         --  inlined.
3187
3188                         Rewrite (Actual,
3189                           Unchecked_Convert_To (Parent_Typ,
3190                             Relocate_Node (Actual)));
3191                         Analyze (Actual);
3192                         Resolve (Actual, Parent_Typ);
3193                      end if;
3194
3195                   --  For array and record types, the parent formal type and
3196                   --  derived formal type have different sizes or pragma Pack
3197                   --  status.
3198
3199                   elsif ((Is_Array_Type (Formal_Typ)
3200                             and then Is_Array_Type (Parent_Typ))
3201                        or else
3202                          (Is_Record_Type (Formal_Typ)
3203                             and then Is_Record_Type (Parent_Typ)))
3204                     and then
3205                       (Esize (Formal_Typ) /= Esize (Parent_Typ)
3206                          or else Has_Pragma_Pack (Formal_Typ) /=
3207                                  Has_Pragma_Pack (Parent_Typ))
3208                   then
3209                      Convert (Actual, Parent_Typ);
3210                   end if;
3211
3212                   Next_Actual (Actual);
3213                   Next_Formal (Formal);
3214                   Next_Formal (Parent_Formal);
3215                end loop;
3216             end;
3217          end if;
3218
3219          Orig_Subp := Subp;
3220          Subp := Parent_Subp;
3221       end if;
3222
3223       --  Check for violation of No_Abort_Statements
3224
3225       if Restriction_Check_Required (No_Abort_Statements)
3226         and then Is_RTE (Subp, RE_Abort_Task)
3227       then
3228          Check_Restriction (No_Abort_Statements, Call_Node);
3229
3230       --  Check for violation of No_Dynamic_Attachment
3231
3232       elsif Restriction_Check_Required (No_Dynamic_Attachment)
3233         and then RTU_Loaded (Ada_Interrupts)
3234         and then (Is_RTE (Subp, RE_Is_Reserved)      or else
3235                   Is_RTE (Subp, RE_Is_Attached)      or else
3236                   Is_RTE (Subp, RE_Current_Handler)  or else
3237                   Is_RTE (Subp, RE_Attach_Handler)   or else
3238                   Is_RTE (Subp, RE_Exchange_Handler) or else
3239                   Is_RTE (Subp, RE_Detach_Handler)   or else
3240                   Is_RTE (Subp, RE_Reference))
3241       then
3242          Check_Restriction (No_Dynamic_Attachment, Call_Node);
3243       end if;
3244
3245       --  Deal with case where call is an explicit dereference
3246
3247       if Nkind (Name (Call_Node)) = N_Explicit_Dereference then
3248
3249       --  Handle case of access to protected subprogram type
3250
3251          if Is_Access_Protected_Subprogram_Type
3252               (Base_Type (Etype (Prefix (Name (Call_Node)))))
3253          then
3254             --  If this is a call through an access to protected operation, the
3255             --  prefix has the form (object'address, operation'access). Rewrite
3256             --  as a for other protected calls: the object is the 1st parameter
3257             --  of the list of actuals.
3258
3259             declare
3260                Call : Node_Id;
3261                Parm : List_Id;
3262                Nam  : Node_Id;
3263                Obj  : Node_Id;
3264                Ptr  : constant Node_Id := Prefix (Name (Call_Node));
3265
3266                T : constant Entity_Id :=
3267                      Equivalent_Type (Base_Type (Etype (Ptr)));
3268
3269                D_T : constant Entity_Id :=
3270                        Designated_Type (Base_Type (Etype (Ptr)));
3271
3272             begin
3273                Obj :=
3274                  Make_Selected_Component (Loc,
3275                    Prefix        => Unchecked_Convert_To (T, Ptr),
3276                    Selector_Name =>
3277                      New_Occurrence_Of (First_Entity (T), Loc));
3278
3279                Nam :=
3280                  Make_Selected_Component (Loc,
3281                    Prefix        => Unchecked_Convert_To (T, Ptr),
3282                    Selector_Name =>
3283                      New_Occurrence_Of (Next_Entity (First_Entity (T)), Loc));
3284
3285                Nam :=
3286                  Make_Explicit_Dereference (Loc,
3287                    Prefix => Nam);
3288
3289                if Present (Parameter_Associations (Call_Node))  then
3290                   Parm := Parameter_Associations (Call_Node);
3291                else
3292                   Parm := New_List;
3293                end if;
3294
3295                Prepend (Obj, Parm);
3296
3297                if Etype (D_T) = Standard_Void_Type then
3298                   Call :=
3299                     Make_Procedure_Call_Statement (Loc,
3300                       Name                   => Nam,
3301                       Parameter_Associations => Parm);
3302                else
3303                   Call :=
3304                     Make_Function_Call (Loc,
3305                       Name                   => Nam,
3306                       Parameter_Associations => Parm);
3307                end if;
3308
3309                Set_First_Named_Actual (Call, First_Named_Actual (Call_Node));
3310                Set_Etype (Call, Etype (D_T));
3311
3312                --  We do not re-analyze the call to avoid infinite recursion.
3313                --  We analyze separately the prefix and the object, and set
3314                --  the checks on the prefix that would otherwise be emitted
3315                --  when resolving a call.
3316
3317                Rewrite (Call_Node, Call);
3318                Analyze (Nam);
3319                Apply_Access_Check (Nam);
3320                Analyze (Obj);
3321                return;
3322             end;
3323          end if;
3324       end if;
3325
3326       --  If this is a call to an intrinsic subprogram, then perform the
3327       --  appropriate expansion to the corresponding tree node and we
3328       --  are all done (since after that the call is gone!)
3329
3330       --  In the case where the intrinsic is to be processed by the back end,
3331       --  the call to Expand_Intrinsic_Call will do nothing, which is fine,
3332       --  since the idea in this case is to pass the call unchanged. If the
3333       --  intrinsic is an inherited unchecked conversion, and the derived type
3334       --  is the target type of the conversion, we must retain it as the return
3335       --  type of the expression. Otherwise the expansion below, which uses the
3336       --  parent operation, will yield the wrong type.
3337
3338       if Is_Intrinsic_Subprogram (Subp) then
3339          Expand_Intrinsic_Call (Call_Node, Subp);
3340
3341          if Nkind (Call_Node) = N_Unchecked_Type_Conversion
3342            and then Parent_Subp /= Orig_Subp
3343            and then Etype (Parent_Subp) /= Etype (Orig_Subp)
3344          then
3345             Set_Etype (Call_Node, Etype (Orig_Subp));
3346          end if;
3347
3348          return;
3349       end if;
3350
3351       if Ekind_In (Subp, E_Function, E_Procedure) then
3352
3353          --  We perform two simple optimization on calls:
3354
3355          --  a) replace calls to null procedures unconditionally;
3356
3357          --  b) for To_Address, just do an unchecked conversion. Not only is
3358          --  this efficient, but it also avoids order of elaboration problems
3359          --  when address clauses are inlined (address expression elaborated
3360          --  at the wrong point).
3361
3362          --  We perform these optimization regardless of whether we are in the
3363          --  main unit or in a unit in the context of the main unit, to ensure
3364          --  that tree generated is the same in both cases, for Inspector use.
3365
3366          if Is_RTE (Subp, RE_To_Address) then
3367             Rewrite (Call_Node,
3368               Unchecked_Convert_To
3369                 (RTE (RE_Address), Relocate_Node (First_Actual (Call_Node))));
3370             return;
3371
3372          elsif Is_Null_Procedure (Subp)  then
3373             Rewrite (Call_Node, Make_Null_Statement (Loc));
3374             return;
3375          end if;
3376
3377          if Is_Inlined (Subp) then
3378
3379             Inlined_Subprogram : declare
3380                Bod         : Node_Id;
3381                Must_Inline : Boolean := False;
3382                Spec        : constant Node_Id := Unit_Declaration_Node (Subp);
3383                Scop        : constant Entity_Id := Scope (Subp);
3384
3385                function In_Unfrozen_Instance return Boolean;
3386                --  If the subprogram comes from an instance in the same unit,
3387                --  and the instance is not yet frozen, inlining might trigger
3388                --  order-of-elaboration problems in gigi.
3389
3390                --------------------------
3391                -- In_Unfrozen_Instance --
3392                --------------------------
3393
3394                function In_Unfrozen_Instance return Boolean is
3395                   S : Entity_Id;
3396
3397                begin
3398                   S := Scop;
3399                   while Present (S)
3400                     and then S /= Standard_Standard
3401                   loop
3402                      if Is_Generic_Instance (S)
3403                        and then Present (Freeze_Node (S))
3404                        and then not Analyzed (Freeze_Node (S))
3405                      then
3406                         return True;
3407                      end if;
3408
3409                      S := Scope (S);
3410                   end loop;
3411
3412                   return False;
3413                end In_Unfrozen_Instance;
3414
3415             --  Start of processing for Inlined_Subprogram
3416
3417             begin
3418                --  Verify that the body to inline has already been seen, and
3419                --  that if the body is in the current unit the inlining does
3420                --  not occur earlier. This avoids order-of-elaboration problems
3421                --  in the back end.
3422
3423                --  This should be documented in sinfo/einfo ???
3424
3425                if No (Spec)
3426                  or else Nkind (Spec) /= N_Subprogram_Declaration
3427                  or else No (Body_To_Inline (Spec))
3428                then
3429                   Must_Inline := False;
3430
3431                --  If this an inherited function that returns a private type,
3432                --  do not inline if the full view is an unconstrained array,
3433                --  because such calls cannot be inlined.
3434
3435                elsif Present (Orig_Subp)
3436                  and then Is_Array_Type (Etype (Orig_Subp))
3437                  and then not Is_Constrained (Etype (Orig_Subp))
3438                then
3439                   Must_Inline := False;
3440
3441                elsif In_Unfrozen_Instance then
3442                   Must_Inline := False;
3443
3444                else
3445                   Bod := Body_To_Inline (Spec);
3446
3447                   if (In_Extended_Main_Code_Unit (Call_Node)
3448                         or else In_Extended_Main_Code_Unit (Parent (Call_Node))
3449                         or else Has_Pragma_Inline_Always (Subp))
3450                     and then (not In_Same_Extended_Unit (Sloc (Bod), Loc)
3451                                or else
3452                                  Earlier_In_Extended_Unit (Sloc (Bod), Loc))
3453                   then
3454                      Must_Inline := True;
3455
3456                   --  If we are compiling a package body that is not the main
3457                   --  unit, it must be for inlining/instantiation purposes,
3458                   --  in which case we inline the call to insure that the same
3459                   --  temporaries are generated when compiling the body by
3460                   --  itself. Otherwise link errors can occur.
3461
3462                   --  If the function being called is itself in the main unit,
3463                   --  we cannot inline, because there is a risk of double
3464                   --  elaboration and/or circularity: the inlining can make
3465                   --  visible a private entity in the body of the main unit,
3466                   --  that gigi will see before its sees its proper definition.
3467
3468                   elsif not (In_Extended_Main_Code_Unit (Call_Node))
3469                     and then In_Package_Body
3470                   then
3471                      Must_Inline := not In_Extended_Main_Source_Unit (Subp);
3472                   end if;
3473                end if;
3474
3475                if Must_Inline then
3476                   Expand_Inlined_Call (Call_Node, Subp, Orig_Subp);
3477
3478                else
3479                   --  Let the back end handle it
3480
3481                   Add_Inlined_Body (Subp);
3482
3483                   if Front_End_Inlining
3484                     and then Nkind (Spec) = N_Subprogram_Declaration
3485                     and then (In_Extended_Main_Code_Unit (Call_Node))
3486                     and then No (Body_To_Inline (Spec))
3487                     and then not Has_Completion (Subp)
3488                     and then In_Same_Extended_Unit (Sloc (Spec), Loc)
3489                   then
3490                      Cannot_Inline
3491                       ("cannot inline& (body not seen yet)?", Call_Node, Subp);
3492                   end if;
3493                end if;
3494             end Inlined_Subprogram;
3495          end if;
3496       end if;
3497
3498       --  Check for protected subprogram. This is either an intra-object call,
3499       --  or a protected function call. Protected procedure calls are rewritten
3500       --  as entry calls and handled accordingly.
3501
3502       --  In Ada 2005, this may be an indirect call to an access parameter that
3503       --  is an access_to_subprogram. In that case the anonymous type has a
3504       --  scope that is a protected operation, but the call is a regular one.
3505       --  In either case do not expand call if subprogram is eliminated.
3506
3507       Scop := Scope (Subp);
3508
3509       if Nkind (Call_Node) /= N_Entry_Call_Statement
3510         and then Is_Protected_Type (Scop)
3511         and then Ekind (Subp) /= E_Subprogram_Type
3512         and then not Is_Eliminated (Subp)
3513       then
3514          --  If the call is an internal one, it is rewritten as a call to the
3515          --  corresponding unprotected subprogram.
3516
3517          Expand_Protected_Subprogram_Call (Call_Node, Subp, Scop);
3518       end if;
3519
3520       --  Functions returning controlled objects need special attention. If
3521       --  the return type is limited, then the context is initialization and
3522       --  different processing applies. If the call is to a protected function,
3523       --  the expansion above will call Expand_Call recursively. Otherwise the
3524       --  function call is transformed into a temporary which obtains the
3525       --  result from the secondary stack.
3526
3527       if Needs_Finalization (Etype (Subp)) then
3528          if not Is_Immutably_Limited_Type (Etype (Subp))
3529            and then
3530              (No (First_Formal (Subp))
3531                 or else
3532                   not Is_Concurrent_Record_Type (Etype (First_Formal (Subp))))
3533          then
3534             Expand_Ctrl_Function_Call (Call_Node);
3535
3536          --  Build-in-place function calls which appear in anonymous contexts
3537          --  need a transient scope to ensure the proper finalization of the
3538          --  intermediate result after its use.
3539
3540          elsif Is_Build_In_Place_Function_Call (Call_Node)
3541            and then Nkind_In (Parent (Call_Node), N_Attribute_Reference,
3542                                           N_Function_Call,
3543                                           N_Indexed_Component,
3544                                           N_Object_Renaming_Declaration,
3545                                           N_Procedure_Call_Statement,
3546                                           N_Selected_Component,
3547                                           N_Slice)
3548          then
3549             Establish_Transient_Scope (Call_Node, Sec_Stack => True);
3550          end if;
3551       end if;
3552
3553       --  Test for First_Optional_Parameter, and if so, truncate parameter list
3554       --  if there are optional parameters at the trailing end.
3555       --  Note: we never delete procedures for call via a pointer.
3556
3557       if (Ekind (Subp) = E_Procedure or else Ekind (Subp) = E_Function)
3558         and then Present (First_Optional_Parameter (Subp))
3559       then
3560          declare
3561             Last_Keep_Arg : Node_Id;
3562
3563          begin
3564             --  Last_Keep_Arg will hold the last actual that should be kept.
3565             --  If it remains empty at the end, it means that all parameters
3566             --  are optional.
3567
3568             Last_Keep_Arg := Empty;
3569
3570             --  Find first optional parameter, must be present since we checked
3571             --  the validity of the parameter before setting it.
3572
3573             Formal := First_Formal (Subp);
3574             Actual := First_Actual (Call_Node);
3575             while Formal /= First_Optional_Parameter (Subp) loop
3576                Last_Keep_Arg := Actual;
3577                Next_Formal (Formal);
3578                Next_Actual (Actual);
3579             end loop;
3580
3581             --  We have Formal and Actual pointing to the first potentially
3582             --  droppable argument. We can drop all the trailing arguments
3583             --  whose actual matches the default. Note that we know that all
3584             --  remaining formals have defaults, because we checked that this
3585             --  requirement was met before setting First_Optional_Parameter.
3586
3587             --  We use Fully_Conformant_Expressions to check for identity
3588             --  between formals and actuals, which may miss some cases, but
3589             --  on the other hand, this is only an optimization (if we fail
3590             --  to truncate a parameter it does not affect functionality).
3591             --  So if the default is 3 and the actual is 1+2, we consider
3592             --  them unequal, which hardly seems worrisome.
3593
3594             while Present (Formal) loop
3595                if not Fully_Conformant_Expressions
3596                     (Actual, Default_Value (Formal))
3597                then
3598                   Last_Keep_Arg := Actual;
3599                end if;
3600
3601                Next_Formal (Formal);
3602                Next_Actual (Actual);
3603             end loop;
3604
3605             --  If no arguments, delete entire list, this is the easy case
3606
3607             if No (Last_Keep_Arg) then
3608                Set_Parameter_Associations (Call_Node, No_List);
3609                Set_First_Named_Actual (Call_Node, Empty);
3610
3611             --  Case where at the last retained argument is positional. This
3612             --  is also an easy case, since the retained arguments are already
3613             --  in the right form, and we don't need to worry about the order
3614             --  of arguments that get eliminated.
3615
3616             elsif Is_List_Member (Last_Keep_Arg) then
3617                while Present (Next (Last_Keep_Arg)) loop
3618                   Discard_Node (Remove_Next (Last_Keep_Arg));
3619                end loop;
3620
3621                Set_First_Named_Actual (Call_Node, Empty);
3622
3623             --  This is the annoying case where the last retained argument
3624             --  is a named parameter. Since the original arguments are not
3625             --  in declaration order, we may have to delete some fairly
3626             --  random collection of arguments.
3627
3628             else
3629                declare
3630                   Temp   : Node_Id;
3631                   Passoc : Node_Id;
3632
3633                begin
3634                   --  First step, remove all the named parameters from the
3635                   --  list (they are still chained using First_Named_Actual
3636                   --  and Next_Named_Actual, so we have not lost them!)
3637
3638                   Temp := First (Parameter_Associations (Call_Node));
3639
3640                   --  Case of all parameters named, remove them all
3641
3642                   if Nkind (Temp) = N_Parameter_Association then
3643                      --  Suppress warnings to avoid warning on possible
3644                      --  infinite loop (because Call_Node is not modified).
3645
3646                      pragma Warnings (Off);
3647                      while Is_Non_Empty_List
3648                              (Parameter_Associations (Call_Node))
3649                      loop
3650                         Temp :=
3651                           Remove_Head (Parameter_Associations (Call_Node));
3652                      end loop;
3653                      pragma Warnings (On);
3654
3655                   --  Case of mixed positional/named, remove named parameters
3656
3657                   else
3658                      while Nkind (Next (Temp)) /= N_Parameter_Association loop
3659                         Next (Temp);
3660                      end loop;
3661
3662                      while Present (Next (Temp)) loop
3663                         Remove (Next (Temp));
3664                      end loop;
3665                   end if;
3666
3667                   --  Now we loop through the named parameters, till we get
3668                   --  to the last one to be retained, adding them to the list.
3669                   --  Note that the Next_Named_Actual list does not need to be
3670                   --  touched since we are only reordering them on the actual
3671                   --  parameter association list.
3672
3673                   Passoc := Parent (First_Named_Actual (Call_Node));
3674                   loop
3675                      Temp := Relocate_Node (Passoc);
3676                      Append_To
3677                        (Parameter_Associations (Call_Node), Temp);
3678                      exit when
3679                        Last_Keep_Arg = Explicit_Actual_Parameter (Passoc);
3680                      Passoc := Parent (Next_Named_Actual (Passoc));
3681                   end loop;
3682
3683                   Set_Next_Named_Actual (Temp, Empty);
3684
3685                   loop
3686                      Temp := Next_Named_Actual (Passoc);
3687                      exit when No (Temp);
3688                      Set_Next_Named_Actual
3689                        (Passoc, Next_Named_Actual (Parent (Temp)));
3690                   end loop;
3691                end;
3692
3693             end if;
3694          end;
3695       end if;
3696    end Expand_Call;
3697
3698    -------------------------------
3699    -- Expand_Ctrl_Function_Call --
3700    -------------------------------
3701
3702    procedure Expand_Ctrl_Function_Call (N : Node_Id) is
3703    begin
3704       --  Optimization, if the returned value (which is on the sec-stack) is
3705       --  returned again, no need to copy/readjust/finalize, we can just pass
3706       --  the value thru (see Expand_N_Simple_Return_Statement), and thus no
3707       --  attachment is needed
3708
3709       if Nkind (Parent (N)) = N_Simple_Return_Statement then
3710          return;
3711       end if;
3712
3713       --  Resolution is now finished, make sure we don't start analysis again
3714       --  because of the duplication.
3715
3716       Set_Analyzed (N);
3717
3718       --  A function which returns a controlled object uses the secondary
3719       --  stack. Rewrite the call into a temporary which obtains the result of
3720       --  the function using 'reference.
3721
3722       Remove_Side_Effects (N);
3723    end Expand_Ctrl_Function_Call;
3724
3725    --------------------------
3726    -- Expand_Inlined_Call --
3727    --------------------------
3728
3729    procedure Expand_Inlined_Call
3730     (N         : Node_Id;
3731      Subp      : Entity_Id;
3732      Orig_Subp : Entity_Id)
3733    is
3734       Loc       : constant Source_Ptr := Sloc (N);
3735       Is_Predef : constant Boolean :=
3736                    Is_Predefined_File_Name
3737                      (Unit_File_Name (Get_Source_Unit (Subp)));
3738       Orig_Bod  : constant Node_Id :=
3739                     Body_To_Inline (Unit_Declaration_Node (Subp));
3740
3741       Blk      : Node_Id;
3742       Bod      : Node_Id;
3743       Decl     : Node_Id;
3744       Decls    : constant List_Id := New_List;
3745       Exit_Lab : Entity_Id := Empty;
3746       F        : Entity_Id;
3747       A        : Node_Id;
3748       Lab_Decl : Node_Id;
3749       Lab_Id   : Node_Id;
3750       New_A    : Node_Id;
3751       Num_Ret  : Int := 0;
3752       Ret_Type : Entity_Id;
3753
3754       Targ : Node_Id;
3755       --  The target of the call. If context is an assignment statement then
3756       --  this is the left-hand side of the assignment. else it is a temporary
3757       --  to which the return value is assigned prior to rewriting the call.
3758
3759       Targ1 : Node_Id;
3760       --  A separate target used when the return type is unconstrained
3761
3762       Temp     : Entity_Id;
3763       Temp_Typ : Entity_Id;
3764
3765       Return_Object : Entity_Id := Empty;
3766       --  Entity in declaration in an extended_return_statement
3767
3768       Is_Unc : constant Boolean :=
3769                  Is_Array_Type (Etype (Subp))
3770                    and then not Is_Constrained (Etype (Subp));
3771       --  If the type returned by the function is unconstrained and the call
3772       --  can be inlined, special processing is required.
3773
3774       procedure Make_Exit_Label;
3775       --  Build declaration for exit label to be used in Return statements,
3776       --  sets Exit_Lab (the label node) and Lab_Decl (corresponding implicit
3777       --  declaration). Does nothing if Exit_Lab already set.
3778
3779       function Process_Formals (N : Node_Id) return Traverse_Result;
3780       --  Replace occurrence of a formal with the corresponding actual, or the
3781       --  thunk generated for it.
3782
3783       function Process_Sloc (Nod : Node_Id) return Traverse_Result;
3784       --  If the call being expanded is that of an internal subprogram, set the
3785       --  sloc of the generated block to that of the call itself, so that the
3786       --  expansion is skipped by the "next" command in gdb.
3787       --  Same processing for a subprogram in a predefined file, e.g.
3788       --  Ada.Tags. If Debug_Generated_Code is true, suppress this change to
3789       --  simplify our own development.
3790
3791       procedure Rewrite_Function_Call (N : Node_Id; Blk : Node_Id);
3792       --  If the function body is a single expression, replace call with
3793       --  expression, else insert block appropriately.
3794
3795       procedure Rewrite_Procedure_Call (N : Node_Id; Blk : Node_Id);
3796       --  If procedure body has no local variables, inline body without
3797       --  creating block, otherwise rewrite call with block.
3798
3799       function Formal_Is_Used_Once (Formal : Entity_Id) return Boolean;
3800       --  Determine whether a formal parameter is used only once in Orig_Bod
3801
3802       ---------------------
3803       -- Make_Exit_Label --
3804       ---------------------
3805
3806       procedure Make_Exit_Label is
3807          Lab_Ent : Entity_Id;
3808       begin
3809          if No (Exit_Lab) then
3810             Lab_Ent := Make_Temporary (Loc, 'L');
3811             Lab_Id  := New_Reference_To (Lab_Ent, Loc);
3812             Exit_Lab := Make_Label (Loc, Lab_Id);
3813             Lab_Decl :=
3814               Make_Implicit_Label_Declaration (Loc,
3815                 Defining_Identifier  => Lab_Ent,
3816                 Label_Construct      => Exit_Lab);
3817          end if;
3818       end Make_Exit_Label;
3819
3820       ---------------------
3821       -- Process_Formals --
3822       ---------------------
3823
3824       function Process_Formals (N : Node_Id) return Traverse_Result is
3825          A   : Entity_Id;
3826          E   : Entity_Id;
3827          Ret : Node_Id;
3828
3829       begin
3830          if Is_Entity_Name (N)
3831            and then Present (Entity (N))
3832          then
3833             E := Entity (N);
3834
3835             if Is_Formal (E)
3836               and then Scope (E) = Subp
3837             then
3838                A := Renamed_Object (E);
3839
3840                --  Rewrite the occurrence of the formal into an occurrence of
3841                --  the actual. Also establish visibility on the proper view of
3842                --  the actual's subtype for the body's context (if the actual's
3843                --  subtype is private at the call point but its full view is
3844                --  visible to the body, then the inlined tree here must be
3845                --  analyzed with the full view).
3846
3847                if Is_Entity_Name (A) then
3848                   Rewrite (N, New_Occurrence_Of (Entity (A), Loc));
3849                   Check_Private_View (N);
3850
3851                elsif Nkind (A) = N_Defining_Identifier then
3852                   Rewrite (N, New_Occurrence_Of (A, Loc));
3853                   Check_Private_View (N);
3854
3855                --  Numeric literal
3856
3857                else
3858                   Rewrite (N, New_Copy (A));
3859                end if;
3860             end if;
3861
3862             return Skip;
3863
3864          elsif Is_Entity_Name (N)
3865            and then Present (Return_Object)
3866            and then Chars (N) = Chars (Return_Object)
3867          then
3868             --  Occurrence within an extended return statement. The return
3869             --  object is local to the body been inlined, and thus the generic
3870             --  copy is not analyzed yet, so we match by name, and replace it
3871             --  with target of call.
3872
3873             if Nkind (Targ) = N_Defining_Identifier then
3874                Rewrite (N, New_Occurrence_Of (Targ, Loc));
3875             else
3876                Rewrite (N, New_Copy_Tree (Targ));
3877             end if;
3878
3879             return Skip;
3880
3881          elsif Nkind (N) = N_Simple_Return_Statement then
3882             if No (Expression (N)) then
3883                Make_Exit_Label;
3884                Rewrite (N,
3885                  Make_Goto_Statement (Loc, Name => New_Copy (Lab_Id)));
3886
3887             else
3888                if Nkind (Parent (N)) = N_Handled_Sequence_Of_Statements
3889                  and then Nkind (Parent (Parent (N))) = N_Subprogram_Body
3890                then
3891                   --  Function body is a single expression. No need for
3892                   --  exit label.
3893
3894                   null;
3895
3896                else
3897                   Num_Ret := Num_Ret + 1;
3898                   Make_Exit_Label;
3899                end if;
3900
3901                --  Because of the presence of private types, the views of the
3902                --  expression and the context may be different, so place an
3903                --  unchecked conversion to the context type to avoid spurious
3904                --  errors, e.g. when the expression is a numeric literal and
3905                --  the context is private. If the expression is an aggregate,
3906                --  use a qualified expression, because an aggregate is not a
3907                --  legal argument of a conversion.
3908
3909                if Nkind_In (Expression (N), N_Aggregate, N_Null) then
3910                   Ret :=
3911                     Make_Qualified_Expression (Sloc (N),
3912                       Subtype_Mark => New_Occurrence_Of (Ret_Type, Sloc (N)),
3913                       Expression => Relocate_Node (Expression (N)));
3914                else
3915                   Ret :=
3916                     Unchecked_Convert_To
3917                       (Ret_Type, Relocate_Node (Expression (N)));
3918                end if;
3919
3920                if Nkind (Targ) = N_Defining_Identifier then
3921                   Rewrite (N,
3922                     Make_Assignment_Statement (Loc,
3923                       Name       => New_Occurrence_Of (Targ, Loc),
3924                       Expression => Ret));
3925                else
3926                   Rewrite (N,
3927                     Make_Assignment_Statement (Loc,
3928                       Name       => New_Copy (Targ),
3929                       Expression => Ret));
3930                end if;
3931
3932                Set_Assignment_OK (Name (N));
3933
3934                if Present (Exit_Lab) then
3935                   Insert_After (N,
3936                     Make_Goto_Statement (Loc, Name => New_Copy (Lab_Id)));
3937                end if;
3938             end if;
3939
3940             return OK;
3941
3942          --  An extended return becomes a block whose first statement is the
3943          --  assignment of the initial expression of the return object to the
3944          --  target of the call itself.
3945
3946          elsif Nkind (N) = N_Extended_Return_Statement then
3947             declare
3948                Return_Decl : constant Entity_Id :=
3949                                First (Return_Object_Declarations (N));
3950                Assign      : Node_Id;
3951
3952             begin
3953                Return_Object := Defining_Identifier (Return_Decl);
3954
3955                if Present (Expression (Return_Decl)) then
3956                   if Nkind (Targ) = N_Defining_Identifier then
3957                      Assign :=
3958                        Make_Assignment_Statement (Loc,
3959                          Name       => New_Occurrence_Of (Targ, Loc),
3960                          Expression => Expression (Return_Decl));
3961                   else
3962                      Assign :=
3963                        Make_Assignment_Statement (Loc,
3964                          Name       => New_Copy (Targ),
3965                          Expression => Expression (Return_Decl));
3966                   end if;
3967
3968                   Set_Assignment_OK (Name (Assign));
3969                   Prepend (Assign,
3970                     Statements (Handled_Statement_Sequence (N)));
3971                end if;
3972
3973                Rewrite (N,
3974                  Make_Block_Statement (Loc,
3975                     Handled_Statement_Sequence =>
3976                       Handled_Statement_Sequence (N)));
3977
3978                return OK;
3979             end;
3980
3981          --  Remove pragma Unreferenced since it may refer to formals that
3982          --  are not visible in the inlined body, and in any case we will
3983          --  not be posting warnings on the inlined body so it is unneeded.
3984
3985          elsif Nkind (N) = N_Pragma
3986            and then Pragma_Name (N) = Name_Unreferenced
3987          then
3988             Rewrite (N, Make_Null_Statement (Sloc (N)));
3989             return OK;
3990
3991          else
3992             return OK;
3993          end if;
3994       end Process_Formals;
3995
3996       procedure Replace_Formals is new Traverse_Proc (Process_Formals);
3997
3998       ------------------
3999       -- Process_Sloc --
4000       ------------------
4001
4002       function Process_Sloc (Nod : Node_Id) return Traverse_Result is
4003       begin
4004          if not Debug_Generated_Code then
4005             Set_Sloc (Nod, Sloc (N));
4006             Set_Comes_From_Source (Nod, False);
4007          end if;
4008
4009          return OK;
4010       end Process_Sloc;
4011
4012       procedure Reset_Slocs is new Traverse_Proc (Process_Sloc);
4013
4014       ---------------------------
4015       -- Rewrite_Function_Call --
4016       ---------------------------
4017
4018       procedure Rewrite_Function_Call (N : Node_Id; Blk : Node_Id) is
4019          HSS : constant Node_Id := Handled_Statement_Sequence (Blk);
4020          Fst : constant Node_Id := First (Statements (HSS));
4021
4022       begin
4023          --  Optimize simple case: function body is a single return statement,
4024          --  which has been expanded into an assignment.
4025
4026          if Is_Empty_List (Declarations (Blk))
4027            and then Nkind (Fst) = N_Assignment_Statement
4028            and then No (Next (Fst))
4029          then
4030             --  The function call may have been rewritten as the temporary
4031             --  that holds the result of the call, in which case remove the
4032             --  now useless declaration.
4033
4034             if Nkind (N) = N_Identifier
4035               and then Nkind (Parent (Entity (N))) = N_Object_Declaration
4036             then
4037                Rewrite (Parent (Entity (N)), Make_Null_Statement (Loc));
4038             end if;
4039
4040             Rewrite (N, Expression (Fst));
4041
4042          elsif Nkind (N) = N_Identifier
4043            and then Nkind (Parent (Entity (N))) = N_Object_Declaration
4044          then
4045             --  The block assigns the result of the call to the temporary
4046
4047             Insert_After (Parent (Entity (N)), Blk);
4048
4049          --  If the context is an assignment, and the left-hand side is free of
4050          --  side-effects, the replacement is also safe.
4051          --  Can this be generalized further???
4052
4053          elsif Nkind (Parent (N)) = N_Assignment_Statement
4054            and then
4055             (Is_Entity_Name (Name (Parent (N)))
4056               or else
4057                 (Nkind (Name (Parent (N))) = N_Explicit_Dereference
4058                   and then Is_Entity_Name (Prefix (Name (Parent (N)))))
4059
4060               or else
4061                 (Nkind (Name (Parent (N))) = N_Selected_Component
4062                   and then Is_Entity_Name (Prefix (Name (Parent (N))))))
4063          then
4064             --  Replace assignment with the block
4065
4066             declare
4067                Original_Assignment : constant Node_Id := Parent (N);
4068
4069             begin
4070                --  Preserve the original assignment node to keep the complete
4071                --  assignment subtree consistent enough for Analyze_Assignment
4072                --  to proceed (specifically, the original Lhs node must still
4073                --  have an assignment statement as its parent).
4074
4075                --  We cannot rely on Original_Node to go back from the block
4076                --  node to the assignment node, because the assignment might
4077                --  already be a rewrite substitution.
4078
4079                Discard_Node (Relocate_Node (Original_Assignment));
4080                Rewrite (Original_Assignment, Blk);
4081             end;
4082
4083          elsif Nkind (Parent (N)) = N_Object_Declaration then
4084             Set_Expression (Parent (N), Empty);
4085             Insert_After (Parent (N), Blk);
4086
4087          elsif Is_Unc then
4088             Insert_Before (Parent (N), Blk);
4089          end if;
4090       end Rewrite_Function_Call;
4091
4092       ----------------------------
4093       -- Rewrite_Procedure_Call --
4094       ----------------------------
4095
4096       procedure Rewrite_Procedure_Call (N : Node_Id; Blk : Node_Id) is
4097          HSS  : constant Node_Id := Handled_Statement_Sequence (Blk);
4098
4099       begin
4100          --  If there is a transient scope for N, this will be the scope of the
4101          --  actions for N, and the statements in Blk need to be within this
4102          --  scope. For example, they need to have visibility on the constant
4103          --  declarations created for the formals.
4104
4105          --  If N needs no transient scope, and if there are no declarations in
4106          --  the inlined body, we can do a little optimization and insert the
4107          --  statements for the body directly after N, and rewrite N to a
4108          --  null statement, instead of rewriting N into a full-blown block
4109          --  statement.
4110
4111          if not Scope_Is_Transient
4112            and then Is_Empty_List (Declarations (Blk))
4113          then
4114             Insert_List_After (N, Statements (HSS));
4115             Rewrite (N, Make_Null_Statement (Loc));
4116          else
4117             Rewrite (N, Blk);
4118          end if;
4119       end Rewrite_Procedure_Call;
4120
4121       -------------------------
4122       -- Formal_Is_Used_Once --
4123       -------------------------
4124
4125       function Formal_Is_Used_Once (Formal : Entity_Id) return Boolean is
4126          Use_Counter : Int := 0;
4127
4128          function Count_Uses (N : Node_Id) return Traverse_Result;
4129          --  Traverse the tree and count the uses of the formal parameter.
4130          --  In this case, for optimization purposes, we do not need to
4131          --  continue the traversal once more than one use is encountered.
4132
4133          ----------------
4134          -- Count_Uses --
4135          ----------------
4136
4137          function Count_Uses (N : Node_Id) return Traverse_Result is
4138          begin
4139             --  The original node is an identifier
4140
4141             if Nkind (N) = N_Identifier
4142               and then Present (Entity (N))
4143
4144                --  Original node's entity points to the one in the copied body
4145
4146               and then Nkind (Entity (N)) = N_Identifier
4147               and then Present (Entity (Entity (N)))
4148
4149                --  The entity of the copied node is the formal parameter
4150
4151               and then Entity (Entity (N)) = Formal
4152             then
4153                Use_Counter := Use_Counter + 1;
4154
4155                if Use_Counter > 1 then
4156
4157                   --  Denote more than one use and abandon the traversal
4158
4159                   Use_Counter := 2;
4160                   return Abandon;
4161
4162                end if;
4163             end if;
4164
4165             return OK;
4166          end Count_Uses;
4167
4168          procedure Count_Formal_Uses is new Traverse_Proc (Count_Uses);
4169
4170       --  Start of processing for Formal_Is_Used_Once
4171
4172       begin
4173          Count_Formal_Uses (Orig_Bod);
4174          return Use_Counter = 1;
4175       end Formal_Is_Used_Once;
4176
4177    --  Start of processing for Expand_Inlined_Call
4178
4179    begin
4180       --  Check for an illegal attempt to inline a recursive procedure. If the
4181       --  subprogram has parameters this is detected when trying to supply a
4182       --  binding for parameters that already have one. For parameterless
4183       --  subprograms this must be done explicitly.
4184
4185       if In_Open_Scopes (Subp) then
4186          Error_Msg_N ("call to recursive subprogram cannot be inlined?", N);
4187          Set_Is_Inlined (Subp, False);
4188          return;
4189       end if;
4190
4191       if Nkind (Orig_Bod) = N_Defining_Identifier
4192         or else Nkind (Orig_Bod) = N_Defining_Operator_Symbol
4193       then
4194          --  Subprogram is renaming_as_body. Calls occurring after the renaming
4195          --  can be replaced with calls to the renamed entity directly, because
4196          --  the subprograms are subtype conformant. If the renamed subprogram
4197          --  is an inherited operation, we must redo the expansion because
4198          --  implicit conversions may be needed. Similarly, if the renamed
4199          --  entity is inlined, expand the call for further optimizations.
4200
4201          Set_Name (N, New_Occurrence_Of (Orig_Bod, Loc));
4202
4203          if Present (Alias (Orig_Bod)) or else Is_Inlined (Orig_Bod) then
4204             Expand_Call (N);
4205          end if;
4206
4207          return;
4208       end if;
4209
4210       --  Use generic machinery to copy body of inlined subprogram, as if it
4211       --  were an instantiation, resetting source locations appropriately, so
4212       --  that nested inlined calls appear in the main unit.
4213
4214       Save_Env (Subp, Empty);
4215       Set_Copied_Sloc_For_Inlined_Body (N, Defining_Entity (Orig_Bod));
4216
4217       Bod := Copy_Generic_Node (Orig_Bod, Empty, Instantiating => True);
4218       Blk :=
4219         Make_Block_Statement (Loc,
4220           Declarations => Declarations (Bod),
4221           Handled_Statement_Sequence => Handled_Statement_Sequence (Bod));
4222
4223       if No (Declarations (Bod)) then
4224          Set_Declarations (Blk, New_List);
4225       end if;
4226
4227       --  For the unconstrained case, capture the name of the local variable
4228       --  that holds the result. This must be the first declaration in the
4229       --  block, because its bounds cannot depend on local variables. Otherwise
4230       --  there is no way to declare the result outside of the block. Needless
4231       --  to say, in general the bounds will depend on the actuals in the call.
4232
4233       --  If the context is an assignment statement, as is the case for the
4234       --  expansion of an extended return, the left-hand side provides bounds
4235       --  even if the return type is unconstrained.
4236
4237       if Is_Unc then
4238          if Nkind (Parent (N)) /= N_Assignment_Statement then
4239             Targ1 := Defining_Identifier (First (Declarations (Blk)));
4240          else
4241             Targ1 := Name (Parent (N));
4242          end if;
4243       end if;
4244
4245       --  If this is a derived function, establish the proper return type
4246
4247       if Present (Orig_Subp) and then Orig_Subp /= Subp then
4248          Ret_Type := Etype (Orig_Subp);
4249       else
4250          Ret_Type := Etype (Subp);
4251       end if;
4252
4253       --  Create temporaries for the actuals that are expressions, or that
4254       --  are scalars and require copying to preserve semantics.
4255
4256       F := First_Formal (Subp);
4257       A := First_Actual (N);
4258       while Present (F) loop
4259          if Present (Renamed_Object (F)) then
4260             Error_Msg_N ("cannot inline call to recursive subprogram", N);
4261             return;
4262          end if;
4263
4264          --  If the argument may be a controlling argument in a call within
4265          --  the inlined body, we must preserve its classwide nature to insure
4266          --  that dynamic dispatching take place subsequently. If the formal
4267          --  has a constraint it must be preserved to retain the semantics of
4268          --  the body.
4269
4270          if Is_Class_Wide_Type (Etype (F))
4271            or else (Is_Access_Type (Etype (F))
4272                      and then Is_Class_Wide_Type (Designated_Type (Etype (F))))
4273          then
4274             Temp_Typ := Etype (F);
4275
4276          elsif Base_Type (Etype (F)) = Base_Type (Etype (A))
4277            and then Etype (F) /= Base_Type (Etype (F))
4278          then
4279             Temp_Typ := Etype (F);
4280          else
4281             Temp_Typ := Etype (A);
4282          end if;
4283
4284          --  If the actual is a simple name or a literal, no need to
4285          --  create a temporary, object can be used directly.
4286
4287          --  If the actual is a literal and the formal has its address taken,
4288          --  we cannot pass the literal itself as an argument, so its value
4289          --  must be captured in a temporary.
4290
4291          if (Is_Entity_Name (A)
4292               and then
4293                (not Is_Scalar_Type (Etype (A))
4294                  or else Ekind (Entity (A)) = E_Enumeration_Literal))
4295
4296          --  When the actual is an identifier and the corresponding formal
4297          --  is used only once in the original body, the formal can be
4298          --  substituted directly with the actual parameter.
4299
4300            or else (Nkind (A) = N_Identifier
4301              and then Formal_Is_Used_Once (F))
4302
4303            or else
4304              (Nkind_In (A, N_Real_Literal,
4305                            N_Integer_Literal,
4306                            N_Character_Literal)
4307                and then not Address_Taken (F))
4308          then
4309             if Etype (F) /= Etype (A) then
4310                Set_Renamed_Object
4311                  (F, Unchecked_Convert_To (Etype (F), Relocate_Node (A)));
4312             else
4313                Set_Renamed_Object (F, A);
4314             end if;
4315
4316          else
4317             Temp := Make_Temporary (Loc, 'C');
4318
4319             --  If the actual for an in/in-out parameter is a view conversion,
4320             --  make it into an unchecked conversion, given that an untagged
4321             --  type conversion is not a proper object for a renaming.
4322
4323             --  In-out conversions that involve real conversions have already
4324             --  been transformed in Expand_Actuals.
4325
4326             if Nkind (A) = N_Type_Conversion
4327               and then Ekind (F) /= E_In_Parameter
4328             then
4329                New_A :=
4330                  Make_Unchecked_Type_Conversion (Loc,
4331                    Subtype_Mark => New_Occurrence_Of (Etype (F), Loc),
4332                    Expression   => Relocate_Node (Expression (A)));
4333
4334             elsif Etype (F) /= Etype (A) then
4335                New_A := Unchecked_Convert_To (Etype (F), Relocate_Node (A));
4336                Temp_Typ := Etype (F);
4337
4338             else
4339                New_A := Relocate_Node (A);
4340             end if;
4341
4342             Set_Sloc (New_A, Sloc (N));
4343
4344             --  If the actual has a by-reference type, it cannot be copied, so
4345             --  its value is captured in a renaming declaration. Otherwise
4346             --  declare a local constant initialized with the actual.
4347
4348             --  We also use a renaming declaration for expressions of an array
4349             --  type that is not bit-packed, both for efficiency reasons and to
4350             --  respect the semantics of the call: in most cases the original
4351             --  call will pass the parameter by reference, and thus the inlined
4352             --  code will have the same semantics.
4353
4354             if Ekind (F) = E_In_Parameter
4355               and then not Is_By_Reference_Type (Etype (A))
4356               and then
4357                 (not Is_Array_Type (Etype (A))
4358                   or else not Is_Object_Reference (A)
4359                   or else Is_Bit_Packed_Array (Etype (A)))
4360             then
4361                Decl :=
4362                  Make_Object_Declaration (Loc,
4363                    Defining_Identifier => Temp,
4364                    Constant_Present    => True,
4365                    Object_Definition   => New_Occurrence_Of (Temp_Typ, Loc),
4366                    Expression          => New_A);
4367             else
4368                Decl :=
4369                  Make_Object_Renaming_Declaration (Loc,
4370                    Defining_Identifier => Temp,
4371                    Subtype_Mark        => New_Occurrence_Of (Temp_Typ, Loc),
4372                    Name                => New_A);
4373             end if;
4374
4375             Append (Decl, Decls);
4376             Set_Renamed_Object (F, Temp);
4377          end if;
4378
4379          Next_Formal (F);
4380          Next_Actual (A);
4381       end loop;
4382
4383       --  Establish target of function call. If context is not assignment or
4384       --  declaration, create a temporary as a target. The declaration for the
4385       --  temporary may be subsequently optimized away if the body is a single
4386       --  expression, or if the left-hand side of the assignment is simple
4387       --  enough, i.e. an entity or an explicit dereference of one.
4388
4389       if Ekind (Subp) = E_Function then
4390          if Nkind (Parent (N)) = N_Assignment_Statement
4391            and then Is_Entity_Name (Name (Parent (N)))
4392          then
4393             Targ := Name (Parent (N));
4394
4395          elsif Nkind (Parent (N)) = N_Assignment_Statement
4396            and then Nkind (Name (Parent (N))) = N_Explicit_Dereference
4397            and then Is_Entity_Name (Prefix (Name (Parent (N))))
4398          then
4399             Targ := Name (Parent (N));
4400
4401          elsif Nkind (Parent (N)) = N_Assignment_Statement
4402            and then Nkind (Name (Parent (N))) = N_Selected_Component
4403            and then Is_Entity_Name (Prefix (Name (Parent (N))))
4404          then
4405             Targ := New_Copy_Tree (Name (Parent (N)));
4406
4407          elsif Nkind (Parent (N)) = N_Object_Declaration
4408            and then Is_Limited_Type (Etype (Subp))
4409          then
4410             Targ := Defining_Identifier (Parent (N));
4411
4412          else
4413             --  Replace call with temporary and create its declaration
4414
4415             Temp := Make_Temporary (Loc, 'C');
4416             Set_Is_Internal (Temp);
4417
4418             --  For the unconstrained case, the generated temporary has the
4419             --  same constrained declaration as the result variable. It may
4420             --  eventually be possible to remove that temporary and use the
4421             --  result variable directly.
4422
4423             if Is_Unc
4424               and then Nkind (Parent (N)) /= N_Assignment_Statement
4425             then
4426                Decl :=
4427                  Make_Object_Declaration (Loc,
4428                    Defining_Identifier => Temp,
4429                    Object_Definition   =>
4430                      New_Copy_Tree (Object_Definition (Parent (Targ1))));
4431
4432                Replace_Formals (Decl);
4433
4434             else
4435                Decl :=
4436                  Make_Object_Declaration (Loc,
4437                    Defining_Identifier => Temp,
4438                    Object_Definition   => New_Occurrence_Of (Ret_Type, Loc));
4439
4440                Set_Etype (Temp, Ret_Type);
4441             end if;
4442
4443             Set_No_Initialization (Decl);
4444             Append (Decl, Decls);
4445             Rewrite (N, New_Occurrence_Of (Temp, Loc));
4446             Targ := Temp;
4447          end if;
4448       end if;
4449
4450       Insert_Actions (N, Decls);
4451
4452       --  Traverse the tree and replace formals with actuals or their thunks.
4453       --  Attach block to tree before analysis and rewriting.
4454
4455       Replace_Formals (Blk);
4456       Set_Parent (Blk, N);
4457
4458       if not Comes_From_Source (Subp) or else Is_Predef then
4459          Reset_Slocs (Blk);
4460       end if;
4461
4462       if Present (Exit_Lab) then
4463
4464          --  If the body was a single expression, the single return statement
4465          --  and the corresponding label are useless.
4466
4467          if Num_Ret = 1
4468            and then
4469              Nkind (Last (Statements (Handled_Statement_Sequence (Blk)))) =
4470                                                             N_Goto_Statement
4471          then
4472             Remove (Last (Statements (Handled_Statement_Sequence (Blk))));
4473          else
4474             Append (Lab_Decl, (Declarations (Blk)));
4475             Append (Exit_Lab, Statements (Handled_Statement_Sequence (Blk)));
4476          end if;
4477       end if;
4478
4479       --  Analyze Blk with In_Inlined_Body set, to avoid spurious errors on
4480       --  conflicting private views that Gigi would ignore. If this is a
4481       --  predefined unit, analyze with checks off, as is done in the non-
4482       --  inlined run-time units.
4483
4484       declare
4485          I_Flag : constant Boolean := In_Inlined_Body;
4486
4487       begin
4488          In_Inlined_Body := True;
4489
4490          if Is_Predef then
4491             declare
4492                Style : constant Boolean := Style_Check;
4493             begin
4494                Style_Check := False;
4495                Analyze (Blk, Suppress => All_Checks);
4496                Style_Check := Style;
4497             end;
4498
4499          else
4500             Analyze (Blk);
4501          end if;
4502
4503          In_Inlined_Body := I_Flag;
4504       end;
4505
4506       if Ekind (Subp) = E_Procedure then
4507          Rewrite_Procedure_Call (N, Blk);
4508
4509       else
4510          Rewrite_Function_Call (N, Blk);
4511
4512          --  For the unconstrained case, the replacement of the call has been
4513          --  made prior to the complete analysis of the generated declarations.
4514          --  Propagate the proper type now.
4515
4516          if Is_Unc then
4517             if Nkind (N) = N_Identifier then
4518                Set_Etype (N, Etype (Entity (N)));
4519             else
4520                Set_Etype (N, Etype (Targ1));
4521             end if;
4522          end if;
4523       end if;
4524
4525       Restore_Env;
4526
4527       --  Cleanup mapping between formals and actuals for other expansions
4528
4529       F := First_Formal (Subp);
4530       while Present (F) loop
4531          Set_Renamed_Object (F, Empty);
4532          Next_Formal (F);
4533       end loop;
4534    end Expand_Inlined_Call;
4535
4536    ----------------------------------------
4537    -- Expand_N_Extended_Return_Statement --
4538    ----------------------------------------
4539
4540    --  If there is a Handled_Statement_Sequence, we rewrite this:
4541
4542    --     return Result : T := <expression> do
4543    --        <handled_seq_of_stms>
4544    --     end return;
4545
4546    --  to be:
4547
4548    --     declare
4549    --        Result : T := <expression>;
4550    --     begin
4551    --        <handled_seq_of_stms>
4552    --        return Result;
4553    --     end;
4554
4555    --  Otherwise (no Handled_Statement_Sequence), we rewrite this:
4556
4557    --     return Result : T := <expression>;
4558
4559    --  to be:
4560
4561    --     return <expression>;
4562
4563    --  unless it's build-in-place or there's no <expression>, in which case
4564    --  we generate:
4565
4566    --     declare
4567    --        Result : T := <expression>;
4568    --     begin
4569    --        return Result;
4570    --     end;
4571
4572    --  Note that this case could have been written by the user as an extended
4573    --  return statement, or could have been transformed to this from a simple
4574    --  return statement.
4575
4576    --  That is, we need to have a reified return object if there are statements
4577    --  (which might refer to it) or if we're doing build-in-place (so we can
4578    --  set its address to the final resting place or if there is no expression
4579    --  (in which case default initial values might need to be set).
4580
4581    procedure Expand_N_Extended_Return_Statement (N : Node_Id) is
4582       Loc : constant Source_Ptr := Sloc (N);
4583
4584       Par_Func     : constant Entity_Id :=
4585                        Return_Applies_To (Return_Statement_Entity (N));
4586       Result_Subt  : constant Entity_Id := Etype (Par_Func);
4587       Ret_Obj_Id   : constant Entity_Id :=
4588                        First_Entity (Return_Statement_Entity (N));
4589       Ret_Obj_Decl : constant Node_Id := Parent (Ret_Obj_Id);
4590
4591       Is_Build_In_Place : constant Boolean :=
4592                             Is_Build_In_Place_Function (Par_Func);
4593
4594       Exp         : Node_Id;
4595       HSS         : Node_Id;
4596       Result      : Node_Id;
4597       Return_Stmt : Node_Id;
4598       Stmts       : List_Id;
4599
4600       function Build_Heap_Allocator
4601         (Temp_Id    : Entity_Id;
4602          Temp_Typ   : Entity_Id;
4603          Func_Id    : Entity_Id;
4604          Ret_Typ    : Entity_Id;
4605          Alloc_Expr : Node_Id) return Node_Id;
4606       --  Create the statements necessary to allocate a return object on the
4607       --  caller's master. The master is available through implicit parameter
4608       --  BIPfinalizationmaster.
4609       --
4610       --    if BIPfinalizationmaster /= null then
4611       --       declare
4612       --          type Ptr_Typ is access Ret_Typ;
4613       --          for Ptr_Typ'Storage_Pool use
4614       --                Base_Pool (BIPfinalizationmaster.all).all;
4615       --          Local : Ptr_Typ;
4616       --
4617       --       begin
4618       --          procedure Allocate (...) is
4619       --          begin
4620       --             System.Storage_Pools.Subpools.Allocate_Any (...);
4621       --          end Allocate;
4622       --
4623       --          Local := <Alloc_Expr>;
4624       --          Temp_Id := Temp_Typ (Local);
4625       --       end;
4626       --    end if;
4627       --
4628       --  Temp_Id is the temporary which is used to reference the internally
4629       --  created object in all allocation forms. Temp_Typ is the type of the
4630       --  temporary. Func_Id is the enclosing function. Ret_Typ is the return
4631       --  type of Func_Id. Alloc_Expr is the actual allocator.
4632
4633       function Move_Activation_Chain return Node_Id;
4634       --  Construct a call to System.Tasking.Stages.Move_Activation_Chain
4635       --  with parameters:
4636       --    From         current activation chain
4637       --    To           activation chain passed in by the caller
4638       --    New_Master   master passed in by the caller
4639
4640       --------------------------
4641       -- Build_Heap_Allocator --
4642       --------------------------
4643
4644       function Build_Heap_Allocator
4645         (Temp_Id    : Entity_Id;
4646          Temp_Typ   : Entity_Id;
4647          Func_Id    : Entity_Id;
4648          Ret_Typ    : Entity_Id;
4649          Alloc_Expr : Node_Id) return Node_Id
4650       is
4651       begin
4652          pragma Assert (Is_Build_In_Place_Function (Func_Id));
4653
4654          --  Processing for build-in-place object allocation. This is disabled
4655          --  on .NET/JVM because the targets do not support pools.
4656
4657          if VM_Target = No_VM
4658            and then Needs_Finalization (Ret_Typ)
4659          then
4660             declare
4661                Decls      : constant List_Id := New_List;
4662                Fin_Mas_Id : constant Entity_Id :=
4663                               Build_In_Place_Formal
4664                                 (Func_Id, BIP_Finalization_Master);
4665                Stmts      : constant List_Id := New_List;
4666                Desig_Typ  : Entity_Id;
4667                Local_Id   : Entity_Id;
4668                Pool_Id    : Entity_Id;
4669                Ptr_Typ    : Entity_Id;
4670
4671             begin
4672                --  Generate:
4673                --    Pool_Id renames Base_Pool (BIPfinalizationmaster.all).all;
4674
4675                Pool_Id := Make_Temporary (Loc, 'P');
4676
4677                Append_To (Decls,
4678                  Make_Object_Renaming_Declaration (Loc,
4679                    Defining_Identifier => Pool_Id,
4680                    Subtype_Mark        =>
4681                      New_Reference_To (RTE (RE_Root_Storage_Pool), Loc),
4682                    Name                =>
4683                      Make_Explicit_Dereference (Loc,
4684                        Prefix =>
4685                          Make_Function_Call (Loc,
4686                            Name                   =>
4687                              New_Reference_To (RTE (RE_Base_Pool), Loc),
4688                            Parameter_Associations => New_List (
4689                              Make_Explicit_Dereference (Loc,
4690                                Prefix =>
4691                                  New_Reference_To (Fin_Mas_Id, Loc)))))));
4692
4693                --  Create an access type which uses the storage pool of the
4694                --  caller's master. This additional type is necessary because
4695                --  the finalization master cannot be associated with the type
4696                --  of the temporary. Otherwise the secondary stack allocation
4697                --  will fail.
4698
4699                Desig_Typ := Ret_Typ;
4700
4701                --  Ensure that the build-in-place machinery uses a fat pointer
4702                --  when allocating an unconstrained array on the heap. In this
4703                --  case the result object type is a constrained array type even
4704                --  though the function type is unconstrained.
4705
4706                if Ekind (Desig_Typ) = E_Array_Subtype then
4707                   Desig_Typ := Base_Type (Desig_Typ);
4708                end if;
4709
4710                --  Generate:
4711                --    type Ptr_Typ is access Desig_Typ;
4712
4713                Ptr_Typ := Make_Temporary (Loc, 'P');
4714
4715                Append_To (Decls,
4716                  Make_Full_Type_Declaration (Loc,
4717                    Defining_Identifier => Ptr_Typ,
4718                    Type_Definition     =>
4719                      Make_Access_To_Object_Definition (Loc,
4720                        Subtype_Indication =>
4721                          New_Reference_To (Desig_Typ, Loc))));
4722
4723                --  Perform minor decoration in order to set the master and the
4724                --  storage pool attributes.
4725
4726                Set_Ekind (Ptr_Typ, E_Access_Type);
4727                Set_Finalization_Master     (Ptr_Typ, Fin_Mas_Id);
4728                Set_Associated_Storage_Pool (Ptr_Typ, Pool_Id);
4729
4730                --  Create the temporary, generate:
4731                --    Local_Id : Ptr_Typ;
4732
4733                Local_Id := Make_Temporary (Loc, 'T');
4734
4735                Append_To (Decls,
4736                  Make_Object_Declaration (Loc,
4737                    Defining_Identifier => Local_Id,
4738                    Object_Definition   =>
4739                      New_Reference_To (Ptr_Typ, Loc)));
4740
4741                --  Allocate the object, generate:
4742                --    Local_Id := <Alloc_Expr>;
4743
4744                Append_To (Stmts,
4745                  Make_Assignment_Statement (Loc,
4746                    Name       => New_Reference_To (Local_Id, Loc),
4747                    Expression => Alloc_Expr));
4748
4749                --  Generate:
4750                --    Temp_Id := Temp_Typ (Local_Id);
4751
4752                Append_To (Stmts,
4753                  Make_Assignment_Statement (Loc,
4754                    Name       => New_Reference_To (Temp_Id, Loc),
4755                    Expression =>
4756                      Unchecked_Convert_To (Temp_Typ,
4757                        New_Reference_To (Local_Id, Loc))));
4758
4759                --  Wrap the allocation in a block. This is further conditioned
4760                --  by checking the caller finalization master at runtime. A
4761                --  null value indicates a non-existent master, most likely due
4762                --  to a Finalize_Storage_Only allocation.
4763
4764                --  Generate:
4765                --    if BIPfinalizationmaster /= null then
4766                --       declare
4767                --          <Decls>
4768                --       begin
4769                --          <Stmts>
4770                --       end;
4771                --    end if;
4772
4773                return
4774                  Make_If_Statement (Loc,
4775                    Condition       =>
4776                      Make_Op_Ne (Loc,
4777                        Left_Opnd  => New_Reference_To (Fin_Mas_Id, Loc),
4778                        Right_Opnd => Make_Null (Loc)),
4779
4780                    Then_Statements => New_List (
4781                      Make_Block_Statement (Loc,
4782                        Declarations               => Decls,
4783                        Handled_Statement_Sequence =>
4784                          Make_Handled_Sequence_Of_Statements (Loc,
4785                            Statements => Stmts))));
4786             end;
4787
4788          --  For all other cases, generate:
4789          --    Temp_Id := <Alloc_Expr>;
4790
4791          else
4792             return
4793               Make_Assignment_Statement (Loc,
4794                 Name       => New_Reference_To (Temp_Id, Loc),
4795                 Expression => Alloc_Expr);
4796          end if;
4797       end Build_Heap_Allocator;
4798
4799       ---------------------------
4800       -- Move_Activation_Chain --
4801       ---------------------------
4802
4803       function Move_Activation_Chain return Node_Id is
4804       begin
4805          return
4806            Make_Procedure_Call_Statement (Loc,
4807              Name                   =>
4808                New_Reference_To (RTE (RE_Move_Activation_Chain), Loc),
4809
4810              Parameter_Associations => New_List (
4811
4812                --  Source chain
4813
4814                Make_Attribute_Reference (Loc,
4815                  Prefix         => Make_Identifier (Loc, Name_uChain),
4816                  Attribute_Name => Name_Unrestricted_Access),
4817
4818                --  Destination chain
4819
4820                New_Reference_To
4821                  (Build_In_Place_Formal (Par_Func, BIP_Activation_Chain), Loc),
4822
4823                --  New master
4824
4825                New_Reference_To
4826                  (Build_In_Place_Formal (Par_Func, BIP_Task_Master), Loc)));
4827       end Move_Activation_Chain;
4828
4829    --  Start of processing for Expand_N_Extended_Return_Statement
4830
4831    begin
4832       if Nkind (Ret_Obj_Decl) = N_Object_Declaration then
4833          Exp := Expression (Ret_Obj_Decl);
4834       else
4835          Exp := Empty;
4836       end if;
4837
4838       HSS := Handled_Statement_Sequence (N);
4839
4840       --  If the returned object needs finalization actions, the function must
4841       --  perform the appropriate cleanup should it fail to return. The state
4842       --  of the function itself is tracked through a flag which is coupled
4843       --  with the scope finalizer. There is one flag per each return object
4844       --  in case of multiple returns.
4845
4846       if Is_Build_In_Place
4847         and then Needs_Finalization (Etype (Ret_Obj_Id))
4848       then
4849          declare
4850             Flag_Decl : Node_Id;
4851             Flag_Id   : Entity_Id;
4852             Func_Bod  : Node_Id;
4853
4854          begin
4855             --  Recover the function body
4856
4857             Func_Bod := Unit_Declaration_Node (Par_Func);
4858
4859             if Nkind (Func_Bod) = N_Subprogram_Declaration then
4860                Func_Bod := Parent (Parent (Corresponding_Body (Func_Bod)));
4861             end if;
4862
4863             --  Create a flag to track the function state
4864
4865             Flag_Id := Make_Temporary (Loc, 'F');
4866             Set_Return_Flag_Or_Transient_Decl (Ret_Obj_Id, Flag_Id);
4867
4868             --  Insert the flag at the beginning of the function declarations,
4869             --  generate:
4870             --    Fnn : Boolean := False;
4871
4872             Flag_Decl :=
4873               Make_Object_Declaration (Loc,
4874                 Defining_Identifier => Flag_Id,
4875                   Object_Definition =>
4876                     New_Reference_To (Standard_Boolean, Loc),
4877                   Expression        => New_Reference_To (Standard_False, Loc));
4878
4879             Prepend_To (Declarations (Func_Bod), Flag_Decl);
4880             Analyze (Flag_Decl);
4881          end;
4882       end if;
4883
4884       --  Build a simple_return_statement that returns the return object when
4885       --  there is a statement sequence, or no expression, or the result will
4886       --  be built in place. Note however that we currently do this for all
4887       --  composite cases, even though nonlimited composite results are not yet
4888       --  built in place (though we plan to do so eventually).
4889
4890       if Present (HSS)
4891         or else Is_Composite_Type (Result_Subt)
4892         or else No (Exp)
4893       then
4894          if No (HSS) then
4895             Stmts := New_List;
4896
4897          --  If the extended return has a handled statement sequence, then wrap
4898          --  it in a block and use the block as the first statement.
4899
4900          else
4901             Stmts := New_List (
4902               Make_Block_Statement (Loc,
4903                 Declarations               => New_List,
4904                 Handled_Statement_Sequence => HSS));
4905          end if;
4906
4907          --  If the result type contains tasks, we call Move_Activation_Chain.
4908          --  Later, the cleanup code will call Complete_Master, which will
4909          --  terminate any unactivated tasks belonging to the return statement
4910          --  master. But Move_Activation_Chain updates their master to be that
4911          --  of the caller, so they will not be terminated unless the return
4912          --  statement completes unsuccessfully due to exception, abort, goto,
4913          --  or exit. As a formality, we test whether the function requires the
4914          --  result to be built in place, though that's necessarily true for
4915          --  the case of result types with task parts.
4916
4917          if Is_Build_In_Place
4918            and then Has_Task (Result_Subt)
4919          then
4920             --  The return expression is an aggregate for a complex type which
4921             --  contains tasks. This particular case is left unexpanded since
4922             --  the regular expansion would insert all temporaries and
4923             --  initialization code in the wrong block.
4924
4925             if Nkind (Exp) = N_Aggregate then
4926                Expand_N_Aggregate (Exp);
4927             end if;
4928
4929             --  Do not move the activation chain if the return object does not
4930             --  contain tasks.
4931
4932             if Has_Task (Etype (Ret_Obj_Id)) then
4933                Append_To (Stmts, Move_Activation_Chain);
4934             end if;
4935          end if;
4936
4937          --  Update the state of the function right before the object is
4938          --  returned.
4939
4940          if Is_Build_In_Place
4941            and then Needs_Finalization (Etype (Ret_Obj_Id))
4942          then
4943             declare
4944                Flag_Id : constant Entity_Id :=
4945                            Return_Flag_Or_Transient_Decl (Ret_Obj_Id);
4946
4947             begin
4948                --  Generate:
4949                --    Fnn := True;
4950
4951                Append_To (Stmts,
4952                  Make_Assignment_Statement (Loc,
4953                    Name       => New_Reference_To (Flag_Id, Loc),
4954                    Expression => New_Reference_To (Standard_True, Loc)));
4955             end;
4956          end if;
4957
4958          --  Build a simple_return_statement that returns the return object
4959
4960          Return_Stmt :=
4961            Make_Simple_Return_Statement (Loc,
4962              Expression => New_Occurrence_Of (Ret_Obj_Id, Loc));
4963          Append_To (Stmts, Return_Stmt);
4964
4965          HSS := Make_Handled_Sequence_Of_Statements (Loc, Stmts);
4966       end if;
4967
4968       --  Case where we build a return statement block
4969
4970       if Present (HSS) then
4971          Result :=
4972            Make_Block_Statement (Loc,
4973              Declarations               => Return_Object_Declarations (N),
4974              Handled_Statement_Sequence => HSS);
4975
4976          --  We set the entity of the new block statement to be that of the
4977          --  return statement. This is necessary so that various fields, such
4978          --  as Finalization_Chain_Entity carry over from the return statement
4979          --  to the block. Note that this block is unusual, in that its entity
4980          --  is an E_Return_Statement rather than an E_Block.
4981
4982          Set_Identifier
4983            (Result, New_Occurrence_Of (Return_Statement_Entity (N), Loc));
4984
4985          --  If the object decl was already rewritten as a renaming, then we
4986          --  don't want to do the object allocation and transformation of of
4987          --  the return object declaration to a renaming. This case occurs
4988          --  when the return object is initialized by a call to another
4989          --  build-in-place function, and that function is responsible for
4990          --  the allocation of the return object.
4991
4992          if Is_Build_In_Place
4993            and then Nkind (Ret_Obj_Decl) = N_Object_Renaming_Declaration
4994          then
4995             pragma Assert
4996               (Nkind (Original_Node (Ret_Obj_Decl)) = N_Object_Declaration
4997                 and then Is_Build_In_Place_Function_Call
4998                            (Expression (Original_Node (Ret_Obj_Decl))));
4999
5000             --  Return the build-in-place result by reference
5001
5002             Set_By_Ref (Return_Stmt);
5003
5004          elsif Is_Build_In_Place then
5005
5006             --  Locate the implicit access parameter associated with the
5007             --  caller-supplied return object and convert the return
5008             --  statement's return object declaration to a renaming of a
5009             --  dereference of the access parameter. If the return object's
5010             --  declaration includes an expression that has not already been
5011             --  expanded as separate assignments, then add an assignment
5012             --  statement to ensure the return object gets initialized.
5013
5014             --    declare
5015             --       Result : T [:= <expression>];
5016             --    begin
5017             --       ...
5018
5019             --  is converted to
5020
5021             --    declare
5022             --       Result : T renames FuncRA.all;
5023             --       [Result := <expression;]
5024             --    begin
5025             --       ...
5026
5027             declare
5028                Return_Obj_Id    : constant Entity_Id :=
5029                                     Defining_Identifier (Ret_Obj_Decl);
5030                Return_Obj_Typ   : constant Entity_Id := Etype (Return_Obj_Id);
5031                Return_Obj_Expr  : constant Node_Id :=
5032                                     Expression (Ret_Obj_Decl);
5033                Constr_Result    : constant Boolean :=
5034                                     Is_Constrained (Result_Subt);
5035                Obj_Alloc_Formal : Entity_Id;
5036                Object_Access    : Entity_Id;
5037                Obj_Acc_Deref    : Node_Id;
5038                Init_Assignment  : Node_Id := Empty;
5039
5040             begin
5041                --  Build-in-place results must be returned by reference
5042
5043                Set_By_Ref (Return_Stmt);
5044
5045                --  Retrieve the implicit access parameter passed by the caller
5046
5047                Object_Access :=
5048                  Build_In_Place_Formal (Par_Func, BIP_Object_Access);
5049
5050                --  If the return object's declaration includes an expression
5051                --  and the declaration isn't marked as No_Initialization, then
5052                --  we need to generate an assignment to the object and insert
5053                --  it after the declaration before rewriting it as a renaming
5054                --  (otherwise we'll lose the initialization). The case where
5055                --  the result type is an interface (or class-wide interface)
5056                --  is also excluded because the context of the function call
5057                --  must be unconstrained, so the initialization will always
5058                --  be done as part of an allocator evaluation (storage pool
5059                --  or secondary stack), never to a constrained target object
5060                --  passed in by the caller. Besides the assignment being
5061                --  unneeded in this case, it avoids problems with trying to
5062                --  generate a dispatching assignment when the return expression
5063                --  is a nonlimited descendant of a limited interface (the
5064                --  interface has no assignment operation).
5065
5066                if Present (Return_Obj_Expr)
5067                  and then not No_Initialization (Ret_Obj_Decl)
5068                  and then not Is_Interface (Return_Obj_Typ)
5069                then
5070                   Init_Assignment :=
5071                     Make_Assignment_Statement (Loc,
5072                       Name       => New_Reference_To (Return_Obj_Id, Loc),
5073                       Expression => Relocate_Node (Return_Obj_Expr));
5074
5075                   Set_Etype (Name (Init_Assignment), Etype (Return_Obj_Id));
5076                   Set_Assignment_OK (Name (Init_Assignment));
5077                   Set_No_Ctrl_Actions (Init_Assignment);
5078
5079                   Set_Parent (Name (Init_Assignment), Init_Assignment);
5080                   Set_Parent (Expression (Init_Assignment), Init_Assignment);
5081
5082                   Set_Expression (Ret_Obj_Decl, Empty);
5083
5084                   if Is_Class_Wide_Type (Etype (Return_Obj_Id))
5085                     and then not Is_Class_Wide_Type
5086                                    (Etype (Expression (Init_Assignment)))
5087                   then
5088                      Rewrite (Expression (Init_Assignment),
5089                        Make_Type_Conversion (Loc,
5090                          Subtype_Mark =>
5091                            New_Occurrence_Of (Etype (Return_Obj_Id), Loc),
5092                          Expression   =>
5093                            Relocate_Node (Expression (Init_Assignment))));
5094                   end if;
5095
5096                   --  In the case of functions where the calling context can
5097                   --  determine the form of allocation needed, initialization
5098                   --  is done with each part of the if statement that handles
5099                   --  the different forms of allocation (this is true for
5100                   --  unconstrained and tagged result subtypes).
5101
5102                   if Constr_Result
5103                     and then not Is_Tagged_Type (Underlying_Type (Result_Subt))
5104                   then
5105                      Insert_After (Ret_Obj_Decl, Init_Assignment);
5106                   end if;
5107                end if;
5108
5109                --  When the function's subtype is unconstrained, a run-time
5110                --  test is needed to determine the form of allocation to use
5111                --  for the return object. The function has an implicit formal
5112                --  parameter indicating this. If the BIP_Alloc_Form formal has
5113                --  the value one, then the caller has passed access to an
5114                --  existing object for use as the return object. If the value
5115                --  is two, then the return object must be allocated on the
5116                --  secondary stack. Otherwise, the object must be allocated in
5117                --  a storage pool (currently only supported for the global
5118                --  heap, user-defined storage pools TBD ???). We generate an
5119                --  if statement to test the implicit allocation formal and
5120                --  initialize a local access value appropriately, creating
5121                --  allocators in the secondary stack and global heap cases.
5122                --  The special formal also exists and must be tested when the
5123                --  function has a tagged result, even when the result subtype
5124                --  is constrained, because in general such functions can be
5125                --  called in dispatching contexts and must be handled similarly
5126                --  to functions with a class-wide result.
5127
5128                if not Constr_Result
5129                  or else Is_Tagged_Type (Underlying_Type (Result_Subt))
5130                then
5131                   Obj_Alloc_Formal :=
5132                     Build_In_Place_Formal (Par_Func, BIP_Alloc_Form);
5133
5134                   declare
5135                      Pool_Id        : constant Entity_Id :=
5136                                         Make_Temporary (Loc, 'P');
5137                      Alloc_Obj_Id   : Entity_Id;
5138                      Alloc_Obj_Decl : Node_Id;
5139                      Alloc_If_Stmt  : Node_Id;
5140                      Heap_Allocator : Node_Id;
5141                      Pool_Decl      : Node_Id;
5142                      Pool_Allocator : Node_Id;
5143                      Ptr_Type_Decl  : Node_Id;
5144                      Ref_Type       : Entity_Id;
5145                      SS_Allocator   : Node_Id;
5146
5147                   begin
5148                      --  Reuse the itype created for the function's implicit
5149                      --  access formal. This avoids the need to create a new
5150                      --  access type here, plus it allows assigning the access
5151                      --  formal directly without applying a conversion.
5152
5153                      --    Ref_Type := Etype (Object_Access);
5154
5155                      --  Create an access type designating the function's
5156                      --  result subtype.
5157
5158                      Ref_Type := Make_Temporary (Loc, 'A');
5159
5160                      Ptr_Type_Decl :=
5161                        Make_Full_Type_Declaration (Loc,
5162                          Defining_Identifier => Ref_Type,
5163                          Type_Definition     =>
5164                            Make_Access_To_Object_Definition (Loc,
5165                              All_Present        => True,
5166                              Subtype_Indication =>
5167                                New_Reference_To (Return_Obj_Typ, Loc)));
5168
5169                      Insert_Before (Ret_Obj_Decl, Ptr_Type_Decl);
5170
5171                      --  Create an access object that will be initialized to an
5172                      --  access value denoting the return object, either coming
5173                      --  from an implicit access value passed in by the caller
5174                      --  or from the result of an allocator.
5175
5176                      Alloc_Obj_Id := Make_Temporary (Loc, 'R');
5177                      Set_Etype (Alloc_Obj_Id, Ref_Type);
5178
5179                      Alloc_Obj_Decl :=
5180                        Make_Object_Declaration (Loc,
5181                          Defining_Identifier => Alloc_Obj_Id,
5182                          Object_Definition   =>
5183                            New_Reference_To (Ref_Type, Loc));
5184
5185                      Insert_Before (Ret_Obj_Decl, Alloc_Obj_Decl);
5186
5187                      --  Create allocators for both the secondary stack and
5188                      --  global heap. If there's an initialization expression,
5189                      --  then create these as initialized allocators.
5190
5191                      if Present (Return_Obj_Expr)
5192                        and then not No_Initialization (Ret_Obj_Decl)
5193                      then
5194                         --  Always use the type of the expression for the
5195                         --  qualified expression, rather than the result type.
5196                         --  In general we cannot always use the result type
5197                         --  for the allocator, because the expression might be
5198                         --  of a specific type, such as in the case of an
5199                         --  aggregate or even a nonlimited object when the
5200                         --  result type is a limited class-wide interface type.
5201
5202                         Heap_Allocator :=
5203                           Make_Allocator (Loc,
5204                             Expression =>
5205                               Make_Qualified_Expression (Loc,
5206                                 Subtype_Mark =>
5207                                   New_Reference_To
5208                                     (Etype (Return_Obj_Expr), Loc),
5209                                 Expression   =>
5210                                   New_Copy_Tree (Return_Obj_Expr)));
5211
5212                      else
5213                         --  If the function returns a class-wide type we cannot
5214                         --  use the return type for the allocator. Instead we
5215                         --  use the type of the expression, which must be an
5216                         --  aggregate of a definite type.
5217
5218                         if Is_Class_Wide_Type (Return_Obj_Typ) then
5219                            Heap_Allocator :=
5220                              Make_Allocator (Loc,
5221                                Expression =>
5222                                  New_Reference_To
5223                                    (Etype (Return_Obj_Expr), Loc));
5224                         else
5225                            Heap_Allocator :=
5226                              Make_Allocator (Loc,
5227                                Expression =>
5228                                  New_Reference_To (Return_Obj_Typ, Loc));
5229                         end if;
5230
5231                         --  If the object requires default initialization then
5232                         --  that will happen later following the elaboration of
5233                         --  the object renaming. If we don't turn it off here
5234                         --  then the object will be default initialized twice.
5235
5236                         Set_No_Initialization (Heap_Allocator);
5237                      end if;
5238
5239                      --  The Pool_Allocator is just like the Heap_Allocator,
5240                      --  except we set Storage_Pool and Procedure_To_Call so
5241                      --  it will use the user-defined storage pool.
5242
5243                      Pool_Allocator := New_Copy_Tree (Heap_Allocator);
5244
5245                      --  Do not generate the renaming of the build-in-place
5246                      --  pool parameter on .NET/JVM/ZFP because the parameter
5247                      --  is not created in the first place.
5248
5249                      if VM_Target = No_VM
5250                        and then RTE_Available (RE_Root_Storage_Pool_Ptr)
5251                      then
5252                         Pool_Decl :=
5253                           Make_Object_Renaming_Declaration (Loc,
5254                             Defining_Identifier => Pool_Id,
5255                             Subtype_Mark        =>
5256                               New_Reference_To
5257                                 (RTE (RE_Root_Storage_Pool), Loc),
5258                             Name                =>
5259                               Make_Explicit_Dereference (Loc,
5260                                 New_Reference_To
5261                                   (Build_In_Place_Formal
5262                                      (Par_Func, BIP_Storage_Pool), Loc)));
5263                         Set_Storage_Pool (Pool_Allocator, Pool_Id);
5264                         Set_Procedure_To_Call
5265                           (Pool_Allocator, RTE (RE_Allocate_Any));
5266                      else
5267                         Pool_Decl := Make_Null_Statement (Loc);
5268                      end if;
5269
5270                      --  If the No_Allocators restriction is active, then only
5271                      --  an allocator for secondary stack allocation is needed.
5272                      --  It's OK for such allocators to have Comes_From_Source
5273                      --  set to False, because gigi knows not to flag them as
5274                      --  being a violation of No_Implicit_Heap_Allocations.
5275
5276                      if Restriction_Active (No_Allocators) then
5277                         SS_Allocator   := Heap_Allocator;
5278                         Heap_Allocator := Make_Null (Loc);
5279                         Pool_Allocator := Make_Null (Loc);
5280
5281                      --  Otherwise the heap and pool allocators may be needed,
5282                      --  so we make another allocator for secondary stack
5283                      --  allocation.
5284
5285                      else
5286                         SS_Allocator := New_Copy_Tree (Heap_Allocator);
5287
5288                         --  The heap and pool allocators are marked as
5289                         --  Comes_From_Source since they correspond to an
5290                         --  explicit user-written allocator (that is, it will
5291                         --  only be executed on behalf of callers that call the
5292                         --  function as initialization for such an allocator).
5293                         --  Prevents errors when No_Implicit_Heap_Allocations
5294                         --  is in force.
5295
5296                         Set_Comes_From_Source (Heap_Allocator, True);
5297                         Set_Comes_From_Source (Pool_Allocator, True);
5298                      end if;
5299
5300                      --  The allocator is returned on the secondary stack. We
5301                      --  don't do this on VM targets, since the SS is not used.
5302
5303                      if VM_Target = No_VM then
5304                         Set_Storage_Pool (SS_Allocator, RTE (RE_SS_Pool));
5305                         Set_Procedure_To_Call
5306                           (SS_Allocator, RTE (RE_SS_Allocate));
5307
5308                         --  The allocator is returned on the secondary stack,
5309                         --  so indicate that the function return, as well as
5310                         --  the block that encloses the allocator, must not
5311                         --  release it. The flags must be set now because
5312                         --  the decision to use the secondary stack is done
5313                         --  very late in the course of expanding the return
5314                         --  statement, past the point where these flags are
5315                         --  normally set.
5316
5317                         Set_Sec_Stack_Needed_For_Return (Par_Func);
5318                         Set_Sec_Stack_Needed_For_Return
5319                           (Return_Statement_Entity (N));
5320                         Set_Uses_Sec_Stack (Par_Func);
5321                         Set_Uses_Sec_Stack (Return_Statement_Entity (N));
5322                      end if;
5323
5324                      --  Create an if statement to test the BIP_Alloc_Form
5325                      --  formal and initialize the access object to either the
5326                      --  BIP_Object_Access formal (BIP_Alloc_Form =
5327                      --  Caller_Allocation), the result of allocating the
5328                      --  object in the secondary stack (BIP_Alloc_Form =
5329                      --  Secondary_Stack), or else an allocator to create the
5330                      --  return object in the heap or user-defined pool
5331                      --  (BIP_Alloc_Form = Global_Heap or User_Storage_Pool).
5332
5333                      --  ??? An unchecked type conversion must be made in the
5334                      --  case of assigning the access object formal to the
5335                      --  local access object, because a normal conversion would
5336                      --  be illegal in some cases (such as converting access-
5337                      --  to-unconstrained to access-to-constrained), but the
5338                      --  the unchecked conversion will presumably fail to work
5339                      --  right in just such cases. It's not clear at all how to
5340                      --  handle this. ???
5341
5342                      Alloc_If_Stmt :=
5343                        Make_If_Statement (Loc,
5344                          Condition =>
5345                            Make_Op_Eq (Loc,
5346                              Left_Opnd  =>
5347                                New_Reference_To (Obj_Alloc_Formal, Loc),
5348                              Right_Opnd =>
5349                                Make_Integer_Literal (Loc,
5350                                  UI_From_Int (BIP_Allocation_Form'Pos
5351                                                 (Caller_Allocation)))),
5352
5353                          Then_Statements => New_List (
5354                            Make_Assignment_Statement (Loc,
5355                              Name       =>
5356                                New_Reference_To (Alloc_Obj_Id, Loc),
5357                              Expression =>
5358                                Make_Unchecked_Type_Conversion (Loc,
5359                                  Subtype_Mark =>
5360                                    New_Reference_To (Ref_Type, Loc),
5361                                  Expression   =>
5362                                    New_Reference_To (Object_Access, Loc)))),
5363
5364                          Elsif_Parts => New_List (
5365                            Make_Elsif_Part (Loc,
5366                              Condition =>
5367                                Make_Op_Eq (Loc,
5368                                  Left_Opnd  =>
5369                                    New_Reference_To (Obj_Alloc_Formal, Loc),
5370                                  Right_Opnd =>
5371                                    Make_Integer_Literal (Loc,
5372                                      UI_From_Int (BIP_Allocation_Form'Pos
5373                                                     (Secondary_Stack)))),
5374
5375                              Then_Statements => New_List (
5376                                Make_Assignment_Statement (Loc,
5377                                  Name       =>
5378                                    New_Reference_To (Alloc_Obj_Id, Loc),
5379                                  Expression => SS_Allocator))),
5380
5381                            Make_Elsif_Part (Loc,
5382                              Condition =>
5383                                Make_Op_Eq (Loc,
5384                                  Left_Opnd  =>
5385                                    New_Reference_To (Obj_Alloc_Formal, Loc),
5386                                  Right_Opnd =>
5387                                    Make_Integer_Literal (Loc,
5388                                      UI_From_Int (BIP_Allocation_Form'Pos
5389                                                     (Global_Heap)))),
5390
5391                              Then_Statements => New_List (
5392                                Build_Heap_Allocator
5393                                  (Temp_Id    => Alloc_Obj_Id,
5394                                   Temp_Typ   => Ref_Type,
5395                                   Func_Id    => Par_Func,
5396                                   Ret_Typ    => Return_Obj_Typ,
5397                                   Alloc_Expr => Heap_Allocator)))),
5398
5399                          Else_Statements => New_List (
5400                            Pool_Decl,
5401                            Build_Heap_Allocator
5402                              (Temp_Id    => Alloc_Obj_Id,
5403                               Temp_Typ   => Ref_Type,
5404                               Func_Id    => Par_Func,
5405                               Ret_Typ    => Return_Obj_Typ,
5406                               Alloc_Expr => Pool_Allocator)));
5407
5408                      --  If a separate initialization assignment was created
5409                      --  earlier, append that following the assignment of the
5410                      --  implicit access formal to the access object, to ensure
5411                      --  that the return object is initialized in that case. In
5412                      --  this situation, the target of the assignment must be
5413                      --  rewritten to denote a dereference of the access to the
5414                      --  return object passed in by the caller.
5415
5416                      if Present (Init_Assignment) then
5417                         Rewrite (Name (Init_Assignment),
5418                           Make_Explicit_Dereference (Loc,
5419                             Prefix => New_Reference_To (Alloc_Obj_Id, Loc)));
5420
5421                         Set_Etype
5422                           (Name (Init_Assignment), Etype (Return_Obj_Id));
5423
5424                         Append_To
5425                           (Then_Statements (Alloc_If_Stmt), Init_Assignment);
5426                      end if;
5427
5428                      Insert_Before (Ret_Obj_Decl, Alloc_If_Stmt);
5429
5430                      --  Remember the local access object for use in the
5431                      --  dereference of the renaming created below.
5432
5433                      Object_Access := Alloc_Obj_Id;
5434                   end;
5435                end if;
5436
5437                --  Replace the return object declaration with a renaming of a
5438                --  dereference of the access value designating the return
5439                --  object.
5440
5441                Obj_Acc_Deref :=
5442                  Make_Explicit_Dereference (Loc,
5443                    Prefix => New_Reference_To (Object_Access, Loc));
5444
5445                Rewrite (Ret_Obj_Decl,
5446                  Make_Object_Renaming_Declaration (Loc,
5447                    Defining_Identifier => Return_Obj_Id,
5448                    Access_Definition   => Empty,
5449                    Subtype_Mark        =>
5450                      New_Occurrence_Of (Return_Obj_Typ, Loc),
5451                    Name                => Obj_Acc_Deref));
5452
5453                Set_Renamed_Object (Return_Obj_Id, Obj_Acc_Deref);
5454             end;
5455          end if;
5456
5457       --  Case where we do not build a block
5458
5459       else
5460          --  We're about to drop Return_Object_Declarations on the floor, so
5461          --  we need to insert it, in case it got expanded into useful code.
5462          --  Remove side effects from expression, which may be duplicated in
5463          --  subsequent checks (see Expand_Simple_Function_Return).
5464
5465          Insert_List_Before (N, Return_Object_Declarations (N));
5466          Remove_Side_Effects (Exp);
5467
5468          --  Build simple_return_statement that returns the expression directly
5469
5470          Return_Stmt := Make_Simple_Return_Statement (Loc, Expression => Exp);
5471          Result := Return_Stmt;
5472       end if;
5473
5474       --  Set the flag to prevent infinite recursion
5475
5476       Set_Comes_From_Extended_Return_Statement (Return_Stmt);
5477
5478       Rewrite (N, Result);
5479       Analyze (N);
5480    end Expand_N_Extended_Return_Statement;
5481
5482    ----------------------------
5483    -- Expand_N_Function_Call --
5484    ----------------------------
5485
5486    procedure Expand_N_Function_Call (N : Node_Id) is
5487    begin
5488       Expand_Call (N);
5489
5490       --  If the return value of a foreign compiled function is VAX Float, then
5491       --  expand the return (adjusts the location of the return value on
5492       --  Alpha/VMS, no-op everywhere else).
5493       --  Comes_From_Source intercepts recursive expansion.
5494
5495       if Vax_Float (Etype (N))
5496         and then Nkind (N) = N_Function_Call
5497         and then Present (Name (N))
5498         and then Present (Entity (Name (N)))
5499         and then Has_Foreign_Convention (Entity (Name (N)))
5500         and then Comes_From_Source (Parent (N))
5501       then
5502          Expand_Vax_Foreign_Return (N);
5503       end if;
5504    end Expand_N_Function_Call;
5505
5506    ---------------------------------------
5507    -- Expand_N_Procedure_Call_Statement --
5508    ---------------------------------------
5509
5510    procedure Expand_N_Procedure_Call_Statement (N : Node_Id) is
5511    begin
5512       Expand_Call (N);
5513    end Expand_N_Procedure_Call_Statement;
5514
5515    --------------------------------------
5516    -- Expand_N_Simple_Return_Statement --
5517    --------------------------------------
5518
5519    procedure Expand_N_Simple_Return_Statement (N : Node_Id) is
5520    begin
5521       --  Defend against previous errors (i.e. the return statement calls a
5522       --  function that is not available in configurable runtime).
5523
5524       if Present (Expression (N))
5525         and then Nkind (Expression (N)) = N_Empty
5526       then
5527          return;
5528       end if;
5529
5530       --  Distinguish the function and non-function cases:
5531
5532       case Ekind (Return_Applies_To (Return_Statement_Entity (N))) is
5533
5534          when E_Function          |
5535               E_Generic_Function  =>
5536             Expand_Simple_Function_Return (N);
5537
5538          when E_Procedure         |
5539               E_Generic_Procedure |
5540               E_Entry             |
5541               E_Entry_Family      |
5542               E_Return_Statement =>
5543             Expand_Non_Function_Return (N);
5544
5545          when others =>
5546             raise Program_Error;
5547       end case;
5548
5549    exception
5550       when RE_Not_Available =>
5551          return;
5552    end Expand_N_Simple_Return_Statement;
5553
5554    ------------------------------
5555    -- Expand_N_Subprogram_Body --
5556    ------------------------------
5557
5558    --  Add poll call if ATC polling is enabled, unless the body will be inlined
5559    --  by the back-end.
5560
5561    --  Add dummy push/pop label nodes at start and end to clear any local
5562    --  exception indications if local-exception-to-goto optimization is active.
5563
5564    --  Add return statement if last statement in body is not a return statement
5565    --  (this makes things easier on Gigi which does not want to have to handle
5566    --  a missing return).
5567
5568    --  Add call to Activate_Tasks if body is a task activator
5569
5570    --  Deal with possible detection of infinite recursion
5571
5572    --  Eliminate body completely if convention stubbed
5573
5574    --  Encode entity names within body, since we will not need to reference
5575    --  these entities any longer in the front end.
5576
5577    --  Initialize scalar out parameters if Initialize/Normalize_Scalars
5578
5579    --  Reset Pure indication if any parameter has root type System.Address
5580    --  or has any parameters of limited types, where limited means that the
5581    --  run-time view is limited (i.e. the full type is limited).
5582
5583    --  Wrap thread body
5584
5585    procedure Expand_N_Subprogram_Body (N : Node_Id) is
5586       Loc      : constant Source_Ptr := Sloc (N);
5587       H        : constant Node_Id    := Handled_Statement_Sequence (N);
5588       Body_Id  : Entity_Id;
5589       Except_H : Node_Id;
5590       L        : List_Id;
5591       Spec_Id  : Entity_Id;
5592
5593       procedure Add_Return (S : List_Id);
5594       --  Append a return statement to the statement sequence S if the last
5595       --  statement is not already a return or a goto statement. Note that
5596       --  the latter test is not critical, it does not matter if we add a few
5597       --  extra returns, since they get eliminated anyway later on.
5598
5599       ----------------
5600       -- Add_Return --
5601       ----------------
5602
5603       procedure Add_Return (S : List_Id) is
5604          Last_Stm : Node_Id;
5605          Loc      : Source_Ptr;
5606
5607       begin
5608          --  Get last statement, ignoring any Pop_xxx_Label nodes, which are
5609          --  not relevant in this context since they are not executable.
5610
5611          Last_Stm := Last (S);
5612          while Nkind (Last_Stm) in N_Pop_xxx_Label loop
5613             Prev (Last_Stm);
5614          end loop;
5615
5616          --  Now insert return unless last statement is a transfer
5617
5618          if not Is_Transfer (Last_Stm) then
5619
5620             --  The source location for the return is the end label of the
5621             --  procedure if present. Otherwise use the sloc of the last
5622             --  statement in the list. If the list comes from a generated
5623             --  exception handler and we are not debugging generated code,
5624             --  all the statements within the handler are made invisible
5625             --  to the debugger.
5626
5627             if Nkind (Parent (S)) = N_Exception_Handler
5628               and then not Comes_From_Source (Parent (S))
5629             then
5630                Loc := Sloc (Last_Stm);
5631             elsif Present (End_Label (H)) then
5632                Loc := Sloc (End_Label (H));
5633             else
5634                Loc := Sloc (Last_Stm);
5635             end if;
5636
5637             declare
5638                Rtn : constant Node_Id := Make_Simple_Return_Statement (Loc);
5639
5640             begin
5641                --  Append return statement, and set analyzed manually. We can't
5642                --  call Analyze on this return since the scope is wrong.
5643
5644                --  Note: it almost works to push the scope and then do the
5645                --  Analyze call, but something goes wrong in some weird cases
5646                --  and it is not worth worrying about ???
5647
5648                Append_To (S, Rtn);
5649                Set_Analyzed (Rtn);
5650
5651                --  Call _Postconditions procedure if appropriate. We need to
5652                --  do this explicitly because we did not analyze the generated
5653                --  return statement above, so the call did not get inserted.
5654
5655                if Ekind (Spec_Id) = E_Procedure
5656                  and then Has_Postconditions (Spec_Id)
5657                then
5658                   pragma Assert (Present (Postcondition_Proc (Spec_Id)));
5659                   Insert_Action (Rtn,
5660                     Make_Procedure_Call_Statement (Loc,
5661                       Name =>
5662                         New_Reference_To (Postcondition_Proc (Spec_Id), Loc)));
5663                end if;
5664             end;
5665          end if;
5666       end Add_Return;
5667
5668    --  Start of processing for Expand_N_Subprogram_Body
5669
5670    begin
5671       --  Set L to either the list of declarations if present, or to the list
5672       --  of statements if no declarations are present. This is used to insert
5673       --  new stuff at the start.
5674
5675       if Is_Non_Empty_List (Declarations (N)) then
5676          L := Declarations (N);
5677       else
5678          L := Statements (H);
5679       end if;
5680
5681       --  If local-exception-to-goto optimization active, insert dummy push
5682       --  statements at start, and dummy pop statements at end, but inhibit
5683       --  this if we have No_Exception_Handlers, since they are useless and
5684       --  intefere with analysis, e.g. by codepeer.
5685
5686       if (Debug_Flag_Dot_G
5687            or else Restriction_Active (No_Exception_Propagation))
5688         and then not Restriction_Active (No_Exception_Handlers)
5689         and then not CodePeer_Mode
5690         and then Is_Non_Empty_List (L)
5691       then
5692          declare
5693             FS  : constant Node_Id    := First (L);
5694             FL  : constant Source_Ptr := Sloc (FS);
5695             LS  : Node_Id;
5696             LL  : Source_Ptr;
5697
5698          begin
5699             --  LS points to either last statement, if statements are present
5700             --  or to the last declaration if there are no statements present.
5701             --  It is the node after which the pop's are generated.
5702
5703             if Is_Non_Empty_List (Statements (H)) then
5704                LS := Last (Statements (H));
5705             else
5706                LS := Last (L);
5707             end if;
5708
5709             LL := Sloc (LS);
5710
5711             Insert_List_Before_And_Analyze (FS, New_List (
5712               Make_Push_Constraint_Error_Label (FL),
5713               Make_Push_Program_Error_Label    (FL),
5714               Make_Push_Storage_Error_Label    (FL)));
5715
5716             Insert_List_After_And_Analyze (LS, New_List (
5717               Make_Pop_Constraint_Error_Label  (LL),
5718               Make_Pop_Program_Error_Label     (LL),
5719               Make_Pop_Storage_Error_Label     (LL)));
5720          end;
5721       end if;
5722
5723       --  Find entity for subprogram
5724
5725       Body_Id := Defining_Entity (N);
5726
5727       if Present (Corresponding_Spec (N)) then
5728          Spec_Id := Corresponding_Spec (N);
5729       else
5730          Spec_Id := Body_Id;
5731       end if;
5732
5733       --  Need poll on entry to subprogram if polling enabled. We only do this
5734       --  for non-empty subprograms, since it does not seem necessary to poll
5735       --  for a dummy null subprogram.
5736
5737       if Is_Non_Empty_List (L) then
5738
5739          --  Do not add a polling call if the subprogram is to be inlined by
5740          --  the back-end, to avoid repeated calls with multiple inlinings.
5741
5742          if Is_Inlined (Spec_Id)
5743            and then Front_End_Inlining
5744            and then Optimization_Level > 1
5745          then
5746             null;
5747          else
5748             Generate_Poll_Call (First (L));
5749          end if;
5750       end if;
5751
5752       --  If this is a Pure function which has any parameters whose root type
5753       --  is System.Address, reset the Pure indication, since it will likely
5754       --  cause incorrect code to be generated as the parameter is probably
5755       --  a pointer, and the fact that the same pointer is passed does not mean
5756       --  that the same value is being referenced.
5757
5758       --  Note that if the programmer gave an explicit Pure_Function pragma,
5759       --  then we believe the programmer, and leave the subprogram Pure.
5760
5761       --  This code should probably be at the freeze point, so that it happens
5762       --  even on a -gnatc (or more importantly -gnatt) compile, so that the
5763       --  semantic tree has Is_Pure set properly ???
5764
5765       if Is_Pure (Spec_Id)
5766         and then Is_Subprogram (Spec_Id)
5767         and then not Has_Pragma_Pure_Function (Spec_Id)
5768       then
5769          declare
5770             F : Entity_Id;
5771
5772          begin
5773             F := First_Formal (Spec_Id);
5774             while Present (F) loop
5775                if Is_Descendent_Of_Address (Etype (F))
5776
5777                  --  Note that this test is being made in the body of the
5778                  --  subprogram, not the spec, so we are testing the full
5779                  --  type for being limited here, as required.
5780
5781                  or else Is_Limited_Type (Etype (F))
5782                then
5783                   Set_Is_Pure (Spec_Id, False);
5784
5785                   if Spec_Id /= Body_Id then
5786                      Set_Is_Pure (Body_Id, False);
5787                   end if;
5788
5789                   exit;
5790                end if;
5791
5792                Next_Formal (F);
5793             end loop;
5794          end;
5795       end if;
5796
5797       --  Initialize any scalar OUT args if Initialize/Normalize_Scalars
5798
5799       if Init_Or_Norm_Scalars and then Is_Subprogram (Spec_Id) then
5800          declare
5801             F : Entity_Id;
5802
5803          begin
5804             --  Loop through formals
5805
5806             F := First_Formal (Spec_Id);
5807             while Present (F) loop
5808                if Is_Scalar_Type (Etype (F))
5809                  and then Ekind (F) = E_Out_Parameter
5810                then
5811                   Check_Restriction (No_Default_Initialization, F);
5812
5813                   --  Insert the initialization. We turn off validity checks
5814                   --  for this assignment, since we do not want any check on
5815                   --  the initial value itself (which may well be invalid).
5816
5817                   Insert_Before_And_Analyze (First (L),
5818                     Make_Assignment_Statement (Loc,
5819                       Name       => New_Occurrence_Of (F, Loc),
5820                       Expression => Get_Simple_Init_Val (Etype (F), N)),
5821                     Suppress => Validity_Check);
5822                end if;
5823
5824                Next_Formal (F);
5825             end loop;
5826          end;
5827       end if;
5828
5829       --  Clear out statement list for stubbed procedure
5830
5831       if Present (Corresponding_Spec (N)) then
5832          Set_Elaboration_Flag (N, Spec_Id);
5833
5834          if Convention (Spec_Id) = Convention_Stubbed
5835            or else Is_Eliminated (Spec_Id)
5836          then
5837             Set_Declarations (N, Empty_List);
5838             Set_Handled_Statement_Sequence (N,
5839               Make_Handled_Sequence_Of_Statements (Loc,
5840                 Statements => New_List (Make_Null_Statement (Loc))));
5841             return;
5842          end if;
5843       end if;
5844
5845       --  Create a set of discriminals for the next protected subprogram body
5846
5847       if Is_List_Member (N)
5848         and then Present (Parent (List_Containing (N)))
5849         and then Nkind (Parent (List_Containing (N))) = N_Protected_Body
5850         and then Present (Next_Protected_Operation (N))
5851       then
5852          Set_Discriminals (Parent (Base_Type (Scope (Spec_Id))));
5853       end if;
5854
5855       --  Returns_By_Ref flag is normally set when the subprogram is frozen but
5856       --  subprograms with no specs are not frozen.
5857
5858       declare
5859          Typ  : constant Entity_Id := Etype (Spec_Id);
5860          Utyp : constant Entity_Id := Underlying_Type (Typ);
5861
5862       begin
5863          if not Acts_As_Spec (N)
5864            and then Nkind (Parent (Parent (Spec_Id))) /=
5865              N_Subprogram_Body_Stub
5866          then
5867             null;
5868
5869          elsif Is_Immutably_Limited_Type (Typ) then
5870             Set_Returns_By_Ref (Spec_Id);
5871
5872          elsif Present (Utyp) and then CW_Or_Has_Controlled_Part (Utyp) then
5873             Set_Returns_By_Ref (Spec_Id);
5874          end if;
5875       end;
5876
5877       --  For a procedure, we add a return for all possible syntactic ends of
5878       --  the subprogram.
5879
5880       if Ekind_In (Spec_Id, E_Procedure, E_Generic_Procedure) then
5881          Add_Return (Statements (H));
5882
5883          if Present (Exception_Handlers (H)) then
5884             Except_H := First_Non_Pragma (Exception_Handlers (H));
5885             while Present (Except_H) loop
5886                Add_Return (Statements (Except_H));
5887                Next_Non_Pragma (Except_H);
5888             end loop;
5889          end if;
5890
5891       --  For a function, we must deal with the case where there is at least
5892       --  one missing return. What we do is to wrap the entire body of the
5893       --  function in a block:
5894
5895       --    begin
5896       --      ...
5897       --    end;
5898
5899       --  becomes
5900
5901       --    begin
5902       --       begin
5903       --          ...
5904       --       end;
5905
5906       --       raise Program_Error;
5907       --    end;
5908
5909       --  This approach is necessary because the raise must be signalled to the
5910       --  caller, not handled by any local handler (RM 6.4(11)).
5911
5912       --  Note: we do not need to analyze the constructed sequence here, since
5913       --  it has no handler, and an attempt to analyze the handled statement
5914       --  sequence twice is risky in various ways (e.g. the issue of expanding
5915       --  cleanup actions twice).
5916
5917       elsif Has_Missing_Return (Spec_Id) then
5918          declare
5919             Hloc : constant Source_Ptr := Sloc (H);
5920             Blok : constant Node_Id    :=
5921                      Make_Block_Statement (Hloc,
5922                        Handled_Statement_Sequence => H);
5923             Rais : constant Node_Id    :=
5924                      Make_Raise_Program_Error (Hloc,
5925                        Reason => PE_Missing_Return);
5926
5927          begin
5928             Set_Handled_Statement_Sequence (N,
5929               Make_Handled_Sequence_Of_Statements (Hloc,
5930                 Statements => New_List (Blok, Rais)));
5931
5932             Push_Scope (Spec_Id);
5933             Analyze (Blok);
5934             Analyze (Rais);
5935             Pop_Scope;
5936          end;
5937       end if;
5938
5939       --  If subprogram contains a parameterless recursive call, then we may
5940       --  have an infinite recursion, so see if we can generate code to check
5941       --  for this possibility if storage checks are not suppressed.
5942
5943       if Ekind (Spec_Id) = E_Procedure
5944         and then Has_Recursive_Call (Spec_Id)
5945         and then not Storage_Checks_Suppressed (Spec_Id)
5946       then
5947          Detect_Infinite_Recursion (N, Spec_Id);
5948       end if;
5949
5950       --  Set to encode entity names in package body before gigi is called
5951
5952       Qualify_Entity_Names (N);
5953    end Expand_N_Subprogram_Body;
5954
5955    -----------------------------------
5956    -- Expand_N_Subprogram_Body_Stub --
5957    -----------------------------------
5958
5959    procedure Expand_N_Subprogram_Body_Stub (N : Node_Id) is
5960    begin
5961       if Present (Corresponding_Body (N)) then
5962          Expand_N_Subprogram_Body (
5963            Unit_Declaration_Node (Corresponding_Body (N)));
5964       end if;
5965    end Expand_N_Subprogram_Body_Stub;
5966
5967    -------------------------------------
5968    -- Expand_N_Subprogram_Declaration --
5969    -------------------------------------
5970
5971    --  If the declaration appears within a protected body, it is a private
5972    --  operation of the protected type. We must create the corresponding
5973    --  protected subprogram an associated formals. For a normal protected
5974    --  operation, this is done when expanding the protected type declaration.
5975
5976    --  If the declaration is for a null procedure, emit null body
5977
5978    procedure Expand_N_Subprogram_Declaration (N : Node_Id) is
5979       Loc       : constant Source_Ptr := Sloc (N);
5980       Subp      : constant Entity_Id  := Defining_Entity (N);
5981       Scop      : constant Entity_Id  := Scope (Subp);
5982       Prot_Decl : Node_Id;
5983       Prot_Bod  : Node_Id;
5984       Prot_Id   : Entity_Id;
5985
5986    begin
5987       --  In SPARK, subprogram declarations are only allowed in package
5988       --  specifications.
5989
5990       if Nkind (Parent (N)) /= N_Package_Specification then
5991          if Nkind (Parent (N)) = N_Compilation_Unit then
5992             Check_SPARK_Restriction
5993               ("subprogram declaration is not a library item", N);
5994
5995          elsif Present (Next (N))
5996            and then Nkind (Next (N)) = N_Pragma
5997            and then Get_Pragma_Id (Pragma_Name (Next (N))) = Pragma_Import
5998          then
5999             --  In SPARK, subprogram declarations are also permitted in
6000             --  declarative parts when immediately followed by a corresponding
6001             --  pragma Import. We only check here that there is some pragma
6002             --  Import.
6003
6004             null;
6005          else
6006             Check_SPARK_Restriction
6007               ("subprogram declaration is not allowed here", N);
6008          end if;
6009       end if;
6010
6011       --  Deal with case of protected subprogram. Do not generate protected
6012       --  operation if operation is flagged as eliminated.
6013
6014       if Is_List_Member (N)
6015         and then Present (Parent (List_Containing (N)))
6016         and then Nkind (Parent (List_Containing (N))) = N_Protected_Body
6017         and then Is_Protected_Type (Scop)
6018       then
6019          if No (Protected_Body_Subprogram (Subp))
6020            and then not Is_Eliminated (Subp)
6021          then
6022             Prot_Decl :=
6023               Make_Subprogram_Declaration (Loc,
6024                 Specification =>
6025                   Build_Protected_Sub_Specification
6026                     (N, Scop, Unprotected_Mode));
6027
6028             --  The protected subprogram is declared outside of the protected
6029             --  body. Given that the body has frozen all entities so far, we
6030             --  analyze the subprogram and perform freezing actions explicitly.
6031             --  including the generation of an explicit freeze node, to ensure
6032             --  that gigi has the proper order of elaboration.
6033             --  If the body is a subunit, the insertion point is before the
6034             --  stub in the parent.
6035
6036             Prot_Bod := Parent (List_Containing (N));
6037
6038             if Nkind (Parent (Prot_Bod)) = N_Subunit then
6039                Prot_Bod := Corresponding_Stub (Parent (Prot_Bod));
6040             end if;
6041
6042             Insert_Before (Prot_Bod, Prot_Decl);
6043             Prot_Id := Defining_Unit_Name (Specification (Prot_Decl));
6044             Set_Has_Delayed_Freeze (Prot_Id);
6045
6046             Push_Scope (Scope (Scop));
6047             Analyze (Prot_Decl);
6048             Freeze_Before (N, Prot_Id);
6049             Set_Protected_Body_Subprogram (Subp, Prot_Id);
6050
6051             --  Create protected operation as well. Even though the operation
6052             --  is only accessible within the body, it is possible to make it
6053             --  available outside of the protected object by using 'Access to
6054             --  provide a callback, so build protected version in all cases.
6055
6056             Prot_Decl :=
6057               Make_Subprogram_Declaration (Loc,
6058                 Specification =>
6059                   Build_Protected_Sub_Specification (N, Scop, Protected_Mode));
6060             Insert_Before (Prot_Bod, Prot_Decl);
6061             Analyze (Prot_Decl);
6062
6063             Pop_Scope;
6064          end if;
6065
6066       --  Ada 2005 (AI-348): Generate body for a null procedure. In most
6067       --  cases this is superfluous because calls to it will be automatically
6068       --  inlined, but we definitely need the body if preconditions for the
6069       --  procedure are present.
6070
6071       elsif Nkind (Specification (N)) = N_Procedure_Specification
6072         and then Null_Present (Specification (N))
6073       then
6074          declare
6075             Bod : constant Node_Id := Body_To_Inline (N);
6076
6077          begin
6078             Set_Has_Completion (Subp, False);
6079             Append_Freeze_Action (Subp, Bod);
6080
6081             --  The body now contains raise statements, so calls to it will
6082             --  not be inlined.
6083
6084             Set_Is_Inlined (Subp, False);
6085          end;
6086       end if;
6087    end Expand_N_Subprogram_Declaration;
6088
6089    --------------------------------
6090    -- Expand_Non_Function_Return --
6091    --------------------------------
6092
6093    procedure Expand_Non_Function_Return (N : Node_Id) is
6094       pragma Assert (No (Expression (N)));
6095
6096       Loc         : constant Source_Ptr := Sloc (N);
6097       Scope_Id    : Entity_Id :=
6098                       Return_Applies_To (Return_Statement_Entity (N));
6099       Kind        : constant Entity_Kind := Ekind (Scope_Id);
6100       Call        : Node_Id;
6101       Acc_Stat    : Node_Id;
6102       Goto_Stat   : Node_Id;
6103       Lab_Node    : Node_Id;
6104
6105    begin
6106       --  Call _Postconditions procedure if procedure with active
6107       --  postconditions. Here, we use the Postcondition_Proc attribute,
6108       --  which is needed for implicitly-generated returns. Functions
6109       --  never have implicitly-generated returns, and there's no
6110       --  room for Postcondition_Proc in E_Function, so we look up the
6111       --  identifier Name_uPostconditions for function returns (see
6112       --  Expand_Simple_Function_Return).
6113
6114       if Ekind (Scope_Id) = E_Procedure
6115         and then Has_Postconditions (Scope_Id)
6116       then
6117          pragma Assert (Present (Postcondition_Proc (Scope_Id)));
6118          Insert_Action (N,
6119            Make_Procedure_Call_Statement (Loc,
6120              Name => New_Reference_To (Postcondition_Proc (Scope_Id), Loc)));
6121       end if;
6122
6123       --  If it is a return from a procedure do no extra steps
6124
6125       if Kind = E_Procedure or else Kind = E_Generic_Procedure then
6126          return;
6127
6128       --  If it is a nested return within an extended one, replace it with a
6129       --  return of the previously declared return object.
6130
6131       elsif Kind = E_Return_Statement then
6132          Rewrite (N,
6133            Make_Simple_Return_Statement (Loc,
6134              Expression =>
6135                New_Occurrence_Of (First_Entity (Scope_Id), Loc)));
6136          Set_Comes_From_Extended_Return_Statement (N);
6137          Set_Return_Statement_Entity (N, Scope_Id);
6138          Expand_Simple_Function_Return (N);
6139          return;
6140       end if;
6141
6142       pragma Assert (Is_Entry (Scope_Id));
6143
6144       --  Look at the enclosing block to see whether the return is from an
6145       --  accept statement or an entry body.
6146
6147       for J in reverse 0 .. Scope_Stack.Last loop
6148          Scope_Id := Scope_Stack.Table (J).Entity;
6149          exit when Is_Concurrent_Type (Scope_Id);
6150       end loop;
6151
6152       --  If it is a return from accept statement it is expanded as call to
6153       --  RTS Complete_Rendezvous and a goto to the end of the accept body.
6154
6155       --  (cf : Expand_N_Accept_Statement, Expand_N_Selective_Accept,
6156       --  Expand_N_Accept_Alternative in exp_ch9.adb)
6157
6158       if Is_Task_Type (Scope_Id) then
6159
6160          Call :=
6161            Make_Procedure_Call_Statement (Loc,
6162              Name => New_Reference_To (RTE (RE_Complete_Rendezvous), Loc));
6163          Insert_Before (N, Call);
6164          --  why not insert actions here???
6165          Analyze (Call);
6166
6167          Acc_Stat := Parent (N);
6168          while Nkind (Acc_Stat) /= N_Accept_Statement loop
6169             Acc_Stat := Parent (Acc_Stat);
6170          end loop;
6171
6172          Lab_Node := Last (Statements
6173            (Handled_Statement_Sequence (Acc_Stat)));
6174
6175          Goto_Stat := Make_Goto_Statement (Loc,
6176            Name => New_Occurrence_Of
6177              (Entity (Identifier (Lab_Node)), Loc));
6178
6179          Set_Analyzed (Goto_Stat);
6180
6181          Rewrite (N, Goto_Stat);
6182          Analyze (N);
6183
6184       --  If it is a return from an entry body, put a Complete_Entry_Body call
6185       --  in front of the return.
6186
6187       elsif Is_Protected_Type (Scope_Id) then
6188          Call :=
6189            Make_Procedure_Call_Statement (Loc,
6190              Name =>
6191                New_Reference_To (RTE (RE_Complete_Entry_Body), Loc),
6192              Parameter_Associations => New_List (
6193                Make_Attribute_Reference (Loc,
6194                  Prefix         =>
6195                    New_Reference_To
6196                      (Find_Protection_Object (Current_Scope), Loc),
6197                  Attribute_Name => Name_Unchecked_Access)));
6198
6199          Insert_Before (N, Call);
6200          Analyze (Call);
6201       end if;
6202    end Expand_Non_Function_Return;
6203
6204    ---------------------------------------
6205    -- Expand_Protected_Object_Reference --
6206    ---------------------------------------
6207
6208    function Expand_Protected_Object_Reference
6209      (N    : Node_Id;
6210       Scop : Entity_Id) return Node_Id
6211    is
6212       Loc   : constant Source_Ptr := Sloc (N);
6213       Corr  : Entity_Id;
6214       Rec   : Node_Id;
6215       Param : Entity_Id;
6216       Proc  : Entity_Id;
6217
6218    begin
6219       Rec := Make_Identifier (Loc, Name_uObject);
6220       Set_Etype (Rec, Corresponding_Record_Type (Scop));
6221
6222       --  Find enclosing protected operation, and retrieve its first parameter,
6223       --  which denotes the enclosing protected object. If the enclosing
6224       --  operation is an entry, we are immediately within the protected body,
6225       --  and we can retrieve the object from the service entries procedure. A
6226       --  barrier function has the same signature as an entry. A barrier
6227       --  function is compiled within the protected object, but unlike
6228       --  protected operations its never needs locks, so that its protected
6229       --  body subprogram points to itself.
6230
6231       Proc := Current_Scope;
6232       while Present (Proc)
6233         and then Scope (Proc) /= Scop
6234       loop
6235          Proc := Scope (Proc);
6236       end loop;
6237
6238       Corr := Protected_Body_Subprogram (Proc);
6239
6240       if No (Corr) then
6241
6242          --  Previous error left expansion incomplete.
6243          --  Nothing to do on this call.
6244
6245          return Empty;
6246       end if;
6247
6248       Param :=
6249         Defining_Identifier
6250           (First (Parameter_Specifications (Parent (Corr))));
6251
6252       if Is_Subprogram (Proc)
6253         and then Proc /= Corr
6254       then
6255          --  Protected function or procedure
6256
6257          Set_Entity (Rec, Param);
6258
6259          --  Rec is a reference to an entity which will not be in scope when
6260          --  the call is reanalyzed, and needs no further analysis.
6261
6262          Set_Analyzed (Rec);
6263
6264       else
6265          --  Entry or barrier function for entry body. The first parameter of
6266          --  the entry body procedure is pointer to the object. We create a
6267          --  local variable of the proper type, duplicating what is done to
6268          --  define _object later on.
6269
6270          declare
6271             Decls   : List_Id;
6272             Obj_Ptr : constant Entity_Id :=  Make_Temporary (Loc, 'T');
6273
6274          begin
6275             Decls := New_List (
6276               Make_Full_Type_Declaration (Loc,
6277                 Defining_Identifier => Obj_Ptr,
6278                   Type_Definition   =>
6279                      Make_Access_To_Object_Definition (Loc,
6280                        Subtype_Indication =>
6281                          New_Reference_To
6282                            (Corresponding_Record_Type (Scop), Loc))));
6283
6284             Insert_Actions (N, Decls);
6285             Freeze_Before (N, Obj_Ptr);
6286
6287             Rec :=
6288               Make_Explicit_Dereference (Loc,
6289                 Prefix =>
6290                   Unchecked_Convert_To (Obj_Ptr,
6291                     New_Occurrence_Of (Param, Loc)));
6292
6293             --  Analyze new actual. Other actuals in calls are already analyzed
6294             --  and the list of actuals is not reanalyzed after rewriting.
6295
6296             Set_Parent (Rec, N);
6297             Analyze (Rec);
6298          end;
6299       end if;
6300
6301       return Rec;
6302    end Expand_Protected_Object_Reference;
6303
6304    --------------------------------------
6305    -- Expand_Protected_Subprogram_Call --
6306    --------------------------------------
6307
6308    procedure Expand_Protected_Subprogram_Call
6309      (N    : Node_Id;
6310       Subp : Entity_Id;
6311       Scop : Entity_Id)
6312    is
6313       Rec   : Node_Id;
6314
6315    begin
6316       --  If the protected object is not an enclosing scope, this is an inter-
6317       --  object function call. Inter-object procedure calls are expanded by
6318       --  Exp_Ch9.Build_Simple_Entry_Call. The call is intra-object only if the
6319       --  subprogram being called is in the protected body being compiled, and
6320       --  if the protected object in the call is statically the enclosing type.
6321       --  The object may be an component of some other data structure, in which
6322       --  case this must be handled as an inter-object call.
6323
6324       if not In_Open_Scopes (Scop)
6325         or else not Is_Entity_Name (Name (N))
6326       then
6327          if Nkind (Name (N)) = N_Selected_Component then
6328             Rec := Prefix (Name (N));
6329
6330          else
6331             pragma Assert (Nkind (Name (N)) = N_Indexed_Component);
6332             Rec := Prefix (Prefix (Name (N)));
6333          end if;
6334
6335          Build_Protected_Subprogram_Call (N,
6336            Name     => New_Occurrence_Of (Subp, Sloc (N)),
6337            Rec      => Convert_Concurrent (Rec, Etype (Rec)),
6338            External => True);
6339
6340       else
6341          Rec := Expand_Protected_Object_Reference (N, Scop);
6342
6343          if No (Rec) then
6344             return;
6345          end if;
6346
6347          Build_Protected_Subprogram_Call (N,
6348            Name     => Name (N),
6349            Rec      => Rec,
6350            External => False);
6351
6352       end if;
6353
6354       --  If it is a function call it can appear in elaboration code and
6355       --  the called entity must be frozen here.
6356
6357       if Ekind (Subp) = E_Function then
6358          Freeze_Expression (Name (N));
6359       end if;
6360
6361       --  Analyze and resolve the new call. The actuals have already been
6362       --  resolved, but expansion of a function call will add extra actuals
6363       --  if needed. Analysis of a procedure call already includes resolution.
6364
6365       Analyze (N);
6366
6367       if Ekind (Subp) = E_Function then
6368          Resolve (N, Etype (Subp));
6369       end if;
6370    end Expand_Protected_Subprogram_Call;
6371
6372    --------------------------------------------
6373    -- Has_Unconstrained_Access_Discriminants --
6374    --------------------------------------------
6375
6376    function Has_Unconstrained_Access_Discriminants
6377      (Subtyp : Entity_Id) return Boolean
6378    is
6379       Discr : Entity_Id;
6380
6381    begin
6382       if Has_Discriminants (Subtyp)
6383         and then not Is_Constrained (Subtyp)
6384       then
6385          Discr := First_Discriminant (Subtyp);
6386          while Present (Discr) loop
6387             if Ekind (Etype (Discr)) = E_Anonymous_Access_Type then
6388                return True;
6389             end if;
6390
6391             Next_Discriminant (Discr);
6392          end loop;
6393       end if;
6394
6395       return False;
6396    end Has_Unconstrained_Access_Discriminants;
6397
6398    -----------------------------------
6399    -- Expand_Simple_Function_Return --
6400    -----------------------------------
6401
6402    --  The "simple" comes from the syntax rule simple_return_statement. The
6403    --  semantics are not at all simple!
6404
6405    procedure Expand_Simple_Function_Return (N : Node_Id) is
6406       Loc : constant Source_Ptr := Sloc (N);
6407
6408       Scope_Id : constant Entity_Id :=
6409                    Return_Applies_To (Return_Statement_Entity (N));
6410       --  The function we are returning from
6411
6412       R_Type : constant Entity_Id := Etype (Scope_Id);
6413       --  The result type of the function
6414
6415       Utyp : constant Entity_Id := Underlying_Type (R_Type);
6416
6417       Exp : constant Node_Id := Expression (N);
6418       pragma Assert (Present (Exp));
6419
6420       Exptyp : constant Entity_Id := Etype (Exp);
6421       --  The type of the expression (not necessarily the same as R_Type)
6422
6423       Subtype_Ind : Node_Id;
6424       --  If the result type of the function is class-wide and the expression
6425       --  has a specific type, then we use the expression's type as the type of
6426       --  the return object. In cases where the expression is an aggregate that
6427       --  is built in place, this avoids the need for an expensive conversion
6428       --  of the return object to the specific type on assignments to the
6429       --  individual components.
6430
6431    begin
6432       if Is_Class_Wide_Type (R_Type)
6433         and then not Is_Class_Wide_Type (Etype (Exp))
6434       then
6435          Subtype_Ind := New_Occurrence_Of (Etype (Exp), Loc);
6436       else
6437          Subtype_Ind := New_Occurrence_Of (R_Type, Loc);
6438       end if;
6439
6440       --  For the case of a simple return that does not come from an extended
6441       --  return, in the case of Ada 2005 where we are returning a limited
6442       --  type, we rewrite "return <expression>;" to be:
6443
6444       --    return _anon_ : <return_subtype> := <expression>
6445
6446       --  The expansion produced by Expand_N_Extended_Return_Statement will
6447       --  contain simple return statements (for example, a block containing
6448       --  simple return of the return object), which brings us back here with
6449       --  Comes_From_Extended_Return_Statement set. The reason for the barrier
6450       --  checking for a simple return that does not come from an extended
6451       --  return is to avoid this infinite recursion.
6452
6453       --  The reason for this design is that for Ada 2005 limited returns, we
6454       --  need to reify the return object, so we can build it "in place", and
6455       --  we need a block statement to hang finalization and tasking stuff.
6456
6457       --  ??? In order to avoid disruption, we avoid translating to extended
6458       --  return except in the cases where we really need to (Ada 2005 for
6459       --  inherently limited). We might prefer to do this translation in all
6460       --  cases (except perhaps for the case of Ada 95 inherently limited),
6461       --  in order to fully exercise the Expand_N_Extended_Return_Statement
6462       --  code. This would also allow us to do the build-in-place optimization
6463       --  for efficiency even in cases where it is semantically not required.
6464
6465       --  As before, we check the type of the return expression rather than the
6466       --  return type of the function, because the latter may be a limited
6467       --  class-wide interface type, which is not a limited type, even though
6468       --  the type of the expression may be.
6469
6470       if not Comes_From_Extended_Return_Statement (N)
6471         and then Is_Immutably_Limited_Type (Etype (Expression (N)))
6472         and then Ada_Version >= Ada_2005
6473         and then not Debug_Flag_Dot_L
6474       then
6475          declare
6476             Return_Object_Entity : constant Entity_Id :=
6477                                      Make_Temporary (Loc, 'R', Exp);
6478             Obj_Decl : constant Node_Id :=
6479                          Make_Object_Declaration (Loc,
6480                            Defining_Identifier => Return_Object_Entity,
6481                            Object_Definition   => Subtype_Ind,
6482                            Expression          => Exp);
6483
6484             Ext : constant Node_Id := Make_Extended_Return_Statement (Loc,
6485                     Return_Object_Declarations => New_List (Obj_Decl));
6486             --  Do not perform this high-level optimization if the result type
6487             --  is an interface because the "this" pointer must be displaced.
6488
6489          begin
6490             Rewrite (N, Ext);
6491             Analyze (N);
6492             return;
6493          end;
6494       end if;
6495
6496       --  Here we have a simple return statement that is part of the expansion
6497       --  of an extended return statement (either written by the user, or
6498       --  generated by the above code).
6499
6500       --  Always normalize C/Fortran boolean result. This is not always needed,
6501       --  but it seems a good idea to minimize the passing around of non-
6502       --  normalized values, and in any case this handles the processing of
6503       --  barrier functions for protected types, which turn the condition into
6504       --  a return statement.
6505
6506       if Is_Boolean_Type (Exptyp)
6507         and then Nonzero_Is_True (Exptyp)
6508       then
6509          Adjust_Condition (Exp);
6510          Adjust_Result_Type (Exp, Exptyp);
6511       end if;
6512
6513       --  Do validity check if enabled for returns
6514
6515       if Validity_Checks_On
6516         and then Validity_Check_Returns
6517       then
6518          Ensure_Valid (Exp);
6519       end if;
6520
6521       --  Check the result expression of a scalar function against the subtype
6522       --  of the function by inserting a conversion. This conversion must
6523       --  eventually be performed for other classes of types, but for now it's
6524       --  only done for scalars.
6525       --  ???
6526
6527       if Is_Scalar_Type (Exptyp) then
6528          Rewrite (Exp, Convert_To (R_Type, Exp));
6529
6530          --  The expression is resolved to ensure that the conversion gets
6531          --  expanded to generate a possible constraint check.
6532
6533          Analyze_And_Resolve (Exp, R_Type);
6534       end if;
6535
6536       --  Deal with returning variable length objects and controlled types
6537
6538       --  Nothing to do if we are returning by reference, or this is not a
6539       --  type that requires special processing (indicated by the fact that
6540       --  it requires a cleanup scope for the secondary stack case).
6541
6542       if Is_Immutably_Limited_Type (Exptyp)
6543         or else Is_Limited_Interface (Exptyp)
6544       then
6545          null;
6546
6547       elsif not Requires_Transient_Scope (R_Type) then
6548
6549          --  Mutable records with no variable length components are not
6550          --  returned on the sec-stack, so we need to make sure that the
6551          --  backend will only copy back the size of the actual value, and not
6552          --  the maximum size. We create an actual subtype for this purpose.
6553
6554          declare
6555             Ubt  : constant Entity_Id := Underlying_Type (Base_Type (Exptyp));
6556             Decl : Node_Id;
6557             Ent  : Entity_Id;
6558          begin
6559             if Has_Discriminants (Ubt)
6560               and then not Is_Constrained (Ubt)
6561               and then not Has_Unchecked_Union (Ubt)
6562             then
6563                Decl := Build_Actual_Subtype (Ubt, Exp);
6564                Ent := Defining_Identifier (Decl);
6565                Insert_Action (Exp, Decl);
6566                Rewrite (Exp, Unchecked_Convert_To (Ent, Exp));
6567                Analyze_And_Resolve (Exp);
6568             end if;
6569          end;
6570
6571       --  Here if secondary stack is used
6572
6573       else
6574          --  Make sure that no surrounding block will reclaim the secondary
6575          --  stack on which we are going to put the result. Not only may this
6576          --  introduce secondary stack leaks but worse, if the reclamation is
6577          --  done too early, then the result we are returning may get
6578          --  clobbered.
6579
6580          declare
6581             S : Entity_Id;
6582          begin
6583             S := Current_Scope;
6584             while Ekind (S) = E_Block or else Ekind (S) = E_Loop loop
6585                Set_Sec_Stack_Needed_For_Return (S, True);
6586                S := Enclosing_Dynamic_Scope (S);
6587             end loop;
6588          end;
6589
6590          --  Optimize the case where the result is a function call. In this
6591          --  case either the result is already on the secondary stack, or is
6592          --  already being returned with the stack pointer depressed and no
6593          --  further processing is required except to set the By_Ref flag
6594          --  to ensure that gigi does not attempt an extra unnecessary copy.
6595          --  (actually not just unnecessary but harmfully wrong in the case
6596          --  of a controlled type, where gigi does not know how to do a copy).
6597          --  To make up for a gcc 2.8.1 deficiency (???), we perform the copy
6598          --  for array types if the constrained status of the target type is
6599          --  different from that of the expression.
6600
6601          if Requires_Transient_Scope (Exptyp)
6602            and then
6603               (not Is_Array_Type (Exptyp)
6604                 or else Is_Constrained (Exptyp) = Is_Constrained (R_Type)
6605                 or else CW_Or_Has_Controlled_Part (Utyp))
6606            and then Nkind (Exp) = N_Function_Call
6607          then
6608             Set_By_Ref (N);
6609
6610             --  Remove side effects from the expression now so that other parts
6611             --  of the expander do not have to reanalyze this node without this
6612             --  optimization
6613
6614             Rewrite (Exp, Duplicate_Subexpr_No_Checks (Exp));
6615
6616          --  For controlled types, do the allocation on the secondary stack
6617          --  manually in order to call adjust at the right time:
6618
6619          --    type Anon1 is access R_Type;
6620          --    for Anon1'Storage_pool use ss_pool;
6621          --    Anon2 : anon1 := new R_Type'(expr);
6622          --    return Anon2.all;
6623
6624          --  We do the same for classwide types that are not potentially
6625          --  controlled (by the virtue of restriction No_Finalization) because
6626          --  gigi is not able to properly allocate class-wide types.
6627
6628          elsif CW_Or_Has_Controlled_Part (Utyp) then
6629             declare
6630                Loc        : constant Source_Ptr := Sloc (N);
6631                Acc_Typ    : constant Entity_Id := Make_Temporary (Loc, 'A');
6632                Alloc_Node : Node_Id;
6633                Temp       : Entity_Id;
6634
6635             begin
6636                Set_Ekind (Acc_Typ, E_Access_Type);
6637
6638                Set_Associated_Storage_Pool (Acc_Typ, RTE (RE_SS_Pool));
6639
6640                --  This is an allocator for the secondary stack, and it's fine
6641                --  to have Comes_From_Source set False on it, as gigi knows not
6642                --  to flag it as a violation of No_Implicit_Heap_Allocations.
6643
6644                Alloc_Node :=
6645                  Make_Allocator (Loc,
6646                    Expression =>
6647                      Make_Qualified_Expression (Loc,
6648                        Subtype_Mark => New_Reference_To (Etype (Exp), Loc),
6649                        Expression   => Relocate_Node (Exp)));
6650
6651                --  We do not want discriminant checks on the declaration,
6652                --  given that it gets its value from the allocator.
6653
6654                Set_No_Initialization (Alloc_Node);
6655
6656                Temp := Make_Temporary (Loc, 'R', Alloc_Node);
6657
6658                Insert_List_Before_And_Analyze (N, New_List (
6659                  Make_Full_Type_Declaration (Loc,
6660                    Defining_Identifier => Acc_Typ,
6661                    Type_Definition     =>
6662                      Make_Access_To_Object_Definition (Loc,
6663                        Subtype_Indication => Subtype_Ind)),
6664
6665                  Make_Object_Declaration (Loc,
6666                    Defining_Identifier => Temp,
6667                    Object_Definition   => New_Reference_To (Acc_Typ, Loc),
6668                    Expression          => Alloc_Node)));
6669
6670                Rewrite (Exp,
6671                  Make_Explicit_Dereference (Loc,
6672                  Prefix => New_Reference_To (Temp, Loc)));
6673
6674                Analyze_And_Resolve (Exp, R_Type);
6675             end;
6676
6677          --  Otherwise use the gigi mechanism to allocate result on the
6678          --  secondary stack.
6679
6680          else
6681             Check_Restriction (No_Secondary_Stack, N);
6682             Set_Storage_Pool (N, RTE (RE_SS_Pool));
6683
6684             --  If we are generating code for the VM do not use
6685             --  SS_Allocate since everything is heap-allocated anyway.
6686
6687             if VM_Target = No_VM then
6688                Set_Procedure_To_Call (N, RTE (RE_SS_Allocate));
6689             end if;
6690          end if;
6691       end if;
6692
6693       --  Implement the rules of 6.5(8-10), which require a tag check in
6694       --  the case of a limited tagged return type, and tag reassignment for
6695       --  nonlimited tagged results. These actions are needed when the return
6696       --  type is a specific tagged type and the result expression is a
6697       --  conversion or a formal parameter, because in that case the tag of
6698       --  the expression might differ from the tag of the specific result type.
6699
6700       if Is_Tagged_Type (Utyp)
6701         and then not Is_Class_Wide_Type (Utyp)
6702         and then (Nkind_In (Exp, N_Type_Conversion,
6703                                  N_Unchecked_Type_Conversion)
6704                     or else (Is_Entity_Name (Exp)
6705                                and then Ekind (Entity (Exp)) in Formal_Kind))
6706       then
6707          --  When the return type is limited, perform a check that the tag of
6708          --  the result is the same as the tag of the return type.
6709
6710          if Is_Limited_Type (R_Type) then
6711             Insert_Action (Exp,
6712               Make_Raise_Constraint_Error (Loc,
6713                 Condition =>
6714                   Make_Op_Ne (Loc,
6715                     Left_Opnd  =>
6716                       Make_Selected_Component (Loc,
6717                         Prefix        => Duplicate_Subexpr (Exp),
6718                         Selector_Name => Make_Identifier (Loc, Name_uTag)),
6719                     Right_Opnd =>
6720                       Make_Attribute_Reference (Loc,
6721                         Prefix         =>
6722                           New_Occurrence_Of (Base_Type (Utyp), Loc),
6723                         Attribute_Name => Name_Tag)),
6724                 Reason    => CE_Tag_Check_Failed));
6725
6726          --  If the result type is a specific nonlimited tagged type, then we
6727          --  have to ensure that the tag of the result is that of the result
6728          --  type. This is handled by making a copy of the expression in
6729          --  the case where it might have a different tag, namely when the
6730          --  expression is a conversion or a formal parameter. We create a new
6731          --  object of the result type and initialize it from the expression,
6732          --  which will implicitly force the tag to be set appropriately.
6733
6734          else
6735             declare
6736                ExpR       : constant Node_Id   := Relocate_Node (Exp);
6737                Result_Id  : constant Entity_Id :=
6738                               Make_Temporary (Loc, 'R', ExpR);
6739                Result_Exp : constant Node_Id   :=
6740                               New_Reference_To (Result_Id, Loc);
6741                Result_Obj : constant Node_Id   :=
6742                               Make_Object_Declaration (Loc,
6743                                 Defining_Identifier => Result_Id,
6744                                 Object_Definition   =>
6745                                   New_Reference_To (R_Type, Loc),
6746                                 Constant_Present    => True,
6747                                 Expression          => ExpR);
6748
6749             begin
6750                Set_Assignment_OK (Result_Obj);
6751                Insert_Action (Exp, Result_Obj);
6752
6753                Rewrite (Exp, Result_Exp);
6754                Analyze_And_Resolve (Exp, R_Type);
6755             end;
6756          end if;
6757
6758       --  Ada 2005 (AI-344): If the result type is class-wide, then insert
6759       --  a check that the level of the return expression's underlying type
6760       --  is not deeper than the level of the master enclosing the function.
6761       --  Always generate the check when the type of the return expression
6762       --  is class-wide, when it's a type conversion, or when it's a formal
6763       --  parameter. Otherwise, suppress the check in the case where the
6764       --  return expression has a specific type whose level is known not to
6765       --  be statically deeper than the function's result type.
6766
6767       --  Note: accessibility check is skipped in the VM case, since there
6768       --  does not seem to be any practical way to implement this check.
6769
6770       elsif Ada_Version >= Ada_2005
6771         and then Tagged_Type_Expansion
6772         and then Is_Class_Wide_Type (R_Type)
6773         and then not Scope_Suppress (Accessibility_Check)
6774         and then
6775           (Is_Class_Wide_Type (Etype (Exp))
6776             or else Nkind_In (Exp, N_Type_Conversion,
6777                                    N_Unchecked_Type_Conversion)
6778             or else (Is_Entity_Name (Exp)
6779                       and then Ekind (Entity (Exp)) in Formal_Kind)
6780             or else Scope_Depth (Enclosing_Dynamic_Scope (Etype (Exp))) >
6781                       Scope_Depth (Enclosing_Dynamic_Scope (Scope_Id)))
6782       then
6783          declare
6784             Tag_Node : Node_Id;
6785
6786          begin
6787             --  Ada 2005 (AI-251): In class-wide interface objects we displace
6788             --  "this" to reference the base of the object. This is required to
6789             --  get access to the TSD of the object.
6790
6791             if Is_Class_Wide_Type (Etype (Exp))
6792               and then Is_Interface (Etype (Exp))
6793               and then Nkind (Exp) = N_Explicit_Dereference
6794             then
6795                Tag_Node :=
6796                  Make_Explicit_Dereference (Loc,
6797                    Prefix =>
6798                      Unchecked_Convert_To (RTE (RE_Tag_Ptr),
6799                        Make_Function_Call (Loc,
6800                          Name                   =>
6801                            New_Reference_To (RTE (RE_Base_Address), Loc),
6802                          Parameter_Associations => New_List (
6803                            Unchecked_Convert_To (RTE (RE_Address),
6804                              Duplicate_Subexpr (Prefix (Exp)))))));
6805             else
6806                Tag_Node :=
6807                  Make_Attribute_Reference (Loc,
6808                    Prefix         => Duplicate_Subexpr (Exp),
6809                    Attribute_Name => Name_Tag);
6810             end if;
6811
6812             Insert_Action (Exp,
6813               Make_Raise_Program_Error (Loc,
6814                 Condition =>
6815                   Make_Op_Gt (Loc,
6816                     Left_Opnd  => Build_Get_Access_Level (Loc, Tag_Node),
6817                     Right_Opnd =>
6818                       Make_Integer_Literal (Loc,
6819                         Scope_Depth (Enclosing_Dynamic_Scope (Scope_Id)))),
6820                 Reason => PE_Accessibility_Check_Failed));
6821          end;
6822
6823       --  AI05-0073: If function has a controlling access result, check that
6824       --  the tag of the return value, if it is not null, matches designated
6825       --  type of return type.
6826       --  The return expression is referenced twice in the code below, so
6827       --  it must be made free of side effects. Given that different compilers
6828       --  may evaluate these parameters in different order, both occurrences
6829       --  perform a copy.
6830
6831       elsif Ekind (R_Type) = E_Anonymous_Access_Type
6832         and then Has_Controlling_Result (Scope_Id)
6833       then
6834          Insert_Action (N,
6835            Make_Raise_Constraint_Error (Loc,
6836              Condition =>
6837                Make_And_Then (Loc,
6838                  Left_Opnd  =>
6839                    Make_Op_Ne (Loc,
6840                      Left_Opnd  => Duplicate_Subexpr (Exp),
6841                      Right_Opnd => Make_Null (Loc)),
6842
6843                  Right_Opnd => Make_Op_Ne (Loc,
6844                    Left_Opnd  =>
6845                      Make_Selected_Component (Loc,
6846                        Prefix        => Duplicate_Subexpr (Exp),
6847                        Selector_Name => Make_Identifier (Loc, Name_uTag)),
6848
6849                    Right_Opnd =>
6850                      Make_Attribute_Reference (Loc,
6851                        Prefix         =>
6852                          New_Occurrence_Of (Designated_Type (R_Type), Loc),
6853                        Attribute_Name => Name_Tag))),
6854
6855              Reason    => CE_Tag_Check_Failed),
6856              Suppress  => All_Checks);
6857       end if;
6858
6859       --  AI05-0234: RM 6.5(21/3). Check access discriminants to
6860       --  ensure that the function result does not outlive an
6861       --  object designated by one of it discriminants.
6862
6863       if Present (Extra_Accessibility_Of_Result (Scope_Id))
6864         and then Has_Unconstrained_Access_Discriminants (R_Type)
6865       then
6866          declare
6867             Discrim_Source : Node_Id;
6868
6869             procedure Check_Against_Result_Level (Level : Node_Id);
6870             --  Check the given accessibility level against the level
6871             --  determined by the point of call. (AI05-0234).
6872
6873             --------------------------------
6874             -- Check_Against_Result_Level --
6875             --------------------------------
6876
6877             procedure Check_Against_Result_Level (Level : Node_Id) is
6878             begin
6879                Insert_Action (N,
6880                  Make_Raise_Program_Error (Loc,
6881                    Condition =>
6882                      Make_Op_Gt (Loc,
6883                        Left_Opnd  => Level,
6884                        Right_Opnd =>
6885                          New_Occurrence_Of
6886                            (Extra_Accessibility_Of_Result (Scope_Id), Loc)),
6887                        Reason => PE_Accessibility_Check_Failed));
6888             end Check_Against_Result_Level;
6889
6890          begin
6891             Discrim_Source := Exp;
6892             while Nkind (Discrim_Source) = N_Qualified_Expression loop
6893                Discrim_Source := Expression (Discrim_Source);
6894             end loop;
6895
6896             if Nkind (Discrim_Source) = N_Identifier
6897               and then Is_Return_Object (Entity (Discrim_Source))
6898             then
6899                Discrim_Source := Entity (Discrim_Source);
6900
6901                if Is_Constrained (Etype (Discrim_Source)) then
6902                   Discrim_Source := Etype (Discrim_Source);
6903                else
6904                   Discrim_Source := Expression (Parent (Discrim_Source));
6905                end if;
6906
6907             elsif Nkind (Discrim_Source) = N_Identifier
6908               and then Nkind_In (Original_Node (Discrim_Source),
6909                                  N_Aggregate, N_Extension_Aggregate)
6910             then
6911                Discrim_Source := Original_Node (Discrim_Source);
6912
6913             elsif Nkind (Discrim_Source) = N_Explicit_Dereference and then
6914               Nkind (Original_Node (Discrim_Source)) = N_Function_Call
6915             then
6916                Discrim_Source := Original_Node (Discrim_Source);
6917             end if;
6918
6919             while Nkind_In (Discrim_Source, N_Qualified_Expression,
6920                                             N_Type_Conversion,
6921                                             N_Unchecked_Type_Conversion)
6922             loop
6923                Discrim_Source := Expression (Discrim_Source);
6924             end loop;
6925
6926             case Nkind (Discrim_Source) is
6927                when N_Defining_Identifier =>
6928
6929                   pragma Assert (Is_Composite_Type (Discrim_Source)
6930                                   and then Has_Discriminants (Discrim_Source)
6931                                   and then Is_Constrained (Discrim_Source));
6932
6933                   declare
6934                      Discrim   : Entity_Id :=
6935                                    First_Discriminant (Base_Type (R_Type));
6936                      Disc_Elmt : Elmt_Id   :=
6937                                    First_Elmt (Discriminant_Constraint
6938                                                  (Discrim_Source));
6939                   begin
6940                      loop
6941                         if Ekind (Etype (Discrim)) =
6942                              E_Anonymous_Access_Type
6943                         then
6944                            Check_Against_Result_Level
6945                              (Dynamic_Accessibility_Level (Node (Disc_Elmt)));
6946                         end if;
6947
6948                         Next_Elmt (Disc_Elmt);
6949                         Next_Discriminant (Discrim);
6950                         exit when not Present (Discrim);
6951                      end loop;
6952                   end;
6953
6954                when N_Aggregate | N_Extension_Aggregate =>
6955
6956                   --  Unimplemented: extension aggregate case where discrims
6957                   --  come from ancestor part, not extension part.
6958
6959                   declare
6960                      Discrim  : Entity_Id :=
6961                                   First_Discriminant (Base_Type (R_Type));
6962
6963                      Disc_Exp : Node_Id   := Empty;
6964
6965                      Positionals_Exhausted
6966                               : Boolean   := not Present (Expressions
6967                                                             (Discrim_Source));
6968
6969                      function Associated_Expr
6970                        (Comp_Id : Entity_Id;
6971                         Associations : List_Id) return Node_Id;
6972
6973                      --  Given a component and a component associations list,
6974                      --  locate the expression for that component; returns
6975                      --  Empty if no such expression is found.
6976
6977                      ---------------------
6978                      -- Associated_Expr --
6979                      ---------------------
6980
6981                      function Associated_Expr
6982                        (Comp_Id : Entity_Id;
6983                         Associations : List_Id) return Node_Id
6984                      is
6985                         Assoc  : Node_Id;
6986                         Choice : Node_Id;
6987
6988                      begin
6989                         --  Simple linear search seems ok here
6990
6991                         Assoc := First (Associations);
6992                         while Present (Assoc) loop
6993                            Choice := First (Choices (Assoc));
6994                            while Present (Choice) loop
6995                               if (Nkind (Choice) = N_Identifier
6996                                    and then Chars (Choice) = Chars (Comp_Id))
6997                                 or else (Nkind (Choice) = N_Others_Choice)
6998                               then
6999                                  return Expression (Assoc);
7000                               end if;
7001
7002                               Next (Choice);
7003                            end loop;
7004
7005                            Next (Assoc);
7006                         end loop;
7007
7008                         return Empty;
7009                      end Associated_Expr;
7010
7011                   --  Start of processing for Expand_Simple_Function_Return
7012
7013                   begin
7014                      if not Positionals_Exhausted then
7015                         Disc_Exp := First (Expressions (Discrim_Source));
7016                      end if;
7017
7018                      loop
7019                         if Positionals_Exhausted then
7020                            Disc_Exp :=
7021                              Associated_Expr
7022                                (Discrim,
7023                                 Component_Associations (Discrim_Source));
7024                         end if;
7025
7026                         if Ekind (Etype (Discrim)) =
7027                              E_Anonymous_Access_Type
7028                         then
7029                            Check_Against_Result_Level
7030                              (Dynamic_Accessibility_Level (Disc_Exp));
7031                         end if;
7032
7033                         Next_Discriminant (Discrim);
7034                         exit when not Present (Discrim);
7035
7036                         if not Positionals_Exhausted then
7037                            Next (Disc_Exp);
7038                            Positionals_Exhausted := not Present (Disc_Exp);
7039                         end if;
7040                      end loop;
7041                   end;
7042
7043                when N_Function_Call =>
7044
7045                   --  No check needed (check performed by callee)
7046
7047                   null;
7048
7049                when others =>
7050
7051                   declare
7052                      Level : constant Node_Id :=
7053                                Make_Integer_Literal (Loc,
7054                                  Object_Access_Level (Discrim_Source));
7055
7056                   begin
7057                      --  Unimplemented: check for name prefix that includes
7058                      --  a dereference of an access value with a dynamic
7059                      --  accessibility level (e.g., an access param or a
7060                      --  saooaaat) and use dynamic level in that case. For
7061                      --  example:
7062                      --    return Access_Param.all(Some_Index).Some_Component;
7063                      --  ???
7064
7065                      Set_Etype (Level, Standard_Natural);
7066                      Check_Against_Result_Level (Level);
7067                   end;
7068
7069             end case;
7070          end;
7071       end if;
7072
7073       --  If we are returning an object that may not be bit-aligned, then copy
7074       --  the value into a temporary first. This copy may need to expand to a
7075       --  loop of component operations.
7076
7077       if Is_Possibly_Unaligned_Slice (Exp)
7078         or else Is_Possibly_Unaligned_Object (Exp)
7079       then
7080          declare
7081             ExpR : constant Node_Id   := Relocate_Node (Exp);
7082             Tnn  : constant Entity_Id := Make_Temporary (Loc, 'T', ExpR);
7083          begin
7084             Insert_Action (Exp,
7085               Make_Object_Declaration (Loc,
7086                 Defining_Identifier => Tnn,
7087                 Constant_Present    => True,
7088                 Object_Definition   => New_Occurrence_Of (R_Type, Loc),
7089                 Expression          => ExpR),
7090               Suppress => All_Checks);
7091             Rewrite (Exp, New_Occurrence_Of (Tnn, Loc));
7092          end;
7093       end if;
7094
7095       --  Generate call to postcondition checks if they are present
7096
7097       if Ekind (Scope_Id) = E_Function
7098         and then Has_Postconditions (Scope_Id)
7099       then
7100          --  We are going to reference the returned value twice in this case,
7101          --  once in the call to _Postconditions, and once in the actual return
7102          --  statement, but we can't have side effects happening twice, and in
7103          --  any case for efficiency we don't want to do the computation twice.
7104
7105          --  If the returned expression is an entity name, we don't need to
7106          --  worry since it is efficient and safe to reference it twice, that's
7107          --  also true for literals other than string literals, and for the
7108          --  case of X.all where X is an entity name.
7109
7110          if Is_Entity_Name (Exp)
7111            or else Nkind_In (Exp, N_Character_Literal,
7112                                   N_Integer_Literal,
7113                                   N_Real_Literal)
7114            or else (Nkind (Exp) = N_Explicit_Dereference
7115                      and then Is_Entity_Name (Prefix (Exp)))
7116          then
7117             null;
7118
7119          --  Otherwise we are going to need a temporary to capture the value
7120
7121          else
7122             declare
7123                ExpR : constant Node_Id   := Relocate_Node (Exp);
7124                Tnn  : constant Entity_Id := Make_Temporary (Loc, 'T', ExpR);
7125
7126             begin
7127                --  For a complex expression of an elementary type, capture
7128                --  value in the temporary and use it as the reference.
7129
7130                if Is_Elementary_Type (R_Type) then
7131                   Insert_Action (Exp,
7132                     Make_Object_Declaration (Loc,
7133                       Defining_Identifier => Tnn,
7134                       Constant_Present    => True,
7135                       Object_Definition   => New_Occurrence_Of (R_Type, Loc),
7136                       Expression          => ExpR),
7137                     Suppress => All_Checks);
7138
7139                   Rewrite (Exp, New_Occurrence_Of (Tnn, Loc));
7140
7141                --  If we have something we can rename, generate a renaming of
7142                --  the object and replace the expression with a reference
7143
7144                elsif Is_Object_Reference (Exp) then
7145                   Insert_Action (Exp,
7146                     Make_Object_Renaming_Declaration (Loc,
7147                       Defining_Identifier => Tnn,
7148                       Subtype_Mark        => New_Occurrence_Of (R_Type, Loc),
7149                       Name                => ExpR),
7150                     Suppress => All_Checks);
7151
7152                   Rewrite (Exp, New_Occurrence_Of (Tnn, Loc));
7153
7154                --  Otherwise we have something like a string literal or an
7155                --  aggregate. We could copy the value, but that would be
7156                --  inefficient. Instead we make a reference to the value and
7157                --  capture this reference with a renaming, the expression is
7158                --  then replaced by a dereference of this renaming.
7159
7160                else
7161                   --  For now, copy the value, since the code below does not
7162                   --  seem to work correctly ???
7163
7164                   Insert_Action (Exp,
7165                     Make_Object_Declaration (Loc,
7166                       Defining_Identifier => Tnn,
7167                       Constant_Present    => True,
7168                       Object_Definition   => New_Occurrence_Of (R_Type, Loc),
7169                       Expression          => Relocate_Node (Exp)),
7170                     Suppress => All_Checks);
7171
7172                   Rewrite (Exp, New_Occurrence_Of (Tnn, Loc));
7173
7174                   --  Insert_Action (Exp,
7175                   --    Make_Object_Renaming_Declaration (Loc,
7176                   --      Defining_Identifier => Tnn,
7177                   --      Access_Definition =>
7178                   --        Make_Access_Definition (Loc,
7179                   --          All_Present  => True,
7180                   --          Subtype_Mark => New_Occurrence_Of (R_Type, Loc)),
7181                   --      Name =>
7182                   --        Make_Reference (Loc,
7183                   --          Prefix => Relocate_Node (Exp))),
7184                   --    Suppress => All_Checks);
7185
7186                   --  Rewrite (Exp,
7187                   --    Make_Explicit_Dereference (Loc,
7188                   --      Prefix => New_Occurrence_Of (Tnn, Loc)));
7189                end if;
7190             end;
7191          end if;
7192
7193          --  Generate call to _postconditions
7194
7195          Insert_Action (Exp,
7196            Make_Procedure_Call_Statement (Loc,
7197              Name => Make_Identifier (Loc, Name_uPostconditions),
7198              Parameter_Associations => New_List (Duplicate_Subexpr (Exp))));
7199       end if;
7200
7201       --  Ada 2005 (AI-251): If this return statement corresponds with an
7202       --  simple return statement associated with an extended return statement
7203       --  and the type of the returned object is an interface then generate an
7204       --  implicit conversion to force displacement of the "this" pointer.
7205
7206       if Ada_Version >= Ada_2005
7207         and then Comes_From_Extended_Return_Statement (N)
7208         and then Nkind (Expression (N)) = N_Identifier
7209         and then Is_Interface (Utyp)
7210         and then Utyp /= Underlying_Type (Exptyp)
7211       then
7212          Rewrite (Exp, Convert_To (Utyp, Relocate_Node (Exp)));
7213          Analyze_And_Resolve (Exp);
7214       end if;
7215    end Expand_Simple_Function_Return;
7216
7217    --------------------------------
7218    -- Is_Build_In_Place_Function --
7219    --------------------------------
7220
7221    function Is_Build_In_Place_Function (E : Entity_Id) return Boolean is
7222    begin
7223       --  This function is called from Expand_Subtype_From_Expr during
7224       --  semantic analysis, even when expansion is off. In those cases
7225       --  the build_in_place expansion will not take place.
7226
7227       if not Expander_Active then
7228          return False;
7229       end if;
7230
7231       --  For now we test whether E denotes a function or access-to-function
7232       --  type whose result subtype is inherently limited. Later this test may
7233       --  be revised to allow composite nonlimited types. Functions with a
7234       --  foreign convention or whose result type has a foreign convention
7235       --  never qualify.
7236
7237       if Ekind_In (E, E_Function, E_Generic_Function)
7238         or else (Ekind (E) = E_Subprogram_Type
7239                   and then Etype (E) /= Standard_Void_Type)
7240       then
7241          --  Note: If you have Convention (C) on an inherently limited type,
7242          --  you're on your own. That is, the C code will have to be carefully
7243          --  written to know about the Ada conventions.
7244
7245          if Has_Foreign_Convention (E)
7246            or else Has_Foreign_Convention (Etype (E))
7247          then
7248             return False;
7249
7250          --  In Ada 2005 all functions with an inherently limited return type
7251          --  must be handled using a build-in-place profile, including the case
7252          --  of a function with a limited interface result, where the function
7253          --  may return objects of nonlimited descendants.
7254
7255          else
7256             return Is_Immutably_Limited_Type (Etype (E))
7257               and then Ada_Version >= Ada_2005
7258               and then not Debug_Flag_Dot_L;
7259          end if;
7260
7261       else
7262          return False;
7263       end if;
7264    end Is_Build_In_Place_Function;
7265
7266    -------------------------------------
7267    -- Is_Build_In_Place_Function_Call --
7268    -------------------------------------
7269
7270    function Is_Build_In_Place_Function_Call (N : Node_Id) return Boolean is
7271       Exp_Node    : Node_Id := N;
7272       Function_Id : Entity_Id;
7273
7274    begin
7275       --  Return False when the expander is inactive, since awareness of
7276       --  build-in-place treatment is only relevant during expansion. Note that
7277       --  Is_Build_In_Place_Function, which is called as part of this function,
7278       --  is also conditioned this way, but we need to check here as well to
7279       --  avoid blowing up on processing protected calls when expansion is
7280       --  disabled (such as with -gnatc) since those would trip over the raise
7281       --  of Program_Error below.
7282
7283       if not Expander_Active then
7284          return False;
7285       end if;
7286
7287       --  Step past qualification or unchecked conversion (the latter can occur
7288       --  in cases of calls to 'Input).
7289
7290       if Nkind_In (Exp_Node, N_Qualified_Expression,
7291                              N_Unchecked_Type_Conversion)
7292       then
7293          Exp_Node := Expression (N);
7294       end if;
7295
7296       if Nkind (Exp_Node) /= N_Function_Call then
7297          return False;
7298
7299       else
7300          --  In Alfa mode, build-in-place calls are not expanded, so that we
7301          --  may end up with a call that is neither resolved to an entity, nor
7302          --  an indirect call.
7303
7304          if Alfa_Mode then
7305             return False;
7306
7307          elsif Is_Entity_Name (Name (Exp_Node)) then
7308             Function_Id := Entity (Name (Exp_Node));
7309
7310          --  In the case of an explicitly dereferenced call, use the subprogram
7311          --  type generated for the dereference.
7312
7313          elsif Nkind (Name (Exp_Node)) = N_Explicit_Dereference then
7314             Function_Id := Etype (Name (Exp_Node));
7315
7316          else
7317             raise Program_Error;
7318          end if;
7319
7320          return Is_Build_In_Place_Function (Function_Id);
7321       end if;
7322    end Is_Build_In_Place_Function_Call;
7323
7324    -----------------------
7325    -- Freeze_Subprogram --
7326    -----------------------
7327
7328    procedure Freeze_Subprogram (N : Node_Id) is
7329       Loc : constant Source_Ptr := Sloc (N);
7330
7331       procedure Register_Predefined_DT_Entry (Prim : Entity_Id);
7332       --  (Ada 2005): Register a predefined primitive in all the secondary
7333       --  dispatch tables of its primitive type.
7334
7335       ----------------------------------
7336       -- Register_Predefined_DT_Entry --
7337       ----------------------------------
7338
7339       procedure Register_Predefined_DT_Entry (Prim : Entity_Id) is
7340          Iface_DT_Ptr : Elmt_Id;
7341          Tagged_Typ   : Entity_Id;
7342          Thunk_Id     : Entity_Id;
7343          Thunk_Code   : Node_Id;
7344
7345       begin
7346          Tagged_Typ := Find_Dispatching_Type (Prim);
7347
7348          if No (Access_Disp_Table (Tagged_Typ))
7349            or else not Has_Interfaces (Tagged_Typ)
7350            or else not RTE_Available (RE_Interface_Tag)
7351            or else Restriction_Active (No_Dispatching_Calls)
7352          then
7353             return;
7354          end if;
7355
7356          --  Skip the first two access-to-dispatch-table pointers since they
7357          --  leads to the primary dispatch table (predefined DT and user
7358          --  defined DT). We are only concerned with the secondary dispatch
7359          --  table pointers. Note that the access-to- dispatch-table pointer
7360          --  corresponds to the first implemented interface retrieved below.
7361
7362          Iface_DT_Ptr :=
7363            Next_Elmt (Next_Elmt (First_Elmt (Access_Disp_Table (Tagged_Typ))));
7364
7365          while Present (Iface_DT_Ptr)
7366            and then Ekind (Node (Iface_DT_Ptr)) = E_Constant
7367          loop
7368             pragma Assert (Has_Thunks (Node (Iface_DT_Ptr)));
7369             Expand_Interface_Thunk (Prim, Thunk_Id, Thunk_Code);
7370
7371             if Present (Thunk_Code) then
7372                Insert_Actions_After (N, New_List (
7373                  Thunk_Code,
7374
7375                  Build_Set_Predefined_Prim_Op_Address (Loc,
7376                    Tag_Node     =>
7377                      New_Reference_To (Node (Next_Elmt (Iface_DT_Ptr)), Loc),
7378                    Position     => DT_Position (Prim),
7379                    Address_Node =>
7380                      Unchecked_Convert_To (RTE (RE_Prim_Ptr),
7381                        Make_Attribute_Reference (Loc,
7382                          Prefix         => New_Reference_To (Thunk_Id, Loc),
7383                          Attribute_Name => Name_Unrestricted_Access))),
7384
7385                  Build_Set_Predefined_Prim_Op_Address (Loc,
7386                    Tag_Node     =>
7387                      New_Reference_To
7388                       (Node (Next_Elmt (Next_Elmt (Next_Elmt (Iface_DT_Ptr)))),
7389                        Loc),
7390                    Position     => DT_Position (Prim),
7391                    Address_Node =>
7392                      Unchecked_Convert_To (RTE (RE_Prim_Ptr),
7393                        Make_Attribute_Reference (Loc,
7394                          Prefix         => New_Reference_To (Prim, Loc),
7395                          Attribute_Name => Name_Unrestricted_Access)))));
7396             end if;
7397
7398             --  Skip the tag of the predefined primitives dispatch table
7399
7400             Next_Elmt (Iface_DT_Ptr);
7401             pragma Assert (Has_Thunks (Node (Iface_DT_Ptr)));
7402
7403             --  Skip tag of the no-thunks dispatch table
7404
7405             Next_Elmt (Iface_DT_Ptr);
7406             pragma Assert (not Has_Thunks (Node (Iface_DT_Ptr)));
7407
7408             --  Skip tag of predefined primitives no-thunks dispatch table
7409
7410             Next_Elmt (Iface_DT_Ptr);
7411             pragma Assert (not Has_Thunks (Node (Iface_DT_Ptr)));
7412
7413             Next_Elmt (Iface_DT_Ptr);
7414          end loop;
7415       end Register_Predefined_DT_Entry;
7416
7417       --  Local variables
7418
7419       Subp : constant Entity_Id  := Entity (N);
7420
7421    --  Start of processing for Freeze_Subprogram
7422
7423    begin
7424       --  We suppress the initialization of the dispatch table entry when
7425       --  VM_Target because the dispatching mechanism is handled internally
7426       --  by the VM.
7427
7428       if Is_Dispatching_Operation (Subp)
7429         and then not Is_Abstract_Subprogram (Subp)
7430         and then Present (DTC_Entity (Subp))
7431         and then Present (Scope (DTC_Entity (Subp)))
7432         and then Tagged_Type_Expansion
7433         and then not Restriction_Active (No_Dispatching_Calls)
7434         and then RTE_Available (RE_Tag)
7435       then
7436          declare
7437             Typ : constant Entity_Id := Scope (DTC_Entity (Subp));
7438
7439          begin
7440             --  Handle private overridden primitives
7441
7442             if not Is_CPP_Class (Typ) then
7443                Check_Overriding_Operation (Subp);
7444             end if;
7445
7446             --  We assume that imported CPP primitives correspond with objects
7447             --  whose constructor is in the CPP side; therefore we don't need
7448             --  to generate code to register them in the dispatch table.
7449
7450             if Is_CPP_Class (Typ) then
7451                null;
7452
7453             --  Handle CPP primitives found in derivations of CPP_Class types.
7454             --  These primitives must have been inherited from some parent, and
7455             --  there is no need to register them in the dispatch table because
7456             --  Build_Inherit_Prims takes care of the initialization of these
7457             --  slots.
7458
7459             elsif Is_Imported (Subp)
7460                and then (Convention (Subp) = Convention_CPP
7461                            or else Convention (Subp) = Convention_C)
7462             then
7463                null;
7464
7465             --  Generate code to register the primitive in non statically
7466             --  allocated dispatch tables
7467
7468             elsif not Building_Static_DT (Scope (DTC_Entity (Subp))) then
7469
7470                --  When a primitive is frozen, enter its name in its dispatch
7471                --  table slot.
7472
7473                if not Is_Interface (Typ)
7474                  or else Present (Interface_Alias (Subp))
7475                then
7476                   if Is_Predefined_Dispatching_Operation (Subp) then
7477                      Register_Predefined_DT_Entry (Subp);
7478                   end if;
7479
7480                   Insert_Actions_After (N,
7481                     Register_Primitive (Loc, Prim => Subp));
7482                end if;
7483             end if;
7484          end;
7485       end if;
7486
7487       --  Mark functions that return by reference. Note that it cannot be part
7488       --  of the normal semantic analysis of the spec since the underlying
7489       --  returned type may not be known yet (for private types).
7490
7491       declare
7492          Typ  : constant Entity_Id := Etype (Subp);
7493          Utyp : constant Entity_Id := Underlying_Type (Typ);
7494       begin
7495          if Is_Immutably_Limited_Type (Typ) then
7496             Set_Returns_By_Ref (Subp);
7497          elsif Present (Utyp) and then CW_Or_Has_Controlled_Part (Utyp) then
7498             Set_Returns_By_Ref (Subp);
7499          end if;
7500       end;
7501    end Freeze_Subprogram;
7502
7503    -----------------------
7504    -- Is_Null_Procedure --
7505    -----------------------
7506
7507    function Is_Null_Procedure (Subp : Entity_Id) return Boolean is
7508       Decl : constant Node_Id := Unit_Declaration_Node (Subp);
7509
7510    begin
7511       if Ekind (Subp) /= E_Procedure then
7512          return False;
7513
7514       --  Check if this is a declared null procedure
7515
7516       elsif Nkind (Decl) = N_Subprogram_Declaration then
7517          if not Null_Present (Specification (Decl)) then
7518             return False;
7519
7520          elsif No (Body_To_Inline (Decl)) then
7521             return False;
7522
7523          --  Check if the body contains only a null statement, followed by
7524          --  the return statement added during expansion.
7525
7526          else
7527             declare
7528                Orig_Bod : constant Node_Id := Body_To_Inline (Decl);
7529
7530                Stat  : Node_Id;
7531                Stat2 : Node_Id;
7532
7533             begin
7534                if Nkind (Orig_Bod) /= N_Subprogram_Body then
7535                   return False;
7536                else
7537                   --  We must skip SCIL nodes because they are currently
7538                   --  implemented as special N_Null_Statement nodes.
7539
7540                   Stat :=
7541                      First_Non_SCIL_Node
7542                        (Statements (Handled_Statement_Sequence (Orig_Bod)));
7543                   Stat2 := Next_Non_SCIL_Node (Stat);
7544
7545                   return
7546                      Is_Empty_List (Declarations (Orig_Bod))
7547                        and then Nkind (Stat) = N_Null_Statement
7548                        and then
7549                         (No (Stat2)
7550                           or else
7551                             (Nkind (Stat2) = N_Simple_Return_Statement
7552                               and then No (Next (Stat2))));
7553                end if;
7554             end;
7555          end if;
7556
7557       else
7558          return False;
7559       end if;
7560    end Is_Null_Procedure;
7561
7562    -------------------------------------------
7563    -- Make_Build_In_Place_Call_In_Allocator --
7564    -------------------------------------------
7565
7566    procedure Make_Build_In_Place_Call_In_Allocator
7567      (Allocator     : Node_Id;
7568       Function_Call : Node_Id)
7569    is
7570       Acc_Type          : constant Entity_Id := Etype (Allocator);
7571       Loc               : Source_Ptr;
7572       Func_Call         : Node_Id := Function_Call;
7573       Function_Id       : Entity_Id;
7574       Result_Subt       : Entity_Id;
7575       New_Allocator     : Node_Id;
7576       Return_Obj_Access : Entity_Id;
7577
7578    begin
7579       --  Step past qualification or unchecked conversion (the latter can occur
7580       --  in cases of calls to 'Input).
7581
7582       if Nkind_In (Func_Call,
7583                    N_Qualified_Expression,
7584                    N_Unchecked_Type_Conversion)
7585       then
7586          Func_Call := Expression (Func_Call);
7587       end if;
7588
7589       --  If the call has already been processed to add build-in-place actuals
7590       --  then return. This should not normally occur in an allocator context,
7591       --  but we add the protection as a defensive measure.
7592
7593       if Is_Expanded_Build_In_Place_Call (Func_Call) then
7594          return;
7595       end if;
7596
7597       --  Mark the call as processed as a build-in-place call
7598
7599       Set_Is_Expanded_Build_In_Place_Call (Func_Call);
7600
7601       Loc := Sloc (Function_Call);
7602
7603       if Is_Entity_Name (Name (Func_Call)) then
7604          Function_Id := Entity (Name (Func_Call));
7605
7606       elsif Nkind (Name (Func_Call)) = N_Explicit_Dereference then
7607          Function_Id := Etype (Name (Func_Call));
7608
7609       else
7610          raise Program_Error;
7611       end if;
7612
7613       Result_Subt := Available_View (Etype (Function_Id));
7614
7615       --  Check whether return type includes tasks. This may not have been done
7616       --  previously, if the type was a limited view.
7617
7618       if Has_Task (Result_Subt) then
7619          Build_Activation_Chain_Entity (Allocator);
7620       end if;
7621
7622       --  When the result subtype is constrained, the return object must be
7623       --  allocated on the caller side, and access to it is passed to the
7624       --  function.
7625
7626       --  Here and in related routines, we must examine the full view of the
7627       --  type, because the view at the point of call may differ from that
7628       --  that in the function body, and the expansion mechanism depends on
7629       --  the characteristics of the full view.
7630
7631       if Is_Constrained (Underlying_Type (Result_Subt)) then
7632
7633          --  Replace the initialized allocator of form "new T'(Func (...))"
7634          --  with an uninitialized allocator of form "new T", where T is the
7635          --  result subtype of the called function. The call to the function
7636          --  is handled separately further below.
7637
7638          New_Allocator :=
7639            Make_Allocator (Loc,
7640              Expression => New_Reference_To (Result_Subt, Loc));
7641          Set_No_Initialization (New_Allocator);
7642
7643          --  Copy attributes to new allocator. Note that the new allocator
7644          --  logically comes from source if the original one did, so copy the
7645          --  relevant flag. This ensures proper treatment of the restriction
7646          --  No_Implicit_Heap_Allocations in this case.
7647
7648          Set_Storage_Pool      (New_Allocator, Storage_Pool      (Allocator));
7649          Set_Procedure_To_Call (New_Allocator, Procedure_To_Call (Allocator));
7650          Set_Comes_From_Source (New_Allocator, Comes_From_Source (Allocator));
7651
7652          Rewrite (Allocator, New_Allocator);
7653
7654          --  Create a new access object and initialize it to the result of the
7655          --  new uninitialized allocator. Note: we do not use Allocator as the
7656          --  Related_Node of Return_Obj_Access in call to Make_Temporary below
7657          --  as this would create a sort of infinite "recursion".
7658
7659          Return_Obj_Access := Make_Temporary (Loc, 'R');
7660          Set_Etype (Return_Obj_Access, Acc_Type);
7661
7662          Insert_Action (Allocator,
7663            Make_Object_Declaration (Loc,
7664              Defining_Identifier => Return_Obj_Access,
7665              Object_Definition   => New_Reference_To (Acc_Type, Loc),
7666              Expression          => Relocate_Node (Allocator)));
7667
7668          --  When the function has a controlling result, an allocation-form
7669          --  parameter must be passed indicating that the caller is allocating
7670          --  the result object. This is needed because such a function can be
7671          --  called as a dispatching operation and must be treated similarly
7672          --  to functions with unconstrained result subtypes.
7673
7674          Add_Unconstrained_Actuals_To_Build_In_Place_Call
7675            (Func_Call, Function_Id, Alloc_Form => Caller_Allocation);
7676
7677          Add_Finalization_Master_Actual_To_Build_In_Place_Call
7678            (Func_Call, Function_Id, Acc_Type);
7679
7680          Add_Task_Actuals_To_Build_In_Place_Call
7681            (Func_Call, Function_Id, Master_Actual => Master_Id (Acc_Type));
7682
7683          --  Add an implicit actual to the function call that provides access
7684          --  to the allocated object. An unchecked conversion to the (specific)
7685          --  result subtype of the function is inserted to handle cases where
7686          --  the access type of the allocator has a class-wide designated type.
7687
7688          Add_Access_Actual_To_Build_In_Place_Call
7689            (Func_Call,
7690             Function_Id,
7691             Make_Unchecked_Type_Conversion (Loc,
7692               Subtype_Mark => New_Reference_To (Result_Subt, Loc),
7693               Expression   =>
7694                 Make_Explicit_Dereference (Loc,
7695                   Prefix => New_Reference_To (Return_Obj_Access, Loc))));
7696
7697       --  When the result subtype is unconstrained, the function itself must
7698       --  perform the allocation of the return object, so we pass parameters
7699       --  indicating that. We don't yet handle the case where the allocation
7700       --  must be done in a user-defined storage pool, which will require
7701       --  passing another actual or two to provide allocation/deallocation
7702       --  operations. ???
7703
7704       else
7705          --  Case of a user-defined storage pool. Pass an allocation parameter
7706          --  indicating that the function should allocate its result in the
7707          --  pool, and pass the pool. Use 'Unrestricted_Access because the
7708          --  pool may not be aliased.
7709
7710          if VM_Target = No_VM
7711            and then Present (Associated_Storage_Pool (Acc_Type))
7712          then
7713             Add_Unconstrained_Actuals_To_Build_In_Place_Call
7714               (Func_Call, Function_Id, Alloc_Form => User_Storage_Pool,
7715                Pool_Actual =>
7716                  Make_Attribute_Reference (Loc,
7717                    Prefix         =>
7718                      New_Reference_To
7719                        (Associated_Storage_Pool (Acc_Type), Loc),
7720                    Attribute_Name => Name_Unrestricted_Access));
7721
7722          --  No user-defined pool; pass an allocation parameter indicating that
7723          --  the function should allocate its result on the heap.
7724
7725          else
7726             Add_Unconstrained_Actuals_To_Build_In_Place_Call
7727               (Func_Call, Function_Id, Alloc_Form => Global_Heap);
7728          end if;
7729
7730          Add_Finalization_Master_Actual_To_Build_In_Place_Call
7731            (Func_Call, Function_Id, Acc_Type);
7732
7733          Add_Task_Actuals_To_Build_In_Place_Call
7734            (Func_Call, Function_Id, Master_Actual => Master_Id (Acc_Type));
7735
7736          --  The caller does not provide the return object in this case, so we
7737          --  have to pass null for the object access actual.
7738
7739          Add_Access_Actual_To_Build_In_Place_Call
7740            (Func_Call, Function_Id, Return_Object => Empty);
7741       end if;
7742
7743       --  If the build-in-place function call returns a controlled object,
7744       --  the finalization master will require a reference to routine
7745       --  Finalize_Address of the designated type. Setting this attribute
7746       --  is done in the same manner to expansion of allocators.
7747
7748       if Needs_Finalization (Result_Subt) then
7749
7750          --  Controlled types with supressed finalization do not need to
7751          --  associate the address of their Finalize_Address primitives with
7752          --  a master since they do not need a master to begin with.
7753
7754          if Is_Library_Level_Entity (Acc_Type)
7755            and then Finalize_Storage_Only (Result_Subt)
7756          then
7757             null;
7758
7759          --  Do not generate the call to Set_Finalize_Address in Alfa mode
7760          --  because it is not necessary and results in unwanted expansion.
7761          --  This expansion is also not carried out in CodePeer mode because
7762          --  Finalize_Address is never built.
7763
7764          elsif not Alfa_Mode
7765            and then not CodePeer_Mode
7766          then
7767             Insert_Action (Allocator,
7768               Make_Set_Finalize_Address_Call (Loc,
7769                 Typ     => Etype (Function_Id),
7770                 Ptr_Typ => Acc_Type));
7771          end if;
7772       end if;
7773
7774       --  Finally, replace the allocator node with a reference to the result
7775       --  of the function call itself (which will effectively be an access
7776       --  to the object created by the allocator).
7777
7778       Rewrite (Allocator, Make_Reference (Loc, Relocate_Node (Function_Call)));
7779       Analyze_And_Resolve (Allocator, Acc_Type);
7780    end Make_Build_In_Place_Call_In_Allocator;
7781
7782    ---------------------------------------------------
7783    -- Make_Build_In_Place_Call_In_Anonymous_Context --
7784    ---------------------------------------------------
7785
7786    procedure Make_Build_In_Place_Call_In_Anonymous_Context
7787      (Function_Call : Node_Id)
7788    is
7789       Loc             : Source_Ptr;
7790       Func_Call       : Node_Id := Function_Call;
7791       Function_Id     : Entity_Id;
7792       Result_Subt     : Entity_Id;
7793       Return_Obj_Id   : Entity_Id;
7794       Return_Obj_Decl : Entity_Id;
7795
7796    begin
7797       --  Step past qualification or unchecked conversion (the latter can occur
7798       --  in cases of calls to 'Input).
7799
7800       if Nkind_In (Func_Call, N_Qualified_Expression,
7801                               N_Unchecked_Type_Conversion)
7802       then
7803          Func_Call := Expression (Func_Call);
7804       end if;
7805
7806       --  If the call has already been processed to add build-in-place actuals
7807       --  then return. One place this can occur is for calls to build-in-place
7808       --  functions that occur within a call to a protected operation, where
7809       --  due to rewriting and expansion of the protected call there can be
7810       --  more than one call to Expand_Actuals for the same set of actuals.
7811
7812       if Is_Expanded_Build_In_Place_Call (Func_Call) then
7813          return;
7814       end if;
7815
7816       --  Mark the call as processed as a build-in-place call
7817
7818       Set_Is_Expanded_Build_In_Place_Call (Func_Call);
7819
7820       Loc := Sloc (Function_Call);
7821
7822       if Is_Entity_Name (Name (Func_Call)) then
7823          Function_Id := Entity (Name (Func_Call));
7824
7825       elsif Nkind (Name (Func_Call)) = N_Explicit_Dereference then
7826          Function_Id := Etype (Name (Func_Call));
7827
7828       else
7829          raise Program_Error;
7830       end if;
7831
7832       Result_Subt := Etype (Function_Id);
7833
7834       --  If the build-in-place function returns a controlled object, then the
7835       --  object needs to be finalized immediately after the context. Since
7836       --  this case produces a transient scope, the servicing finalizer needs
7837       --  to name the returned object. Create a temporary which is initialized
7838       --  with the function call:
7839       --
7840       --    Temp_Id : Func_Type := BIP_Func_Call;
7841       --
7842       --  The initialization expression of the temporary will be rewritten by
7843       --  the expander using the appropriate mechanism in Make_Build_In_Place_
7844       --  Call_In_Object_Declaration.
7845
7846       if Needs_Finalization (Result_Subt) then
7847          declare
7848             Temp_Id   : constant Entity_Id := Make_Temporary (Loc, 'R');
7849             Temp_Decl : Node_Id;
7850
7851          begin
7852             --  Reset the guard on the function call since the following does
7853             --  not perform actual call expansion.
7854
7855             Set_Is_Expanded_Build_In_Place_Call (Func_Call, False);
7856
7857             Temp_Decl :=
7858               Make_Object_Declaration (Loc,
7859                 Defining_Identifier => Temp_Id,
7860                 Object_Definition =>
7861                   New_Reference_To (Result_Subt, Loc),
7862                 Expression =>
7863                   New_Copy_Tree (Function_Call));
7864
7865             Insert_Action (Function_Call, Temp_Decl);
7866
7867             Rewrite (Function_Call, New_Reference_To (Temp_Id, Loc));
7868             Analyze (Function_Call);
7869          end;
7870
7871       --  When the result subtype is constrained, an object of the subtype is
7872       --  declared and an access value designating it is passed as an actual.
7873
7874       elsif Is_Constrained (Underlying_Type (Result_Subt)) then
7875
7876          --  Create a temporary object to hold the function result
7877
7878          Return_Obj_Id := Make_Temporary (Loc, 'R');
7879          Set_Etype (Return_Obj_Id, Result_Subt);
7880
7881          Return_Obj_Decl :=
7882            Make_Object_Declaration (Loc,
7883              Defining_Identifier => Return_Obj_Id,
7884              Aliased_Present     => True,
7885              Object_Definition   => New_Reference_To (Result_Subt, Loc));
7886
7887          Set_No_Initialization (Return_Obj_Decl);
7888
7889          Insert_Action (Func_Call, Return_Obj_Decl);
7890
7891          --  When the function has a controlling result, an allocation-form
7892          --  parameter must be passed indicating that the caller is allocating
7893          --  the result object. This is needed because such a function can be
7894          --  called as a dispatching operation and must be treated similarly
7895          --  to functions with unconstrained result subtypes.
7896
7897          Add_Unconstrained_Actuals_To_Build_In_Place_Call
7898            (Func_Call, Function_Id, Alloc_Form => Caller_Allocation);
7899
7900          Add_Finalization_Master_Actual_To_Build_In_Place_Call
7901            (Func_Call, Function_Id);
7902
7903          Add_Task_Actuals_To_Build_In_Place_Call
7904            (Func_Call, Function_Id, Make_Identifier (Loc, Name_uMaster));
7905
7906          --  Add an implicit actual to the function call that provides access
7907          --  to the caller's return object.
7908
7909          Add_Access_Actual_To_Build_In_Place_Call
7910            (Func_Call, Function_Id, New_Reference_To (Return_Obj_Id, Loc));
7911
7912       --  When the result subtype is unconstrained, the function must allocate
7913       --  the return object in the secondary stack, so appropriate implicit
7914       --  parameters are added to the call to indicate that. A transient
7915       --  scope is established to ensure eventual cleanup of the result.
7916
7917       else
7918          --  Pass an allocation parameter indicating that the function should
7919          --  allocate its result on the secondary stack.
7920
7921          Add_Unconstrained_Actuals_To_Build_In_Place_Call
7922            (Func_Call, Function_Id, Alloc_Form => Secondary_Stack);
7923
7924          Add_Finalization_Master_Actual_To_Build_In_Place_Call
7925            (Func_Call, Function_Id);
7926
7927          Add_Task_Actuals_To_Build_In_Place_Call
7928            (Func_Call, Function_Id, Make_Identifier (Loc, Name_uMaster));
7929
7930          --  Pass a null value to the function since no return object is
7931          --  available on the caller side.
7932
7933          Add_Access_Actual_To_Build_In_Place_Call
7934            (Func_Call, Function_Id, Empty);
7935       end if;
7936    end Make_Build_In_Place_Call_In_Anonymous_Context;
7937
7938    --------------------------------------------
7939    -- Make_Build_In_Place_Call_In_Assignment --
7940    --------------------------------------------
7941
7942    procedure Make_Build_In_Place_Call_In_Assignment
7943      (Assign        : Node_Id;
7944       Function_Call : Node_Id)
7945    is
7946       Lhs          : constant Node_Id := Name (Assign);
7947       Func_Call    : Node_Id := Function_Call;
7948       Func_Id      : Entity_Id;
7949       Loc          : Source_Ptr;
7950       Obj_Decl     : Node_Id;
7951       Obj_Id       : Entity_Id;
7952       Ptr_Typ      : Entity_Id;
7953       Ptr_Typ_Decl : Node_Id;
7954       Result_Subt  : Entity_Id;
7955       Target       : Node_Id;
7956
7957    begin
7958       --  Step past qualification or unchecked conversion (the latter can occur
7959       --  in cases of calls to 'Input).
7960
7961       if Nkind_In (Func_Call, N_Qualified_Expression,
7962                               N_Unchecked_Type_Conversion)
7963       then
7964          Func_Call := Expression (Func_Call);
7965       end if;
7966
7967       --  If the call has already been processed to add build-in-place actuals
7968       --  then return. This should not normally occur in an assignment context,
7969       --  but we add the protection as a defensive measure.
7970
7971       if Is_Expanded_Build_In_Place_Call (Func_Call) then
7972          return;
7973       end if;
7974
7975       --  Mark the call as processed as a build-in-place call
7976
7977       Set_Is_Expanded_Build_In_Place_Call (Func_Call);
7978
7979       Loc := Sloc (Function_Call);
7980
7981       if Is_Entity_Name (Name (Func_Call)) then
7982          Func_Id := Entity (Name (Func_Call));
7983
7984       elsif Nkind (Name (Func_Call)) = N_Explicit_Dereference then
7985          Func_Id := Etype (Name (Func_Call));
7986
7987       else
7988          raise Program_Error;
7989       end if;
7990
7991       Result_Subt := Etype (Func_Id);
7992
7993       --  When the result subtype is unconstrained, an additional actual must
7994       --  be passed to indicate that the caller is providing the return object.
7995       --  This parameter must also be passed when the called function has a
7996       --  controlling result, because dispatching calls to the function needs
7997       --  to be treated effectively the same as calls to class-wide functions.
7998
7999       Add_Unconstrained_Actuals_To_Build_In_Place_Call
8000         (Func_Call, Func_Id, Alloc_Form => Caller_Allocation);
8001
8002       Add_Finalization_Master_Actual_To_Build_In_Place_Call
8003         (Func_Call, Func_Id);
8004
8005       Add_Task_Actuals_To_Build_In_Place_Call
8006         (Func_Call, Func_Id, Make_Identifier (Loc, Name_uMaster));
8007
8008       --  Add an implicit actual to the function call that provides access to
8009       --  the caller's return object.
8010
8011       Add_Access_Actual_To_Build_In_Place_Call
8012         (Func_Call,
8013          Func_Id,
8014          Make_Unchecked_Type_Conversion (Loc,
8015            Subtype_Mark => New_Reference_To (Result_Subt, Loc),
8016            Expression   => Relocate_Node (Lhs)));
8017
8018       --  Create an access type designating the function's result subtype
8019
8020       Ptr_Typ := Make_Temporary (Loc, 'A');
8021
8022       Ptr_Typ_Decl :=
8023         Make_Full_Type_Declaration (Loc,
8024           Defining_Identifier => Ptr_Typ,
8025           Type_Definition     =>
8026             Make_Access_To_Object_Definition (Loc,
8027               All_Present        => True,
8028               Subtype_Indication =>
8029                 New_Reference_To (Result_Subt, Loc)));
8030       Insert_After_And_Analyze (Assign, Ptr_Typ_Decl);
8031
8032       --  Finally, create an access object initialized to a reference to the
8033       --  function call.
8034
8035       Obj_Id := Make_Temporary (Loc, 'R');
8036       Set_Etype (Obj_Id, Ptr_Typ);
8037
8038       Obj_Decl :=
8039         Make_Object_Declaration (Loc,
8040           Defining_Identifier => Obj_Id,
8041           Object_Definition   => New_Reference_To (Ptr_Typ, Loc),
8042           Expression => Make_Reference (Loc, Relocate_Node (Func_Call)));
8043       Insert_After_And_Analyze (Ptr_Typ_Decl, Obj_Decl);
8044
8045       Rewrite (Assign, Make_Null_Statement (Loc));
8046
8047       --  Retrieve the target of the assignment
8048
8049       if Nkind (Lhs) = N_Selected_Component then
8050          Target := Selector_Name (Lhs);
8051       elsif Nkind (Lhs) = N_Type_Conversion then
8052          Target := Expression (Lhs);
8053       else
8054          Target := Lhs;
8055       end if;
8056
8057       --  If we are assigning to a return object or this is an expression of
8058       --  an extension aggregate, the target should either be an identifier
8059       --  or a simple expression. All other cases imply a different scenario.
8060
8061       if Nkind (Target) in N_Has_Entity then
8062          Target := Entity (Target);
8063       else
8064          return;
8065       end if;
8066    end Make_Build_In_Place_Call_In_Assignment;
8067
8068    ----------------------------------------------------
8069    -- Make_Build_In_Place_Call_In_Object_Declaration --
8070    ----------------------------------------------------
8071
8072    procedure Make_Build_In_Place_Call_In_Object_Declaration
8073      (Object_Decl   : Node_Id;
8074       Function_Call : Node_Id)
8075    is
8076       Loc             : Source_Ptr;
8077       Obj_Def_Id      : constant Entity_Id :=
8078                           Defining_Identifier (Object_Decl);
8079       Enclosing_Func  : constant Entity_Id :=
8080                           Enclosing_Subprogram (Obj_Def_Id);
8081       Call_Deref      : Node_Id;
8082       Caller_Object   : Node_Id;
8083       Def_Id          : Entity_Id;
8084       Fmaster_Actual  : Node_Id := Empty;
8085       Func_Call       : Node_Id := Function_Call;
8086       Function_Id     : Entity_Id;
8087       Pool_Actual     : Node_Id;
8088       Ptr_Typ_Decl    : Node_Id;
8089       Pass_Caller_Acc : Boolean := False;
8090       New_Expr        : Node_Id;
8091       Ref_Type        : Entity_Id;
8092       Result_Subt     : Entity_Id;
8093
8094    begin
8095       --  Step past qualification or unchecked conversion (the latter can occur
8096       --  in cases of calls to 'Input).
8097
8098       if Nkind_In (Func_Call, N_Qualified_Expression,
8099                               N_Unchecked_Type_Conversion)
8100       then
8101          Func_Call := Expression (Func_Call);
8102       end if;
8103
8104       --  If the call has already been processed to add build-in-place actuals
8105       --  then return. This should not normally occur in an object declaration,
8106       --  but we add the protection as a defensive measure.
8107
8108       if Is_Expanded_Build_In_Place_Call (Func_Call) then
8109          return;
8110       end if;
8111
8112       --  Mark the call as processed as a build-in-place call
8113
8114       Set_Is_Expanded_Build_In_Place_Call (Func_Call);
8115
8116       Loc := Sloc (Function_Call);
8117
8118       if Is_Entity_Name (Name (Func_Call)) then
8119          Function_Id := Entity (Name (Func_Call));
8120
8121       elsif Nkind (Name (Func_Call)) = N_Explicit_Dereference then
8122          Function_Id := Etype (Name (Func_Call));
8123
8124       else
8125          raise Program_Error;
8126       end if;
8127
8128       Result_Subt := Etype (Function_Id);
8129
8130       --  If the the object is a return object of an enclosing build-in-place
8131       --  function, then the implicit build-in-place parameters of the
8132       --  enclosing function are simply passed along to the called function.
8133       --  (Unfortunately, this won't cover the case of extension aggregates
8134       --  where the ancestor part is a build-in-place unconstrained function
8135       --  call that should be passed along the caller's parameters. Currently
8136       --  those get mishandled by reassigning the result of the call to the
8137       --  aggregate return object, when the call result should really be
8138       --  directly built in place in the aggregate and not in a temporary. ???)
8139
8140       if Is_Return_Object (Defining_Identifier (Object_Decl)) then
8141          Pass_Caller_Acc := True;
8142
8143          --  When the enclosing function has a BIP_Alloc_Form formal then we
8144          --  pass it along to the callee (such as when the enclosing function
8145          --  has an unconstrained or tagged result type).
8146
8147          if Needs_BIP_Alloc_Form (Enclosing_Func) then
8148             if VM_Target = No_VM and then
8149               RTE_Available (RE_Root_Storage_Pool_Ptr)
8150             then
8151                Pool_Actual :=
8152                  New_Reference_To (Build_In_Place_Formal
8153                    (Enclosing_Func, BIP_Storage_Pool), Loc);
8154
8155             --  The build-in-place pool formal is not built on .NET/JVM
8156
8157             else
8158                Pool_Actual := Empty;
8159             end if;
8160
8161             Add_Unconstrained_Actuals_To_Build_In_Place_Call
8162               (Func_Call,
8163                Function_Id,
8164                Alloc_Form_Exp =>
8165                  New_Reference_To
8166                    (Build_In_Place_Formal (Enclosing_Func, BIP_Alloc_Form),
8167                     Loc),
8168                Pool_Actual => Pool_Actual);
8169
8170          --  Otherwise, if enclosing function has a constrained result subtype,
8171          --  then caller allocation will be used.
8172
8173          else
8174             Add_Unconstrained_Actuals_To_Build_In_Place_Call
8175               (Func_Call, Function_Id, Alloc_Form => Caller_Allocation);
8176          end if;
8177
8178          if Needs_BIP_Finalization_Master (Enclosing_Func) then
8179             Fmaster_Actual :=
8180               New_Reference_To
8181                 (Build_In_Place_Formal
8182                    (Enclosing_Func, BIP_Finalization_Master), Loc);
8183          end if;
8184
8185          --  Retrieve the BIPacc formal from the enclosing function and convert
8186          --  it to the access type of the callee's BIP_Object_Access formal.
8187
8188          Caller_Object :=
8189             Make_Unchecked_Type_Conversion (Loc,
8190               Subtype_Mark =>
8191                 New_Reference_To
8192                   (Etype
8193                      (Build_In_Place_Formal (Function_Id, BIP_Object_Access)),
8194                    Loc),
8195               Expression   =>
8196                 New_Reference_To
8197                   (Build_In_Place_Formal (Enclosing_Func, BIP_Object_Access),
8198                    Loc));
8199
8200       --  In the constrained case, add an implicit actual to the function call
8201       --  that provides access to the declared object. An unchecked conversion
8202       --  to the (specific) result type of the function is inserted to handle
8203       --  the case where the object is declared with a class-wide type.
8204
8205       elsif Is_Constrained (Underlying_Type (Result_Subt)) then
8206          Caller_Object :=
8207             Make_Unchecked_Type_Conversion (Loc,
8208               Subtype_Mark => New_Reference_To (Result_Subt, Loc),
8209               Expression   => New_Reference_To (Obj_Def_Id, Loc));
8210
8211          --  When the function has a controlling result, an allocation-form
8212          --  parameter must be passed indicating that the caller is allocating
8213          --  the result object. This is needed because such a function can be
8214          --  called as a dispatching operation and must be treated similarly
8215          --  to functions with unconstrained result subtypes.
8216
8217          Add_Unconstrained_Actuals_To_Build_In_Place_Call
8218            (Func_Call, Function_Id, Alloc_Form => Caller_Allocation);
8219
8220       --  In other unconstrained cases, pass an indication to do the allocation
8221       --  on the secondary stack and set Caller_Object to Empty so that a null
8222       --  value will be passed for the caller's object address. A transient
8223       --  scope is established to ensure eventual cleanup of the result.
8224
8225       else
8226          Add_Unconstrained_Actuals_To_Build_In_Place_Call
8227            (Func_Call, Function_Id, Alloc_Form => Secondary_Stack);
8228          Caller_Object := Empty;
8229
8230          Establish_Transient_Scope (Object_Decl, Sec_Stack => True);
8231       end if;
8232
8233       --  Pass along any finalization master actual, which is needed in the
8234       --  case where the called function initializes a return object of an
8235       --  enclosing build-in-place function.
8236
8237       Add_Finalization_Master_Actual_To_Build_In_Place_Call
8238         (Func_Call  => Func_Call,
8239          Func_Id    => Function_Id,
8240          Master_Exp => Fmaster_Actual);
8241
8242       if Nkind (Parent (Object_Decl)) = N_Extended_Return_Statement
8243         and then Has_Task (Result_Subt)
8244       then
8245          --  Here we're passing along the master that was passed in to this
8246          --  function.
8247
8248          Add_Task_Actuals_To_Build_In_Place_Call
8249            (Func_Call, Function_Id,
8250             Master_Actual =>
8251               New_Reference_To (Build_In_Place_Formal
8252                 (Enclosing_Func, BIP_Task_Master), Loc));
8253
8254       else
8255          Add_Task_Actuals_To_Build_In_Place_Call
8256            (Func_Call, Function_Id, Make_Identifier (Loc, Name_uMaster));
8257       end if;
8258
8259       Add_Access_Actual_To_Build_In_Place_Call
8260         (Func_Call, Function_Id, Caller_Object, Is_Access => Pass_Caller_Acc);
8261
8262       --  Create an access type designating the function's result subtype. We
8263       --  use the type of the original expression because it may be a call to
8264       --  an inherited operation, which the expansion has replaced with the
8265       --  parent operation that yields the parent type.
8266
8267       Ref_Type := Make_Temporary (Loc, 'A');
8268
8269       Ptr_Typ_Decl :=
8270         Make_Full_Type_Declaration (Loc,
8271           Defining_Identifier => Ref_Type,
8272           Type_Definition     =>
8273             Make_Access_To_Object_Definition (Loc,
8274               All_Present        => True,
8275               Subtype_Indication =>
8276                 New_Reference_To (Etype (Function_Call), Loc)));
8277
8278       --  The access type and its accompanying object must be inserted after
8279       --  the object declaration in the constrained case, so that the function
8280       --  call can be passed access to the object. In the unconstrained case,
8281       --  or if the object declaration is for a return object, the access type
8282       --  and object must be inserted before the object, since the object
8283       --  declaration is rewritten to be a renaming of a dereference of the
8284       --  access object.
8285
8286       if Is_Constrained (Underlying_Type (Result_Subt))
8287         and then not Is_Return_Object (Defining_Identifier (Object_Decl))
8288       then
8289          Insert_After_And_Analyze (Object_Decl, Ptr_Typ_Decl);
8290       else
8291          Insert_Action (Object_Decl, Ptr_Typ_Decl);
8292       end if;
8293
8294       --  Finally, create an access object initialized to a reference to the
8295       --  function call.
8296
8297       New_Expr := Make_Reference (Loc, Relocate_Node (Func_Call));
8298
8299       Def_Id := Make_Temporary (Loc, 'R', New_Expr);
8300       Set_Etype (Def_Id, Ref_Type);
8301
8302       Insert_After_And_Analyze (Ptr_Typ_Decl,
8303         Make_Object_Declaration (Loc,
8304           Defining_Identifier => Def_Id,
8305           Object_Definition   => New_Reference_To (Ref_Type, Loc),
8306           Expression          => New_Expr));
8307
8308       --  If the result subtype of the called function is constrained and
8309       --  is not itself the return expression of an enclosing BIP function,
8310       --  then mark the object as having no initialization.
8311
8312       if Is_Constrained (Underlying_Type (Result_Subt))
8313         and then not Is_Return_Object (Defining_Identifier (Object_Decl))
8314       then
8315          Set_Expression (Object_Decl, Empty);
8316          Set_No_Initialization (Object_Decl);
8317
8318       --  In case of an unconstrained result subtype, or if the call is the
8319       --  return expression of an enclosing BIP function, rewrite the object
8320       --  declaration as an object renaming where the renamed object is a
8321       --  dereference of <function_Call>'reference:
8322       --
8323       --      Obj : Subt renames <function_call>'Ref.all;
8324
8325       else
8326          Call_Deref :=
8327            Make_Explicit_Dereference (Loc,
8328              Prefix => New_Reference_To (Def_Id, Loc));
8329
8330          Loc := Sloc (Object_Decl);
8331          Rewrite (Object_Decl,
8332            Make_Object_Renaming_Declaration (Loc,
8333              Defining_Identifier => Make_Temporary (Loc, 'D'),
8334              Access_Definition   => Empty,
8335              Subtype_Mark        => New_Occurrence_Of (Result_Subt, Loc),
8336              Name                => Call_Deref));
8337
8338          Set_Renamed_Object (Defining_Identifier (Object_Decl), Call_Deref);
8339
8340          Analyze (Object_Decl);
8341
8342          --  Replace the internal identifier of the renaming declaration's
8343          --  entity with identifier of the original object entity. We also have
8344          --  to exchange the entities containing their defining identifiers to
8345          --  ensure the correct replacement of the object declaration by the
8346          --  object renaming declaration to avoid homograph conflicts (since
8347          --  the object declaration's defining identifier was already entered
8348          --  in current scope). The Next_Entity links of the two entities also
8349          --  have to be swapped since the entities are part of the return
8350          --  scope's entity list and the list structure would otherwise be
8351          --  corrupted. Finally, the homonym chain must be preserved as well.
8352
8353          declare
8354             Renaming_Def_Id  : constant Entity_Id :=
8355                                  Defining_Identifier (Object_Decl);
8356             Next_Entity_Temp : constant Entity_Id :=
8357                                  Next_Entity (Renaming_Def_Id);
8358          begin
8359             Set_Chars (Renaming_Def_Id, Chars (Obj_Def_Id));
8360
8361             --  Swap next entity links in preparation for exchanging entities
8362
8363             Set_Next_Entity (Renaming_Def_Id, Next_Entity (Obj_Def_Id));
8364             Set_Next_Entity (Obj_Def_Id, Next_Entity_Temp);
8365             Set_Homonym     (Renaming_Def_Id, Homonym (Obj_Def_Id));
8366
8367             Exchange_Entities (Renaming_Def_Id, Obj_Def_Id);
8368
8369             --  Preserve source indication of original declaration, so that
8370             --  xref information is properly generated for the right entity.
8371
8372             Preserve_Comes_From_Source
8373               (Object_Decl, Original_Node (Object_Decl));
8374
8375             Preserve_Comes_From_Source
8376               (Obj_Def_Id, Original_Node (Object_Decl));
8377
8378             Set_Comes_From_Source (Renaming_Def_Id, False);
8379          end;
8380       end if;
8381
8382       --  If the object entity has a class-wide Etype, then we need to change
8383       --  it to the result subtype of the function call, because otherwise the
8384       --  object will be class-wide without an explicit initialization and
8385       --  won't be allocated properly by the back end. It seems unclean to make
8386       --  such a revision to the type at this point, and we should try to
8387       --  improve this treatment when build-in-place functions with class-wide
8388       --  results are implemented. ???
8389
8390       if Is_Class_Wide_Type (Etype (Defining_Identifier (Object_Decl))) then
8391          Set_Etype (Defining_Identifier (Object_Decl), Result_Subt);
8392       end if;
8393    end Make_Build_In_Place_Call_In_Object_Declaration;
8394
8395    -----------------------------------
8396    -- Needs_BIP_Finalization_Master --
8397    -----------------------------------
8398
8399    function Needs_BIP_Finalization_Master
8400      (Func_Id : Entity_Id) return Boolean
8401    is
8402       pragma Assert (Is_Build_In_Place_Function (Func_Id));
8403       Func_Typ : constant Entity_Id := Underlying_Type (Etype (Func_Id));
8404    begin
8405       return
8406         not Restriction_Active (No_Finalization)
8407           and then Needs_Finalization (Func_Typ);
8408    end Needs_BIP_Finalization_Master;
8409
8410    --------------------------
8411    -- Needs_BIP_Alloc_Form --
8412    --------------------------
8413
8414    function Needs_BIP_Alloc_Form (Func_Id : Entity_Id) return Boolean is
8415       pragma Assert (Is_Build_In_Place_Function (Func_Id));
8416       Func_Typ : constant Entity_Id := Underlying_Type (Etype (Func_Id));
8417    begin
8418       return not Is_Constrained (Func_Typ) or else Is_Tagged_Type (Func_Typ);
8419    end Needs_BIP_Alloc_Form;
8420
8421    --------------------------------------
8422    -- Needs_Result_Accessibility_Level --
8423    --------------------------------------
8424
8425    function Needs_Result_Accessibility_Level
8426      (Func_Id : Entity_Id) return Boolean
8427    is
8428       Func_Typ : constant Entity_Id := Underlying_Type (Etype (Func_Id));
8429
8430       function Has_Unconstrained_Access_Discriminant_Component
8431         (Comp_Typ : Entity_Id) return Boolean;
8432       --  Returns True if any component of the type has an unconstrained access
8433       --  discriminant.
8434
8435       -----------------------------------------------------
8436       -- Has_Unconstrained_Access_Discriminant_Component --
8437       -----------------------------------------------------
8438
8439       function Has_Unconstrained_Access_Discriminant_Component
8440         (Comp_Typ :  Entity_Id) return Boolean
8441       is
8442       begin
8443          if not Is_Limited_Type (Comp_Typ) then
8444             return False;
8445
8446             --  Only limited types can have access discriminants with
8447             --  defaults.
8448
8449          elsif Has_Unconstrained_Access_Discriminants (Comp_Typ) then
8450             return True;
8451
8452          elsif Is_Array_Type (Comp_Typ) then
8453             return Has_Unconstrained_Access_Discriminant_Component
8454                      (Underlying_Type (Component_Type (Comp_Typ)));
8455
8456          elsif Is_Record_Type (Comp_Typ) then
8457             declare
8458                Comp : Entity_Id;
8459
8460             begin
8461                Comp := First_Component (Comp_Typ);
8462                while Present (Comp) loop
8463                   if Has_Unconstrained_Access_Discriminant_Component
8464                        (Underlying_Type (Etype (Comp)))
8465                   then
8466                      return True;
8467                   end if;
8468
8469                   Next_Component (Comp);
8470                end loop;
8471             end;
8472          end if;
8473
8474          return False;
8475       end Has_Unconstrained_Access_Discriminant_Component;
8476
8477       Feature_Disabled : constant Boolean := True;
8478       --  Temporary
8479
8480    --  Start of processing for Needs_Result_Accessibility_Level
8481
8482    begin
8483       --  False if completion unavailable (how does this happen???)
8484
8485       if not Present (Func_Typ) then
8486          return False;
8487
8488       elsif Feature_Disabled then
8489          return False;
8490
8491       --  False if not a function, also handle enum-lit renames case
8492
8493       elsif Func_Typ = Standard_Void_Type
8494         or else Is_Scalar_Type (Func_Typ)
8495       then
8496          return False;
8497
8498       --  Handle a corner case, a cross-dialect subp renaming. For example,
8499       --  an Ada2012 renaming of an Ada05 subprogram. This can occur when a
8500       --  non-Ada2012 unit references predefined runtime units.
8501
8502       elsif Present (Alias (Func_Id)) then
8503
8504          --  Unimplemented: a cross-dialect subp renaming which does not set
8505          --  the Alias attribute (e.g., a rename of a dereference of an access
8506          --  to subprogram value). ???
8507
8508          return Present (Extra_Accessibility_Of_Result (Alias (Func_Id)));
8509
8510       --  Remaining cases require Ada 2012 mode
8511
8512       elsif Ada_Version < Ada_2012 then
8513          return False;
8514
8515       elsif Ekind (Func_Typ) = E_Anonymous_Access_Type
8516         or else Is_Tagged_Type (Func_Typ)
8517       then
8518          --  In the case of, say, a null tagged record result type, the need
8519          --  for this extra parameter might not be obvious. This function
8520          --  returns True for all tagged types for compatibility reasons.
8521          --  A function with, say, a tagged null controlling result type might
8522          --  be overridden by a primitive of an extension having an access
8523          --  discriminant and the overrider and overridden must have compatible
8524          --  calling conventions (including implicitly declared parameters).
8525          --  Similarly, values of one access-to-subprogram type might designate
8526          --  both a primitive subprogram of a given type and a function
8527          --  which is, for example, not a primitive subprogram of any type.
8528          --  Again, this requires calling convention compatibility.
8529          --  It might be possible to solve these issues by introducing
8530          --  wrappers, but that is not the approach that was chosen.
8531
8532          return True;
8533
8534       elsif Has_Unconstrained_Access_Discriminants (Func_Typ) then
8535          return True;
8536
8537       elsif Has_Unconstrained_Access_Discriminant_Component (Func_Typ) then
8538          return True;
8539
8540       --  False for all other cases
8541
8542       else
8543          return False;
8544       end if;
8545    end Needs_Result_Accessibility_Level;
8546
8547 end Exp_Ch6;